[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

[E8] Activated Methods (chunk format)

 ! APIBuilder methodsFor: #private !
register: aMethod
	" Private - Register aMethod as related to the receiver. "

	token isNil ifTrue: [ ^false ].
	bound isNil ifTrue: [ bound := Array new ].
	bound add: aMethod.
	^true! !

 ! APIBuilder class methodsFor: #building !
register: aMethod
	" Register aMethod as related to current builder. "

	^default notNil and: [ default register: aMethod ]! !

 ! Array methodsFor: #copying !
, aCollection
	" Return a copy of the receiver with all contents of aCollection. "

	^self #concat: aCollection asArray! !

 ! Array methodsFor: #adding !
addLast: anObject
	" Add anObject to the receiver. "

	self #push: anObject.
	^anObject! !

 ! Array methodsFor: #adding !
add: anObject
	" Add anObject to the receiver. "

	self #push: anObject.
	^anObject! !

 ! Array methodsFor: #converting !
asArray
	" Return an array with the contents of the receiver. "

	^self! !

 ! Array methodsFor: #accessing !
at: anIndex
	" Return the contents of the receiver at anIndex. "

{'	var value = self[anIndex - 1];
	if(value === undefined) { return self.objectNotFoundAt_(anIndex); }
	return value;'}! !

 ! Array methodsFor: #accessing !
at: anIndex ifAbsent: aBlock
	" Return the contents of the receiver at anIndex or the result of evaluating aBlock. "

{'	var value = self[anIndex - 1];
	if(value === undefined) { return aBlock(); }
	return value;'}! !

 ! Array methodsFor: #accessing !
at: anIndex put: anObject
	" Set the contents of the receiver at anIndex. "

{'	return self[anIndex - 1] = anObject'}! !

 ! Array methodsFor: #enumerating !
do: aBlock
	" Evaluate aBlock with the contents of the receiver. "

{'	for(var i=0;i<self.length;i++){aBlock(self[i]);} '}! !

 ! Array methodsFor: #accessing !
first
	" Return the object in the receiver. "

	^self[0] ifUndefined: [self at: 1]! !

 ! Array methodsFor: #accessing !
fourth
	" Return the object in the receiver. "

	^self[3] ifUndefined: [self at: 4]! !

 ! Array methodsFor: #testing !
isArray
	" Return true if the receiver is an Array. "

	^self class == Array! !

 ! Array methodsFor: #accessing !
second
	" Return the object in the receiver. "

	^self[1] ifUndefined: [self at: 2]! !

 ! Array methodsFor: #copying !
shallowCopy
	" Return a shallow copy of the receiver. "

	^self #slice: 0! !

 ! Array methodsFor: #accessing !
size
	" Return the size of the receiver. "

	^self#length! !

 ! Array methodsFor: #accessing !
third
	" Return the object in the receiver. "

	^self[2] ifUndefined: [self at: 3]! !

 ! Array class methodsFor: #instantiation !
new
	" Return an instance of the receiver. "

	^#()! !

 ! Array class methodsFor: #instantiation !
with: anObject
	" Return an instance of the receiver. "

{'	return [ anObject ];	'}! !

 ! Array class methodsFor: #instantiation !
with: anObject with: anotherObject
	" Return an instance of the receiver. "

{'	return [ anObject, anotherObject ];	'}! !

 ! Array class methodsFor: #instantiation !
with: firstObject with: secondObject with: thirdObject
	" Return an instance of the receiver. "

{'	return [ firstObject, secondObject, thirdObject ];	'}! !

 ! Behavior methodsFor: #instantiation !
new
	" Return an instance of the receiver. "

	^self basicNew initialize! !

 ! Behavior methodsFor: #accessing !
>>> aSymbol
	" Return the method at aSymbol searching up in receiver's hierarchy (or nil if not implemented by the receiver nor its superclasses). "

	| result |
	result := self compiledMethodAt: aSymbol.
	(result isNil and: [self superclass notNil]) ifTrue: [
		^self superclass >>> aSymbol
	].
	^result! !

 ! Behavior methodsFor: #methods !
addCompiledMethod: aMethod
	" Add the compiled method, if appropiate, and register the method in recent methods. "

	| isDoIt |
	isDoIt := aMethod selector = String doItSelector.
	(OverwriteMethods notNil and: [	OverwriteMethods ]) ifFalse: [
		(self implements: aMethod selector) ifTrue: [
			isDoIt ifFalse: [
				(DumpOverwritenMethods notNil
				and: [ DumpOverwritenMethods
				and: [ Exporter notNil ]]) ifTrue: [
					self print: '//? ',self name,'>>#',aMethod selector.
					self print: (Exporter new export: self method: aMethod).
				] ifFalse: [
					self print: '//-Overwrite Conflict- ',self name,'>>#',aMethod selector.
				].
				^self
			].
		].
	].
	(Exporter notNil and: [ isDoIt not ]) ifTrue: [
" DEBUG -	self print: '// ',self name,'>>#',aMethod selector."
		self print: (Exporter new export: self method: aMethod).
	].
	^self basicAddCompiledMethod: aMethod! !

 ! Behavior methodsFor: 'Builders-private' !
basicAddCompiledMethod: aMethod
	" Private - Effectivelly add aMethod to the receiver. "

	APIBuilder register: aMethod.
	#{smalltalk} #addMethod: aMethod selector asSelector method: aMethod to: self! !

 ! Behavior methodsFor: #instantiation !
basicNew
	" Return a new (non-initialized) instance of the receiver. "

{'	return new self.$fn()'}! !

 ! Behavior methodsFor: #accessing !
classVariableAt: aName ifAbsent: aBlock
	" Return the value of classVariable named aName. "

	| bindings |
	self instanceClass withAllSuperclassesDo: [:each|
		bindings := each classVariables.
		bindings notNil ifTrue: [
			(bindings includesKey: aName) ifTrue: [
				^bindings at: aName
			]
		]
	].
	^aBlock evaluate! !

 ! Behavior methodsFor: #accessing !
compiledMethodAt: aSymbol
	" Return the compiled method at aSymbol implemented by the receiver (or nil). "

{'	return self.$fn.prototype.$methods[aSymbol] || nil; '}! !

 ! Behavior methodsFor: #accessing !
name
	" Return the name of the receiver. "

	^self basicAt: '$className'! !

 ! Behavior methodsFor: #private !
removeCompiledMethod: aMethod
	" Remove aMethod from the receiver. "

	self smalltalk #removeMethod: self method: aMethod! !

 ! Behavior methodsFor: #methods !
removeSelector: aSelector
	" Remove the method for message aSelector implemented by the receiver. "

	| method |
	method := self compiledMethodAt: aSelector.
	method notNil ifTrue: [ self removeCompiledMethod: method ].! !

 ! Behavior methodsFor: #accessing !
superclass
	" Return the superclass of the receiver. "

	^self basicAt: '$superclass'! !

 ! Behavior methodsFor: #accessing !
withAllSuperclassesDo: aBlock
	" Evaluate aBlock with the receiver and it's superclasses.
	The superclasses are walked in inverse hierarchical order, i.e class Object is last.
	"

	aBlock value: self.
	^self allSuperclassesDo: aBlock! !

 ! BlockClosure methodsFor: #error !
ensure: aBlock
	" Returns the result of evaluating the receiver.
	Execute aBlock after the receiver is executed.
	"

{'	try{return self();} finally {aBlock();}	'}! !

 ! BlockClosure methodsFor: #evaluating !
evaluate
	" Return the result of evaluating the receiver. "

	^# self! !

 ! BlockClosure methodsFor: #evaluating !
evaluateWithArguments: anArray
	" Return the result of evaluating the receiver. "

	^self valueWithPossibleArguments: anArray! !

 ! BlockClosure methodsFor: #error !
on: anExceptionType do: aBlock
	" Return the result of evaluating the receiver catching exceptions. "

	^self try: self catch: [:error |
		(error isKindOf: anExceptionType)
		ifTrue: [ aBlock value: error ]
		ifFalse: [ error signal ]
	]! !

 ! BlockClosure methodsFor: #private !
try: aBlock catch: anotherBlock
	" Private - Try to evaluate aBlock catching exceptions with catchBlock. "

{'	var result;
	try{ result = aBlock() } catch(e) {
		result = anotherBlock( self.smalltalkErrorOf_(e) )
	};
	return result;'}! !

 ! BlockClosure methodsFor: #evaluating !
value
	" Return the result of evaluating the receiver. "

	^# #self! !

 ! BlockClosure methodsFor: #evaluating !
valueWithPossibleArguments: aCollection
	" Return the result of evaluating the receiver with potential arguments. "

	aCollection isArray ifFalse: [
		self error: '// Invalid arguments in #valueWithPossibleArguments: (must be anArray). receiver=',self toString
	].
	^self #apply: #{null} arguments: aCollection! !

 ! BlockClosure methodsFor: #evaluating !
value: anObject
	" Return the result of evaluating the receiver with anObject. "

	^# #self: anObject! !

 ! BlockNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitBlockNode: self! !

 ! BlockNode methodsFor: #accessing !
parameters
	parameters isNil ifTrue: [ parameters := Array new ].
	^parameters! !

 ! BlockNode methodsFor: #accessing !
parameters: aCollection
	parameters := aCollection! !

 ! BlockSequenceNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitBlockSequenceNode: self! !

 ! Boolean methodsFor: #control !
and: aBlock
	" Return true if the receiver is true and the result of evaluating aBlock is also true. "

	^self ifTrue: [ aBlock value ] ifFalse: [false]! !

 ! Boolean methodsFor: #testing !
mustBeBoolean
	" Signal an error if the receiver is not a Boolean. "

	^self! !

 ! Boolean methodsFor: #control !
not
	" Return true if the receiver is false. "

	^{' self == false '}! !

 ! Boolean methodsFor: #control !
or: aBlock
	" Return true if the receiver is true or the result of evaluating aBlock is true. "

	^self ifTrue: [true] ifFalse: [ aBlock value ]! !

 ! Class methodsFor: #accessing !
classVariables
	" Return the class variables of the receiver. "

	| names |
	names := self basicAt: '$classVariableNames' ifAbsent: [].
	names isNil ifTrue: [ ^self basicAt: '$classVariables' ].
	self basicDelete: '$classVariableNames'.
	self classVariableNames: names.
	^self basicAt: '$classVariables'! !

 ! Class methodsFor: #accessing !
instanceClass
	" Return the receiver. "

	^self! !

 ! Collection methodsFor: #converting !
asArray
	" Return an array with the contents of the receiver. "

	| result index |
	result := Array new.
	index := 0.
	self do: [:each |
	    index := index + 1.
	    result at: index put: each
	].
	^result! !

 ! Collection methodsFor: #enumerating !
collect: aBlock
	" Return a collection with the result of evaluating aBlock with the contents of the receiver. "

	| result |
	result := self class new.
	self do: [:each | result add: (aBlock value: each) ].
	^result! !

 ! Collection methodsFor: #copying !
copyWith: anObject
	" Return a copy of the receiver with anObject. "

	^self copy add: anObject; yourself! !

 ! Collection methodsFor: #enumerating !
do: aBlock separatedBy: anotherBlock
	" Evaluate aBlock for contents of the receiver evaluating anotherBlock inbetween aBlock evaluations. "

	| first |
	first := true.
	self do: [:each |
	    first
		ifTrue: [ first := false ]
		ifFalse: [ anotherBlock value ].
	    aBlock value: each
	]! !

 ! Collection methodsFor: #accessing !
readStream
	" Return a read stream on the receiver. "

	^self stream! !

 ! Collection methodsFor: #accessing !
stream
	" Return a stream on the receiver. "

	^self streamClass on: self! !

 ! Collection methodsFor: #accessing !
streamClass
	" Private - Return the support for streamming on the receiver. "

	^self class streamClass! !

 ! Collection methodsFor: #accessing !
writeStream
	" Return a write stream on the receiver. "

	^self stream! !

 ! CompiledMethod methodsFor: #accessing !
selector
	" Return the selector of the receiver. "

	^self basicAt: '$selector'! !

 ! CompilerNodeVisitor methodsFor: #visiting !
visit: aNode
	aNode accept: self! !

 ! CompilerNode methodsFor: #accessing !
addNode: aNode
	self nodes add: aNode! !

 ! CompilerNode methodsFor: #accessing !
end
	^end! !

 ! CompilerNode methodsFor: #testing !
isAssignment
	" Return true if the receiver is of this type. "

	^false! !

 ! CompilerNode methodsFor: #testing !
isSuper
	" Return true if the receiver is super. "

	^false! !

 ! CompilerNode methodsFor: #accessing !
messageSendConnector
	" Return the binder used to send message to the receiver. "

	^'.'! !

 ! CompilerNode methodsFor: #accessing !
nodes
	nodes isNil ifTrue: [ nodes := Array new ].
	^nodes! !

 ! CompilerNode methodsFor: #accessing !
nodes: aCollection
	nodes := aCollection! !

 ! CompilerNode methodsFor: #accessing !
start
	^start! !

 ! CompilerNode methodsFor: #accessing !
start: startOffset end: endOffset
	" Set the offsets of the receiver in source code. "

	start := startOffset.
	end := endOffset.! !

 ! Compiler methodsFor: #private !
compileNode: aNode
	" Private - Compile aNode. "

	^self
		startCompiling: aNode;
		prepare: aNode;
		visit: aNode;
		endCompiling: aNode;
		emmitedCode! !

 ! Compiler methodsFor: #accessing !
currentClass: aClass
	" Set the current class of the receiver. "

	currentClass := aClass! !

 ! Compiler methodsFor: #optimization !
defaultOptimizationMap
	" Private - Return the default message optimization specification. "

	^#(
		#( 0 #( "selectors without arguments"
			#( #class	'%receiver%.$klass' )
			#( #isNil	'(nil.isNil_(%receiver%))' )
			#( #notNil	'(nil.isNil_(%receiver%)===false)' )
			#( #whileTrue #receiverIsBlockNoArguments: '(function(){while(%receiver%()){};return nil})()' )
			#( #whileFalse #receiverIsBlockNoArguments: '(function(){while(!!%receiver%()){};return nil})()' )
			#( #basicValueOrNil '(function(){var $1$;return (nil.isNil_($1$ = %receiver%)) ? nil : $1$;})()' )
		) )
		#( 1 #( "one argument selectors and operations"
			#( #ifTrue: #hasBlockNoArguments: '((%receiver%).mustBeBoolean()==true ? %arg1%() : nil)' )
			#( #ifFalse: #hasBlockNoArguments: '((%receiver%).mustBeBoolean()==true ? nil : %arg1%())' )
			#( #whileTrue: #allBlockNoArguments: '(function(){while(%receiver%()){%arg1%()};return nil})()' )
			#( #whileFalse: #allBlockNoArguments: '(function(){while(!!%receiver%()){%arg1%()};return nil})()' )
			#( #ifNil: #hasBlockArguments: '(function(){var $1$;return (nil.isNil_($1$ = %receiver%)) ? %arg1%() : $1$;})()' )
			#( #ifNotNil: #hasBlockArguments: '(function(){var $1$;return (nil.isNil_($1$ = %receiver%)===false) ? %arg1%() : $1$;})()' )
			#( #==	'(nil.is_eqeq_(%receiver%,%arg1%))' )
			#( #===	'(%receiver% === %arg1%)' )
			#( #||	'(%receiver% || %arg1%)' )
			#( #basicAt:	'((function(){var $1$=%receiver%[%arg1%];if(nil.isNil_($1$))return nil;return $1$;})())' )
			#( #ifUndefined: #hasBlockNoArguments: '(function(){var $1$ = %receiver%;if (typeof ($1$) == "undefined") return %arg1%(); return $1$;})()' )
			#( #timesRepeat: #hasBlockNoArguments: '(function(){for(var $1$=%receiver%;$1$>0;$1$--){%arg1%()};return nil})()' )
			#( #isKindOf: 'smalltalk.is_kindOf_(%receiver%,(%arg1%))' )
			#( #respondsTo: 'smalltalk.responds_to_(%receiver%,(%arg1%))' )
"			#( #> #hasNumber: '(%receiver% > %arg1%)' )
			#( #< #hasNumber: '(%receiver% < %arg1%)' )
			#( #>= #hasNumber: '(%receiver% >= %arg1%)' )
			#( #<= #hasNumber: '(%receiver% <= %arg1%)' )
			#( #+ #hasNumber: '(%receiver% + %arg1%)' )
			#( #- #hasNumber: '(%receiver% - %arg1%)' )
			#( #* #hasNumber: '(%receiver% * %arg1%)' )
			#( #/ #hasNumber: '(%receiver% / %arg1%)' )
			#( #=  #hasNumber: '(%receiver% == %arg1%)' )
"		) )
		#( 2 #( "two argument messages and operations"
			#( #ifTrue:ifFalse: #hasBlockNoArguments: '((%receiver%).mustBeBoolean()==true ? %arg1%() : %arg2%())' )
			#( #ifFalse:ifTrue: #hasBlockNoArguments: '((%receiver%).mustBeBoolean()==true ? %arg2%() : %arg1%())' )
			#( #ifNil:ifNotNil: #hasBlockNoArguments: '(nil.isNil_(%receiver%)) ? %arg1%() : %arg2%()' )
			#( #ifNotNil:ifNil: #hasBlockNoArguments: '(nil.isNil_(%receiver%)===false) ? %arg1%() : %arg2%()' )
			#( #basicAt:ifAbsent: '((function(){var $1$=%receiver%[%arg1%];if(nil.isNil_($1$))return (%arg2%.value());return $1$;})())' )
			#( #basicAt:put: '(%receiver%[%arg1%]=(%arg2%))' )
		) )
)! !

 ! Compiler methodsFor: #generation !
