Future.st
author Claus Gittinger <cg@exept.de>
Thu, 02 Mar 2000 15:15:13 +0100
changeset 885 c31412b26306
parent 484 d50c08ae6e3d
child 1140 cbb20fd710fa
permissions -rw-r--r--
package-definitions fixed/updated

"{ Package: 'stx:goodies' }"

"       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
! !

Object subclass: #Future
	instanceVariableNames: 'result semaphore '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'
!

Future comment:
'I represent an execution in progress.  Any messages sent to me are delayed until
 execution has completed.'
!

!Future class methodsFor:'documentation'!

copyright
"
 This 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 
"
!

documentation
"
    I represent an execution in progress.  
    Any messages sent to me are delayed until execution has completed.'
"
!

examples
"
  Starts evaluating the factorial immediately, but waits until
  the result is available before printing the answer
								    [exBegin]
    | fac |

    fac := [100 factorial] futureValue.
    Transcript showCR: 'evaluating factorial...'.
    Transcript showCR: fac printString
								    [exEnd]


  An example illustrating the use of multiple futures and
  explicit resynchronisation.

  Starts evaluating both factorials immediately, but waits until
  both blocks have finished before continuing.
								    [exBegin]
    | fac1 fac2 |

    fac1 := [Transcript showCR: 'Starting fac1.. '. 1000 factorial] futureValue.
    fac2 := [Transcript showCR: 'Starting fac2.. '. 2000 factorial] futureValue.
    fac2 touch.
    fac1 touch.
    Transcript showCR: 'both completed.'.
								    [exEnd]

  Example showing how arguments may be passed to futures.
								    [exBegin]
    | temp |

    temp := [:x :y | 10 * x * y] futureValue: 3 value: 4.
    Transcript  showCR: temp printString.

								    [exEnd]

  Claus:
    The above examples do not really show the power of Futures;
    they can be useful, whenever some long-time computation is
    to be done, and some other useful work can be done in the meanwhile.
    for example:

    Here, the input is read before - the readTime and view creation
    times sum up:
								    [exBegin]
	|p text v|

	p := PipeStream readingFrom:'ls -l /bin /usr/bin /usr/lib'.
	text := p contents.
	p close.
	v := TextView new openAndWait.
	v contents:text
								    [exEnd]

    The same here:
								    [exBegin]
	|p text v|

	v := TextView new openAndWait.
	p := PipeStream readingFrom:'ls -l /bin /usr/bin /usr/lib'.
	text := p contents.
	p close.
	v contents:text
								    [exEnd]


    Here, the view creation and reading are done in parallel:
    (if the user is slow when opening the view, the contents may
     be already available)
								    [exBegin]
	|p text v|

	text := [   |p t|

		    p := PipeStream readingFrom:'ls -l /bin /usr/bin /usr/lib'.
		    t := p contents.
		    p close.
		    t
		] futureValue.
	v := TextView new openAndWait.
	v contents:text
								    [exEnd]
"
!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Future.st,v 1.6 2000-03-02 14:14:58 cg Exp $'
! !

!Future methodsFor: 'synchronising'!

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

	semaphore wait.     "Wait for evaluation to complete"
			    "(if not already completed)"
	semaphore signal.   "Wake up anything else that might be waiting"
	^result perform: aMessage selector 
		withArguments: aMessage arguments
! !

!Future methodsFor: 'evaluating'!

block: aBlock
	"Execute aBlock in parallel with whatever called me, but
	 ensure that any messages sent to me before execution
	 of the block has terminated are suspended until it has terminated."

	semaphore := Semaphore new.
	[result := aBlock value.  semaphore signal] fork
!

block: aBlock value: aValue
	"Execute aBlock in parallel with whatever called me, but
	 ensure that any messages sent to me before execution
	 of the block has terminated are suspended until it has terminated."

	semaphore := Semaphore new.
	[result := aBlock value: aValue.  semaphore signal] fork
!

block: aBlock value: value1 value: value2
	"Execute aBlock in parallel with whatever called me, but
	 ensure that any messages sent to me before execution
	 of the block has terminated are suspended until it has terminated."

	semaphore := Semaphore new.
	[result := aBlock value: value1 value: value2.
	 semaphore signal] fork
!

block: aBlock value: value1 value: value2 value: value3
	"Execute aBlock in parallel with whatever called me, but
	 ensure that any messages sent to me before execution
	 of the block has terminated are suspended until it has terminated."

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

block: aBlock valueWithArguments: anArray
	"Execute aBlock in parallel with whatever called me, but
	 ensure that any messages sent to me before execution
	 of the block has terminated are suspended until it has terminated."

	semaphore := Semaphore new.
	[result := aBlock valueWithArguments: anArray.
	 semaphore signal] fork
! !

!Future class methodsFor: 'class initialization'!

initialize
	"must avoid the checks"

	superclass := nil

	"Future initialize."
! !

Future initialize!

!Block methodsFor: 'parallel evaluation'!

futureValue
	"Fork a synchronised evaluation of myself. Starts the
	 evaluation in parallel immediately."

	^Future new block: self
!

futureValue: aValue
	"Fork a synchronised evaluation of myself. Starts the
	 evaluation in parallel immediately."

	^Future new block: self value: aValue
!

futureValue: aValue value: anotherValue
	"Fork a synchronised evaluation of myself. Starts the
	 evaluation in parallel immediately."

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

futureValue: aValue value: anotherValue value: bValue
	"Fork a synchronised evaluation of myself. Starts the
	 evaluation in parallel immediately."

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

futureValueWithArguments: anArray
	"Fork a synchronised evaluation of myself. Starts the
	 evaluation in parallel immediately."

	^Future new block: self valueWithArguments: anArray
! 

parallelAnd: aBlock 
	"Executes the receiver in parallel with aBlock. Once both   
	 have completed, perform a logical AND operation."

	| first second |
	first := self futureValue.
	second := aBlock futureValue.
	^first touch & second touch!

parallelEqv: aBlock 
	"Executes the receiver in parallel with aBlock. Once both   
	 have completed, perform a logical equivalence (exclusive-NOR)
	 operation."

	| first second |
	first := self futureValue.
	second := aBlock futureValue.
	^first touch eqv: second touch!

parallelOr: aBlock 
	"Executes the receiver in parallel with aBlock. Once both   
	 have completed, perform a logical OR operation."

	| first second |
	first := self futureValue.
	second := aBlock futureValue.
	^first touch | second touch!

parallelPerform: aSymbol with: aBlock 
	"Executes the receiver in parallel with aBlock. Once both  
	 have completed, perform the operation given by aSymbol."

	| first second |
	first := self futureValue.
	second := aBlock futureValue.
	^first touch perform: aSymbol with: second touch!

parallelXor: aBlock 
	"Executes the receiver in parallel with aBlock. Once both   
	 have completed, perform a logical equivalence (exclusive-NOR)
	 operation."

	| first second |
	first := self futureValue.
	second := aBlock futureValue.
	^first touch xor: second touch
! !


"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 
"!