Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.371.mcz ==================== Summary ==================== Name: Compiler-eem.371 Author: eem Time: 11 January 2018, 9:04:32.236416 am UUID: 36ba34e7-1d85-4f34-8f83-9f161918c3b2 Ancestors: Compiler-eem.370 Implement source mapping for full blocks; to this end: Have the pc in a node belonging to a full block be an association from the block method to the pc within it. Add a blockMethod inst var to BytecodeEncoder to hold the currently generated block method and have nodes access their pc via BytecodeEncoder>>pc & nextPC. Introduce startKeys instead of startPcs, to generalize to full blocks and embedded blocks. Refactor full block method generation a little to avoid unnecessary non-self sends. Have LiteralNode print a block, not storeString it, for readability. =============== Diff against Compiler-eem.370 =============== Item was changed: ----- Method: AssignmentNode>>emitCodeForEffect:encoder: (in category 'code generation') ----- emitCodeForEffect: stack encoder: encoder variable emitCodeForLoad: stack forValue: false encoder: encoder. value emitCodeForValue: stack encoder: encoder. + pc := encoder nextPC. "debug pc is first byte of the store, i.e. the next byte". - pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte". variable emitCodeForStorePop: stack encoder: encoder! Item was changed: ----- Method: AssignmentNode>>emitCodeForValue:encoder: (in category 'code generation') ----- emitCodeForValue: stack encoder: encoder variable emitCodeForLoad: stack forValue: true encoder: encoder. value emitCodeForValue: stack encoder: encoder. + pc := encoder nextPC. "debug pc is first byte of the store, i.e. the next byte". - pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte". variable emitCodeForStore: stack encoder: encoder! Item was changed: ----- Method: BlockNode>>createBlockLiteral: (in category 'code generation') ----- createBlockLiteral: encoder ^self + reindexingLocalsDo: [encoder blockLiteralFor: self] - reindexingLocalsDo: - [encoder reindexingLiteralsDo: - [encoder copyWithNewLiterals - generateBlockMethodOfClass: CompiledBlock - trailer: CompiledMethodTrailer empty - from: self]] encoder: encoder! Item was changed: ----- Method: BlockNode>>emitCodeForEvaluatedClosureValue:encoder: (in category 'code generation') ----- emitCodeForEvaluatedClosureValue: stack encoder: encoder | position | position := stack position. stack position: arguments size + temporaries size + copiedValues size. encoder genPushNClosureTemps: temporaries size. self reindexingLocalsDo: [self emitCodeForEvaluatedValue: stack encoder: encoder] encoder: encoder. self returns ifFalse: [encoder genReturnTopToCaller. + pc := encoder pc]. - pc := encoder methodStreamPosition]. stack position: position! Item was changed: ----- Method: BlockNode>>emitCodeForEvaluatedFullClosureValue:encoder: (in category 'code generation') ----- emitCodeForEvaluatedFullClosureValue: stack encoder: encoder | position | position := stack position. self emitCodeExceptLast: stack encoder: encoder. (statements last == NodeNil and: [self returns not]) ifTrue: [stack push: 1. encoder genReturnNilToCaller. + pc := encoder pc] - pc := encoder methodStreamPosition] ifFalse: [statements last emitCodeForBlockValue: stack encoder: encoder. self returns ifFalse: [encoder genReturnTopToCaller. + pc := encoder pc]]. - pc := encoder methodStreamPosition]]. self assert: stack position - 1 = position! Item was changed: ----- Method: BlockNode>>emitCodeForValue:encoder: (in category 'code generation') ----- emitCodeForValue: stack encoder: encoder encoder supportsFullBlocks ifTrue: [^self emitCodeForFullBlockValue: stack encoder: encoder]. copiedValues do: [:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder]. + closureCreationNode pc: encoder nextPC. - closureCreationNode pc: encoder methodStreamPosition + 1. encoder genPushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size. stack pop: copiedValues size; push: 1. "Emit the body of the block" self emitCodeForEvaluatedClosureValue: stack encoder: encoder! Item was changed: Encoder subclass: #BytecodeEncoder + instanceVariableNames: 'stream position rootNode blockExtentsToLocals blockMethod' - instanceVariableNames: 'stream position rootNode blockExtentsToLocals' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! + !BytecodeEncoder commentStamp: 'eem 1/10/2018 17:28' prior: 0! + I am an abstract superclass for different bytecode set encoders. Subclasses inherit the literal management of Encoder and encapsulate the mapping of opcodes to specific bytecodes. + + Instance Variables + blockExtentsToLocals: <Dictionary from: Interval to: (Array of: String)> + blockMethod: <CompiledBlock> + position: <Integer> + rootNode: <MethodNode> + stream: <WriteStream | BytecodeEncoder> + + blockExtentsToLocals + - is a map from block extent to the sequence of temps defined in the block with that extent + + blockMethod + - the compiled block being generated in generateBlockMethodOfClass:trailer:from: + + position + - used to size bytecodes by having the receiver masquerade as a stream during sizeOpcodeSelector:withArguments: + + rootNode + - the MethodNode for the method being generated + + stream + - during bytecode sizing this is the receiver. During bytecode generation this is the WriteStream on the method! - !BytecodeEncoder commentStamp: '<historical>' prior: 0! - I am an abstract superclass for different bytecode set encoders. Subclasses inherit the literal management of Encoder and encapsulate the mapping of opcodes to specific bytecodes.! Item was added: + ----- Method: BytecodeEncoder class>>supportsFullBlocks (in category 'testing') ----- + supportsFullBlocks + "Answer if the instruction set supports full closures (closure creation from + specfic methods instead of bytecodes embedded in an outer home method)." + + ^self basicNew supportsFullBlocks! Item was added: + ----- Method: BytecodeEncoder>>blockLiteralFor: (in category 'full blocks') ----- + blockLiteralFor: aBlockNode + "Answer a new CompiledBlock for the code in aBlockNode" + ^self reindexingLiteralsDo: + [self shallowCopy resetForFullBlockGeneration + generateBlockMethodOfClass: CompiledBlock + trailer: CompiledMethodTrailer empty + from: aBlockNode]! Item was removed: - ----- Method: BytecodeEncoder>>copyWithNewLiterals (in category 'full blocks') ----- - copyWithNewLiterals - ^self shallowCopy resetLiteralStreamForFullBlock! Item was changed: ----- 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 allLiterals) 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 methodStreamPosition ~= (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 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 methodStreamPosition ~= (method size - trailer size) ifTrue: [^self error: 'Compiler code size discrepancy']. method needsFrameSize: stack size - method numTemps. ^method! Item was added: + ----- Method: BytecodeEncoder>>nextPC (in category 'accessing') ----- + nextPC + "Answer the pc to store in a node for source range identification when the node is associated with its following pc." + ^blockMethod + ifNil: [stream position + 1] + ifNotNil: [:proxy| proxy -> (stream position + 1)]! Item was added: + ----- Method: BytecodeEncoder>>pc (in category 'accessing') ----- + pc + "Answer the pc to store in a node for source range identification." + ^blockMethod + ifNil: [stream position] + ifNotNil: [:proxy| proxy -> (stream position)]! Item was added: + ----- Method: BytecodeEncoder>>resetForFullBlockGeneration (in category 'code generation') ----- + resetForFullBlockGeneration + literalStream := WriteStream on: (Array new: 8). + addedSelectorAndMethodClassLiterals := false. + optimizedSelectors := Set new! Item was changed: ----- Method: BytecodeEncoder>>supportsFullBlocks (in category 'testing') ----- supportsFullBlocks "Answer if the instruction set supports full closures (closure creation from specfic methods instead of bytecodes embedded in an outer home method)." + - ^self subclassResponsibility! Item was added: + ----- Method: CompiledBlock>>startKeysToBlockExtents (in category '*Compiler-support') ----- + startKeysToBlockExtents + ^self homeMethod startKeysToBlockExtents! Item was added: + ----- Method: CompiledBlock>>startpcsToBlockExtents (in category '*Compiler-support') ----- + startpcsToBlockExtents + ^self outerCode startpcsToBlockExtents! Item was added: + ----- Method: CompiledMethod>>blockExtentsInto:from:to:method:numberer: (in category '*Compiler-support') ----- + blockExtentsInto: aDictionary from: initialPC to: endPC method: method numberer: numbererBlock + "Support routine for startpcsToBlockExtents" + | pcs extentStart locator scanner blockSizeOrMethodOrLocator | + self flag: 'belongs in DebuggerMethodMap'. + extentStart := numbererBlock value. + locator := BlockStartLocator new. + scanner := InstructionStream new method: method pc: initialPC. + pcs := OrderedCollection new. + [pcs addLast: scanner pc. + scanner pc <= endPC] whileTrue: + [blockSizeOrMethodOrLocator := scanner interpretNextInstructionFor: locator. + blockSizeOrMethodOrLocator ~~ locator ifTrue: + [blockSizeOrMethodOrLocator isInteger + ifTrue: + [self + blockExtentsInto: aDictionary + from: scanner pc + to: scanner pc + blockSizeOrMethodOrLocator - 1 + method: method + numberer: numbererBlock. + scanner pc: scanner pc + blockSizeOrMethodOrLocator] + ifFalse: + [self assert: blockSizeOrMethodOrLocator isCompiledBlock. + self + blockExtentsInto: aDictionary + from: blockSizeOrMethodOrLocator initialPC + to: blockSizeOrMethodOrLocator endPC + method: blockSizeOrMethodOrLocator + numberer: numbererBlock]]]. + aDictionary + at: (method isCompiledBlock + ifTrue: [method] + ifFalse: [initialPC]) + put: (extentStart to: numbererBlock value). + ^aDictionary! Item was added: + ----- Method: CompiledMethod>>mapFromBlockKeys:toSchematicTemps: (in category '*Compiler-support') ----- + mapFromBlockKeys: keys toSchematicTemps: schematicTempNamesString + "Decode a schematicTempNamesString that encodes the layout of temp names + in a method and any closures/blocks within it, matching keys in keys to + vectors of temp names." + | map tempNames | + map := Dictionary new. + tempNames := schematicTempNamesString readStream. + keys do: + [:key| | tempSequence tempIndex | + tempSequence := OrderedCollection new. + tempIndex := 0. + [(tempNames skipSeparators; peek) ifNil: [true] ifNotNil: [:ch| '[]' includes: ch]] whileFalse: + [tempNames peek = $( + ifTrue: [tempSequence addAllLast: ((self tempsSubSequenceFrom: (tempNames next; yourself)) withIndexCollect: + [:temp :index| + { temp. { tempIndex + 1. index } }]). + tempNames peek ~= $) ifTrue: [self error: 'parse error']. + tempIndex := tempIndex + 1. + tempNames next] + ifFalse: [tempSequence addAllLast: ((self tempsSubSequenceFrom: tempNames) withIndexCollect: + [:temp :index| + { temp. tempIndex := tempIndex + 1 }])]]. + map at: key put: tempSequence asArray. + [tempNames peek = $]] whileTrue: [tempNames next]. + tempNames peek = $[ ifTrue: + [tempNames next]]. + ^map! Item was added: + ----- Method: CompiledMethod>>startKeysToBlockExtents (in category '*Compiler-support') ----- + startKeysToBlockExtents + "Answer a Dictionary of start key to Interval of blockExtent, using the + identical numbering scheme described in and orchestrated by + BlockNode>>analyseArguments:temporaries:rootNode:. A start key + identifies a block within a method and is either the startpc for an + embedded block or the block method itself for a full block. This is + used in part to find the temp names for any block in a method, as + needed by the debugger. The other half is to recompile the method, + obtaining the temp names for each block extent. By indirecting through + the blockExtent instead of using the startpc directly we decouple the + debugger's access to temp names from the exact bytecode; insulating + debugging from minor changes in the compiler (e.g. changes in literal + pooling, adding prefix bytecodes, adding inst vars to CompiledMethod + in literals towards the end of the literal frame, etc). If the recompilation + doesn't produce exactly the same bytecode at exactly the same offset + no matter; the blockExtents will be the same." + | index | + self flag: 'belongs in DebuggerMethodMap'. + index := 0. + ^self + blockExtentsInto: Dictionary new + from: self initialPC + to: self endPC + method: self + numberer: [| value | value := index. index := index + 2. value]! Item was changed: ----- Method: Decompiler>>initSymbols: (in category 'initialize-release') ----- initSymbols: aClass constructor method: method class: aClass literals: method literals. constTable := constructor codeConstants. instVars := Array new: aClass instSize. tempVarCount := method numTemps. "(tempVars isNil and: [method holdsTempNames]) ifTrue: [tempVars := method tempNamesString]." tempVars isString ifTrue: + [blockStartsToTempVars := self mapFromBlockKeysIn: method - [blockStartsToTempVars := self mapFromBlockStartsIn: method toTempVarsFrom: tempVars constructor: constructor. tempVars := blockStartsToTempVars at: method initialPC] ifFalse: [| namedTemps | namedTemps := tempVars ifNil: [(1 to: tempVarCount) collect: [:i| 't', i printString]]. tempVars := (1 to: tempVarCount) collect: [:i | i <= namedTemps size ifTrue: [constructor codeTemp: i - 1 named: (namedTemps at: i)] ifFalse: [constructor codeTemp: i - 1]]]. 1 to: method numArgs do: [:i| (tempVars at: i) beMethodArg]. tempReadCounts := Dictionary new! Item was added: + ----- Method: Decompiler>>mapFromBlockKeysIn:toTempVarsFrom:constructor: (in category 'initialize-release') ----- + mapFromBlockKeysIn: aMethod toTempVarsFrom: schematicTempNamesString constructor: aDecompilerConstructor + | map | + map := aMethod + mapFromBlockKeys: aMethod startKeysToBlockExtents keys asArray sort + toSchematicTemps: schematicTempNamesString. + map keysAndValuesDo: + [:startKey :tempNameTupleVector| + tempNameTupleVector isEmpty ifFalse: + [| subMap numTemps tempVector | + subMap := Dictionary new. + "Find how many temp slots there are (direct & indirect temp vectors) + and for each indirect temp vector find how big it is." + tempNameTupleVector do: + [:tuple| + tuple last isArray + ifTrue: + [subMap at: tuple last first put: tuple last last. + numTemps := tuple last first] + ifFalse: + [numTemps := tuple last]]. + "create the temp vector for this scope level." + tempVector := Array new: numTemps. + "fill it in with any indirect temp vectors" + subMap keysAndValuesDo: + [:index :size| + tempVector at: index put: (Array new: size)]. + "fill it in with temp nodes." + tempNameTupleVector do: + [:tuple| | itv | + tuple last isArray + ifTrue: + [itv := tempVector at: tuple last first. + itv at: tuple last last + put: (aDecompilerConstructor + codeTemp: tuple last last - 1 + named: tuple first)] + ifFalse: + [tempVector + at: tuple last + put: (aDecompilerConstructor + codeTemp: tuple last - 1 + named: tuple first)]]. + "replace any indirect temp vectors with proper RemoteTempVectorNodes" + subMap keysAndValuesDo: + [:index :size| + tempVector + at: index + put: (aDecompilerConstructor + codeRemoteTemp: index + remoteTemps: (tempVector at: index))]. + "and update the entry in the map" + map at: startKey put: tempVector]]. + ^map! Item was removed: - ----- Method: Decompiler>>mapFromBlockStartsIn:toTempVarsFrom:constructor: (in category 'initialize-release') ----- - mapFromBlockStartsIn: aMethod toTempVarsFrom: schematicTempNamesString constructor: aDecompilerConstructor - | map | - map := aMethod - mapFromBlockKeys: aMethod startpcsToBlockExtents keys asArray sort - toSchematicTemps: schematicTempNamesString. - map keysAndValuesDo: - [:startpc :tempNameTupleVector| - tempNameTupleVector isEmpty ifFalse: - [| subMap numTemps tempVector | - subMap := Dictionary new. - "Find how many temp slots there are (direct & indirect temp vectors) - and for each indirect temp vector find how big it is." - tempNameTupleVector do: - [:tuple| - tuple last isArray - ifTrue: - [subMap at: tuple last first put: tuple last last. - numTemps := tuple last first] - ifFalse: - [numTemps := tuple last]]. - "create the temp vector for this scope level." - tempVector := Array new: numTemps. - "fill it in with any indirect temp vectors" - subMap keysAndValuesDo: - [:index :size| - tempVector at: index put: (Array new: size)]. - "fill it in with temp nodes." - tempNameTupleVector do: - [:tuple| | itv | - tuple last isArray - ifTrue: - [itv := tempVector at: tuple last first. - itv at: tuple last last - put: (aDecompilerConstructor - codeTemp: tuple last last - 1 - named: tuple first)] - ifFalse: - [tempVector - at: tuple last - put: (aDecompilerConstructor - codeTemp: tuple last - 1 - named: tuple first)]]. - "replace any indirect temp vectors with proper RemoteTempVectorNodes" - subMap keysAndValuesDo: - [:index :size| - tempVector - at: index - put: (aDecompilerConstructor - codeRemoteTemp: index - remoteTemps: (tempVector at: index))]. - "and update the entry in the map" - map at: startpc put: tempVector]]. - ^map! Item was changed: ----- Method: EncoderForSistaV1>>supportsFullBlocks (in category 'testing') ----- supportsFullBlocks "Answer if the instruction set supports full closures (closure creation from specfic methods instead of bytecodes embedded in an outer home method)." + - ^true! Item was changed: ----- Method: LiteralNode>>printOn:indent: (in category 'printing') ----- printOn: aStream indent: level key isVariableBinding ifTrue: [key key isNil ifTrue: [aStream nextPutAll: '###'; nextPutAll: key value soleInstance name] ifFalse: [aStream nextPutAll: '##'; nextPutAll: key key]. ^self]. key isLiteral ifTrue: [key printAsLiteralOn: aStream. ^self]. + (key isCompiledCode and: [key isCompiledBlock]) ifTrue: + [key printOn: aStream. + ^self]. key storeOn: aStream! Item was changed: ----- Method: MessageNode>>emitCodeForIf:encoder:value: (in category 'code generation') ----- emitCodeForIf: stack encoder: encoder value: forValue | thenExpr thenSize elseExpr elseSize | thenSize := sizes at: 1. elseSize := sizes at: 2. thenExpr := arguments at: 1. elseExpr := arguments at: 2. receiver emitCodeForValue: stack encoder: encoder. elseSize * thenSize > 0 ifTrue: "Code for two-armed" [self emitCodeForBranchOn: false dist: thenSize pop: stack encoder: encoder. + pc := encoder pc. - pc := encoder methodStreamPosition. thenExpr emitCodeForEvaluatedValue: stack encoder: encoder. stack pop: 1. "then and else alternate; they don't accumulate" thenExpr returns ifFalse: "Elide jump over else after a return" [self emitCodeForJump: elseSize encoder: encoder]. elseExpr emitCodeForEvaluatedValue: stack encoder: encoder. forValue ifFalse: ["Two-armed IFs forEffect share a single pop - except if both return" (arguments allSatisfy: #returns) ifFalse: [encoder genPop]. stack pop: 1]] ifFalse: "One arm is empty here (this can only ever be for effect)" [thenSize > 0 ifTrue: [self emitCodeForBranchOn: false dist: thenSize pop: stack encoder: encoder. + pc := encoder pc. - pc := encoder methodStreamPosition. thenExpr emitCodeForEvaluatedEffect: stack encoder: encoder] ifFalse: [self emitCodeForBranchOn: true dist: elseSize pop: stack encoder: encoder. + pc := encoder pc. - pc := encoder methodStreamPosition. elseExpr emitCodeForEvaluatedEffect: stack encoder: encoder]]! Item was changed: ----- Method: MessageNode>>emitCodeForIfNil:encoder:value: (in category 'code generation') ----- emitCodeForIfNil: stack encoder: encoder value: forValue | theNode theSize ifNotNilSelector | theNode := arguments first. theSize := sizes at: 1. ifNotNilSelector := #ifNotNil:. receiver emitCodeForValue: stack encoder: encoder. forValue ifTrue: [encoder genDup. stack push: 1]. encoder genPushSpecialLiteral: nil. stack push: 1. equalNode emitCode: stack args: 1 encoder: encoder. self emitCodeForBranchOn: (selector key == ifNotNilSelector) dist: theSize pop: stack encoder: encoder. + pc := encoder pc. - pc := encoder methodStreamPosition. forValue ifTrue: [encoder genPop. stack pop: 1. theNode emitCodeForEvaluatedValue: stack encoder: encoder] ifFalse: [theNode emitCodeForEvaluatedEffect: stack encoder: encoder]! Item was changed: ----- Method: MessageNode>>emitCodeForToDo:encoder:value: (in category 'code generation') ----- emitCodeForToDo: stack encoder: encoder value: forValue " var := rcvr. L1: [var <= arg1] Bfp(L2) [block body. var := var + inc] Jmp(L1) L2: " | loopSize initStmt limitInit test block incStmt blockSize | initStmt := arguments at: 4. limitInit := arguments at: 7. test := arguments at: 5. block := arguments at: 3. incStmt := arguments at: 6. blockSize := sizes at: 1. loopSize := sizes at: 2. "This will return the receiver of to:do: which is the initial value of the loop" forValue ifTrue: [initStmt emitCodeForValue: stack encoder: encoder] ifFalse: [initStmt emitCodeForEffect: stack encoder: encoder]. limitInit ifNotNil: [limitInit emitCodeForEffect: stack encoder: encoder]. test emitCodeForValue: stack encoder: encoder. self emitCodeForBranchOn: false dist: blockSize pop: stack encoder: encoder. + pc := encoder pc. - pc := encoder methodStreamPosition. block emitCodeForEvaluatedEffect: stack encoder: encoder. incStmt emitCodeForEffect: stack encoder: encoder. self emitCodeForJump: 0 - loopSize encoder: encoder! Item was changed: ----- Method: MessageNode>>emitCodeForValue:encoder: (in category 'code generation') ----- emitCodeForValue: stack encoder: encoder "For #ifTrue:ifFalse: and #whileTrue: / #whileFalse: style messages, the pc is set to the jump instruction, so that mustBeBoolean exceptions can be shown correctly." special > 0 ifTrue: [pc := 0. self perform: (MacroEmitters at: special) with: stack with: encoder with: true] ifFalse: [receiver ~~ nil ifTrue: [receiver emitCodeForValue: stack encoder: encoder]. arguments do: [:argument | argument emitCodeForValue: stack encoder: encoder]. + pc := encoder nextPC. "debug pc is first byte of the send, i.e. the next byte". - pc := encoder methodStreamPosition + 1. "debug pc is first byte of the send, i.e. the next byte". selector emitCode: stack args: arguments size encoder: encoder super: receiver == NodeSuper]! Item was changed: ----- Method: MessageNode>>emitCodeForWhile:encoder:value: (in category 'code generation') ----- emitCodeForWhile: stack encoder: encoder value: forValue "L1: ... Bfp(L2)|Btp(L2) ... Jmp(L1) L2: " | cond stmt stmtSize loopSize | cond := receiver. stmt := arguments at: 1. stmtSize := sizes at: 1. loopSize := sizes at: 2. cond emitCodeForEvaluatedValue: stack encoder: encoder. self emitCodeForBranchOn: (selector key == #whileFalse:) "Bfp for whileTrue" dist: stmtSize pop: stack encoder: encoder. "Btp for whileFalse" + pc := encoder pc. - pc := encoder methodStreamPosition. stmt emitCodeForEvaluatedEffect: stack encoder: encoder. self emitCodeForJump: 0 - loopSize encoder: encoder. forValue ifTrue: [encoder genPushSpecialLiteral: nil. stack push: 1]! Item was changed: ----- Method: ReturnNode>>emitCodeForReturn:encoder: (in category 'code generation') ----- emitCodeForReturn: stack encoder: encoder expr emitCodeForReturn: stack encoder: encoder. + pc := encoder pc! - pc := encoder methodStreamPosition! Item was changed: ----- Method: ReturnNode>>emitCodeForValue:encoder: (in category 'code generation') ----- emitCodeForValue: stack encoder: encoder expr emitCodeForReturn: stack encoder: encoder. + pc := encoder pc! - pc := encoder methodStreamPosition! |
Free forum by Nabble | Edit this page |