| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896 | 
							- Smalltalk createPackage: 'Kernel-Methods'!
 
- Object subclass: #BlockClosure
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Methods'!
 
- !BlockClosure commentStamp!
 
- I represent a lexical closure.
 
- I am is directly mapped to JavaScript Function.
 
- ## API
 
- 1. Evaluation
 
-     My instances get evaluated with the `#value*` methods in the 'evaluating' protocol.
 
-     Example: ` [ :x | x + 1 ] value: 3 "Answers 4" `
 
- 2. Control structures
 
-     Blocks are used (together with `Boolean`) for control structures (methods in the `controlling` protocol).
 
-     Example: `aBlock whileTrue: [ ... ]`
 
- 3. Error handling
 
-     I provide the `#on:do:` method for handling exceptions.
 
-     Example: ` aBlock on: MessageNotUnderstood do: [ :ex | ... ] `!
 
- !BlockClosure methodsFor: 'accessing'!
 
- compiledSource
 
- 	<return self.toString()>
 
- !
 
- numArgs
 
- 	<return self.length>
 
- !
 
- receiver
 
- 	^ nil
 
- ! !
 
- !BlockClosure methodsFor: 'controlling'!
 
- whileFalse
 
- 	self whileFalse: []
 
- !
 
- whileFalse: aBlock
 
- 	<while(!!$core.assert(self._value())) {aBlock._value()}>
 
- !
 
- whileTrue
 
- 	self whileTrue: []
 
- !
 
- whileTrue: aBlock
 
- 	<while($core.assert(self._value())) {aBlock._value()}>
 
- ! !
 
- !BlockClosure methodsFor: 'converting'!
 
- asCompiledMethod: aString
 
- 	<return $core.method({selector:aString, fn:self});>
 
- !
 
- currySelf
 
- 	"Transforms [ :selfarg :x :y | stcode ] block
 
- 	which represents JS function (selfarg, x, y, ...) {jscode}
 
- 	into function (x, y, ...) {jscode} that takes selfarg from 'this'.
 
- 	IOW, it is usable as JS method and first arg takes the receiver."
 
- 	
 
- 	<
 
- 		return function () {
 
- 			var args = [ this ];
 
- 			args.push.apply(args, arguments);
 
- 			return self.apply(null, args);
 
- 		}
 
- 	>
 
- ! !
 
- !BlockClosure methodsFor: 'error handling'!
 
- on: anErrorClass do: aBlock
 
- 	"All exceptions thrown in the Smalltalk stack are cought.
 
- 	Convert all JS exceptions to JavaScriptException instances."
 
- 	
 
- 	^ self tryCatch: [ :error | | smalltalkError |
 
- 		smalltalkError := Smalltalk asSmalltalkException: error.
 
- 		(smalltalkError isKindOf: anErrorClass)
 
- 		ifTrue: [ aBlock value: smalltalkError ]
 
- 		ifFalse: [ smalltalkError resignal ] ]
 
- !
 
- tryCatch: aBlock
 
- 	<
 
- 		try {
 
- 			return self._value();
 
- 		} catch(error) {
 
- 			// pass non-local returns undetected
 
- 			if (Array.isArray(error) && error.length === 1) throw error;
 
- 			return aBlock._value_(error);
 
- 		}
 
- 	>
 
- ! !
 
- !BlockClosure methodsFor: 'evaluating'!
 
- applyTo: anObject arguments: aCollection
 
- 	<return self.apply(anObject, aCollection)>
 
- !
 
- ensure: aBlock
 
- 	<try{return self._value()}finally{aBlock._value()}>
 
- !
 
- new
 
- 	"Use the receiver as a JS constructor.
 
- 	*Do not* use this method to instanciate Smalltalk objects!!"
 
- 	<return new self()>
 
- !
 
- newValue: anObject
 
- 	^ self newWithValues: { anObject }
 
- !
 
- newValue: anObject value: anObject2
 
- 	^ self newWithValues: { anObject. anObject2 }.
 
- !
 
- newValue: anObject value: anObject2 value: anObject3
 
- 	^ self newWithValues: { anObject. anObject2. anObject3 }.
 
- !
 
- newWithValues: aCollection
 
