[prev in list] [next in list] [prev in thread] [next in thread] 

List:       squeak-dev
Subject:    [squeak-dev] The Trunk: Compiler-eem.308.mcz
From:       commits () source ! squeak ! org
Date:       2015-09-16 18:42:13
[Download RAW message or body]

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

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

Name: Compiler-eem.308
Author: eem
Time: 16 September 2015, 11:42:08.344 am
UUID: 0420593e-81fc-463c-8d0d-5a0cc7de2845
Ancestors: Compiler-eem.307

Addition:
Scanner>>typedScan:do:, useful for tools (watch this space).

Optimisation:
Avoid an expensive visit of the parse tree if there are no temps when checking if \
they need nilling before being read.

Polish:
Better error message with bindTemp:.

Decompile empty blocks as [] not [nil].

Nuke obsolete method creation methods generateMethodOfClass:trailer:from:.

=============== Diff against Compiler-eem.307 ===============

Item was changed:
  ----- Method: BlockNode>>nilReadBeforeWrittenTemps (in category 'code generation \
(closures)') -----  nilReadBeforeWrittenTemps
  	| visitor readBeforeWritten |
+ 	temporaries isEmpty ifTrue:
+ 		[^self].
  	self accept: (visitor := OptimizedBlockLocalTempReadBeforeWrittenVisitor new).
  	readBeforeWritten := visitor readBeforeWritten.
  	temporaries reverseDo:
  		[:temp|
  		((readBeforeWritten includes: temp)
  		 and: [temp isRemote not]) ifTrue:
  			[statements addFirst: (AssignmentNode new variable: temp value: NodeNil)]]!

Item was changed:
  ----- Method: BytecodeEncoder class>>extensionsFor:in:into: (in category \
'instruction stream support') -----  extensionsFor: pc in: aCompiledMethod into: \
trinaryBlock  "If the bytecode at pc is an extension, or if the bytecode at pc is \
preceeded by extensions,  then evaluate aTrinaryBlock with the values of extA and \
extB and number of extension *bytes*.  If the bytecode at pc is neither an extension \
or extended then evaluate with 0, 0, 0." +  
+ 	| prevPC |
+ 	"If there is what appears to be an extension bytecode before this bytecode
+ 	 then scan for the previous pc to confirm."
+ 	(pc - 2 >= aCompiledMethod initialPC
+ 	 and: [self isExtension: (aCompiledMethod at: pc - 2)]) ifTrue:
+ 		[prevPC := aCompiledMethod pcPreviousTo: pc.
+ 		 (self nonExtensionPcAt: prevPC in: aCompiledMethod) = pc ifTrue:
+ 			[^self extensionsAt: prevPC in: aCompiledMethod into: trinaryBlock]].
+ 	^self extensionsAt: pc in: aCompiledMethod into: trinaryBlock!
- 
- 	self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder class>>nonExtensionPcAt:in: (in category 'instruction \
stream support') ----- + nonExtensionPcAt: pc in: method
+ 	"Answer the pc of the actual bytecode at pc in method, skipping past any \
preceeding extensions." + 	| thePC bytecode |
+ 	thePC := pc.
+ 	[self isExtension: (bytecode := method at: thePC)] whileTrue:
+ 		[thePC := thePC + (self bytecodeSize: bytecode)].
+ 	^thePC!

Item was removed:
- ----- Method: BytecodeEncoder>>generateMethodOfClass:trailer:from: (in category \
                'method generation') -----
- generateMethodOfClass: aCompiledMethodClass trailer: trailer from: methodNode
- 	"methodNode is the root of a parse tree. Answer an instance of \
                aCompiledMethodClass
- 	 in the receiver's bytecode set and using the receiver's method header format.
- 	 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."
- 
- 	self subclassResponsibility!

Item was changed:
  ----- Method: Decompiler>>blockTo: (in category 'control') -----
  blockTo: end
  	"Decompile a range of code as in statementsTo:, but return a block node."
+ 	| exprs block oldBase lastStatementOfBlockIsNil |
- 	| exprs block oldBase |
  	oldBase := blockStackBase.
  	blockStackBase := stack size.
  	exprs := self statementsTo: end.