emmitEnterMethod: aNode
	" Private - Generate local definitions for aNode. "

	stream nextPutAll: 'var self=this;'! !

 ! Compiler methodsFor: #generation !
emmitFunction: fName arguments: argList doing: aBlock
	" Private - Emmit function on receiver's code stream. "

	self
		triggerEvent: #startFunction:with:
		withArguments: (Array with: fName with: argList)
		ifNotHandled: [
			stream nextPutAll: 'function'.
			self triggerEvent: #startFunctionName: with: fName.
			stream nextPutAll: '(' ,argList ,$)
		].
	stream nextPutAll: ${.
	self	triggerEvent: #startFunctionBody:with:
		withArguments: (Array with: fName with: argList).
	aBlock evaluate.
	stream nextPutAll: $}.
	self triggerEvent: #endFunction: with: fName.! !

 ! Compiler methodsFor: #generation !
emmitFunction: fName node: aNode arguments: argumentsArray doing: aBlock
	" Private - Generate function for aNode. "

	| args |
	args := '' writeStream.
	argumentsArray do: [:each | 
		tempVariables add: each.
		args nextPutAll: (self localName: each) ]
	    separatedBy: [ args nextPutAll: ',' ].
	self	emmitFunction: fName
		arguments: args contents
		doing: aBlock! !

 ! Compiler methodsFor: #generation !
emmitFunction: fName node: aNode doing: aBlock
	" Private - Generate function for aNode. "

	^self	emmitFunction: fName
		node: aNode arguments: aNode arguments
		doing: aBlock! !

 ! Compiler methodsFor: #generation !
emmitMethod: aNode
	" Private - Generate code of method aNode. "

	| code |
	functionName := aNode selector asSelector.
	self emmitFunction: functionName node: aNode doing: [
		self triggerEvent: #startMethod: with: aNode.
		code := self generatedCodeFor: aNode while: [
			self	triggerEvent: #enterMethod: withArguments: (Array with: aNode)
				ifNotHandled: [	self emmitEnterMethod: aNode ].
			aNode nodes do: [:each | self visit: each ].
			self emmitReturn: #self.
		].
		self generate: functionName early: earlyReturn return: code.
		self triggerEvent: #endMethod: with: aNode.
	]! !

 ! Compiler methodsFor: #generation !
