[pypy-commit] lang-smalltalk default: Some experiments with actor-like parallelism

amintos noreply at buildbot.pypy.org
Thu Apr 3 11:32:38 CEST 2014


Author: amintos
Branch: 
Changeset: r760:a81003656c0e
Date: 2014-01-17 01:25 +0100
http://bitbucket.org/pypy/lang-smalltalk/changeset/a81003656c0e/

Log:	Some experiments with actor-like parallelism

diff too long, truncating to 2000 out of 2072 lines

diff --git a/images/Squeak4.5-12568.changes b/images/Squeak4.5-12568.changes
--- a/images/Squeak4.5-12568.changes
+++ b/images/Squeak4.5-12568.changes
@@ -1,2 +1,2 @@
 
-

----STARTUP----{15 January 2014 . 2:16:33 pm} as /home/bot/lang-smalltalk/images/Squeak4.5-12568.image!

!Integer methodsFor: 'benchmarks' stamp: 'toma 1/15/2014 14:33' prior: 42646392!
benchStm
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 1 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 2 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 3 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 4 reporting!!']] parallelFork.
	(1 to: 1000)
		do: [:x | SPyVM print: '* spinlock *'].
	^ 42 printString! !

----SNAPSHOT----{15 January 2014 . 2:33:47 pm} Squeak4.5-12568.image priorSource: 9103122!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/15/2014 14:35' prior: 42656801!
benchStm3
	| t1 t2 |
	t1 := [(1 to: 100)
				do: [:t3 | SPyVM print: 'Thread 1 reporting!!']] parallelFork.
	t2 := [(1 to: 100)
				do: [:t3 | SPyVM print: 'Thread 2 reporting!!']] parallelFork.
	SPyVM print: 'Waiting for Task 1'.
	t1 wait.
	SPyVM print: 'Waiting for Task 2'.
	t2 wait.
	SPyVM print: 'Finished waiting.'! !

----SNAPSHOT----{15 January 2014 . 2:36:01 pm} Squeak4.5-12568.image priorSource: 594!
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/15/2014 14:37' prior: 42653846!
wait
	<primitive: 789>
	SPyVM print: ' Failed to wait for process!! '! !

----SNAPSHOT----{15 January 2014 . 2:37:09 pm} Squeak4.5-12568.image priorSource: 1091!

----STARTUP----{16 January 2014 . 9:13:20 pm} as /home/bot/lang-smalltalk/images/Squeak4.5-12568.image!

!BlockClosure methodsFor: 'scheduling' stamp: 'toma 1/16/2014 21:13' prior: 42654183!
parallelFork
	^ (self newSTMProcess) fork; yourself! !

----SNAPSHOT----{16 January 2014 . 9:14:01 pm} Squeak4.5-12568.image priorSource: 1345!
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:14'!
primWait
	<primitive: 789>
	SPyVM print: ' Failed to wait for process!! '! !
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:15' prior: 33555705!
wait
	
	SPyVM print: '[squeak] wait'
	self primWait! !
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:15' prior: 33556450!
wait
	
	SPyVM print: '[squeak] wait'.
	self primWait! !

----SNAPSHOT----{16 January 2014 . 9:15:29 pm} Squeak4.5-12568.image priorSource: 1681!
!BasicClassOrganizer methodsFor: 'accessing' stamp: 'toma 1/16/2014 22:18' prior: 17298983!
classComment
	classComment
		ifNil: [^ ''].
	^ [classComment text ifNil: ['']] on: Error do: [^ ''].! !

Object subclass: #SPySTM
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SPy-Benchmarks'!

Object subclass: #SPySTM
	instanceVariableNames: ''
	classVariableNames: 'Shared'
	poolDictionaries: ''
	category: 'SPy-Benchmarks'!
!SPySTM class methodsFor: 'nil' stamp: 'toma 1/16/2014 22:22'!
shared
	
	^self Shared! !
!SPySTM class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:23' prior: 33557264!
shared
	
	^Shared! !
!SPySTM class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:23'!
shared: aValue
	
	Shared := aValue! !

----SNAPSHOT----{16 January 2014 . 10:24:08 pm} Squeak4.5-12568.image priorSource: 2221!

Object subclass: #STMAtomic
	instanceVariableNames: 'lock'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!
!STMAtomic methodsFor: 'nil' stamp: 'toma 1/16/2014 22:28'!
primEnter
	<primitive: 790>! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:28' prior: 33557810!