- 	"Simulates JS new operator by combination of Object.create and .apply"
 
- 	<
 
- 		var object = Object.create(self.prototype);
 
- 		var result = self.apply(object, aCollection);
 
- 		return typeof result === "object" ? result : object;
 
- 	>
 
- !
 
- timeToRun
 
- 	"Answer the number of milliseconds taken to execute this block."
 
- 	^ Date millisecondsToRun: self
 
- !
 
- value
 
- 	<return self();>
 
- !
 
- value: anArg
 
- 	<return self(anArg);>
 
- !
 
- value: firstArg value: secondArg
 
- 	<return self(firstArg, secondArg);>
 
- !
 
- value: firstArg value: secondArg value: thirdArg
 
- 	<return self(firstArg, secondArg, thirdArg);>
 
- !
 
- valueWithPossibleArguments: aCollection
 
- 	<return self.apply(null, aCollection);>
 
- ! !
 
- !BlockClosure methodsFor: 'timeout/interval'!
 
- fork
 
- 	ForkPool default fork: self
 
- !
 
- valueWithInterval: aNumber
 
- 	<
 
- 		var interval = setInterval(self, aNumber);
 
- 		return $globals.Timeout._on_(interval);
 
- 	>
 
- !
 
- valueWithTimeout: aNumber
 
- 	<
 
- 		var timeout = setTimeout(self, aNumber);
 
- 		return $globals.Timeout._on_(timeout);
 
- 	>
 
- ! !
 
- Object subclass: #CompiledMethod
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Methods'!
 
- !CompiledMethod commentStamp!
 
- I represent a class method of the system. I hold the source and compiled code of a class method.
 
- ## API
 
- My instances can be accessed using `Behavior >> #methodAt:`
 
-     Object methodAt: 'asString'
 
- Source code access:
 
- 	(String methodAt: 'lines') source
 
- Referenced classes:
 
- 	(String methodAt: 'lines') referencedClasses
 
- Messages sent from an instance:
 
- 	
 
- 	(String methodAt: 'lines') messageSends!
 
- !CompiledMethod methodsFor: 'accessing'!
 
- arguments
 
- 	<return self.args || []>
 
- !
 
- category
 
- 	^ self protocol
 
- !
 
- fn
 
- 	^ self basicAt: 'fn'
 
- !
 
- fn: aBlock
 
- 	self basicAt: 'fn' put: aBlock
 
- !
 
- messageSends
 
- 	^ self basicAt: 'messageSends'
 
- !
 
- methodClass
 
- 	^ self basicAt: 'methodClass'
 
- !
 
- package
 
- 	"Answer the package the receiver belongs to:
 
- 	- if it is an extension method, answer the corresponding package
 
- 	- else answer the `methodClass` package"
 
- 	
 
- 	^ self methodClass ifNotNil: [ :class | class packageOfProtocol: self protocol ]
 
- !
 
- protocol
 
- 	^ (self basicAt: 'protocol') ifNil: [ self defaultProtocol ]
 
- !
 
- protocol: aString
 
- 	| oldProtocol |
 
- 	oldProtocol := self protocol.
 
- 	self basicAt: 'protocol' put: aString.
 
- 	SystemAnnouncer current announce: (MethodMoved new
 
- 		method: self;
 
- 		oldProtocol: oldProtocol;
 
- 		yourself).
 
- 	self methodClass ifNotNil: [ :methodClass |
 
- 		methodClass organization addElement: aString.
 
- 		methodClass removeProtocolIfEmpty: oldProtocol ]
 
- !
 
- referencedClasses
 
- 	^ self basicAt: 'referencedClasses'
 
- !
 
- selector
 
- 	^ self basicAt: 'selector'
 
- !
 
- selector: aString
 
- 	self basicAt: 'selector' put: aString
 
- !
 
- source
 
- 	^ (self basicAt: 'source') ifNil: [ '' ]
 
- !
 
- source: aString
 
- 	self basicAt: 'source' put: aString
 
- ! !
 
- !CompiledMethod methodsFor: 'browsing'!
 
- browse
 
- 	Finder findMethod: self
 
- ! !
 
- !CompiledMethod methodsFor: 'defaults'!
 
