| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257 | 
							- Smalltalk current createPackage: 'Kernel-Methods' properties: #{}!
 
- Object subclass: #CompiledMethod
 
- 	instanceVariableNames: ''
 
- 	category: 'Kernel-Methods'!
 
- !CompiledMethod methodsFor: 'accessing'!
 
- source
 
- 	^(self basicAt: 'source') ifNil: ['']
 
- !
 
- source: aString
 
- 	self basicAt: 'source' put: aString
 
- !
 
- category
 
- 	^(self basicAt: 'category') ifNil: ['']
 
- !
 
- category: aString
 
- 	self basicAt: 'category' put: aString
 
- !
 
- selector
 
- 	^self basicAt: 'selector'
 
- !
 
- selector: aString
 
- 	self basicAt: 'selector' put: aString
 
- !
 
- fn
 
- 	^self basicAt: 'fn'
 
- !
 
- fn: aBlock
 
- 	self basicAt: 'fn' put: aBlock
 
- !
 
- messageSends
 
- 	^self basicAt: 'messageSends'
 
- !
 
- methodClass
 
- 	^self basicAt: 'methodClass'
 
- !
 
- referencedClasses
 
- 	^self basicAt: 'referencedClasses'
 
- !
 
- arguments
 
- 	<return self.args || []>
 
- ! !
 
- Object subclass: #BlockClosure
 
- 	instanceVariableNames: ''
 
- 	category: 'Kernel-Methods'!
 
- !BlockClosure commentStamp!
 
- A BlockClosure is a lexical closure.
 
- The JavaScript representation is a function.
 
- A BlockClosure is evaluated with the #value* methods in the 'evaluating' protocol.!
 
- !BlockClosure methodsFor: 'accessing'!
 
- compiledSource
 
- 	<return self.toString()>
 
- !
 
- numArgs
 
- 	<return self.length>
 
- ! !
 
- !BlockClosure methodsFor: 'controlling'!
 
- whileTrue: aBlock
 
- 	"inlined in the Compiler"
 
- 	<while(self()) {aBlock()}>
 
- !
 
- whileFalse: aBlock
 
- 	"inlined in the Compiler"
 
- 	<while(!!self()) {aBlock()}>
 
- !
 
- whileFalse
 
- 	"inlined in the Compiler"
 
- 	self whileFalse: []
 
- !
 
- whileTrue
 
- 	"inlined in the Compiler"
 
- 	self whileTrue: []
 
- ! !
 
- !BlockClosure methodsFor: 'error handling'!
 
- on: anErrorClass do: aBlock
 
- 	^self try: self catch: [:error |
 
- 	    (error isKindOf: anErrorClass) 
 
- 	     ifTrue: [aBlock value: error]
 
- 	     ifFalse: [error signal]]
 
- ! !
 
- !BlockClosure methodsFor: 'evaluating'!
 
- value
 
- 	"inlined in the Compiler"
 
- 	<return self();>
 
- !
 
- value: anArg
 
- 	"inlined in the Compiler"
 
- 	<return self(anArg);>
 
- !
 
- value: firstArg value: secondArg
 
- 	"inlined in the Compiler"
 
- 	<return self(firstArg, secondArg);>
 
- !
 
- value: firstArg value: secondArg value: thirdArg
 
- 	"inlined in the Compiler"
 
- 	<return self(firstArg, secondArg, thirdArg);>
 
- !
 
- valueWithPossibleArguments: aCollection
 
- 	<return self.apply(null, aCollection);>
 
- !
 
- new
 
- 	"Use the receiver as a JS constructor. 
 
- 	*Do not* use this method to instanciate Smalltalk objects!!"
 
- 	<return new self()>
 
- !
 
- applyTo: anObject arguments: aCollection
 
- 	<return self.apply(anObject, aCollection)>
 
- !
 
- timeToRun
 
- 	"Answer the number of milliseconds taken to execute this block."
 
- 	^ Date millisecondsToRun: self
 
- !
 
- ensure: aBlock
 
- 	| success |
 
- 	success := false.
 
- 	^[self value. success := true. aBlock value]
 
- 		on: Error
 
- 		do: [:ex |
 
- 			success ifFalse: [aBlock value].
 
- 			ex signal]
 
- !
 
- newValue: anObject
 
- 	"Use the receiver as a JS constructor. 
 
- 	*Do not* use this method to instanciate Smalltalk objects!!"
 
- 	<return new self(anObject)>
 
- !
 
- newValue:  anObject value: anObject2
 
- 	"Use the receiver as a JS constructor. 
 
- 	*Do not* use this method to instanciate Smalltalk objects!!"
 
- 	<return new self(anObject, anObject2)>
 
- !
 
- newValue:  anObject value: anObject2 value: anObject3
 
- 	"Use the receiver as a JS constructor. 
 
- 	*Do not* use this method to instanciate Smalltalk objects!!"
 
- 	<return new self(anObject, anObject2)>
 
- ! !
 
- !BlockClosure methodsFor: 'timeout/interval'!
 
- valueWithTimeout: aNumber
 
- 	<return setTimeout(self, aNumber)>
 
- !
 
- valueWithInterval: aNumber
 
- 	<return setInterval(self, aNumber)>
 
- ! !
 
- Object subclass: #MethodContext
 
- 	instanceVariableNames: ''
 
- 	category: 'Kernel-Methods'!
 
- !MethodContext methodsFor: 'accessing'!
 
- receiver
 
- 	<return self.receiver>
 
- !
 
- selector
 
- 	<return smalltalk.convertSelector(self.selector)>
 
- !
 
- home
 
- 	<return self.homeContext>
 
- !
 
- temps
 
- 	<return self.temps>
 
- !
 
- printString
 
- 	^super printString, '(', self asString, ')'
 
- !
 
- asString
 
- 	^self receiver class printString, ' >> ', self selector
 
- ! !
 
- Object subclass: #Message
 
- 	instanceVariableNames: 'selector arguments'
 
- 	category: 'Kernel-Methods'!
 
- !Message methodsFor: 'accessing'!
 
- selector
 
- 	^selector
 
- !
 
- selector: aString
 
- 	selector := aString
 
- !
 
- arguments: anArray
 
- 	arguments := anArray
 
- !
 
- arguments
 
- 	^arguments
 
- ! !
 
- !Message methodsFor: 'printing'!
 
- printString
 
- 	^ String streamContents: [:aStream|  
 
-                                   				aStream 
 
-                                   					nextPutAll: super printString;
 
-                                   					nextPutAll: '(';
 
-                                   					nextPutAll: selector;
 
-                                   					nextPutAll: ')' 				]
 
- ! !
 
- !Message class methodsFor: 'instance creation'!
 
- selector: aString arguments: anArray
 
- 	^self new
 
- 		selector: aString;
 
- 		arguments: anArray;
 
- 		yourself
 
- ! !
 
 
  |