primEnter
	<primitive: 790>
	SPyVM print: 'primEnter failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:28' prior: 33557933!
primEnter
	<primitive: 790>
	
	SPyVM print: 'primEnter failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29'!
primLeave
	<primitive: 791>
	
	SPyVM print: 'primLeave failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29'!
value
	
	self primEnter.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29' prior: 33558376!
value
	
	| result |
	
	self primEnter.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:30' prior: 33558498!
value
	
	| result |
	
	self primEnter.
	result := self.
	self primLeave
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:30' prior: 33558634!
value
	
	| result |
	
	self primEnter.
	result := self.
	self primLeave.
	! !

Object subclass: #STMAtomic
	instanceVariableNames: 'block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:31' prior: 33558803!
value
	
	| result |
	
	self primEnter.
	result := self block value.
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:31' prior: 33559111!
value
	
	| result error |
	
	self primEnter.
	result := self block value.
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559293!
value
	
	| result error |
	
	self primEnter.
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559481!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559707!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559950!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err].
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:33' prior: 33560207!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error raise]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:33' prior: 33560465!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error raise]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33560754!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33561047!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass]
	
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33561339!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass].
	^result
	! !
!STMAtomic class methodsFor: 'nil' stamp: 'toma 1/16/2014 22:36'!
from: aBlock
	
	^ (STMAtomic new)
		block: aBlock;
		yourself.! !
!STMAtomic class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:36' prior: 33561909!
from: aBlock
	
	^ (STMAtomic new)
		block: aBlock;
		yourself! !
!BlockClosure methodsFor: 'nil' stamp: 'toma 1/16/2014 22:37'!
atomic
	
	^STMAtomic from: self! !

SystemOrganization addCategory: #'Kernel-STM'!

SystemOrganization classify: #STMAtomic under: #'Kernel-STM'!

SystemOrganization classify: #STMProcess under: #'Kernel-STM'!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40'!
benchStmAtomic
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562476!
benchStmAtomic
	
	| sum |
	sum := 0.
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562577!
benchStmAtomic
	
	| sum |
	sum := 0.
	
! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562700!
benchStmAtomic
	
	| sum |
	sum := 0.
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:41'!
benchStmParallel
	
	| sum |
	sum := 0.
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:41' prior: 33562933!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: self) do: [ :i |
		[(1 to: 100) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563060!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[(1 to: 100) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563258!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[(i to: (i + 1000)) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563453!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33563655!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k ]] parallelFork
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33563872!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33564102!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(0 to: 7) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33564334!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(0 to: 7) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33564566!
benchStmParallel
	
	| sum t |
	sum := 0.
	
	(0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33564800!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33565051!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait.]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33565319!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 10:47:04 pm} Squeak4.5-12568.image priorSource: 3090!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:56' prior: 33562824!
benchStmAtomic

	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				[sum := sum + k. ] atomic value]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33566018!
benchStmAtomic

	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				[sum := sum + k. ] atomic value]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33565614!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33566678!
benchStmParallel
	
	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 10:58:17 pm} Squeak4.5-12568.image priorSource: 11414!
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:01' prior: 33561633!
value
	
	| result  |
	
	self primEnter.
	result := self block value.
	self primLeave.
	^result
	! !
!STMAtomic methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:02'!
block

	^ block! !
!STMAtomic methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:02'!
block: anObject

	block := anObject! !

[ 1 + 1 ] atomic value!

[ 1 + 1 ] atomic value!

----SNAPSHOT----{16 January 2014 . 11:03:21 pm} Squeak4.5-12568.image priorSource: 12802!

----SNAPSHOT----{16 January 2014 . 11:03:41 pm} Squeak4.5-12568.image priorSource: 13325!

----SNAPSHOT----{16 January 2014 . 11:03:45 pm} Squeak4.5-12568.image priorSource: 13416!

BlockClosure organization addCategory: #STM!

BlockClosure organization classify: #atomic under: #STM!
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 22:37' prior: 33562201!
atomic
	
	^STMAtomic from: self! !

BlockClosure organization classify: #newSTMProcess under: #STM!
!BlockClosure methodsFor: 'STM' stamp: '' prior: 42643259!
newSTMProcess
	^ STMProcess forContext: [self value] asContext priority: Processor activePriority! !