- defaultProtocol
 
- 	^ 'as yet unclassified'
 
- ! !
 
- !CompiledMethod methodsFor: 'evaluating'!
 
- sendTo: anObject arguments: aCollection
 
- 	^ self fn applyTo: anObject arguments: aCollection
 
- ! !
 
- !CompiledMethod methodsFor: 'testing'!
 
- isCompiledMethod
 
- 	^ true
 
- !
 
- isOverridden
 
- 	| selector |
 
-     
 
-     selector := self selector.
 
-     self methodClass allSubclassesDo: [ :each |
 
- 	    (each includesSelector: selector)
 
-         	ifTrue: [ ^ true ] ].
 
- 	^ false
 
- !
 
- isOverride
 
- 	| superclass |
 
-     
 
-     superclass := self methodClass superclass.
 
- 	superclass ifNil: [ ^ false ].
 
- 	
 
-     ^ (self methodClass superclass lookupSelector: self selector) notNil
 
- ! !
 
- Object subclass: #ForkPool
 
- 	instanceVariableNames: 'poolSize maxPoolSize queue worker'
 
- 	package: 'Kernel-Methods'!
 
- !ForkPool commentStamp!
 
- I am responsible for handling forked blocks.
 
- The pool size sets the maximum concurrent forked blocks.
 
- ## API
 
- The default instance is accessed with `#default`.
 
- The maximum concurrent forked blocks can be set with `#maxPoolSize:`.
 
- Forking is done via `BlockClosure >> #fork`!
 
- !ForkPool methodsFor: 'accessing'!
 
- maxPoolSize
 
- 	^ maxPoolSize ifNil: [ self defaultMaxPoolSize ]
 
- !
 
- maxPoolSize: anInteger
 
- 	maxPoolSize := anInteger
 
- ! !
 
- !ForkPool methodsFor: 'actions'!
 
- fork: aBlock
 
- 	poolSize < self maxPoolSize ifTrue: [ self addWorker ].
 
- 	queue nextPut: aBlock
 
- ! !
 
- !ForkPool methodsFor: 'defaults'!
 
- defaultMaxPoolSize
 
- 	^ self class defaultMaxPoolSize
 
- ! !
 
- !ForkPool methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- 	
 
- 	poolSize := 0.
 
- 	queue := Queue new.
 
- 	worker := self makeWorker
 
- !
 
- makeWorker
 
- 	| sentinel |
 
- 	sentinel := Object new.
 
- 	^ [ | block |
 
- 		poolSize := poolSize - 1.
 
- 		block := queue nextIfAbsent: [ sentinel ].
 
- 		block == sentinel ifFalse: [
 
- 			[ block value ] ensure: [ self addWorker ] ]]
 
- ! !
 
- !ForkPool methodsFor: 'private'!
 
- addWorker
 
- 	worker valueWithTimeout: 0.
 
- 	poolSize := poolSize + 1
 
- ! !
 
- ForkPool class instanceVariableNames: 'default'!
 
- !ForkPool class methodsFor: 'accessing'!
 
- default
 
- 	^ default ifNil: [ default := self new ]
 
- !
 
- defaultMaxPoolSize
 
- 	^ 100
 
- !
 
- resetDefault
 
- 	default := nil
 
- ! !
 
- Object subclass: #Message
 
- 	instanceVariableNames: 'selector arguments'
 
- 	package: 'Kernel-Methods'!
 
- !Message commentStamp!
 
- In general, the system does not use instances of me for efficiency reasons.
 
- However, when a message is not understood by its receiver, the interpreter will make up an instance of it in order to capture the information involved in an actual message transmission.
 
- This instance is sent it as an argument with the message `#doesNotUnderstand:` to the receiver.
 
- See boot.js, `messageNotUnderstood` and its counterpart `Object >> #doesNotUnderstand:`
 
- ## API
 
- Besides accessing methods, `#sendTo:` provides a convenient way to send a message to an object.!
 
- !Message methodsFor: 'accessing'!
 
- arguments
 
- 	^ arguments
 
- !
 
- arguments: anArray
 
- 	arguments := anArray
 
- !
 
- selector
 
- 	^ selector
 
- !
 
- selector: aString
 