emmitReturn: aBlockOrString
	" Private - Generate return code. "

	^self emmitReturn: aBlockOrString early: false! !

 ! Compiler methodsFor: #generation !
emmitReturn: aBlockOrString early: early
	" Private - Generate return code. "

	self triggerEvent: #aboutReturn: with: aBlockOrString.
	stream nextPutAll: 'return '.
	self triggerEvent: #return: with: aBlockOrString.
	aBlockOrString isString
		ifTrue: [ stream nextPutAll: aBlockOrString ]
		ifFalse: [ aBlockOrString evaluate ].
	aBlockOrString notNil ifTrue: [
		self	triggerEvent: #returned:early:
			withArguments: (Array with: aBlockOrString with: early).
		stream nextPutAll: $;.
	]! !

 ! Compiler methodsFor: #results !
emmitedCode
	" Return the emmited code during compilation (or nil). "

	^stream notNil ifTrue: [ stream contents ]! !

 ! Compiler methodsFor: #private !
endCompiling: aNode
	" Private - Finish emmiting code for aNode. "

	self triggerEvent: #endCompiling: with: aNode.! !

 ! Compiler methodsFor: #evaluation !
eval: jsExpression
	" Return the result of evaluating a javascript expression in global context. "

	^Smalltalk current eval: jsExpression! !

 ! Compiler methodsFor: #doIt !
evaluate: smalltalkExpression
	" Return the result of evaluating the smalltalk expression in global context. "

	^self evaluate: smalltalkExpression in: nil class to: nil! !

 ! Compiler methodsFor: #evaluation !
evaluate: smalltalkExpression in: aClass to: aReceiver
	" Return the result of evaluating the smalltalk expression with aReceiver. "

	| result doIt node jsCode |
	doIt := String doItSelector.
	self currentClass: aClass.
	node := self parseCode: doIt,' ^[', smalltalkExpression, '] value'.
	jsCode := self compileNode: node.
	aClass addCompiledMethod: (self eval: jsCode).
	[ result := aReceiver perform: doIt.
	] ensure: [ aClass removeSelector: doIt. ].
	^result! !

 ! Compiler methodsFor: #generation !
generate: fName early: early return: code
	" Private - Generate code to catch early return of code expression in fName. "

	early ifFalse: [ ^stream nextPutAll: code ].
	stream nextPutAll: 'var $s8Ret$={name:"stReturn"};try{'; nextPutAll: code.
	stream nextPutAll: '} catch($$ex) {if($$ex === $s8Ret$){'.
	self emmitReturn: '$$ex.result' early: true.
	stream nextPutAll: '} throw($$ex);}'! !

 ! Compiler methodsFor: #generation !
generatedCodeFor: aNode while: aBlock
	" Private - Return the code generated during evaluation of aBlock. "

	| backup result |
	backup := Array with: stream with: startOffset.
	startOffset := stream position.
	stream := '' writeStream.
	self visit: aNode doing: aBlock.
	result := stream contents.
	stream := backup first.
	startOffset := backup last.
	^result ! !

 ! Compiler methodsFor: #generation !
includeSourceCode
	" Private - Return true if source code is included as method argument. "

	^true! !

 ! Compiler methodsFor: #initialize !
initialize
	" Private - Initialize the receiver. "

	super initialize.
	unknownVariables := #().
	tempVariables := #()! !

 ! Compiler methodsFor: #operations !
isOperation: aNode
	" Private - Return true if aNode is an operation. "

	^aNode arguments size = 1 and: [
		aNode selector size > 1 and: [
		aNode selector first = $# and: [
		'|&\\+*/=><,@%~-' includes: (aNode selector at: 2)
		]]]! !

 ! Compiler methodsFor: #generation !
newMethodFunctionName
	" Private - Return the function to call when installing a new method. "

	^'smalltalk.newMethod'! !

 ! Compiler methodsFor: #templates !