!BlockClosure methodsFor: 'STM' stamp: '' prior: 33568373!
newSTMProcess
	^ STMProcess forContext: [self value] asContext priority: Processor activePriority! !

BlockClosure organization classify: #parallelFork under: #STM!
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 21:13' prior: 33556059!
parallelFork
	^ (self newSTMProcess) fork; yourself! !

Object subclass: #STMFuture
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

Object subclass: #STMFuture
	instanceVariableNames: 'block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:33'!
block

	^ block! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:33'!
block: anObject

	block := anObject! !
!STMFuture methodsFor: 'nil' stamp: 'toma 1/16/2014 23:34'!
invoke
	
	! !

Object subclass: #STMFuture
	instanceVariableNames: 'block process'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:34'!
process

	^ process! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:34'!
process: anObject

	process := anObject! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:35' prior: 33569341!
invoke
	
	self process: (self block parallelFork)! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:35'!
value
	
! !

Object subclass: #STMFuture
	instanceVariableNames: 'block process result'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:35'!
result

	^ result! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:35'!
result: anObject

	result := anObject! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33569785!
invoke
	
	self process: ([self result: self block value] parallelFork)! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33569914!
value
	
	self process wait.! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33570525!
value
	
	self process wait.
	^self result! !
!STMFuture class methodsFor: 'nil' stamp: 'toma 1/16/2014 23:37'!
invoke: aBlock
	
	^(STMFuture new)
		block: aBlock;
		invoke;
		yourself! !
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 23:38'!
async

	^STMFuture invoke: self! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:38'!
benchStmFuture
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:39' prior: 33570998!
benchStmFuture
	
	| futures | 
	! !

(1 to: 100) sum!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:40' prior: 33571101!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id |
		[(1 to: 1000) sum ]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:41' prior: 33571236!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:41' prior: 33571416!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async]
	! !

(1 to: 100) inject: 0 into: [ :i :k | i + k]!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:43' prior: 33571596!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :s :f | s + (f value)]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:44' prior: 33571825!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :next :each | next + (each value)]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:44' prior: 33572069!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :next :each | next + (each value)].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 11:45:18 pm} Squeak4.5-12568.image priorSource: 13507!

----SNAPSHOT----{16 January 2014 . 11:45:23 pm} Squeak4.5-12568.image priorSource: 18085!

----SNAPSHOT----{16 January 2014 . 11:46:35 pm} Squeak4.5-12568.image priorSource: 18176!
\ No newline at end of file
+

----STARTUP----{15 January 2014 . 2:16:33 pm} as /home/bot/lang-smalltalk/images/Squeak4.5-12568.image!

!Integer methodsFor: 'benchmarks' stamp: 'toma 1/15/2014 14:33' prior: 42646392!
benchStm
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 1 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 2 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 3 reporting!!']] parallelFork.
	[(1 to: 1000)
		do: [:t1 | SPyVM print: 'Thread 4 reporting!!']] parallelFork.
	(1 to: 1000)
		do: [:x | SPyVM print: '* spinlock *'].
	^ 42 printString! !

----SNAPSHOT----{15 January 2014 . 2:33:47 pm} Squeak4.5-12568.image priorSource: 9103122!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/15/2014 14:35' prior: 42656801!
benchStm3
	| t1 t2 |
	t1 := [(1 to: 100)
				do: [:t3 | SPyVM print: 'Thread 1 reporting!!']] parallelFork.
	t2 := [(1 to: 100)
				do: [:t3 | SPyVM print: 'Thread 2 reporting!!']] parallelFork.
	SPyVM print: 'Waiting for Task 1'.
	t1 wait.
	SPyVM print: 'Waiting for Task 2'.
	t2 wait.
	SPyVM print: 'Finished waiting.'! !

----SNAPSHOT----{15 January 2014 . 2:36:01 pm} Squeak4.5-12568.image priorSource: 594!
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/15/2014 14:37' prior: 42653846!
wait
	<primitive: 789>
	SPyVM print: ' Failed to wait for process!! '! !

----SNAPSHOT----{15 January 2014 . 2:37:09 pm} Squeak4.5-12568.image priorSource: 1091!

----STARTUP----{16 January 2014 . 9:13:20 pm} as /home/bot/lang-smalltalk/images/Squeak4.5-12568.image!

!BlockClosure methodsFor: 'scheduling' stamp: 'toma 1/16/2014 21:13' prior: 42654183!
parallelFork
	^ (self newSTMProcess) fork; yourself! !

----SNAPSHOT----{16 January 2014 . 9:14:01 pm} Squeak4.5-12568.image priorSource: 1345!
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:14'!
primWait
	<primitive: 789>
	SPyVM print: ' Failed to wait for process!! '! !
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:15' prior: 33555705!
wait
	
	SPyVM print: '[squeak] wait'
	self primWait! !
!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 21:15' prior: 33556450!
wait
	
	SPyVM print: '[squeak] wait'.
	self primWait! !

----SNAPSHOT----{16 January 2014 . 9:15:29 pm} Squeak4.5-12568.image priorSource: 1681!
!BasicClassOrganizer methodsFor: 'accessing' stamp: 'toma 1/16/2014 22:18' prior: 17298983!
classComment
	classComment
		ifNil: [^ ''].
	^ [classComment text ifNil: ['']] on: Error do: [^ ''].! !

Object subclass: #SPySTM
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SPy-Benchmarks'!

Object subclass: #SPySTM
	instanceVariableNames: ''
	classVariableNames: 'Shared'
	poolDictionaries: ''
	category: 'SPy-Benchmarks'!
!SPySTM class methodsFor: 'nil' stamp: 'toma 1/16/2014 22:22'!
shared
	
	^self Shared! !
!SPySTM class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:23' prior: 33557264!
shared
	
	^Shared! !
!SPySTM class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:23'!
shared: aValue
	
	Shared := aValue! !

----SNAPSHOT----{16 January 2014 . 10:24:08 pm} Squeak4.5-12568.image priorSource: 2221!

Object subclass: #STMAtomic
	instanceVariableNames: 'lock'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!
!STMAtomic methodsFor: 'nil' stamp: 'toma 1/16/2014 22:28'!
primEnter
	<primitive: 790>! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:28' prior: 33557810!
primEnter
	<primitive: 790>
	SPyVM print: 'primEnter failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:28' prior: 33557933!
primEnter
	<primitive: 790>
	
	SPyVM print: 'primEnter failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29'!
primLeave
	<primitive: 791>
	
	SPyVM print: 'primLeave failed'.! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29'!
value
	
	self primEnter.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:29' prior: 33558376!
value
	
	| result |
	
	self primEnter.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:30' prior: 33558498!
value
	
	| result |
	
	self primEnter.
	result := self.
	self primLeave
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:30' prior: 33558634!
value
	
	| result |
	
	self primEnter.
	result := self.
	self primLeave.
	! !

Object subclass: #STMAtomic
	instanceVariableNames: 'block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Processes'!
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:31' prior: 33558803!
value
	
	| result |
	
	self primEnter.
	result := self block value.
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:31' prior: 33559111!
value
	
	| result error |
	
	self primEnter.
	result := self block value.
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559293!
value
	
	| result error |
	
	self primEnter.
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559481!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559707!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err]
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:32' prior: 33559950!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err].
	self primLeave.
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:33' prior: 33560207!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Error do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error raise]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:33' prior: 33560465!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error raise]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33560754!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass]
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33561047!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass]
	
	! !
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:35' prior: 33561339!
value
	
	| result error |
	
	self primEnter.
	error := nil.
	result := nil.
	[result := self block value.] on: Exception do: [:err | error := err].
	self primLeave.
	error ifNotNil: [error pass].
	^result
	! !
!STMAtomic class methodsFor: 'nil' stamp: 'toma 1/16/2014 22:36'!
from: aBlock
	
	^ (STMAtomic new)
		block: aBlock;
		yourself.! !
!STMAtomic class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:36' prior: 33561909!
from: aBlock
	
	^ (STMAtomic new)
		block: aBlock;
		yourself! !
!BlockClosure methodsFor: 'nil' stamp: 'toma 1/16/2014 22:37'!
atomic
	
	^STMAtomic from: self! !

SystemOrganization addCategory: #'Kernel-STM'!

SystemOrganization classify: #STMAtomic under: #'Kernel-STM'!

SystemOrganization classify: #STMProcess under: #'Kernel-STM'!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40'!
benchStmAtomic
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562476!
benchStmAtomic
	
	| sum |
	sum := 0.
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562577!
benchStmAtomic
	
	| sum |
	sum := 0.
	
! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:40' prior: 33562700!
benchStmAtomic
	
	| sum |
	sum := 0.
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:41'!
benchStmParallel
	
	| sum |
	sum := 0.
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:41' prior: 33562933!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: self) do: [ :i |
		[(1 to: 100) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563060!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[(1 to: 100) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563258!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[(i to: (i + 1000)) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:42' prior: 33563453!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k ]]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33563655!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k ]] parallelFork
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33563872!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(1 to: 8) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33564102!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(0 to: 7) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:43' prior: 33564334!
benchStmParallel
	
	| sum |
	sum := 0.
	
	(0 to: 7) do: [ :i |
		[((i * 1000) to: ((i + 1) * 1000)) do: [ :k | sum := sum + k. ]] parallelFork.
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33564566!
benchStmParallel
	
	| sum t |
	sum := 0.
	
	(0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33564800!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33565051!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait.]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:46' prior: 33565319!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 10:47:04 pm} Squeak4.5-12568.image priorSource: 3090!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:56' prior: 33562824!
benchStmAtomic

	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000)) do: [ :k | 
				[sum := sum + k. ] atomic value]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33566018!
benchStmAtomic

	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				[sum := sum + k. ] atomic value]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33565614!
benchStmParallel
	
	| sum threads |
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 22:57' prior: 33566678!
benchStmParallel
	
	| sum threads |
	
	sum := 0.
	
	threads := (0 to: 7) collect: [ :i | 
		 [((i * 1000) to: ((i + 1) * 1000 - 1)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 10:58:17 pm} Squeak4.5-12568.image priorSource: 11414!
!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:01' prior: 33561633!
value
	
	| result  |
	
	self primEnter.
	result := self block value.
	self primLeave.
	^result
	! !
!STMAtomic methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:02'!
block

	^ block! !
!STMAtomic methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:02'!
block: anObject

	block := anObject! !

[ 1 + 1 ] atomic value!

[ 1 + 1 ] atomic value!

----SNAPSHOT----{16 January 2014 . 11:03:21 pm} Squeak4.5-12568.image priorSource: 12802!

----SNAPSHOT----{16 January 2014 . 11:03:41 pm} Squeak4.5-12568.image priorSource: 13325!

----SNAPSHOT----{16 January 2014 . 11:03:45 pm} Squeak4.5-12568.image priorSource: 13416!

BlockClosure organization addCategory: #STM!

BlockClosure organization classify: #atomic under: #STM!
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 22:37' prior: 33562201!
atomic
	
	^STMAtomic from: self! !

BlockClosure organization classify: #newSTMProcess under: #STM!
!BlockClosure methodsFor: 'STM' stamp: '' prior: 42643259!
newSTMProcess
	^ STMProcess forContext: [self value] asContext priority: Processor activePriority! !
!BlockClosure methodsFor: 'STM' stamp: '' prior: 33568373!
newSTMProcess
	^ STMProcess forContext: [self value] asContext priority: Processor activePriority! !

BlockClosure organization classify: #parallelFork under: #STM!
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 21:13' prior: 33556059!
parallelFork
	^ (self newSTMProcess) fork; yourself! !

Object subclass: #STMFuture
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

Object subclass: #STMFuture
	instanceVariableNames: 'block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:33'!
block

	^ block! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:33'!
block: anObject

	block := anObject! !
!STMFuture methodsFor: 'nil' stamp: 'toma 1/16/2014 23:34'!
invoke
	
	! !

Object subclass: #STMFuture
	instanceVariableNames: 'block process'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:34'!
process

	^ process! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:34'!
process: anObject

	process := anObject! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:35' prior: 33569341!
invoke
	
	self process: (self block parallelFork)! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:35'!
value
	
! !

Object subclass: #STMFuture
	instanceVariableNames: 'block process result'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:35'!
result

	^ result! !
!STMFuture methodsFor: 'accessing' stamp: 'toma 1/16/2014 23:35'!
result: anObject

	result := anObject! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33569785!
invoke
	
	self process: ([self result: self block value] parallelFork)! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33569914!
value
	
	self process wait.! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:36' prior: 33570525!
value
	
	self process wait.
	^self result! !
!STMFuture class methodsFor: 'nil' stamp: 'toma 1/16/2014 23:37'!
invoke: aBlock
	
	^(STMFuture new)
		block: aBlock;
		invoke;
		yourself! !
!BlockClosure methodsFor: 'STM' stamp: 'toma 1/16/2014 23:38'!
async

	^STMFuture invoke: self! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:38'!
benchStmFuture
	
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:39' prior: 33570998!
benchStmFuture
	
	| futures | 
	! !

(1 to: 100) sum!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:40' prior: 33571101!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id |
		[(1 to: 1000) sum ]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:41' prior: 33571236!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:41' prior: 33571416!
benchStmFuture
	
	| futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async]
	! !

(1 to: 100) inject: 0 into: [ :i :k | i + k]!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:43' prior: 33571596!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :s :f | s + (f value)]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:44' prior: 33571825!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :next :each | next + (each value)]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/16/2014 23:44' prior: 33572069!
benchStmFuture
	
	| sum futures | 
	futures := (0 to: 7) collect: [ :id | [(1 to: 1000) sum] async].
	sum := futures inject: 0 into: [ :next :each | next + (each value)].
	^ sum printString! !

----SNAPSHOT----{16 January 2014 . 11:45:18 pm} Squeak4.5-12568.image priorSource: 13507!

----SNAPSHOT----{16 January 2014 . 11:45:23 pm} Squeak4.5-12568.image priorSource: 18085!

----SNAPSHOT----{16 January 2014 . 11:46:35 pm} Squeak4.5-12568.image priorSource: 18176!

Object subclass: #STMWorker
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

Object subclass: #STMWorker
	instanceVariableNames: 'queue'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:23' prior: 33570359!
invoke
	self process ifNil: [
		self process: ([self result: self block value] parallelFork)
		] ifNotNil: [
		]! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:23' prior: 33573142!
invoke
	self process ifNil: [
		self process: ([self result: self block value] parallelFork)
	] ifNotNil: [
		
	]! !

self!
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:23' prior: 33573350!
invoke
	self process ifNil: [
		self process: ([self result: self block value] parallelFork)
	] ifNotNil: [
		self error: 'Future already invoked'
	]! !
!STMFuture methodsFor: 'nil' stamp: 'toma 1/17/2014 00:24'!
initialize
	
	super initialize.! !

STMFuture removeSelector: #initialize!
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:26' prior: 33570648!
value
	
	self process ifNotNil: [
		self process wait.
		^self result
	] ifNil: [
		self error: 'Future not invoked'
	]
	! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:26' prior: 33573946!
value
	
	self process ifNotNil: [
		self wait.
		^self result
	] ifNil: [
		self error: 'Future not invoked'
	]
	! !
!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:26'!
wait
	
	self process wait.! !
!STMWorker methodsFor: 'nil' stamp: 'toma 1/17/2014 00:28'!
submit: aBlock callback: aUnaryBlock
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:30'!
send: aSymbol with: anArgument
	! !

STMWorker removeSelector: #submit:callback:!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:30'!
on: aSymbol do: aBlock
	
! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:30' prior: 33574724!
on: aSymbol do: aBlock
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:31'!
onMessage: aSymbol do: aBlock
	
	! !

STMWorker removeSelector: #on:do:!

Object subclass: #STMWorker
	instanceVariableNames: 'queue handlers'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMWorker methodsFor: 'nil' stamp: 'toma 1/17/2014 00:31'!
initialize
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:31' prior: 33575225!
initialize
	
	handlers := Dictionary new.! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
queue

	^ queue! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
queue: anObject

	queue := anObject! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
handlers

	^ handlers! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
handlers: anObject

	handlers := anObject! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:32' prior: 33575335!
initialize
	
	self handlers: Dictionary new.! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:32' prior: 33574951!
onMessage: aSymbol do: aBlock
	
	self handlers at: aSymbol put: aBlock! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:32' prior: 33574566!
send: aSymbol with: anArgument
	
! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:32' prior: 33576170!
send: aSymbol with: anArgument
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:34' prior: 33576299!
send: aSymbol with: anArgument
	
	! !

Object subclass: #STMMessage
	instanceVariableNames: 'queue handlers'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

Object subclass: #STMMessage
	instanceVariableNames: 'name arg'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

Object subclass: #STMMessage
	instanceVariableNames: 'name args'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

{1. 2.}!

{1. 2. World.}!

[:i :j | i + j]!

[:i :j | i + j] valueWithArguments: {1. 2.}!
!STMMessage class methodsFor: 'nil' stamp: 'toma 1/17/2014 00:39'!
named: aSymbol withArgs: anArray
	
	^(self new)
		name: aSymbol;
		arguments: anArray;
		yourself! !

Object subclass: #STMMessage
	instanceVariableNames: 'name arguments'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMMessage methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:39'!
name: anObject

	name := anObject! !
!STMMessage methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:39'!
arguments

	^ arguments! !
!STMMessage methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:39'!
arguments: anObject

	arguments := anObject! !

Object subclass: #STMMessage
	instanceVariableNames: 'messageName arguments'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMMessage methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:40'!
messageName

	^ messageName! !
!STMMessage methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:40'!
messageName: anObject

	messageName := anObject! !

STMMessage removeSelector: #name:!
!STMMessage class methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:40' prior: 33577040!
named: aSymbol withArgs: anArray
	
	^(self new)
		messageName: aSymbol;
		arguments: anArray;
		yourself! !

a := {1. 2. 3.}!

a := OrderedCollection new!

a add: 5!

a!

a add: 5!

a!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:44' prior: 33576429!
send: aSymbol with: anArgument
	
	self queue! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:44' prior: 33575864!
initialize
	
	self handlers: Dictionary new.
	self queue: Stack new.! !

a := Stack new!

a := Stack new!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:47' prior: 33578512!
initialize
	
	self handlers: Dictionary new.
	self queue: LinkedList new.! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:48' prior: 33578372!
send: aSymbol with: anArgument
	
	self queue addLast: (STMMessage named: aSymbol with: {anArgument})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:48' prior: 33578879!
send: aSymbol with: anArgument
	
	self queue addLast: (STMMessage named: aSymbol withArgs: {anArgument})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:48' prior: 33579075!
send: aSymbol with: anArgument
	
	self queue addLast: (
		STMMessage named: aSymbol withArgs: {anArgument})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:49'!
send: aSymbol with: anArgument with: anotherArgument
	
	self queue addLast: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument.})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:49'!