- 	selector := aString
 
- ! !
 
- !Message methodsFor: 'actions'!
 
- sendTo: anObject
 
- 	^ anObject perform: self selector withArguments: self arguments
 
- ! !
 
- !Message methodsFor: 'printing'!
 
- printOn: aStream
 
- 	super printOn: aStream.
 
- 	aStream
 
- 		nextPutAll: '(';
 
- 		nextPutAll: self selector;
 
- 		nextPutAll: ')'
 
- ! !
 
- !Message class methodsFor: 'instance creation'!
 
- selector: aString arguments: anArray
 
- 	^ self new
 
- 		selector: aString;
 
- 		arguments: anArray;
 
- 		yourself
 
- ! !
 
- Object subclass: #MessageSend
 
- 	instanceVariableNames: 'receiver message'
 
- 	package: 'Kernel-Methods'!
 
- !MessageSend commentStamp!
 
- I encapsulate message sends to objects. Arguments can be either predefined or supplied when the message send is performed. 
 
- ## API
 
- Use `#value` to perform a message send with its predefined arguments and `#value:*` if additonal arguments have to supplied.!
 
- !MessageSend methodsFor: 'accessing'!
 
- arguments
 
- 	^ message arguments
 
- !
 
- arguments: aCollection
 
- 	message arguments: aCollection
 
- !
 
- receiver
 
- 	^ receiver
 
- !
 
- receiver: anObject
 
- 	receiver := anObject
 
- !
 
- selector
 
- 	^ message selector
 
- !
 
- selector: aString
 
- 	message selector: aString
 
- ! !
 
- !MessageSend methodsFor: 'evaluating'!
 
- value
 
- 	^ message sendTo: self receiver
 
- !
 
- value: anObject
 
- 	^ message 
 
- 		arguments: { anObject };
 
- 		sendTo: self receiver
 
- !
 
- value: firstArgument value: secondArgument
 
- 	^ message 
 
- 		arguments: { firstArgument. secondArgument };
 
- 		sendTo: self receiver
 
- !
 
- value: firstArgument value: secondArgument value: thirdArgument
 
- 	^ message 
 
- 		arguments: { firstArgument. secondArgument. thirdArgument };
 
- 		sendTo: self receiver
 
- !
 
- valueWithPossibleArguments: aCollection
 
- 	self arguments: aCollection.
 
- 	^ self value
 
- ! !
 
- !MessageSend methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- 	message := Message new
 
- ! !
 
- !MessageSend methodsFor: 'printing'!
 
- printOn: aStream
 
- 	super printOn: aStream.
 
- 	aStream
 
- 		nextPutAll: '(';
 
- 		nextPutAll: self receiver;
 
- 		nextPutAll: ' >> ';
 
- 		nextPutAll: self selector;
 
- 		nextPutAll: ')'
 
- ! !
 
- Object subclass: #MethodContext
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Methods'!
 
- !MethodContext commentStamp!
 
- I hold all the dynamic state associated with the execution of either a method activation resulting from a message send. I am used to build the call stack while debugging.
 
- My instances are JavaScript `SmalltalkMethodContext` objects defined in `boot.js`.!
 
- !MethodContext methodsFor: 'accessing'!
 
- basicReceiver
 
- 	<return self.receiver>
 
- !
 
- evaluatedSelector
 
- 	<return self.evaluatedSelector>
 
- !
 
- findContextSuchThat: testBlock
 
- 	"Search self and my sender chain for first one that satisfies `testBlock`.  
 
- 	Answer `nil` if none satisfy"
 
- 	| context |
 
- 	
 
- 	context := self.
 
- 	[ context isNil] whileFalse: [
 
- 		(testBlock value: context) 
 
- 			ifTrue: [ ^ context ].
 
- 		context := context outerContext ].
 
- 	^ nil
 
- !
 
- home
 
- 	<return self.homeContext>
 
- !
 
- index
 
- 	<return self.index || 0>
 
- !
 
- locals
 
- 	<return self.locals || {}>
 
- !
 
- method
 
- 	| method lookupClass receiverClass supercall |
 
- 	
 
- 	self methodContext ifNil: [ ^ nil ].
 
- 	receiverClass := self methodContext receiver class.
 
- 	method := receiverClass lookupSelector: self methodContext selector.
 
- 	supercall := self outerContext 
 
- 		ifNil: [ false ]
 
- 		ifNotNil: [ :outer | outer supercall ].
 
- 	^ supercall
 
- 		ifFalse: [ method ]
 
- 		ifTrue: [ method methodClass superclass lookupSelector: self methodContext selector ]
 
- !
 
- methodContext
 
- 	self isBlockContext ifFalse: [ ^ self ].
 
- 	
 
- 	^ self outerContext ifNotNil: [ :outer |
 
- 		outer methodContext ]
 
- !
 
- outerContext
 
- 	<return self.outerContext || self.homeContext>
 
- !
 
- receiver
 
- 	^ (self isBlockContext and: [ self outerContext notNil ])
 
- 		ifTrue: [ self outerContext receiver ]
 
- 		ifFalse: [ self basicReceiver ]
 
- !
 
- selector
 
- 	<
 
- 		if(self.selector) {
 
- 			return $core.js2st(self.selector);
 
- 		} else {
 
- 			return nil;
 
- 		}
 
- 	>
 
- !
 
- sendIndexAt: aSelector
 
- 	<return self.sendIdx[aSelector] || 0>
 
- !
 
- sendIndexes
 
- 	<return self.sendIdx>
 
- !
 
- supercall
 
- 	<return self.supercall == true>
 
- ! !
 
- !MethodContext methodsFor: 'converting'!
 
- asString
 
- 	^ self isBlockContext
 
- 		ifTrue: [ 'a block (in ', self methodContext asString, ')' ]
 
- 		ifFalse: [ 
 
- 			| methodClass |
 
- 			methodClass := self method methodClass.
 
- 			methodClass = self receiver class 
 
- 				ifTrue: [ self receiver class name, ' >> ', self selector ]
 
- 				ifFalse: [ self receiver class name, '(', methodClass name, ') >> ', self selector ] ]
 
- ! !
 
- !MethodContext methodsFor: 'printing'!
 
- printOn: aStream
 
- 	super printOn: aStream.
 
- 	aStream 
 
- 		nextPutAll: '(';
 
- 		nextPutAll: self asString;
 
- 		nextPutAll: ')'
 
- ! !
 
- !MethodContext methodsFor: 'testing'!
 
- isBlockContext
 
- 	"Block context do not have selectors."
 
- 	
 
- 	^ self selector isNil
 
- ! !
 
- Object subclass: #NativeFunction
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Methods'!
 
- !NativeFunction commentStamp!
 
- I am a wrapper around native functions, such as `WebSocket`.
 
- For 'normal' functions (whose constructor is the JavaScript `Function` object), use `BlockClosure`.
 
- ## API
 
- See the class-side `instance creation` methods for instance creation.
 
- Created instances will most probably be instance of `JSObjectProxy`.
 
- ## Usage example:
 
- 	| ws |
 
- 	ws := NativeFunction constructor: 'WebSocket' value: 'ws://localhost'.
 
- 	ws at: 'onopen' put: [ ws send: 'hey there from Amber' ]!
 
- !NativeFunction class methodsFor: 'function calling'!
 
- functionNamed: aString
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return nativeFunc();
 
- 	>
 
- !
 
- functionNamed: aString value: anObject
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return nativeFunc(anObject);
 
- 	>
 
- !
 
- functionNamed: aString value: anObject value: anObject2
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return nativeFunc(anObject,anObject2);
 
- 	>
 
- !
 
- functionNamed: aString value: anObject value: anObject2 value: anObject3
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return nativeFunc(anObject,anObject2, anObject3);
 
- 	>
 
- !
 
- functionNamed: aString valueWithArgs: args
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return Function.prototype.apply.call(nativeFunc, null, args);
 
- 	>
 
- !
 
- functionOf: nativeFunc
 
- 	<
 
- 		return nativeFunc();
 
- 	>
 
- !
 
- functionOf: nativeFunc value: anObject
 
- 	<
 
- 		return nativeFunc(anObject);
 
- 	>
 
- !
 
- functionOf: nativeFunc value: anObject value: anObject2
 
- 	<
 
