Lazy.st
author Claus Gittinger <cg@exept.de>
Fri, 08 Nov 1996 22:16:44 +0100
changeset 457 c862c91716b6
parent 351 c7c0c33286b8
child 885 c31412b26306
permissions -rw-r--r--
packages

"{ Package: 'goodies/Parallelism-Lazy' }"

"       NAME            Parallelism
	AUTHOR          tph@cs.man.ac.uk
	FUNCTION throttled Futures; lazy eval; explicit pa'l'l procs 
	ST-VERSIONS     stx
	PREREQUISITES    
	CONFLICTS       
	DISTRIBUTION    world
	VERSION         1.1
	DATE    22 Jan 1989
	SUMMARY 
Parallelism contains a number of explicitly parallel constructs,
including a new version of Future, Lazy evaluation, and explicit
parallel processes.  Lots of code in here.  Contains an early
version (read: doesn't work) of a ""throttled"" future mechanism.
New version RSN.(2.2).TPH

claus: I have separated the original Parallelism package into
       individual ones: Lazy, Future, ThrottledFuture and ParallelEvaluation
"!

'From Smalltalk-80, version 2, of April 1, 1983 on 29 March 1987 at 5:13:27 pm'!

!Object methodsFor: 'parallel evaluation'!

touch
	"Simply returns self.  If the receiver is an uncompleted
	 Future or Lazy, this forces complete evaluation."

	^self
! !

'From Smalltalk-80, version 2, of April 1, 1983 on 29 March 1987 at 5:09:10 pm'!

Object subclass: #Lazy
	instanceVariableNames: 'result startSemaphore endSemaphore '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!
Lazy comment:
'I represent an execution which may not be required.  I will
not start execution until at least one message has been
received.  The messages sent to me are delayed until execution
has completed.'!


!Lazy methodsFor: 'synchronising'!

doesNotUnderstand: aMessage
	"Any message to a Lazy will end up here."

	startSemaphore signal.          "Start the evaluation."
	endSemaphore wait.              "Wait until evaluation completed."
	endSemaphore signal.            "Wake up anything else."
	^result perform: aMessage selector withArguments: aMessage arguments
		"Perform the message, having re-synchronised."! !

!Lazy methodsFor: 'evaluating'!

block: aBlock
	"Execute aBlock in parallel, but ensure that any messages sent
	 to me before execution of the block has terminated are
	 suspended until it has terminated. Do not start the evaluation
	 until at least one message has been sent to the receiver."

	startSemaphore := Semaphore new.
	endSemaphore := Semaphore new.
	[startSemaphore wait.
	 result := aBlock value.
	 endSemaphore signal] fork!

block: aBlock value: aValue
	"Execute aBlock in parallel, but ensure that any messages sent
	 to me before execution of the block has terminated are
	 suspended until it has terminated. Do not start the evaluation
	 until at least one message has been sent to the receiver."

	startSemaphore := Semaphore new.
	endSemaphore := Semaphore new.
	[startSemaphore wait.
	 result := aBlock value: aValue.
	 endSemaphore signal] fork!

block: aBlock value: value1 value: value2
	"Execute aBlock in parallel, but ensure that any messages sent
	 to me before execution of the block has terminated are
	 suspended until it has terminated. Do not start the evaluation
	 until at least one message has been sent to the receiver."

	startSemaphore := Semaphore new.
	endSemaphore := Semaphore new.
	[startSemaphore wait.
	 result := aBlock value: value1 value: value2.
	 endSemaphore signal] fork!

block: aBlock value: value1 value: value2 value: value3
	"Execute aBlock in parallel, but ensure that any messages sent
	 to me before execution of the block has terminated are
	 suspended until it has terminated. Do not start the evaluation
	 until at least one message has been sent to the receiver."

	startSemaphore := Semaphore new.
	endSemaphore := Semaphore new.
	[startSemaphore wait.
	 result := aBlock value: value1 value: value2 value: value3.
	 endSemaphore signal] fork!

block: aBlock valueWithArguments: anArray
	"Execute aBlock in parallel, but ensure that any messages sent
	 to me before execution of the block has terminated are
	 suspended until it has terminated. Do not start the evaluation
	 until at least one message has been sent to the receiver."

	startSemaphore := Semaphore new.
	endSemaphore := Semaphore new.
	[startSemaphore wait.
	 result := aBlock valueWithArguments: anArray.
	 endSemaphore signal] fork! !

!Lazy class methodsFor: 'class initialization'!

initialize
	"must avoid the checks"

	superclass := nil

	"Lazy initialize."! !

!Lazy class methodsFor: 'examples'!

example1
	"Evaluates the factorial, starting only when the
	 result is actually required (when printString is sent)."

	| fac |
	fac := [100 factorial] futureValue.
	Transcript showCR: 'Doing nothing. '.
	(Delay forSeconds: 2) wait.
	Transcript showCR: fac printString

	"Lazy example1"!

example2
	"Starts evaluating both factorials only when required (by the touch),
	 and waits until both blocks have finished before continuing."

	| fac1 fac2 |
	fac1 := [Transcript showCR: 'Starting fac1.. '. 100 factorial] lazyValue.
	fac2 := [Transcript showCR: 'Starting fac2.. '. 120 factorial] lazyValue.
	fac2 touch.
	fac1 touch.
	Transcript showCR: 'both completed.'.

	"Lazy example2"!

example3
	"Demonstrates how to pass arguments to a lazy evaluation block."

	| temp |
	temp := [:x :y :z | x * y * z] lazyValueWithArguments: #(2 3 4).
	Transcript  showCR: temp printString.

	"Lazy example3"! !

Lazy initialize!

!Block methodsFor: 'parallel evaluation'!

lazyValue
	"Fork a synchronised evaluation of myself. Only starts
	 the evaluation when the result is requested."

	^Lazy new block: self!

lazyValue: aValue
	"Fork a synchronised evaluation of myself. Only starts
	 the evaluation when the result is requested."

	^Lazy new block: self value: aValue!

lazyValue: aValue value: anotherValue
	"Fork a synchronised evaluation of myself. Only starts
	 the evaluation when the result is requested."

	^Lazy new block: self value: aValue value: anotherValue!

lazyValue: aValue value: anotherValue value: bValue
	"Fork a synchronised evaluation of myself. Only starts
	 the evaluation when the result is requested."

	^Lazy new block: self value: aValue value: anotherValue value: bValue!

lazyValueWithArguments: anArray
	"Fork a synchronised evaluation of myself. Only starts
	 the evaluation when the result is requested."

	^Lazy new block: self valueWithArguments: anArray
! !

"COPYRIGHT.
 The above file is a Manchester Goodie protected by copyright.
 These conditions are imposed on the whole Goodie, and on any significant
 part of it which is separately transmitted or stored:
	* You must ensure that every copy includes this notice, and that
	  source and author(s) of the material are acknowledged.
	* These conditions must be imposed on anyone who receives a copy.
	* The material shall not be used for commercial gain without the prior
	  written consent of the author(s).
 Further information on the copyright conditions may be obtained by
 sending electronic mail:
	To: goodies-lib@cs.man.ac.uk
	Subject: copyright
 or by writing to The Smalltalk Goodies Library Manager, Dept of
 Computer Science, The University, Manchester M13 9PL, UK

 (C) Copyright 1992 University of Manchester
 For more information about the Manchester Goodies Library (from which 
 this file was distributed) send e-mail:
	To: goodies-lib@cs.man.ac.uk
	Subject: help 
"!