Eliot Miranda uploaded a new version of VMMakerCompatibilityForPharo6 to project VM Maker: http://source.squeak.org/VMMaker/VMMakerCompatibilityForPharo6-eem.4.mcz ==================== Summary ==================== Name: VMMakerCompatibilityForPharo6-eem.4 Author: eem Time: 17 August 2018, 7:20:11.114764 pm UUID: 0d8c7b0d-0e30-0d00-adaa-684a0e5da6b0 Ancestors: VMMakerCompatibilityForPharo6-EliotMiranda.3 Stream compatibility methods for ThreadSafeTranscript which I shouldmn;'t have to implement (it's supposed to be a WriteStream). Initial support for Slang TMehtod creation from RBProgramNodes. =============== Diff against VMMakerCompatibilityForPharo6-EliotMiranda.3 =============== Item was added: + ----- Method: RBAssignmentNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + | varNode valueNode | + varNode := variable asTranslatorNodeIn: aTMethod. + valueNode := value asTranslatorNodeIn: aTMethod. + valueNode isStmtList ifFalse: + [^TAssignmentNode new + setVariable: varNode + expression: valueNode; + comment: comment]. + "This is a super expansion. We are in trouble if any statement other than the last is a return." + (self anyReturns: valueNode statements allButLast) ifTrue: + [self error: 'haven''t implemented pushing down assignments into other than the last return']. + "As of 6/25/2012 19:30 superExpansionNodeFor:args: elides the final return." + self assert: valueNode statements last isReturn not. + ^TStmtListNode new + setStatements: valueNode statements allButLast, + { TAssignmentNode new + setVariable: varNode + expression: valueNode statements last; + comment: comment }; + yourself! Item was added: + ----- Method: RBBlockNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + | statementList | + statementList := OrderedCollection new. + body statements do: + [:s | | newS | + newS := s asTranslatorNodeIn: aTMethod. + "inline the statement list returned when a CascadeNode is translated and/or when ifNotNil: is transformed" + newS isStmtList + ifTrue: [statementList addAll: newS statements] + ifFalse: [statementList add: newS]]. + ^TStmtListNode new + setArguments: (arguments asArray collect: [:arg | arg key]) + statements: statementList; + comment: self missingCommentNeededForCTranslation! Item was added: + ----- Method: RBBlockNode>>isBlockNode (in category '*VMMakerCompatibilityForPharo6-testing') ----- + isBlockNode + ^true! Item was added: + ----- Method: RBCascadeNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me." + ^TStmtListNode new + setArguments: #() + statements: + (Array streamContents: + [:s| | receiverNode | + receiverNode := receiver asTranslatorNodeIn: aTMethod. + "don't expand the receiver if it is a send to get an implicit receiver, + e.g self interpreter printHex: oop => printHex(oop), /not/ printHex(cascade0,oop)." + (receiverNode isSend and: [aTMethod definingClass isNonArgumentImplicitReceiverVariableName: receiverNode selector]) ifTrue: + [receiverNode := TVariableNode new setName: receiverNode selector]. + receiverNode isLeaf ifFalse: + [| varNode | + varNode := aTMethod newCascadeTempFor: receiverNode. + s nextPut: (TAssignmentNode new + setVariable: varNode + expression: receiverNode). + receiverNode := varNode]. + messages do: + [ :msg | s nextPut: ((msg asTranslatorNodeIn: aTMethod) receiver: receiverNode)]]); + comment: comment! Item was added: + ----- Method: RBLiteralNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + + ^TConstantNode new setValue: key! Item was added: + ----- Method: RBMessageNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + "selector is sometimes a Symbol, sometimes a SelectorNode!! + On top of this, numArgs is needed due to the (truly grody) use of + arguments as a place to store the extra expressions needed to generate + code for in-line to:by:do:, etc. see below, where it is used. + + Expand super nodes in place. Elide sends of halt so that halts can be + sprinkled through the simulator but will be eliminated from the generated C." + | rcvrOrNil sel args ifNotNilBlock | + rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod]. + (rcvrOrNil notNil + and: [rcvrOrNil isVariable + and: [rcvrOrNil name = 'super']]) ifTrue: + [^aTMethod superExpansionNodeFor: selector key args: arguments]. + sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key]. + sel == #halt ifTrue: [^rcvrOrNil]. + (sel == #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block." + or: [sel == #cCode:]) ifTrue: + [arguments first isBlockNode ifTrue: + [| block | + ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1 + ifTrue: [block statements first] + ifFalse: [block]]. + (arguments first isLiteralNode + and: [arguments first key isString + and: [arguments first key isEmpty]]) ifTrue: + [^arguments first asTranslatorNodeIn: aTMethod]]. + args := arguments + select: [:arg| arg notNil] + thenCollect: [:arg| arg asTranslatorNodeIn: aTMethod]. + (sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue: + ["Restore limit expr that got moved by transformToDo:" + args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. + args second. + args third. "add the limit var as a hidden extra argument; we may need it later" + TVariableNode new setName: arguments first key}]. + (sel == #ifTrue:ifFalse: and: [arguments first isJust: NodeNil]) ifTrue: + [sel := #ifFalse:. args := {args last}]. + (sel == #ifTrue:ifFalse: and: [arguments last isJust: NodeNil]) ifTrue: + [sel := #ifTrue:. args := {args first}]. + (sel == #ifFalse:ifTrue: and: [arguments first isJust: NodeNil]) ifTrue: + [sel := #ifTrue:. args := {args last}]. + (sel == #ifFalse:ifTrue: and: [arguments last isJust: NodeNil]) ifTrue: + [sel := #ifTrue:. args := {args first}]. + ((sel == #ifFalse: or: [sel == #or:]) + and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue: + ["Restore argument block that got moved by transformOr: or transformIfFalse:" + args := {(arguments at: 2) asTranslatorNodeIn: aTMethod}]. + (args size > sel numArgs and: [sel ~~ #to:by:do:]) ifTrue: "to:by:do: has iLimiT hidden in last arg" + ["prune the extra blocks left by ifTrue:, ifFalse:, and: & or:" + self assert: args size - sel numArgs = 1. + self assert: (args last isStmtList + and: [args last statements size = 1 + and: [(args last statements first isVariable + or: [args last statements first isConstant]) + and: [#('nil' true false) includes: args last statements first nameOrValue]]]). + args := args first: sel numArgs]. + "For the benefit of later passes, e.g. value: inlining, + transform e ifNotNil: [:v| ...] into v := e. v ifNotNil: [...], + which in fact means transforming (v := e) ifTrue: [:v|...] into v := e. v ifTrue: [...]." + ((sel == #ifTrue: or: [sel == #ifFalse: or: [sel == #ifTrue:ifFalse: or: [sel == #ifFalse:ifTrue:]]]) + and: [receiver notNil + and: [receiver isAssignmentEqualsEqualsNil + and: [(ifNotNilBlock := args detect: [:arg| arg isStmtList and: [arg args size = 1]] ifNone: []) notNil]]]) ifTrue: + [ifNotNilBlock setArguments: #(). + ^TStmtListNode new + setArguments: #() + statements: + { receiver receiver asTranslatorNodeIn: aTMethod. + TSendNode new + setSelector: sel + receiver: (TSendNode new + setSelector: #== + receiver: (receiver receiver variable asTranslatorNodeIn: aTMethod) + arguments: {receiver arguments first asTranslatorNodeIn: aTMethod}) + arguments: args }]. + ((CCodeGenerator isVarargsSelector: sel) + and: [args last isCollection + and: [args last isSequenceable]]) ifTrue: + [args := args allButLast, args last]. + ^TSendNode new + setSelector: sel + receiver: rcvrOrNil + arguments: args! Item was added: + ----- Method: RBMethodNode>>asTranslationMethodOfClass: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslationMethodOfClass: aTMethodClass + "Answer a TMethod (or subclass) derived from the receiver." + ^aTMethodClass new + setSelector: selector + definingClass: scope instanceScope outerScope class + args: arguments + locals: ((self allDefinedVariables copyWithoutAll: arguments) collect: [:string| string -> string]) + block: body + primitive: ((pragmas ifNotNil: + [pragmas detect: [:pragmaNode| pragmaNode selector beginsWith: #primitve:] ifNone: []]) + ifNil: [0] + ifNotNil: [:pragmaNode| pragmaNode arguments first value]) + properties: (properties ifNil: [AdditionalMethodState new]) + comment: self missingCommentNeededForCTranslation! Item was added: + ----- Method: RBProgramNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + self subclassResponsibility! Item was added: + ----- Method: RBProgramNode>>isBlockNode (in category '*VMMakerCompatibilityForPharo6-testing') ----- + isBlockNode + ^false! Item was added: + ----- Method: RBProgramNode>>missingCommentNeededForCTranslation (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + missingCommentNeededForCTranslation + "So far the RBProgramNode hierarchy omits/elides comments :-(" + ^nil! Item was added: + ----- Method: RBReturnNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of a return." + | exprTranslation lastExpr | + exprTranslation := expr asTranslatorNodeIn: aTMethod. + (expr isMessage + and: [expr receiver isVariableNode + and: [expr receiver key = 'super' + and: [exprTranslation isStmtList]]]) ifTrue: + ["super expansions containing returns are fine, and (as of 6/25/2012 19:27) the last + return is elided from the expansion by TMethod>>superExpansionNodeFor:args:. + So we need to ensure the last expression is a return and simply reuse any other + returns in the expansion." + lastExpr := exprTranslation statements last. + (lastExpr isReturn + or: [lastExpr isReturningIf]) ifFalse: + [exprTranslation statements + at: exprTranslation statements size + put: + (TReturnNode new + setExpression: lastExpr; + comment: comment; + yourself)]. + ^exprTranslation]. + ^TReturnNode new + setExpression: exprTranslation; + comment: comment; + yourself! Item was added: + ----- Method: RBSequenceNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + | statementList | + statementList := OrderedCollection new. + statements do: + [:s | | newS | + newS := s asTranslatorNodeIn: aTMethod. + "inline the statement list returned when a CascadeNode is translated and/or when ifNotNil: is transformed" + newS isStmtList + ifTrue: [statementList addAll: newS statements] + ifFalse: [statementList add: newS]]. + ^TStmtListNode new + setArguments: (parent arguments asArray collect: [:arg | arg key]) + statements: statementList; + comment: self missingCommentNeededForCTranslation! Item was added: + ----- Method: RBVariableNode>>asTranslatorNodeIn: (in category '*VMMakerCompatibilityForPharo6-C translation') ----- + asTranslatorNodeIn: aTMethod + "Answer a TParseNode subclass equivalent of me" + name = 'true' ifTrue: [^ TConstantNode new setValue: true]. + name = 'false' ifTrue: [^ TConstantNode new setValue: false]. + ^ TVariableNode new setName: name! Item was added: + ----- Method: ThreadSafeTranscript>>crtab (in category '*VMMakerCompatibilityForPharo6-accessing') ----- + crtab + self critical: [stream crtab]! Item was added: + ----- Method: ThreadSafeTranscript>>ensureCr (in category '*VMMakerCompatibilityForPharo6-accessing') ----- + ensureCr + (stepContents notEmpty and: [stepContents last ~~ Character cr]) ifTrue: + [ self nextPut: Character cr]! Item was added: + ----- Method: ThreadSafeTranscript>>next:put: (in category '*VMMakerCompatibilityForPharo6-accessing') ----- + next: anInteger put: anObject + "This is supposed to be a fucking WriteStream. Why am I doing donkey work like this??" + self critical: [stream next: anInteger put: anObject]! |
Free forum by Nabble | Edit this page |