- 		return nativeFunc(anObject,anObject2);
 
- 	>
 
- !
 
- functionOf: nativeFunc value: anObject value: anObject2 value: anObject3
 
- 	<
 
- 		return nativeFunc(anObject,anObject2, anObject3);
 
- 	>
 
- !
 
- functionOf: nativeFunc valueWithArgs: args
 
- 	<
 
- 		return Function.prototype.apply.call(nativeFunc, null, args);
 
- 	>
 
- ! !
 
- !NativeFunction class methodsFor: 'instance creation'!
 
- constructorNamed: aString
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return new nativeFunc();
 
- 	>
 
- !
 
- constructorNamed: aString value: anObject
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return new nativeFunc(anObject);
 
- 	>
 
- !
 
- constructorNamed: aString value: anObject value: anObject2
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return new nativeFunc(anObject,anObject2);
 
- 	>
 
- !
 
- constructorNamed: aString value: anObject value: anObject2 value: anObject3
 
- 	<
 
- 		var nativeFunc=(new Function('return this'))()[aString];
 
- 		return new nativeFunc(anObject,anObject2, anObject3);
 
- 	>
 
- !
 
- constructorOf: nativeFunc
 
- 	<
 
- 		return new nativeFunc();
 
- 	>
 
- !
 
- constructorOf: nativeFunc value: anObject
 
- 	<
 
- 		return new nativeFunc(anObject);
 
- 	>
 
- !
 
- constructorOf: nativeFunc value: anObject value: anObject2
 
- 	<
 
- 		return new nativeFunc(anObject,anObject2);
 
- 	>
 
- !
 
- constructorOf: nativeFunc value: anObject value: anObject2 value: anObject3
 
- 	<
 
- 		return new nativeFunc(anObject,anObject2, anObject3);
 
- 	>
 
- ! !
 
- !NativeFunction class methodsFor: 'method calling'!
 
- methodOf: nativeFunc this: thisObject
 
- 	<
 
- 		return Function.prototype.call.call(nativeFunc, thisObject);
 
- 	>
 
- !
 
- methodOf: nativeFunc this: thisObject value: anObject
 
- 	<
 
- 		return Function.prototype.call.call(nativeFunc, thisObject, anObject);
 
- 	>
 
- !
 
- methodOf: nativeFunc this: thisObject value: anObject value: anObject2
 
- 	<
 
- 		return Function.prototype.call.call(nativeFunc, thisObject,anObject,anObject2);
 
- 	>
 
- !
 
- methodOf: nativeFunc this: thisObject value: anObject value: anObject2 value: anObject3
 
- 	<
 
- 		return Function.prototype.call.call(nativeFunc, thisObject,anObject,anObject2, anObject3);
 
- 	>
 
- !
 
- methodOf: nativeFunc this: thisObject valueWithArgs: args
 
- 	<
 
- 		return Function.prototype.apply.call(nativeFunc, thisObject, args);
 
- 	>
 
- ! !
 
- !NativeFunction class methodsFor: 'testing'!
 
- exists: aString
 
- 	^ Smalltalk existsJsGlobal: aString
 
- ! !
 
- Object subclass: #Timeout
 
- 	instanceVariableNames: 'rawTimeout'
 
- 	package: 'Kernel-Methods'!
 
- !Timeout commentStamp!
 
- I am wrapping the returns from `set{Timeout,Interval}`.
 
- ## Motivation
 
- Number suffices in browsers, but node.js returns an object.!
 
- !Timeout methodsFor: 'accessing'!
 
- rawTimeout: anObject
 
- 	rawTimeout := anObject
 
- ! !
 
- !Timeout methodsFor: 'timeout/interval'!
 
- clearInterval
 
- 	<
 
- 		var interval = self["@rawTimeout"];
 
- 		clearInterval(interval);
 
- 	>
 
- !
 
- clearTimeout
 
- 	<
 
- 		var timeout = self["@rawTimeout"];
 
- 		clearTimeout(timeout);
 
- 	>
 
- ! !
 
- !Timeout class methodsFor: 'instance creation'!
 
- on: anObject
 
- 	^ self new rawTimeout: anObject; yourself
 
- ! !
 
 
  |