+ 	lastStatementOfBlockIsNil := pc < method endPC and: [exprs notEmpty and: [exprs \
last == (constTable at: 4)]]. + 	lastStatementOfBlockIsNil ifTrue:
+ 		[exprs := exprs allButLast].
  	block := constructor codeBlock: exprs returns: lastReturnPc = lastPc.
  	blockStackBase := oldBase.
  	lastReturnPc := -1.  "So as not to mislead outer calls"
  	^block!

Item was changed:
  ----- Method: Encoder>>bindTemp: (in category 'temps') -----
  bindTemp: name 
  	"Declare a temporary; error not if a field or class variable."
  	scopeTable at: name ifPresent:[:node|
  		"When non-interactive raise the error only if its a duplicate"
+ 		node isTemp
+ 			ifTrue:[^self notify:'Name already used in this method']
- 		(node isTemp)
- 			ifTrue:[^self notify:'Name is already defined']
  			ifFalse:[self warnAboutShadowed: name]].
  	^self reallyBind: name!

Item was removed:
- ----- Method: EncoderForV3>>generateMethodOfClass:trailer:from: (in category \
                'method generation') -----
- 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 literals header method stack |
- 	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
- 						[self fixTemp: methodNode primitiveErrorVariableName].
- 	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
- 				+ (primErrNode
- 					ifNil: [0]
- 					ifNotNil: [primErrNode sizeCodeForStore: self "The VM relies on storeIntoTemp: \
                (129)"]).
- 	header := self computeMethodHeaderForNumArgs: methodNode arguments size
- 					numTemps: self maxTemp
- 					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)].
- 	self streamToMethod: method.
- 	stack := ParseStack new init.
- 	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 CompiledMethod \
                class>>#new:"
- 			ex signalerContext sender method = (CompiledMethod class>>#new:)
- 				ifTrue: [^self error: 'Compiler code size discrepancy']
- 				ifFalse: [ex pass]].
- 	stack position ~= (method numTemps + 1) ifTrue:
- 		[^self error: 'Compiler stack discrepancy'].
- 	self methodStreamPosition ~= (method size - trailer size) ifTrue:
- 		[^self error: 'Compiler code size discrepancy'].
- 	method needsFrameSize: stack size - method numTemps.
- 	^method!

Item was removed:
- ----- Method: EncoderForV3PlusClosures>>generateMethodOfClass:trailer:from: (in \
                category 'method generation') -----
- 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)
- 				+ (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)].
- 	self streamToMethod: method.
- 	stack := ParseStack new init.
- 	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 CompiledMethod \
                class>>#new:"
- 			ex signalerContext sender method = (CompiledMethod class>>#new:)
- 				ifTrue: [^self error: 'Compiler code size discrepancy']
- 				ifFalse: [ex pass]].
- 	stack position ~= (method numTemps + 1) ifTrue:
- 		[^self error: 'Compiler stack discrepancy'].
- 	self methodStreamPosition ~= (method size - trailer size) ifTrue:
- 		[^self error: 'Compiler code size discrepancy'].
- 	method needsFrameSize: stack size - method numTemps.
- 	^method!

Item was added:
+ ----- Method: Scanner>>typedScan:do: (in category 'public access') -----
+ typedScan: textOrString do: aBinaryBlock
+ 	"Evaluate aBinaryBlock with the token and its type for the first token in input,
+ 	 mapping literals to type #literal and anything else to type #word."
+ 	| theTokensType atNumber theToken |
+ 	self initScannerForTokenization.
+ 	self scan: (ReadStream on: textOrString asString).
+ 	atNumber := hereChar notNil and: [hereChar isDigit].
+ 	theTokensType := tokenType.
+ 	theToken := self advance.
+ 	(theToken == #- and: [atNumber and: [token isNumber]]) ifTrue:
+ 		[theToken := self advance negated].
+ 	theToken isNumber ifTrue: [theTokensType := #number].
+ 	^aBinaryBlock
+ 		value: theToken
+ 		value: ((#(number string literal) includes: theTokensType)
+ 				ifTrue: [#literal]
+ 				ifFalse: [#word])!


[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic