[pypy-commit] lang-smalltalk default: File out sources! (puuuh... conflicted changes not nice)

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


Author: amintos
Branch: 
Changeset: r762:faed200eb69c
Date: 2014-01-20 11:24 +0100
http://bitbucket.org/pypy/lang-smalltalk/changeset/faed200eb69c/

Log:	File out sources! (puuuh... conflicted changes not nice)

diff --git a/images/Integer-benchStmAtomic.st b/images/Integer-benchStmAtomic.st
new file mode 100644
--- /dev/null
+++ b/images/Integer-benchStmAtomic.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 10:59:50 am'!

!Integer methodsFor: 'benchmarks' stamp: 'toma 1/18/2014 22:07'!
benchStmAtomic
	
	| sum num threads max start |
	
	num := self \\ 100.
	max := (self - num) // num.
	sum := 0.
	SPyVM print: ('Threads:', (num printString)).
	SPyVM print: ('Items/Thread:', (max printString)).
	
	start := Time now asNanoSeconds.
	
	threads := (1 to: num) collect: [ :i | 
		 [((i * max) to: ((i + 1) * max - 1)) do: [ :k | 
				[sum := sum + k.] atomic value. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	SPyVM print: '[squeak] milliseconds inside method:'.
	SPyVM print: (((Time now asNanoSeconds) - start) // 1000000) printString.
	^ sum printString! !
\ No newline at end of file
diff --git a/images/Integer-benchStmFuture.st b/images/Integer-benchStmFuture.st
new file mode 100644
--- /dev/null
+++ b/images/Integer-benchStmFuture.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 10:59:37 am'!

!Integer methodsFor: 'benchmarks' stamp: 'toma 1/18/2014 16:36'!
benchStmFuture
	
	| sum num max futures start |
	
	num := self \\ 100.
	max := (self - num) // num.
	sum := 0.
	SPyVM print: ('Threads:', (num printString)).
	SPyVM print: ('Items/Thread:', (max printString)).
	
	start := Time now asNanoSeconds.
	
	futures := (1 to: num) collect: [ :id | [(1 to: max) sum] async].
	sum := futures inject: 0 into: [ :next :each | next + (each value)].
	
	SPyVM print: '[squeak] milliseconds inside method:'.
	SPyVM print: (((Time now asNanoSeconds) - start) // 1000000) printString.
	
	^ sum printString! !
\ No newline at end of file
diff --git a/images/Integer-benchStmParallel.st b/images/Integer-benchStmParallel.st
new file mode 100644
--- /dev/null
+++ b/images/Integer-benchStmParallel.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 10:59:46 am'!

!Integer methodsFor: 'benchmarks' stamp: 'toma 1/18/2014 22:07'!
benchStmParallel
	
	| sum num threads max start |
	
	num := self \\ 100.
	max := (self - num) // num.
	sum := 0.
	SPyVM print: ('Threads:', (num printString)).
	SPyVM print: ('Items/Thread:', (max printString)).
	
	start := Time now asNanoSeconds.
	
	threads := (1 to: num) collect: [ :i | 
		 [((i * max) to: ((i + 1) * max - 1)) do: [ :k | 
				sum := sum + k. ]
			] parallelFork
		].
	threads do: [:t | t wait].
	SPyVM print: '[squeak] milliseconds inside method:'.
	SPyVM print: (((Time now asNanoSeconds) - start) // 1000000) printString.
	^ sum printString! !
\ No newline at end of file
diff --git a/images/STMActor.st b/images/STMActor.st
new file mode 100644
--- /dev/null
+++ b/images/STMActor.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 11:01:35 am'!
Object subclass: #STMActor
	instanceVariableNames: 'queue handlers active'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:47'!
initialize
	
	self handlers: Dictionary new.
	self queue: LinkedList new.! !

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:01'!
loop
	
	self active: true.
	[self active] whileTrue: [
		self receive ifNotNilDo: [ :m |
			(self handlers at: (m messageName))
				valueWithArguments: (m arguments)
			]
	]! !

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:32'!
onMessage: aSymbol do: aBlock
	
	self handlers at: aSymbol put: aBlock! !

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

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:56'!
schedule: aMessage

	[self queue addLast: aMessage] atomic value! !

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58'!
send: aSymbol with: anArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument})! !

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58'!
send: aSymbol with: anArgument and: anotherArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument.})! !

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:58'!
send: aSymbol with: anArgument and: anotherArgument and: aThirdArgument
	
	self schedule: (
		STMMessage named: aSymbol withArgs: {anArgument. anotherArgument. aThirdArgument})! !

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

!STMActor methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 01:04'!
stop

	self active: false! !


!STMActor methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:50'!
active

	^ active! !

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

	active := anObject! !

!STMActor methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
handlers

	^ handlers! !

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

	handlers := anObject! !

!STMActor methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:32'!
queue

	^ queue! !

!STMActor methodsFor: 'accessing' stamp: 'toma 1/17/2014 00:56'!
queue: anObject
	
	queue := anObject! !
\ No newline at end of file
diff --git a/images/STMAtomic.st b/images/STMAtomic.st
new file mode 100644
--- /dev/null
+++ b/images/STMAtomic.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 11:01:40 am'!
Object subclass: #STMAtomic
	instanceVariableNames: 'block'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

!STMAtomic methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:28'!
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 23:01'!
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! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

STMAtomic class
	instanceVariableNames: ''!

!STMAtomic class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 22:36'!
from: aBlock
	
	^ (STMAtomic new)
		block: aBlock;
		yourself! !
\ No newline at end of file
diff --git a/images/STMFuture.st b/images/STMFuture.st
new file mode 100644
--- /dev/null
+++ b/images/STMFuture.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 11:01:42 am'!
Object subclass: #STMFuture
	instanceVariableNames: 'block process result'
	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: '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: '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/17/2014 00:23'!
invoke
	self process ifNil: [
		self process: ([self result: self block value] parallelFork)
	] ifNotNil: [
		self error: 'Future already invoked'
	]! !

!STMFuture methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:26'!
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.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

STMFuture class
	instanceVariableNames: ''!

!STMFuture class methodsFor: 'as yet unclassified' stamp: 'toma 1/16/2014 23:37'!
invoke: aBlock
	
	^(STMFuture new)
		block: aBlock;
		invoke;
		yourself! !
\ No newline at end of file
diff --git a/images/STMMessage.st b/images/STMMessage.st
new file mode 100644
--- /dev/null
+++ b/images/STMMessage.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 11:01:44 am'!
Object subclass: #STMMessage
	instanceVariableNames: 'messageName arguments'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

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

!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 class
	instanceVariableNames: ''!

!STMMessage class methodsFor: 'as yet unclassified' stamp: 'toma 1/17/2014 00:40'!
named: aSymbol withArgs: anArray
	
	^(self new)
		messageName: aSymbol;
		arguments: anArray;
		yourself! !
\ No newline at end of file
diff --git a/images/STMProcess.st b/images/STMProcess.st
new file mode 100644
--- /dev/null
+++ b/images/STMProcess.st
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 28 April 2013 [latest update: #12627] on 20 January 2014 at 11:05:53 am'!
Process subclass: #STMProcess
	instanceVariableNames: 'lock'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-STM'!

!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
fork
	<primitive: 787>
	Transcript show: '* STM Process did not fork *' , Character cr.
	self resume! !

!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
initialize
	lock := 1.
	super initialize! !

!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
primWait
	<primitive: 789>
	SPyVM print: ' Failed to wait for process!! '! !

!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
signal
	<primitive: 788>
	Transcript show: ' Failed to signal process!! '! !

!STMProcess methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
wait
	
	self primWait ! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

STMProcess class
	instanceVariableNames: ''!

!STMProcess class methodsFor: 'as yet unclassified' stamp: 'toma 1/20/2014 11:05'!
forContext: t1 priority: t2 
	| t3 |
	t3 := self new.
	t3 suspendedContext: t1.
	t3 priority: t2.
	^ t3 ! !
\ No newline at end of file


More information about the pypy-commit mailing list