[squeak-dev] The Trunk: Compiler-eem.451.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 30 19:01:11 UTC 2020


Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.451.mcz

==================== Summary ====================

Name: Compiler-eem.451
Author: eem
Time: 30 October 2020, 12:01:09.305583 pm
UUID: 30f155c7-a9c4-4cb8-bac6-f5089bbf7b36
Ancestors: Compiler-ct.450

just recategorizations.

=============== Diff against Compiler-tobe.448 ===============

Item was changed:
+ ----- Method: BytecodeEncoder>>generateBlockMethodOfClass:trailer:from: (in category 'method generation') -----
- ----- Method: BytecodeEncoder>>generateBlockMethodOfClass:trailer:from: (in category 'method encoding') -----
  generateBlockMethodOfClass: aCompiledBlockClass trailer: trailer from: blockNode
  	"Generate a CompiledBlock for the block whose parse tree is blockNode."
  
  	"The closure analysis should already have been done."
  	| blkSize header literals locals method nLits stack |
  	self assert: blockNode blockExtent notNil.
  	self assert: rootNode notNil.
  	blkSize := blockNode sizeCodeForEvaluatedFullClosureValue: self.
  	locals := blockNode localsNodes.
  	self noteBlockExtent: blockNode blockExtent hasLocals: locals.
  	header := self computeMethodHeaderForNumArgs: blockNode arguments size
  					numTemps: locals size
  					numLits: (nLits := (literals := self allLiteralsForBlockMethod) size)
  					primitive: 0.
  	method := trailer
  					createMethod: blkSize
  					class: aCompiledBlockClass
  					header: header.
  	1 to: nLits do:
  		[:lit |
  		(method literalAt: lit put: (literals at: lit)) isCompiledCode ifTrue:
  			[(literals at: lit) outerCode: method]].
  	self streamToMethod: method.
  	stack := ParseStack new init.
  	stack position: method numTemps.
  	blockMethod := method. "For BytecodeEncoder>>pc & BytecodeEncoder>>nextPC"
  	[blockNode emitCodeForEvaluatedFullClosureValue: stack encoder: self]
  		on: Error "If an attempt is made to write too much code the method will be asked"
  		do: [:ex|  "to grow, and the grow attempt will fail in CompiledCode class>>#newMethodViaNewError"
  			ex signalerContext sender method = (CompiledCode class>>#newMethodViaNewError)
  				ifTrue: [^self error: 'Compiler code size discrepancy']
  				ifFalse: [ex pass]].
  	stack position ~= (method numTemps + 1) ifTrue:
  		[^self error: 'Compiler stack discrepancy'].
  	stream position ~= (method size - trailer size) ifTrue:
  		[^self error: 'Compiler code size discrepancy'].
  	method needsFrameSize: stack size - method numTemps.
  	^method!

Item was changed:
+ ----- Method: BytecodeEncoder>>generateMethodOfClass:trailer:from: (in category 'method generation') -----
- ----- Method: BytecodeEncoder>>generateMethodOfClass:trailer:from: (in category 'method encoding') -----
  generateMethodOfClass: aCompiledMethodClass trailer: trailer from: methodNode
  	"The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
  	 The argument, trailer, is arbitrary but is typically either the reference to the source code
  	 that is stored with every CompiledMethod, or an encoding of the method's temporary names."
  
  	| primErrNode blkSize nLits locals literals header method stack |
  	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
  						[self fixTemp: methodNode primitiveErrorVariableName].
  	methodNode ensureClosureAnalysisDone.
  	self rootNode: methodNode. "this is for BlockNode>>sizeCodeForClosureValue:"
  	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
  				+ (methodNode primitive > 0
  					ifTrue: [self sizeCallPrimitive: methodNode primitive]
  					ifFalse: [0])
  				+ (primErrNode
  					ifNil: [0]
  					ifNotNil:
  						[primErrNode
  							index: methodNode arguments size + methodNode temporaries size;
  							sizeCodeForStore: self "The VM relies on storeIntoTemp: (129)"]).
  	locals := methodNode arguments, methodNode temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]).
  	self noteBlockExtent: methodNode block blockExtent hasLocals: locals.
  	header := self computeMethodHeaderForNumArgs: methodNode arguments size
  					numTemps: locals size
  					numLits: (nLits := (literals := self allLiterals) size)
  					primitive: methodNode primitive.
  	method := trailer
  					createMethod: blkSize
  					class: aCompiledMethodClass
  					header: header.
  	1 to: nLits do:
  		[:lit |
  		(method literalAt: lit put: (literals at: lit)) isCompiledCode ifTrue:
  			[(literals at: lit) outerCode: method]].
  	self streamToMethod: method.
  	stack := ParseStack new init.
  	methodNode primitive > 0 ifTrue:
  		[self genCallPrimitive: methodNode primitive].
  	primErrNode ifNotNil:
  		[primErrNode emitCodeForStore: stack encoder: self].
  	stack position: method numTemps.
  	[methodNode block emitCodeForEvaluatedValue: stack encoder: self]
  		on: Error "If an attempt is made to write too much code the method will be asked"
  		do: [:ex|  "to grow, and the grow attempt will fail in CompiledCode class>>#newMethodViaNewError"
  			ex signalerContext sender method = (CompiledCode class>>#newMethodViaNewError)
  				ifTrue: [^self error: 'Compiler code size discrepancy']
  				ifFalse: [ex pass]].
  	stack position ~= (method numTemps + 1) ifTrue:
  		[^self error: 'Compiler stack discrepancy'].
  	stream position ~= (method size - trailer size) ifTrue:
  		[^self error: 'Compiler code size discrepancy'].
  	method needsFrameSize: stack size - method numTemps.
  	^method!

Item was added:
+ ----- Method: CompilationCue>>source: (in category 'accessing') -----
+ source: aString
+ 
+ 	source := aString.
+ 	sourceStream := source readStream.!

Item was changed:
+ ----- Method: EncoderForSistaV1>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method generation') -----
- ----- Method: EncoderForSistaV1>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method encoding') -----
  computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
  	numTemps > 63 ifTrue:
  		[^self error: 'Cannot compile -- too many temporary variables'].	
  	numLits > 65535 ifTrue:
  		[^self error: 'Cannot compile -- too many literals'].
  	^SmallInteger minVal "sign bit is the flag for the alternative bytecode set"
  	+ (numArgs bitShift: 24)
  	+ (numTemps bitShift: 18)
  	"+ (largeBit bitShift: 17)" "largeBit gets filled in later"
  	+ numLits
  	+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])!