nodeFromTemplateIn: aString
	" Returns the nodes syntetized from inlined templates in aString (or nil).
	Inlined templates are detected from last comment in source.
	"

	| src driver selector count found |
	(aString isEmpty or: [(aString last = $") not]) ifTrue: [ ^nil ].
	src := ((aString upToLast: $") fromLast: $") stream.
	src peek = $# ifTrue: [ src next ] ifFalse: [
		#template = (src nextLine upTo: $ ) ifFalse: [ ^nil ]
	].
	driver := src upTo: $ .
	driver = #self  ifTrue: [ driver := self ].
	driver = #class ifTrue: [ driver := self currentClass ].
	driver = #api   ifTrue: [ driver := #APIBuilder ].
	driver isString ifTrue: [ driver := Smalltalk at: driver ifAbsent: [] ].
	selector := src upTo: $ .
	(driver respondsTo: selector) ifFalse: [ ^nil ].
	count := selector occurrencesOf: $:.
	found := [:mth| mth notNil ifTrue: [ mth source: aString; yourself ] ].
	count = 0 ifTrue: [ ^found value: (driver perform: selector) ].
	count = 1 ifTrue: [ ^found value: (driver perform: selector with: src upToEnd) ].
	^nil! !

 ! Compiler methodsFor: #accessing !
optimizationMap
	" Return the message send optimization map of the receiver. "

	optimizationMap isNil ifTrue: [
		optimizationMap  := self
			triggerEvent: #needsOptimizationMap
			ifNotHandled: [ self defaultOptimizationMap ].
		self triggerEvent: #customizeOptimizations
	].
	^optimizationMap! !

 ! Compiler methodsFor: #parsing !
parseCode: aString
	" Parse the S8 code in aString. "

	| result |
	self	triggerEvent: #aboutToParse:
		with: aString ifNotHandled: [
			result := self nodeFromTemplateIn: aString.
			result notNil ifTrue: [ ^result ]
		].
	result := self parser parse: aString readStream.
	^result! !

 ! Compiler methodsFor: #private !
parser
	" Private - Return the parser of the receiver. "

	^self	triggerEvent: #needsParser
		ifNotHandled: [ SmalltalkParser new ]! !

 ! Compiler methodsFor: #private !
prepare: aNode
	" Private - Apply tranformations/optimization to aNode. "

	self transformers do: [:each| each visit: aNode ].! !

 ! Compiler methodsFor: #private !
smalltalkNameFor: aClass
	" Private - Return the global name of aClass (can be nil). "

	^self class smalltalkNameFor: aClass! !

 ! Compiler methodsFor: #private !
startCompiling: aNode
	" Private - Set the receiver to start emmiting code for aNode. "

	stream := '' writeStream.
	startOffset := stream position.
	self triggerEvent: #startCompiling: with: aNode.! !

 ! Compiler methodsFor: #accessing !
transformers
	" Return the node transformers installed in the receiver. "

	transformers isNil ifTrue: [
		transformers := Array new.
		self triggerEvent: #setTransformers: with: transformers.
	].
	^transformers! !

 ! Compiler methodsFor: #visiting !
visitArgument: aNode
	" Private - Visit the argument emmitting output. "

	aNode isAssignment ifTrue: [ ^self visitLocalAssignment: aNode. ].
	^self visit: aNode! !

 ! Compiler methodsFor: #visiting !
visitBlockNode: aNode
	stream nextPutAll: $(.
	self	emmitFunction: '' node: aNode
		arguments: aNode parameters
		doing: [ aNode nodes do: [:each | self visit: each ] ].
	stream nextPutAll: $).! !

 ! Compiler methodsFor: #visiting !
visitBlockSequenceNode: aNode
	| index |
	nestedBlocks := nestedBlocks + 1.
	aNode nodes isEmpty
	    ifTrue: [ self emmitReturn: #nil ]
	    ifFalse: [
		aNode temps do: [:each |
		    tempVariables add: each.
		    stream nextPutAll: 'var ', (self localName: each), '=nil;'
		].
		index := 0.
		aNode nodes do: [:each |
		    index := index + 1.
		    index = aNode nodes size
			ifTrue: [ self emmitReturn: [ self visit: each ] ]
		    	ifFalse: [ self visit: each. stream nextPutAll: $; ]
		].
	].
	nestedBlocks := nestedBlocks - 1! !

 ! Compiler methodsFor: #visiting !
visitExtendedSequenceNode: aNode
	" Private - Visit a directive node. "

	aNode directive notNil ifTrue: [
		stream nextPutAll: (aNode directive
			asJavascript: functionName
			for: self on: stream); cr.
	].
	^self visitSequenceNode: aNode! !

 ! Compiler methodsFor: #visiting !
visitMethodNode: aNode
	nestedBlocks := 0.
	earlyReturn := false.
	unknownVariables := #().
	tempVariables := #().
	stream 
		nextPutAll: self newMethodFunctionName, '(';
		nextPutAll: (self smalltalkNameFor: currentClass);
		nextPutAll: ',"', aNode selector, '",'; cr.
	self emmitMethod: aNode.
	self includeSourceCode ifTrue: [
		stream	cr; "warning: this cr is important for debugger"
			nextPutAll: ',' ,aNode source escapedCode
	].
	stream nextPutAll: ')'! !

 ! Compiler methodsFor: #visiting !
visitNormalSend: aNode
	" Generate code for direct/inlined message send."

	self triggerEvent: #aboutSend: with: aNode.
	self visitReceiver: aNode receiver.
	stream
		nextPutAll: aNode receiver messageSendConnector;
		nextPutAll: aNode selector asSelector;
		nextPutAll: '('.
	self visitSendArguments: aNode.
	stream	nextPutAll: ')'.
	self triggerEvent: #send: with: aNode.! !

 ! Compiler methodsFor: #visiting !
visitOptimizedSend: aNode
	" Private - Generate optimal code for aNode using optimization map.
	Return true if optimization was successfull.
	"

	^self visitOptimizedSend: aNode with: self optimizationMap! !

 ! Compiler methodsFor: #visiting !
visitOptimizedSend: aNode with: mapping
	" Private - Generate optimal code for aNode using mapping.
	Return true if the code has been generated.
	Leave the code stream intact if the optimization do not apply.
	"

	| argCount |
	argCount := aNode arguments size.
	mapping do: [:tuple|
		(tuple first isNumber and: [ tuple first = argCount ]) ifTrue: [ "arguments size match"
			(self visitOptimizedSend: aNode with: tuple last) ifTrue: [ ^true ].
		] ifFalse: [
			tuple first = aNode selector ifTrue: [ "selector match"
				(self visitOptimizedNode: aNode as: tuple) ifTrue: [ ^true ].
			].
		].
	].
	^false! !

 ! Compiler methodsFor: #visiting !
visitReceiver: aNode
	" Private - Visit the node (as receiver) emmitting output. "

	aNode isAssignment ifTrue: [ ^self visitLocalAssignment: aNode. ].
	^self visit: aNode! !

 ! Compiler methodsFor: #visiting !
visitReturnNode: aNode

	| theReturn |
	nestedBlocks > 0 ifTrue: [ earlyReturn := true ].
	theReturn := [
		self emmitReturn: [
			aNode nodes do: [:each | self visit: each ]
		]
	].
	earlyReturn ifFalse: [ ^theReturn value ].
	stream nextPutAll: $(.
	self emmitFunctionDoing: [
		stream nextPutAll: '$s8Ret$.result=('.
		self emmitFunctionDoing: theReturn.
		stream nextPutAll: ')();throw($s8Ret$)'
	].
	stream nextPutAll: ')()'.! !

 ! Compiler methodsFor: #visiting !
visitSendArguments: aNode
	aNode arguments 
	    do: [:each | self visitArgument: each ]
	    separatedBy: [ stream nextPutAll: ', ' ].! !

 ! Compiler methodsFor: #visiting !
visitSendNode: aNode
	aNode receiver isSuper ifTrue: [ ^self visitSendToSuper: aNode ].
	(self visitOptimizedSend: aNode) ifTrue: [ ^self ].
	(self isOperation: aNode) ifTrue: [ ^self visitOperation: aNode ].
	^self visitNormalSend: aNode! !

 ! Compiler methodsFor: #visiting !
visitSequenceNode: aNode
	aNode temps do: [:each |
		tempVariables add: each.
		stream nextPutAll: 'var ', (self localName: each), '=nil;'
	].
	aNode nodes do: [:each |
		self visit: each.
		stream nextPutAll: ';'
	] separatedBy: [stream cr]! !

 ! Compiler methodsFor: #visiting !
visitValueNode: aNode
	stream nextPutAll: aNode value asJavascript! !

 ! Compiler methodsFor: #visiting !
visit: aNode
	^self visit: aNode doing: [ super visit: aNode ]! !

 ! Compiler methodsFor: #visiting !
visit: aNode doing: aBlock
	| cookie result |
	cookie := self
		triggerEvent: #needsCookie: with: aNode
		ifNotHandled: [ ^aBlock evaluate ].
	self triggerEvent: #startVisit: with: cookie.
	result := aBlock evaluate.
	self triggerEvent: #endVisit: with: cookie.
	^result! !

 ! Compiler class methodsFor: #evaluation !
doIt: smalltalkExpression
	" Return the result of evaluating the smalltalk expression in the global context or a description of an error situation occurred evaluating the code. "

	^self doIt: smalltalkExpression to: nil! !

 ! Compiler class methodsFor: #evaluation !
doIt: smalltalkExpression to: aReceiver
	" Return the result of evaluating the smalltalk expression in the context of aReceiver or a description of an error situation occurred evaluating the code. "

	| result |
	[ result := aReceiver isNil
			ifTrue:  [ self evaluate: smalltalkExpression ]
			ifFalse: [ self evaluate: smalltalkExpression to: aReceiver ]
	] on: Error do: [:error|
		((Smalltalk isObject: error) not or: [ error isString ])
		ifTrue: [ result := error ]
		ifFalse: [ result := error class name,': ', error messageText asString ].
		self print: '// ', result
	].
	^result! !

 ! Compiler class methodsFor: #evaluation !
evaluate: smalltalkExpression
	" Return the result of evaluating the smalltalk expression in a global context. "

	^self new evaluate: smalltalkExpression! !

 ! Compiler class methodsFor: #private !
smalltalkNameFor: aClass
	" Private - Return the global name of aClass (can be nil). "

	aClass isNil ifTrue: [ ^#undefined ].
	^'smalltalk.', (aClass isMetaclass
	    ifTrue: [ aClass instanceClass name, '.$klass' ]
	    ifFalse: [ aClass name ])! !

 ! EventManager methodsFor: #events !
eventTable
	" Private - Returns the mapping event names to actions of the receiver. "

	^handlers isNil
		ifTrue: [ self eventTableCreate ]
		ifFalse: [ handlers ]! !

 ! ExtendedSequenceNode methodsFor: #visiting !
accept: aVisitor
	" Accept aVisitor. "

	aVisitor visitExtendedSequenceNode: self! !

 ! ExtendedSequenceNode methodsFor: #accessing !
directive
	" Return the directive of the receiver. "

	^directive! !

 ! ExtendedSequenceNode methodsFor: #accessing !
directive: aDirective
	" Set the directive of the receiver. "

	directive := aDirective! !

 ! KeyedCollection methodsFor: #accessing !
at: aKey
	" Return the value at aKey.
	Signal an error if the key is not present.
	"

	^self at: aKey ifAbsent: [ self objectNotFoundAt: aKey ]! !

 ! KeyedCollection methodsFor: #private !
newHash
	" Private - Return a new hash object. "

	^{'{}'}! !

 ! MethodNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitMethodNode: self! !

 ! MethodNode methodsFor: #accessing !
arguments
	^arguments isNil ifTrue: [ #() ] ifFalse: [ arguments ]! !

 ! MethodNode methodsFor: #accessing !
arguments: aCollection
	arguments := aCollection! !

 ! MethodNode methodsFor: #accessing !
selector
	^selector! !

 ! MethodNode methodsFor: #accessing !
selector: aString
	selector := aString! !

 ! MethodNode methodsFor: #accessing !
source
	^source! !

 ! MethodNode methodsFor: #accessing !
source: aString
	source := aString! !

 ! Number methodsFor: #comparing !
= anObject
    " Return true if the receiver is equal to anObject. "

{'  if (nil.isNil_(anObject)) return false;
    if (!!(anObject.isNumber)) return false;
    if (!!(anObject.isNumber())) return false;
    if (self == anObject) return true;
    return ((0+self-anObject) == 0);
'}! !

 ! Number methodsFor: #comparing !
> aNumber
	" Return true if the receiver is greater to aNumber. "

	aNumber mustBeNumber.
{'	return self > aNumber; '}! !

 ! Number methodsFor: #comparing !
>= aNumber
	" Return true if the receiver is greater or equal to aNumber. "

	aNumber mustBeNumber.
{'	return self >= aNumber; '}! !

 ! Number methodsFor: #comparing !
< aNumber
	" Return true if the receiver is smaller to aNumber. "

	aNumber mustBeNumber.
{'	return self < aNumber; '}! !

 ! Number methodsFor: #arithmetic !
- aNumber
	" Return the result of operation on receiver and aNumber. "

	aNumber mustBeNumber.
{'	return self - aNumber; '}! !

 ! Number methodsFor: #arithmetic !
+ aNumber
	" Return the result of operation on receiver and aNumber. "

	aNumber mustBeNumber.
{'	return self + aNumber; '}! !

 ! Number methodsFor: #converting !
asJavascript
	" Return the javascript representation of the receiver. "

	^'(', self printString, ')'! !

 ! Number methodsFor: #testing !
isNumber
	" Return true if the receiver is a number. "

	^(# #isNaN: self) not! !

 ! Number methodsFor: #arithmetic !
max: aNumber
	" Return the result of operation on receiver and aNumber. "

	^#{Math} #max: self with: aNumber! !

 ! Number methodsFor: #arithmetic !
min: aNumber
	" Return the result of operation on receiver and aNumber. "

	^#{Math} #min: self with: aNumber! !

 ! Number methodsFor: #testing !
mustBeNumber
	" Signal an error if the receiver is not a Number.
	WARNING: this check impose a severe loss of perfomance (five times slower).
	If you are sure the operation/compare arguments are ok (a number),
	 comment the implementation of this method making the code empty.
	"

	"(# #isNaN: self) ifTrue: [ super mustBeNumber ]"! !

 ! Number methodsFor: #printing !
printString
	" Return the printable representation of the receiver. "

	^# #String: self! !

 ! Object methodsFor: #events !
actionForEvent: anEvent
	" Return the action to evaluate when the event is triggered by the receiver (or nil). "

	^self eventTable at: anEvent ifAbsent: [ nil ]! !

 ! Object methodsFor: #private !
basicPerform: jsSelector withArguments: anArray
	" Private - Basic implementation of #perform... "

	^(self basicAt: jsSelector
		ifAbsent: [ self[#dnu:withArguments:] ])
		#apply: self withArguments: anArray! !

 ! Object methodsFor: #copying !
copy
	" Return a copy of the receiver. "

	^self shallowCopy! !

 ! Object methodsFor: #evaluating !
evaluate
	" Return the result of evaluating the receiver. "

	^self! !

 ! Object methodsFor: #evaluating !
evaluateWithArguments: anArray
	" Return the result of evaluating the receiver. "

	^self! !

 ! Object methodsFor: #events !
eventTableCreate
	" Private - Returns a new mapping for the receiver. "

	^PoolDictionary new! !

 ! Object methodsFor: #initialize !
initialize
	" Private - Initialize the receiver.
	The default implementation do nothing.
	This method can be refined by subclasses to support creation time initialization of collaborators.
	"! !

 ! Object methodsFor: #testing !
isMetaclass
	" Return true if the receiver is a metaclass. "

	^false! !

 ! Object methodsFor: #testing !
isNil
	" Return true if the receiver is nil. "

	^false! !

 ! Object methodsFor: #testing !
isNumber
	" Return true if the receiver is a Number. "

	^false! !

 ! Object methodsFor: #testing !
isObject: anObject
	" Return true if anObject is a smalltalk object.
	Return false if the object is foreign (e.g. javascript) object.
	"

	anObject isNil ifTrue: [ ^anObject == nil ].
{'	return (anObject.$klass)?true:false;	'}! !

 ! Object methodsFor: 'Compiler-testing' !
isParseFailure
	" Return true if the receiver is a parsing failure. "

	^false! !

 ! Object methodsFor: #testing !
isString
	" Return true if the receiver is a String. "

	^false! !

 ! Object methodsFor: #messages !
methodFor: aSymbol 
	" Return the method implementing aSymbol (or nil). "

	^self class >>> aSymbol! !

 ! Object methodsFor: #perform !
perform: aSymbol
	" Return the result of sending message aSymbol to the receiver. "

	^self perform: aSymbol withArguments: #()! !

 ! Object methodsFor: #perform !
perform: aSymbol withArguments: aCollection
	" Return the result of sending message aSymbol to the receiver. "

	aCollection isArray ifFalse: [ self error: '// Invalid arguments in #perform:withArguments: (#',aSymbol,') (must be anArray).' ].
	^self basicPerform: aSymbol asSelector withArguments: aCollection! !

 ! Object methodsFor: #messages !
respondsTo: aSymbol 
	" Return true if the receiver respond to message aSymbol. "

	^(self methodFor: aSymbol) notNil! !

 ! Object methodsFor: #system !
smalltalk
	" Return the smalltalk system containing the receiver. "

	 ^#{smalltalk}! !

 ! Object methodsFor: #events !
triggerEvent: anEvent
	" Return the result of triggering the event. "

	^(self actionForEvent: anEvent) evaluate! !

 ! Object methodsFor: #events !
triggerEvent: anEvent ifNotHandled: aBlock
	" Trigger the event.
	If the event is not handled, return the value of evaluating aBlock,
        or the value returned by the most recently defined event handler.
	"

	^(self eventTable at: anEvent ifAbsent: [ aBlock ]) evaluate! !

 ! Object methodsFor: #events !
triggerEvent: anEvent withArguments: array
	" Return the result of triggering the event. "

	^(self actionForEvent: anEvent) evaluateWithArguments: array! !

 ! Object methodsFor: #events !
triggerEvent: anEvent withArguments: array ifNotHandled: aBlock
	" Return the result of triggering the eventwith the arguments.
	If the event is not handled, return the value of evaluating aBlock,
	or the value returned by the most recently defined event handler action.
	"

	^(self eventTable at: anEvent ifAbsent: [ aBlock ]) evaluateWithArguments: array! !

 ! Object methodsFor: #events !
triggerEvent: anEvent with: anObject
	" Return the result of triggering the event. "

	^self triggerEvent: anEvent withArguments: (Array with: anObject)! !

 ! Object methodsFor: #events !
triggerEvent: anEvent with: anObject ifNotHandled: aBlock
	" Return the result of triggering the eventwith. "

	^self triggerEvent: anEvent withArguments: (Array with: anObject) ifNotHandled: aBlock! !

 ! Object methodsFor: #events !
triggerEvent: anEvent with: anObject with: anotherObject
	" Return the result of triggering the event. "

	^self triggerEvent: anEvent withArguments: (Array with: anObject with: anotherObject)! !

 ! Object methodsFor: #identity !
yourself
	" Return the receiver. "

	^self! !

 ! PPActionParser methodsFor: #accessing !
block
	" Return the block of the receiver. "

	^block! !

 ! PPActionParser methodsFor: #accessing !
block: aBlock
	" Set the block of the receiver. "

	block := aBlock! !

 ! PPActionParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| element |
	element := self parser memoizedParse: aStream.
	element isParseFailure ifTrue: [ ^element ].
	^self block value: element! !

 ! PPActionParser class methodsFor: #instantiation !
on: aParser block: aBlock
	" Return an instance of the receiver. "

	^self new
		parser: aParser;
		block: aBlock;
		yourself! !

 ! PPAndParser methodsFor: #parsing !
basicParse: aStream
	" Parse contents in aStream. "

	| element position |
	position := aStream position.
	element := self parser memoizedParse: aStream.
	aStream position: position.
	^element! !

 ! PPCharacterParser methodsFor: #private !
match: aString
	" Match the receiver to string. "

	^aString match: regexp! !

 ! PPCharacterParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	(aStream peek notNil
	and: [ self match: aStream peek ])
	ifTrue: [ ^aStream next ].

	^PPFailure reason: 'Could not match' at: aStream position! !

 ! PPCharacterParser methodsFor: #accessing !
string: aString
	" Set the string of the receiver. "

	regexp := RegularExpression fromString: '[', aString, ']'! !

 ! PPChoiceParser methodsFor: #copying !
/ aRule
	" Return the receiver composed with aRule. "

	^self copyWith: aRule! !

 ! PPChoiceParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| result |
	self parsers detect: [:each |
		result := each memoizedParse: aStream.
		result isParseFailure not
	] ifNone: [].
	^result! !

 ! PPDelegateParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	^self parser memoizedParse: aStream! !

 ! PPDelegateParser methodsFor: #accessing !
parser
	" Return the parser of the receiver. "

	^parser! !

 ! PPDelegateParser methodsFor: #accessing !
parser: aParser
	" Set the parser of the receiver. "

	parser := aParser! !

 ! PPDelegateParser class methodsFor: #instantiation !
on: aParser
	" Return an instance of the receiver. "

	    ^self new
		parser: aParser;
		yourself! !

 ! PPEOFParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	aStream atEnd ifTrue: [ ^nil ] .
	^PPFailure reason: 'EOF expected' at: aStream position! !

 ! PPEpsilonParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	^nil! !

 ! PPFailure methodsFor: #testing !
isParseFailure
	" Return true if the receiver is a parse failure. "

	^true! !

 ! PPFailure methodsFor: #accessing !
position: aNumber
	" Set the position of the rceiver. "

	position := aNumber! !

 ! PPFailure methodsFor: #accessing !
reason: aString
	" Set the reason of the receiver. "

	reason := aString! !

 ! PPFailure methodsFor: #accessing !
reason: aString at: anInteger
	" Set the reason and position of the receiver. "

	self
		reason: aString; 
		position: anInteger! !

 ! PPFailure class methodsFor: #instantiation !
reason: aString at: anInteger
	" Return an instance of the receiver. "

	^self new reason: aString at: anInteger! !

 ! PPFlattenParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| start element |
	start := aStream position.
	element := self parser memoizedParse: aStream.
	element isParseFailure ifTrue: [ ^element ].
	^aStream collection 
		copyFrom: start + 1 
		to: aStream position! !

 ! PPInlineParser methodsFor: #accessing !
terminator: aString
	" Set terminator of the receiver. "

	terminator := aString! !

 ! PPInlineParser class methodsFor: #instantiation !
upTo: aString
	" Return an instance of the receiver. "

	^self new terminator: aString; yourself! !

 ! PPListParser methodsFor: #copying !
copyWith: aParser
	" Return a copy of the receiver with aParser. "

	^self class withAll: (self parsers copyWith: aParser)! !

 ! PPListParser methodsFor: #accessing !
parsers
	" Return the parsers of the receiver. "

	parsers isNil ifTrue: [ ^#() ].
	^parsers! !

 ! PPListParser methodsFor: #accessing !
parsers: aCollection
	" Set the parsers of the receiver. "

	parsers := aCollection collect: [:each| each asParser ]! !

 ! PPListParser class methodsFor: #instantiation !
withAll: aCollection
	" Return an instance of the receiver. "

	    ^self basicNew
		parsers: aCollection;
		yourself! !

 ! PPListParser class methodsFor: #instantiation !
with: aParser with: anotherParser
	" Return an instance of the receiver. "

	^self withAll: (Array with: aParser with: anotherParser)! !

 ! PPNotParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| element |
	element := self basicParse: aStream.
	element isParseFailure ifTrue: [ ^nil ].
	^PPFailure reason: element at: aStream position! !

 ! PPParser methodsFor: #operations !
, aParser
	" Return a composed version of the receiver and aParser. "

	^PPSequenceParser with: self with: aParser! !

 ! PPParser methodsFor: #operations !
==> aBlock
	" Return an action parser on the receiver. "

	^PPActionParser on: self block: aBlock! !

 ! PPParser methodsFor: #operations !
/ aParser
	" Return a choice composite version of the receiver and aParser. "

	^PPChoiceParser with: self with: aParser! !

 ! PPParser methodsFor: #converting !
asParser
	" Return a parser on the receiver. "

	^self! !

 ! PPParser methodsFor: #operations !
flatten
	" Return a flattened version of the receiver. "

	^PPFlattenParser on: self! !

 ! PPParser methodsFor: #accessing !
memo
	" Return the memoized information. "

	memo isNil ifTrue: [ memo := #() ].
	^memo! !

 ! PPParser methodsFor: #operations !
memoizedParse: aStream
	" Private - Evaluate the receiver. "

	| start value |
	start := aStream position.
	value := self memo at: start ifAbsent: [ | end node |
		node := self parse: aStream.
		end := aStream position.
		self set: node start: start end: end.
		self memo at: start put: (Array with: node with: end).
		^node
	].
	aStream position: value second.
	^value first! !

 ! PPParser methodsFor: #operations !
not
	" Return the negation of the receiver. "

	^PPNotParser on: self! !

 ! PPParser methodsFor: #operations !
optional
	" Return an optional version of the receiver. "

	^self / PPEpsilonParser new! !

 ! PPParser methodsFor: #operations !
plus
	" Return an iterative version of the receiver. "

	^PPRepeatingParser on: self min: 1! !

 ! PPParser methodsFor: #private !
set: anElement start: start end: end
	" Private - Set start&end source offest of anElement. "

	(anElement respondsTo: #start:end:) ifTrue: [
		anElement start: start end: end
	]! !

 ! PPParser methodsFor: #operations !
star
	" Return an iterative version of the receiver. "

	^PPRepeatingParser on: self min: 0! !

 ! PPParser methodsFor: #operations !
withSource
	" Return a source parser on the receiver. "

	^PPSourceParser on: self! !

 ! PPRepeatingParser methodsFor: #accessing !
min
	" Return the min of the receiver. "

	^min! !

 ! PPRepeatingParser methodsFor: #accessing !
min: aNumber
	" Set the min of the receiver. "

	min := aNumber! !

 ! PPRepeatingParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| start element result failure |
	start := aStream position.
	result := Array new.
	[ (result size < self min) and: [ failure isNil ]
	] whileTrue: [
	    element := self parser memoizedParse: aStream.
	    element isParseFailure
		ifFalse: [ result addLast: element ]
		ifTrue: [ aStream position: start.
			  failure := element ]
	].
	failure notNil ifTrue: [ ^failure ].
	[failure isNil] whileTrue: [
		element := self parser memoizedParse: aStream.
	 	element isParseFailure
			ifTrue: [ failure := element ]
			ifFalse: [ result addLast: element ]
	].
	^result! !

 ! PPRepeatingParser class methodsFor: #instantiation !
on: aParser min: aNumber
	" Return an instance of the receiver. "

	^self new
		parser: aParser;
		min: aNumber;
		yourself! !

 ! PPSequenceParser methodsFor: #copying !
, aRule
	" Return a copy of the receiver with aRule. "

	^self copyWith: aRule! !

 ! PPSequenceParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| start result element |
	result := #().
	start := aStream position.
	self parsers do: [:each |
		element := each memoizedParse: aStream.
		result add: element.
		element isParseFailure ifTrue: [
			aStream position: start.
			^element
		]
	].
	^result! !

 ! PPSourceParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| start element result |
	start := aStream position.
	element := self parser memoizedParse: aStream.
	element isParseFailure ifTrue: [ ^element ].
	result := aStream collection
		copyFrom: start + 1
		to: aStream position.
	^Array with: element with: result! !

 ! PPStringParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	| back reason |
	string isEmpty ifTrue: [ ^string ].
	(aStream peekForAll: string) ifTrue: [ ^string ].
	back := aStream position.
	reason := 'Expecting ', string toString printString
		,' at ',back printString
		,' read ',(aStream next: string size) printString.
	aStream position: back.
	^PPFailure reason: reason at: back! !

 ! PPStringParser methodsFor: #accessing !
string: aString
	" Set the string of the receiver. "

	string := aString! !

 ! PoolDictionary methodsFor: #accessing !
at: aKey ifAbsent: aBlock
	" Return the value at aKey or the result of evaluating aBlock. "

{'	var value = self["@hash"][aKey];
	if(value === undefined) { return aBlock(); }
	return value;'}.! !

 ! PoolDictionary methodsFor: #testing !
includesKey: aKey
	" Return true if the receiver's keys include aKey. "

	self at: aKey ifAbsent: [ ^false ].
	^true! !

 ! PoolDictionary methodsFor: #initialize !
initialize
	" Private - Initialize the receiver. "

	super initialize.
	hash := self newHash.! !

 ! RegularExpression class methodsFor: #instantiation !
fromString: aString
	" Return an instance of the receiver. "

	    ^self fromString: aString flag: ''! !

 ! RegularExpression class methodsFor: #instantiation !
fromString: aString flag: anotherString
	" Return an instance of the receiver. "

{'	return new RegExp(aString, anotherString);'}! !

 ! ReturnNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitReturnNode: self! !

 ! SendNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitSendNode: self! !

 ! SendNode methodsFor: #accessing !
arguments
	^arguments isNil ifTrue: [ #() ] ifFalse: [ arguments ]! !

 ! SendNode methodsFor: #accessing !
arguments: aCollection
	arguments := aCollection! !

 ! SendNode methodsFor: #accessing !
receiver
	^receiver! !

 ! SendNode methodsFor: #accessing !
receiver: aNode
	receiver := aNode! !

 ! SendNode methodsFor: #accessing !
selector
	^selector! !

 ! SendNode methodsFor: #accessing !
selector: aString
	selector := aString! !

 ! SendNode methodsFor: #accessing !
valueForReceiver: anObject
	^SendNode new
	    receiver: (self receiver isNil ifTrue: [anObject]
		ifFalse: [self receiver valueForReceiver: anObject]);
	    selector: self selector;
	    arguments: self arguments;
	    start: self start end: self end;
	    yourself! !

 ! SequenceNode methodsFor: #converting !
asBlockSequenceNode
	^BlockSequenceNode new
	    nodes: self nodes;
	    temps: self temps;
	    start: self start end: self end;
	    yourself! !

 ! SequenceNode methodsFor: #accessing !
temps
	^temps isNil ifTrue: [ #() ] ifFalse: [ temps ]! !

 ! SequenceNode methodsFor: #accessing !
temps: aCollection
	temps := aCollection! !

 ! SequenceableCollection methodsFor: #enumerating !
detect: aBlock ifNone: anotherBlock
	" Return the object in the receiver that return true when evaluated with aBlock or the result of evaluating anotherBlock. "

{'	for(var i = 0; i < self.length; i++) if(aBlock(self[i])) return self[i];
	return anotherBlock();
'}! !

 ! SequenceableCollection methodsFor: #accessing !
first
	" Return the object in the receiver. "

	^self at: 1! !

 ! SequenceableCollection methodsFor: #testing !
includes: anObject
	" Return true if anObject is in the receiver.
	Note: the indexOf() function fail to search in case of string literals in Array contents.
	"

	(self isObject: anObject) ifFalse: [
		^(self #indexOf: anObject) > -1
	].
{'	if (anObject.isNumber() && (self.indexOf(anObject) > -1)) return true;
	if (anObject.isString() && (self.indexOf(anObject) > -1)) return true;
	var i = self.length;
	while (i--) { if (anObject._eq(self[i])) { return true; } }
	return false; '}! !

 ! SequenceableCollection methodsFor: #testing !
isEmpty
	" Return true if the receiver is empty.
	Note: ^self size = 0 is slower than inlined impl.
	"

{'	return (this.length)?false:true; '}! !

 ! SequenceableCollection methodsFor: #accessing !
last
	" Return the object in the receiver. "

	^self at: self size! !

 ! SmalltalkParser methodsFor: #constants !
binarySelectorChars
	" Return the binary selector characters mask. "

	^'|&\\+*/=><,@%~-'! !

 ! SmalltalkParser methodsFor: #directives !
defaultDirective: number ws: ws
	" Private - Return the parser for default support of directives.
	We support inlined javascript directives.
	"

	^(self jsDirective: number ws: ws)
	/(self missingDirective: number ws: ws)! !

 ! SmalltalkParser methodsFor: #directives !
directive: number ws: ws
	" Private - Return the parser for directives. "

	| parser |
	parser := self
		triggerEvent: #needsDirectiveParser:ws:
		withArguments: (Array with: number with: ws)
		ifNotHandled: [ self defaultDirective: number ws: ws ].

	^$< asParser, (ws, parser, ws)
		==> [:node | node second second ]! !

 ! SmalltalkParser methodsFor: #constants !
extendedSymbolChars
	" Return the extended symbol characters mask. "

	^self symbolChars ,':' , self binarySelectorChars! !

 ! SmalltalkParser methodsFor: #gc !
gc
	" Private - Perform (preventive) garbage collection.
	Note: JavascriptCore VM can crash reporting
	 'memory issues' if we do not GC asap.
	 This issue will persist while Apple continue
	  distributing a version of JSC with issue reported
		http://swiki.smalltalking.net/U8/232
		https://bugs.webkit.org/show_bug.cgi?id=160027
	"

	(Smalltalk includesKey: #JSC) ifTrue: [ Smalltalk gc ].! !

 ! SmalltalkParser methodsFor: #parsers !
globalNameParser
	" Return the parser for global names. "

	^('A-Z' asCharacterParser, self symbolChars asCharacterParser star) flatten! !

 ! SmalltalkParser methodsFor: #directives !
jsDirective: number ws: ws
	" Private - Return the parser for javascript directives.
	"

	^('js:' asParser / 'javascript:' asParser), (PPInlineParser upTo: ':>')
		==> [:node| JSDirectiveNode code: node second protected: node first = #javascript ]! !

 ! SmalltalkParser methodsFor: #constants !
jsSymbolChars
	" Return the javascript symbol characters mask. "

	^self symbolChars ,$$! !

 ! SmalltalkParser methodsFor: #private !
methodParserParts
	" Private - Return a parser for parts of a method. "

 | expression separator comment ws identifier keyword stSelectorPart
  string symbol number variable reference globalReference
  literal returnExpression expressionParser keyword unarySelector
  binarySelector keywordPattern unaryPattern binaryPattern assignment
  temps blockParamList block expression expressions subexpression
  statements sequence operand unaryMessage unarySend unaryTail
  binaryMessage binarySend binaryTail keywordMessage keywordSend
  keywordPair cascade message jsStatement jsIndex character directive
  arrayLiteral arrayVariable literalArray aSymbol
  stIdentifier jsIdentifier noReference alienReference
  alienIdentifier emptyArray hashedString
 |

 separator := (String cr, String space, String lf, String tab) asChoiceParser.
 comment := ($" asCharacterParser, ($" asParser not, PPAnyParser new) star, $" asCharacterParser) flatten.
 ws := (separator / comment) star.
 
 string := $' asParser , PPStStringParser new
  ==> [:node| ValueNode new value: node second ].
 
 hashedString := ($#,$') asParser , PPStStringParser new
  ==> [:node| ValueNode new value: node second ].

 stIdentifier := ('a-z_' asCharacterParser, self symbolChars asCharacterParser star) flatten.
 stSelectorPart := ('A-Za-z_' asCharacterParser, self symbolChars asCharacterParser star) flatten.
 jsIdentifier := ($# asParser, self jsSymbolChars asCharacterParser plus) flatten.
 alienIdentifier := self jsSymbolChars asCharacterParser plus flatten.
 identifier := jsIdentifier / stIdentifier.

 keyword := (stSelectorPart / identifier, $:) flatten.

 symbol := $# asParser, self extendedSymbolChars asCharacterParser plus flatten
  ==> [:node | ValueNode new value: node second ].

 number := ('-0-9' asCharacterParser plus
  , ($. asParser, '0-9' asCharacterParser plus) optional
  , ($r asParser, 'A-Z0-9' asCharacterParser plus) optional
  ) flatten
  ==> [:node | ValueNode new value: node asNumber ].

 character := $$ asParser, PPAnyParser new
  ==> [:node | ValueNode new value: (node at: 2) ].

 directive := self directive: number ws: ws.

 variable := identifier ==> [:token | VariableNode new value: token ].
 noReference := $# asParser ==> [:token | NoReceiverNode new ].
 literal := PPDelegateParser new.
 expression := PPDelegateParser new.

 arrayVariable :=
    (#true asParser ==> [:node| ValueNode new value: true ])
  / (#false asParser ==> [:node| ValueNode new value: false ])
  / (#nil asParser ==> [:node| ValueNode new value: nil ]).
 aSymbol := self extendedSymbolChars asCharacterParser plus flatten
  ==> [:node| ValueNode new value: node ].

 arrayLiteral := literal / arrayVariable / aSymbol / variable.
 literalArray := '#(' asParser, (ws, arrayLiteral, ws) star, $)
  ==> [:node | self gc. ValueNode new value:
    (Array withAll: (node second
     collect: [:each | each second value])) ].
 emptyArray := '#(' asParser ,ws ,$)
  ==> [:node | ValueNode new value: Array new ].

 globalReference := self globalNameParser
  ==> [:token | self gc. GlobalReferenceNode new value: token ].
 alienReference := '#{' asParser, alienIdentifier, $}
  ==> [:node | AlienNode new value: node second ].

 jsIndex := $[ asParser, expression, $]
  / ($# asParser, identifier).
 reference := (variable / globalReference / alienReference) , jsIndex star
  ==> [:nodes | nodes first indexedAs: nodes ].

 binarySelector := ($# asParser optional, self binarySelectorChars asCharacterParser plus) flatten.

 unarySelector := stSelectorPart / identifier.

 keywordPattern := (ws, keyword, ws, identifier) plus
  ==> [:nodes | Array
   with: ((nodes collect: [:each | each at: 2]) join: '')
   with: (nodes collect: [:each | each at: 4]) ].

 binaryPattern := ws, binarySelector, ws, identifier
  ==> [:node | Array with: node second with: (Array with: node fourth)].

 unaryPattern := ws, unarySelector
  ==> [:node | Array with: node second with: Array new].
 
 expressions := expression, ((ws, $., ws, expression) ==> [:node | node fourth]) star
  ==> [:node | (Array with: node first) ,node second ].

 assignment := reference, ws, ':=', ws, expression
  ==> [:node | AssignmentNode new left: node first; right: (node at: 5)].

 returnExpression := $^ asParser, ws, expression, ws, $. asParser optional
     ==> [:node | ReturnNode new addNode: node third; yourself ].

 temps := $| asParser, (ws, identifier) star, ws, $|
  ==> [:node | node second collect: [:each | each second ] ].

 blockParamList := ($: asParser, ws, identifier, ws) plus, $|
  ==> [:node | node first collect: [:each | each third ] ].

 subexpression := $( asParser, ws, expression, ws, $)
  ==> [:node | node third ].

 statements := (returnExpression ==> [:node | Array with: node])
  / (expressions, ws, $., ws, returnExpression ==> [:node | node first add: (node at: 5); yourself ])
  / (expressions , $. asParser optional ==> [:node | node first ]).

 sequence := temps optional, ws, directive optional, ws, statements optional, ws
  ==> [:node | ExtendedSequenceNode new
   directive: node third;
   temps: node first;
   nodes: (node at: 5);
   yourself ].

 block := $[ asParser, ws, blockParamList optional, ws, sequence optional, ws, $]
  ==> [:node | self gc. BlockNode new
   parameters: node third;
   addNode: (node at: 5) asBlockSequenceNode ].

 operand := block / literal / reference / noReference / subexpression.

 literal parser: symbol / number / string / character
  / emptyArray / literalArray / hashedString.

 unaryMessage := ws, unarySelector, $: asParser not
  ==> [:node | SendNode new selector: node second ].

 unaryTail := PPDelegateParser new.
 unaryTail parser: (unaryMessage, unaryTail optional
  ==> [:node | node second isNil ifTrue: [ node first ]
   ifFalse: [ node second valueForReceiver: node first ] ]).

 unarySend := operand, unaryTail optional
  ==> [:node | node second isNil ifTrue: [ node first ]
   ifFalse: [ node second valueForReceiver: node first ] ].

 binaryMessage := ws, binarySelector, ws, (unarySend / operand)
  ==> [:node | SendNode new
   selector: node second;
   arguments: (Array with: node fourth) ].

 binaryTail := PPDelegateParser new.
 binaryTail parser: (binaryMessage, binaryTail optional
  ==> [:node | node second isNil ifTrue: [ node first ]
   ifFalse: [ node second valueForReceiver: node first ] ]).

 binarySend := unarySend, binaryTail optional
  ==> [:node | node second isNil ifTrue: [ node first ]
   ifFalse: [ node second valueForReceiver: node first ] ].

 keywordPair := keyword, ws, binarySend.

 keywordMessage := (ws, keywordPair) plus
  ==> [:nodes | SendNode new
   selector: ((nodes collect: [:each | each second first]) join: '');
   arguments: (nodes collect: [:each | each second third])].

 keywordSend := binarySend, keywordMessage
  ==> [:node | node second valueForReceiver: node first].

 message := binaryMessage / unaryMessage / keywordMessage.

 cascade := (keywordSend / binarySend), (ws, $;, message) plus
  ==> [:node | node first cascadeNodeWithMessages: 
   (node second collect: [:each | each third ])].

 jsStatement := ${ asParser, ws, string, ws, $}
  ==> [:node | InlineNode new source: node third; yourself ].

 expression parser: assignment / cascade / keywordSend / binarySend / jsStatement.

	^Array	with: ws
		with: keywordPattern / binaryPattern / unaryPattern
		with: sequence optional! !

 ! SmalltalkParser methodsFor: #directives !
missingDirective: number ws: ws
	" Private - Return the parser for missing support of directives. "

	^'^>' asCharacterParser star flatten, $>
		==> [:node| node first error: 'Invalid directive.' ]! !

 ! SmalltalkParser methodsFor: #parsing !
parse: aStream
	" Parse contents in aStream. "

	^self parser parse: aStream! !

 ! SmalltalkParser methodsFor: #parsers !
parser
	" Returns the method parser. "

	| parts ws header body method |
	parts := self methodParserParts.
	ws := parts first.
	header := parts second.
	body := parts third.

	method := (ws ,header ,ws ,body ,ws) withSource
	  ==> [:node | MethodNode new
		selector: node first second first;
		arguments: node first second second;
		addNode: node first fourth;
		source: node second;
		yourself ].
 
 	^method ,PPEOFParser new ==> [:nodes | nodes first ]! !

 ! SmalltalkParser methodsFor: #constants !
symbolChars
	" Return the symbol characters mask. "

	^'a-zA-Z0-9_'! !

 ! Smalltalk methodsFor: 'Compiler-accessing' !
compilerSupport
	" Return the compiler support for the receiver. "

	^Compiler! !

 ! Smalltalk methodsFor: #javascript !
eval: jsExpression
	" Return the result of evaluating a javascript expression in global context. "

	^# #eval: jsExpression! !

 ! Smalltalk class methodsFor: #accessing !
current
	" Return the current smalltalk system instance. "

	^#{smalltalk}! !

 ! Smalltalk class methodsFor: #accessing !
includesKey: aGlobalName
	" Returns true if the global aGlobalName is defined in the receiver. "

	^((Smalltalk current
		basicAt: aGlobalName ifAbsent: [#{undefined}])
		== #{undefined}) not! !

 ! Stream methodsFor: #testing !
atEnd
	" Return true if the receiver is at end. "

	^self position >= self size! !

 ! Stream methodsFor: #accessing !
collection
	" Private - Return the collection of the receiver. "

	^collection! !

 ! Stream methodsFor: #accessing !
collection: aCollection
	" Private - Set the collection of the receiver. "

	collection := aCollection! !

 ! Stream methodsFor: #accessing !
contents
	" Return the contents of the receiver. "

	| result |
	result := self collection.
	self readLimit = result size ifTrue: [ ^result ].
	^result copyFrom: 1 to: self readLimit! !

 ! Stream methodsFor: #writing !
cr
	" Put a line break sequence onto the receiver.
	Note: this implementation MUST be consistent with #nextLine
	"

	self nextPutAll: String crlf! !

 ! Stream methodsFor: #initialize !
initialize
	" Private - Initialize the receiver. "

	super initialize.
	position := 0.! !

 ! Stream methodsFor: #accessing !
position
	" Return the position of the receiver. "

	^position! !

 ! Stream methodsFor: #accessing !
position: anInteger
	" Set the position of the receiver. "

	position := anInteger! !

 ! Stream methodsFor: #accessing !
readLimit
	" Private - Return the read limit of the receiver. "

	readLimit == nil ifTrue: [ readLimit := self collection size ].
	^readLimit! !

 ! Stream methodsFor: #accessing !
readLimit: anInteger
	" Private - Set the stream size of the receiver. "

	readLimit := anInteger! !

 ! Stream methodsFor: #accessing !
size
	" Return the size of the receiver. "

	^self readLimit! !

 ! Stream class methodsFor: #instantiation !
on: aCollection
	" Return an instance of the receiver. "

	^self new 
		collection: aCollection;
		readLimit: aCollection size;
		yourself! !

 ! StringStream methodsFor: #reading !
next
	" Return the next readable element in the receiver (or nil). "

	| result |
	result := self peek.
	result notNil ifTrue: [ position := position + 1 ].
	^result! !

 ! StringStream methodsFor: #writing !
nextPutAll: aString
	" Put aString onto the receiver at current position; expanding internal contents. "

	| result |
	self position = self collection size
	ifTrue: [ result := self collection , aString ]
	ifFalse: [ | substring |
		substring := self collection copyFrom: 1 to: self position.
		result := substring isEmpty ifTrue: [ aString ] ifFalse: [ substring , aString ].
		substring := self collection
			copyFrom: self position + 1 + aString size
			to: self collection size.
		result := substring isEmpty ifTrue: [ result ] ifFalse: [ result , substring ].
	].
	self collection: result.
	self position: self position + aString size.
	self readLimit: (self readLimit max: position)! !

 ! StringStream methodsFor: #reading !
next: anInteger
	" Return the next anInteger elements read from the receiver.
	If the receiver reach its end, the returned collection has less elements.
	"

	| start result stop |
	start := self position.
	stop := start + anInteger min: self readLimit.
	result := self collection copyFrom: start + 1 to: stop.
	self position: stop.
	^result! !

 ! StringStream methodsFor: #reading !
peek
	" Return the next readable element from the receiver without advancing (or nil). "

	^(collection #charAt: self position) || nil! !

 ! StringStream methodsFor: #reading !
peekForAll: aCollection
	" Return true if the next readable elements from the receiver matches aCollection.
	Advance the receiver if the result is true.
	"

	aCollection isString ifFalse: [ ^super peekForAll: aCollection ].
{'	var start = self.position();
	for (var i=0;i<aCollection.length; i++){
		if (self["@collection"].charCodeAt(start+i) !!= aCollection.charCodeAt(i)) return false;
	}
'}.	position := position + aCollection#length.
	^true! !

 ! String methodsFor: #copying !
, aString
	" Return a copy of the receiver with aString appended. "

{'	if (nil.isNil_(aString)) return self+""; // we need this ugly patch for JSC under iOS
	return self + aString.toString()'}! !

 ! String methodsFor: #comparing !
= anObject
    " Return true if the receiver is equal to anObject. "

{'  if (nil.isNil_(anObject)) return false;
    if (!!(anObject.isString)) return false;
    if (!!(anObject.isString())) return false;
    if (self == anObject) return true;
    return ((""+self) == (""+anObject));
'}! !

 ! String methodsFor: 'Compiler-converting' !
asCharacterParser
	" Return a parser on the characters of the receiver. "

	^PPCharacterParser new string: self! !

 ! String methodsFor: 'Compiler-converting' !
asChoiceParser
	" Return a parser of choices for each character the receiver. "

	^PPChoiceParser withAll: (self asArray collect: [:each | each asParser ])! !

 ! String methodsFor: #converting !
asJavascriptName
	" Private - Return the receiver as a valid javascript name. "

	self first = $_ ifTrue: [ ^self ].
	(String reservedWords includes: self) ifTrue: [ ^'$$',self ].
	^self! !

 ! String methodsFor: #converting !
asNumber
	" Return the receiver as a Number. "

	(self includes: "$r"'r') ifTrue: [
		^Number readFrom: self readStream
	].
	^# #Number: self! !

 ! String methodsFor: 'Compiler-converting' !
asParser
	" Return a parser on the receiver. "

	^PPStringParser new string: self! !

 ! String methodsFor: #converting !
asSelector
	" Private - Return the receiver as a valid javascript selector. "

	| selector |
	self isEmpty ifTrue: [ ^'$' ].
	(self match: '^#') ifTrue: [ ^self upTo: $: startingAt: 2 ].
	self isBackSlash ifTrue: [ ^'_bk' ].
{'	 return self
		.replace(/:/g,"_")
		.replace(/[+]/g,"_plus")
		.replace(/-/g,"_minus")
		.replace(/[*]/g,"_star")
		.replace(/[/]/g,"_slash")
		.replace(/[|]/g,"_bar")
		.replace(/[&]/g,"_amp")
		.replace(/>/g,"_gt")
		.replace(/</g,"_lt")
		.replace(/=/g,"_eq")
		.replace(/,/g,"_comma")
		.replace(/[@]/g,"_at")
		.replace(/~/g,"_no")
		.replace(/\\/g,"_bk")
		.asJavascriptName();
	'}! !

 ! String methodsFor: #accessing !
at: anIndex
	" Return the receiver at anIndex. "

	^self #charAt: anIndex - 1! !

 ! String methodsFor: #copying !
copyFrom: anIndex to: anotherIndex
	" Return the receiver between limits. "

	^self #substring: anIndex - 1 to: anotherIndex! !

 ! String methodsFor: 'Tools-evaluating' !
doIt
	" Return the result of evaluating the receiver or the error occurred during compilation or evaluation. "

	^self smalltalk compilerSupport doIt: self! !

 ! String methodsFor: #enumerating !
do: aBlock
	" Evaluate aBlock with the contents of the receiver. "

{'	for(var i=0;i<self.length;i++){aBlock(self.charAt(i));}'}! !

 ! String methodsFor: #converting !
escaped
	" Return the receiver with escape codes. "

	^# #escape: self! !

 ! String methodsFor: #converting !
escapedCode
	" Return the code to reproduce receiver from (javascript) code. "

	| escaped |
	escaped := self escaped.
	escaped = self ifTrue: [ ^$" ,escaped ,$" ].
	^'unescape("' ,escaped ,'")'! !

 ! String methodsFor: #testing !
includes: anObject
	" Return true if anObject is in receiver's contents. "

	^(self indexOf: anObject) > 0! !

 ! String methodsFor: #accessing !
indexOf: aString
	" Return the position of first occurrence of aString (or 0 if not present). "

	^(self #indexOf: aString) + 1! !

 ! String methodsFor: #testing !
isBackSlash
	" Return true if the receiver is a back-slash string. "

	^self = $\ ! !

 ! String methodsFor: #testing !
isString
	" Return true if the receiver is a String. "

	^true! !

 ! String methodsFor: 'regular expressions' !
match: aRegexp
	" Return the match index of aRegexp in the receiver. "

{'	return self.search(aRegexp) !!= -1'}! !

 ! String methodsFor: #printing !
printString
	" Return the printable representation of the receiver. "

	^'''', self, ''''! !

 ! String methodsFor: #accessing !
size
	" Return the size of the receiver. "

	^self#length! !

 ! String class methodsFor: #accessing !
cr
	" Return the singular instance. "

	^{'"\r"'}! !

 ! String class methodsFor: #accessing !
crlf
	" Return the singular instance. "

	^{'"\r\n"'}! !

 ! String class methodsFor: #doIt !
doItSelector
	" Return the selector to use for doIt evaluations.
	Warning: this selector will not be dump on image nor change log expressions.
	"

	^#s8DoIt! !

 ! String class methodsFor: #accessing !
lf
	" Return the singular instance. "

	^{'"\n"'}! !

 ! String class methodsFor: #private !
reservedWords
	" Private - Return the reserved names of javascript language. "

	^#(
	abstract	as		boolean		break		byte
	case		catch		char		class		continue
	const		debugger	default		delete		do
	double		else		enum		export		extends
	false		final		finally		float		for
	function	goto		if		implements	import
	in		instanceof	int		interface	is
	long		namespace	native		new		null
	package		private		protected	public		return
	short		static		super		switch		synchronized
	this		throw		throws		transient	true
	try		typeof		use		var		void
	volatile	while		with
	)! !

 ! String class methodsFor: #accessing !
space
	" Return the singular instance. "

	^{'" "'}! !

 ! String class methodsFor: #accessing !
streamClass
	" Return the streamming support for the receiver's instances. "

	^StringStream! !

 ! String class methodsFor: #accessing !
tab
	" Return the singular instance. "

	^{'"\t"'}! !

 ! SystemManager methodsFor: 'tracking-methods' !
aboutToBind: aMethod to: aClass
	" Private - The method will be bound to aClass. "

	^self triggerEvent: #aboutToBind:to: with: aMethod with: aClass ! !

 ! SystemManager methodsFor: 'tracking-methods' !
aboutToRemove: aMethod from: aClass
	" Private - The method will be removed from aClass. "

	^self triggerEvent: #aboutToRemove:from: with: aMethod with: aClass ! !

 ! SystemManager methodsFor: 'tracking-methods' !
methodBound: aMethod to: aClass
	" Private - The method has been bound to aClass. "

	^self triggerEvent: #methodBound:to: with: aMethod with: aClass ! !

 ! SystemManager methodsFor: 'tracking-methods' !
methodRemoved: aMethod from: aClass
	" Private - The method has been removed from aClass. "

	^self triggerEvent: #methodRemoved:from: with: aMethod with: aClass ! !

 ! SystemManager class methodsFor: #singleton !
currentOrNil
	" Return the current instance of the receiver. "

	^self classVariableAt: #Current ifAbsent: [ nil ]! !

 ! ValueNode methodsFor: #visiting !
accept: aVisitor
	aVisitor visitValueNode: self! !

 ! ValueNode methodsFor: #accessing !
value
	^value! !

 ! ValueNode methodsFor: #accessing !
value: anObject
	value := anObject! !