send: aSymbol with: anArgument and: anotherArgument
	
	self queue addLast: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument.})! !

STMWorker removeSelector: #send:with:with:!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:49'!
send: aSymbol with: anArgument and: anotherArgument and: aThirdArgument
	
	self queue addLast: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument. aThirdArgument})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:50'!
loop
	! !

Object subclass: #STMWorker
	instanceVariableNames: 'queue handlers active'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:50'!
active

	^ active! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:50'!
active: anObject

	active := anObject! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:50' prior: 33580221!
loop
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:51' prior: 33580665!
loop
	
	self active: true.
	[self active] whileTrue: [
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:51' prior: 33580769!
loop
	
	self active: true.
	[self active] whileTrue: [
		
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:52' prior: 33580922!
loop
	
	self active: true.
	[self active] whileTrue: [
		[self queue isEmpty] ifFalse: [
			
		]
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:52' prior: 33581078!
loop
	
	self active: true.
	[self active] whileTrue: [
		[self queue isEmpty] ifFalse: [
			| message | 
			[message := self queue removeFirst]
		]
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:52' prior: 33581273!
loop
	
	self active: true.
	[self active] whileTrue: [
		| message | 
		[self queue isEmpty] ifFalse: [
			
			[message := self queue removeFirst]
		]
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:53' prior: 33581519!
loop
	
	self active: true.
	[self active] whileTrue: [
		| message | 
		message := nil.
		[self queue isEmpty] ifFalse: [
			
			[message := self queue removeFirst]
		]
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:53' prior: 33581768!
loop
	
	self active: true.
	[self active] whileTrue: [
		| message | 
		message := nil.
		[ [self queue isEmpty] ifFalse: [	
			[message := self queue removeFirst]
		] ] atomic value.

	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:53' prior: 33582035!
loop
	
	self active: true.
	[self active] whileTrue: [
		| message | 
		message := nil.
		[ [self queue isEmpty] ifFalse: [	
			[message := self queue removeFirst]
		] ] atomic value.
		
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:54'!
receive
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:54' prior: 33582318!
loop
	
	self active: true.
	[self active] whileTrue: [
		
		
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:54' prior: 33582587!
receive
	
	| message | 
		message := nil.
		[ [self queue isEmpty] ifFalse: [	
			[message := self queue removeFirst]
		] ] atomic value.! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:54' prior: 33582853!
receive
	
	| message | 
	
	message := nil.
	[ [self queue isEmpty] ifFalse: [	
			[message := self queue removeFirst]] 
	] atomic value.
	^message! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:55' prior: 33575531!
queue: aMessage
	
	! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:55' prior: 33583328!
queue: aMessage
	
	[self queue addLast: aMessage] atomic value! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:56' prior: 33583443!
queue: anObject
	
	queue := anObject! !
!STMWorker methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:56'!
schedule: aMessage

	[self queue addLast: aMessage] atomic value! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58' prior: 33579275!
send: aSymbol with: anArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58' prior: 33579689!
send: aSymbol with: anArgument and: anotherArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument.})! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58' prior: 33579960!
send: aSymbol with: anArgument and: anotherArgument and: aThirdArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument. aThirdArgument})! !

STMWorker organization classify: #schedule: under: #'as yet unclassified'!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:56' prior: 33583697!
schedule: aMessage

	[self queue addLast: aMessage] atomic value! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:00' prior: 33582694!
loop
	
	self active: true.
	[self active] whileTrue: [
		self receive ifNotNilDo: [ :m
			
			]
		
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:01' prior: 33584800!
loop
	
	self active: true.
	[self active] whileTrue: [
		self receive ifNotNilDo: [ :m |
			(self handlers at: (m messageName))
				valueWithArguments: (m arguments)
			]
		
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:01' prior: 33584997!
loop
	
	self active: true.
	[self active] whileTrue: [
		self receive ifNotNilDo: [ :m |
			(self handlers at: (m messageName))
				valueWithArguments: (m arguments)
			]
	]! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:01'!
stop

	self active: False! !
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:01'!
start
	
	[self loop] parallelFork! !

w := STMWorker new!

w onMessage: #test do: [:i | Transcript show: i]!

w start!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:03' prior: 33583086!
receive
	
	| message | 
	
	message := nil.
	[ (self queue isEmpty) ifFalse: [	
			[message := self queue removeFirst]] 
	] atomic value.
	^message! !

w stop!
!STMWorker methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:04' prior: 33585522!
stop

	self active: false! !

Smalltalk renameClassNamed: #STMWorker as: #STMActor!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:06'!
benchStmActor
	
	| a1 a2 |
	
! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:06' prior: 33586238!
benchStmActor
	
	| a1 a2 |
	
	a1 := STMActor new.
	a2 := STMActor new.
	! !

1 printString!

1 printString!

1 printString!

'1'!
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:14' prior: 33586352!
benchStmActor
	
	| a |
	
	a := STMActor new.
	a onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		(n < 1) 
			ifTrue: [SPyVM print: (sum2 printString) ] 
			ifFalse: [a send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		]! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:14' prior: 33586563!
benchStmActor
	
	| a |
	
	a := STMActor new.
	a onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		(n < 1) 
			ifTrue: [SPyVM print: (sum1 printString) ] 
			ifFalse: [a send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		]
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:15' prior: 33586879!
benchStmActor
	
	| a |
	
	a := STMActor new.
	a onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		(n < 1) 
			ifTrue: [SPyVM print: (sum1 printString) ] 
			ifFalse: [a send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		]
	a start.
	! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:18' prior: 33587197!
benchStmActor
	
	| a b |
	
	a := STMActor new.
	b := STMActor new.
	a onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		SPyVM print: 'a'.
		(n < 1) 
			ifTrue: [SPyVM print: (sum1 printString) ] 
			ifFalse: [b send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		].
	b onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		SPyVM print: 'b'.
		(n < 1) 
			ifTrue: [SPyVM print: (sum1 printString) ] 
			ifFalse: [a send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		].
	a start.
	b start.
	a send: #fibonacci with: self and: 1 and: 1.! !
!Integer methodsFor: 'benchmarks' stamp: 'toma 1/17/2014 01:19' prior: 33587525!
benchStmActor
	
	| a b |
	
	a := STMActor new.
	b := STMActor new.
	a onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		SPyVM print: 'a'.
		(n < 1) 
			ifTrue: [SPyVM print: (sum1 printString) ] 
			ifFalse: [b send: #fibonacci with: (n - 1) and: sum2 and: (sum1 + sum2)]
		].
	b onMessage: #fibonacci do: [ :n :sum1 :sum2 | 
		SPyVM print: 'b'.


More information about the pypy-commit mailing list