Item was changed:
+ ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'bytecode generation') -----
- ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'extended bytecode generation') -----
  genCallInlinePrimitive: primitiveIndex
  	"	248	(2)	11111000 	iiiiiiii		mssjjjjj		Call Primitive #iiiiiiii + (jjjjj * 256) 
  								m=1 means inlined primitive, no hard return after execution. 
  								ss defines the unsafe operation set used to encode the operations. 
  								(ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
  	"N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
  	 complicate the VM's determination of the primitive number and the primitive error code
  	 store since the extension, being optional, would make the sequence variable length."
  	(primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
  		[self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
  	stream
  		nextPut: 248;
  		nextPut: (primitiveIndex bitAnd: 255);
  		nextPut: (primitiveIndex bitShift: -8) + 128!

Item was changed:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied: (in category 'bytecode generation') -----
- ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied: (in category 'extended bytecode generation') -----
  genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
  	"By default the closure will have an outer context and the receiver will be fetched from the current context"
  	self genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: false ignoreOuterContext: false!

Item was changed:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'bytecode generation') -----
- ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'extended bytecode generation') -----
  genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: receiverOnStack ignoreOuterContext: ignoreOuterContext
  	"*	249		11111001 	xxxxxxxx	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
  	| extendedIndex |
  	(numCopied < 0 or: [numCopied > 64]) ifTrue:
  		[self outOfRangeError: 'num copied' index: numCopied range: 1 to: 64].
  	(compiledBlockLiteralIndex < 0 or: [compiledBlockLiteralIndex > 32767]) ifTrue:
  		[^self outOfRangeError: 'index' index: compiledBlockLiteralIndex range: 0 to: 32767].
  	(extendedIndex := compiledBlockLiteralIndex) > 255 ifTrue:
  		[self genUnsignedSingleExtendA: extendedIndex // 256.
  		 extendedIndex := extendedIndex \\ 256].
  	stream
  		nextPut: 249;
  		nextPut: extendedIndex;
  		nextPut: receiverOnStack asBit << 7 + (ignoreOuterContext asBit << 6) + numCopied!

Item was changed:
+ ----- Method: EncoderForSistaV1>>genSendDirectedSuper:numArgs: (in category 'bytecode generation') -----
- ----- Method: EncoderForSistaV1>>genSendDirectedSuper:numArgs: (in category 'extended bytecode generation') -----
  genSendDirectedSuper: selectorLiteralIndex numArgs: nArgs
  	| extendedIndex |
  	(selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
  		[^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
  	(nArgs < 0 or: [nArgs > 31]) ifTrue:
  		[^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
  	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
  		[self genUnsignedMultipleExtendA: extendedIndex // 32.
  		 extendedIndex := extendedIndex \\ 32].
  	"Bit 6 of the ExtB byte is the directed send flag.  Bit 6 allows for future expansion to up to 255 args."
  	self genUnsignedSingleExtendB: nArgs // 8 + 64.
  	"235		11101011	iiiiijjj		Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	stream
  		nextPut: 235;
  		nextPut: nArgs \\ 8 + (extendedIndex * 8)!

Item was changed:
  ----- Method: Parser>>notify:at: (in category 'error handling') -----
  notify: string at: location 
  	| messageText |
  	messageText := '"' , string , ' ->"'.
  	cue requestor isNil
  		ifTrue: [
  			| notification |
  			(encoder == self or: [encoder isNil])
  				ifTrue: [^ self fail "failure setting up syntax error"].
  			(notification := SyntaxErrorNotification
+ 				cue: (cue copy
+ 					source: (source contents asText
+ 						copyReplaceFrom: location
+ 						to: location - 1
+ 						with: messageText);
+ 					yourself)
- 				inClass: encoder classEncoding
- 				withCode: (source contents asText
- 					copyReplaceFrom: location
- 					to: location - 1
- 					with: messageText)
  				doitFlag: doitFlag
  				errorMessage: string
  				location: location) signal.
  			notification tryNewSourceIfAvailable]
  		ifFalse: [cue requestor
  			notify: messageText
  			at: location
  			in: source].
  	^ self fail!

Item was changed:
  Error subclass: #SyntaxErrorNotification
+ 	instanceVariableNames: 'cue doitFlag errorMessage location newSource'
- 	instanceVariableNames: 'inClass code doitFlag errorMessage location newSource'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Exceptions'!
  
+ !SyntaxErrorNotification commentStamp: 'ct 10/24/2020 00:01' prior: 0!
- !SyntaxErrorNotification commentStamp: 'nice 9/18/2013 22:16' prior: 0!
  A SyntaxErrorNotification is an Exception occuring when compiling a Smalltalk source code with incorrect syntax.
  Note that in interactive mode, this exception is not raised because the Compiler will interact directly with source code editor.
  The defaultAction is to raise a SyntaxError pop up window so as to enable interactive handling even in non interactive mode.
  
  Instance Variables
+ 	cue:		<CompilationCue>
- 	category:		<String | nil>
- 	code:		<String | Text | Stream>
  	doitFlag:		<Boolean>
  	errorMessage:		<String>
- 	inClass:		<Behavior>
  	location:		<Integer>
  	newSource:		<String | Text | Stream | nil>
  
+ cue
+ 	- the cue for compilation, including receiver class, optional context, and original source code
- category
- 	- the category in which the method will be classified
  
- code
- 	- the source code to be compiled or evaluated
- 
  doitFlag
  	- true if this is a doIt (code to evaluate), false if this is a method (code of a method to be compiled)
  
  errorMessage
  	- contains information about the syntax error
  
- inClass
- 	- target class in which to compile the method
- 
  location
  	- position in the source code where the syntax error occured
  
  newSource
+ 	- eventually hold a source code replacement typically passed by the SyntaxError window!
- 	- eventually hold a source code replacement typically passed by the SyntaxError window
- !

Item was added:
+ ----- Method: SyntaxErrorNotification class>>cue:doitFlag:errorMessage:location: (in category 'instance creation') -----
+ cue: aCue doitFlag: doitFlag errorMessage: errorString location: location
+ 
+ 	^ self new
+ 		setCue: aCue
+ 		doitFlag: doitFlag
+ 		errorMessage: errorString
+ 		location: location!

Item was changed:
+ ----- Method: SyntaxErrorNotification class>>inClass:withCode:doitFlag:errorMessage:location: (in category 'instance creation') -----
- ----- Method: SyntaxErrorNotification class>>inClass:withCode:doitFlag:errorMessage:location: (in category 'exceptionInstantiator') -----
  inClass: aClass withCode: codeString doitFlag: doitFlag errorMessage: errorString location: location
+ 
+ 	self deprecated: 'ct: Use #cue:doitFlag:errorMessage:location:'.
+ 	^ self
+ 		cue: (CompilationCue source: codeString class: aClass requestor: nil)
- 	^self new
- 		setClass: aClass
- 		code: codeString
  		doitFlag: doitFlag
  		errorMessage: errorString
  		location: location!

Item was added:
+ ----- Method: SyntaxErrorNotification>>context (in category 'accessing') -----
+ context
+ 
+ 	^ cue context!

Item was added:
+ ----- Method: SyntaxErrorNotification>>environment (in category 'accessing') -----
+ environment
+ 
+ 	^ cue environment!

Item was changed:
  ----- Method: SyntaxErrorNotification>>errorClass (in category 'accessing') -----
  errorClass
+ 
+ 	^ cue getClass!
- 	^inClass!

Item was changed:
  ----- Method: SyntaxErrorNotification>>errorCode (in category 'accessing') -----
  errorCode
+ 
+ 	^ cue source!
- 	^code!

Item was changed:
  ----- Method: SyntaxErrorNotification>>messageText (in category 'accessing') -----
  messageText
  	^ super messageText
+ 		ifEmpty: [messageText := self errorCode]!
- 		ifEmpty: [messageText := code]!

Item was changed:
  ----- Method: SyntaxErrorNotification>>reparse:notifying:ifFail: (in category 'accessing') -----
  reparse: aString notifying: aController ifFail: failBlock
  	"Try to parse if aString has correct syntax, but do not evaluate/install any code.
  	In case of incorrect syntax, execute failBlock and let a Compiler interact with the requestor.
  	In case of correct syntax, set newSource."
+ 
+ 	(doitFlag ifTrue: [nil class] ifFalse: [self errorClass]) newCompiler
+ 		compileCue: (cue copy
+ 			source: aString;
+ 			requestor: aController;
+ 			yourself)
+ 		noPattern: doitFlag
+ 		ifFail: failBlock.
+ 	newSource := aString.!
- 	doitFlag
- 		ifTrue: [nil class newCompiler compileNoPattern: aString in: nil class notifying: aController ifFail: failBlock]
- 		ifFalse: [inClass newCompiler compile: aString in: inClass notifying: aController ifFail: failBlock].
- 	newSource := aString!

Item was removed:
- ----- Method: SyntaxErrorNotification>>setClass:code:doitFlag:errorMessage:location: (in category 'accessing') -----
- setClass: aClass code: codeString doitFlag: aBoolean errorMessage: errorString location: anInteger
- 	inClass := aClass.
- 	code := codeString.
- 	doitFlag := aBoolean.
- 	errorMessage := errorString.
- 	location := anInteger!

Item was added:
+ ----- Method: SyntaxErrorNotification>>setCue:doitFlag:errorMessage:location: (in category 'initialize-release') -----
+ setCue: aCue doitFlag: aBoolean errorMessage: errorString location: anInteger
+ 
+ 	cue := aCue.
+ 	doitFlag := aBoolean.
+ 	errorMessage := errorString.
+ 	location := anInteger!



More information about the Squeak-dev mailing list