[Vm-dev] VM Maker: VMMaker.oscog-eem.1103.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Sat Mar 21 09:17:57 UTC 2015


Hi Eliot

2015-03-21 3:56 GMT+01:00 Eliot Miranda <eliot.miranda at gmail.com>:

>
> Hi Nicolas,
>
> On Mar 20, 2015, at 1:32 PM, Nicolas Cellier <
> nicolas.cellier.aka.nice at gmail.com> wrote:
>
>
>
> 2015-03-20 0:21 GMT+01:00 <commits at source.squeak.org>:
>
>>
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1103.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-eem.1103
>> Author: eem
>> Time: 19 March 2015, 4:20:02.926 pm
>> UUID: 64ddd2e1-e5f5-4ad0-b512-b1d0e32e99f7
>> Ancestors: VMMaker.oscog-eem.1102
>>
>> Fix some Slang issues with ARM methods (clashing
>> arg names).
>>
>> Provide an abstraction for saving & restoring link reg
>> around calls.
>>
>> =============== Diff against VMMaker.oscog-eem.1102 ===============
>>
>> Item was changed:
>>   ----- Method: CoInterpreter>>ceTraceLinkedSend: (in category 'debug
>> support') -----
>>   ceTraceLinkedSend: theReceiver
>>         | cogMethod |
>>         <api>
>>         <var: #cogMethod type: #'CogMethod *'>
>>         cogMethod := self cCoerceSimple: (self stackTop - cogit
>> traceLinkedSendOffset)
>>                                                 to: #'CogMethod *'.
>>         self cCode: [] inSmalltalk:
>>                 [cogit checkStackDepthOnSend ifTrue:
>>                         [self maybeCheckStackDepth: (cogMethod cmNumArgs
>> > cogit numRegArgs
>>
>>               ifTrue: [cogMethod cmNumArgs + 1]
>>
>>               ifFalse: [0])
>>                                 sp: stackPointer + objectMemory wordSize
>>                                 pc: (self stackValue: 1)]].
>>         "cogit recordSendTrace ifTrue: is implicit; wouldn't compile the
>> call otherwise."
>>         self recordTrace: (objectMemory fetchClassOf: theReceiver)
>>                 thing: cogMethod selector
>>                 source: TraceIsFromMachineCode.
>>         cogit printOnTrace ifTrue:
>>                 [self printActivationNameFor: cogMethod methodObject
>>                         receiver: theReceiver
>>                         isBlock: false
>> +                       firstTemporary: (self cCode: [nil] inSmalltalk:
>> [0]);
>> -                       firstTemporary: nil;
>>                         cr].
>>         self sendBreakpoint: cogMethod selector receiver: theReceiver!
>>
>> Item was changed:
>>   ----- Method: CogARMCompiler>>concretizeDataOperationCqR: (in category
>> 'generate machine code - concretize') -----
>> + concretizeDataOperationCqR: armOpcode
>> - concretizeDataOperationCqR: opcode
>>         "Will get inlined into concretizeAt: switch."
>>         "4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12, Bic == 14"
>>         <inline: true>
>>         self
>>                 rotateable8bitImmediate: (operands at: 0)
>>                 ifTrue: [:rot :immediate | | rd rn |
>>                         rn := self concreteRegister: (operands at: 1).
>>                         rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
>> +                       self machineCodeAt: 0 put: (self type: 1 op:
>> armOpcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we
>> have to halve the rot value" << 8 bitOr: immediate)).
>> -                       self machineCodeAt: 0 put: (self type: 1 op:
>> opcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we have
>> to halve the rot value" << 8 bitOr: immediate)).
>>                         ^machineCodeSize := 4]
>> +               ifFalse: [^self concretizeDataOperationCwR: armOpcode].
>> -               ifFalse: [^self concretizeDataOperationCwR: opcode].
>>         !
>>
>> Item was changed:
>>   ----- Method: CogARMCompiler>>concretizeDataOperationCwR: (in category
>> 'generate machine code - concretize') -----
>> + concretizeDataOperationCwR: armOpcode
>> - concretizeDataOperationCwR: opcode
>>         "Will get inlined into concretizeAt: switch."
>>         "Load the word into the RISCTempReg, then cmp R, RISCTempReg"
>>         <inline: true>
>>         | constant rn rd instrOffset|
>>         constant := operands at: 0.
>>         rn := (self concreteRegister: (operands at: 1)).
>> +       rd := armOpcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
>> -       rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
>>         instrOffset := self at: 0 moveCw: constant intoR: RISCTempReg.
>>         self machineCodeAt: instrOffset
>> +               put: (self type: 0 op: armOpcode set: 1 rn: rn rd: rd
>> shifterOperand: RISCTempReg).
>> -               put: (self type: 0 op: opcode set: 1 rn: rn rd: rd
>> shifterOperand: RISCTempReg).
>>         ^machineCodeSize := instrOffset + 4!
>>
>> Item was changed:
>>   ----- Method: CogARMCompiler>>concretizeDataOperationRR: (in category
>> 'generate machine code - concretize') -----
>> + concretizeDataOperationRR: armOpcode
>> - concretizeDataOperationRR: opcode
>>         "Will get inlined into concretizeAt: switch."
>>         "Load the word into the RISCTempReg, then op R, RISCTempReg"
>>         <inline: true>
>>         | rn rd srcReg |
>>         srcReg := self concreteRegister: (operands at: 0).
>>         rn := (self concreteRegister: (operands at: 1)).
>> +       rd := armOpcode = CmpOpcode ifTrue: [0] ifFalse: [rn].
>> -       rd := opcode = CmpOpcode ifTrue: [0] ifFalse: [rn].
>>         self machineCodeAt: 0
>> +               put: (self type: 0 op: armOpcode set: 1 rn: rn rd: rd
>> shifterOperand: srcReg).
>> -               put: (self type: 0 op: opcode set: 1 rn: rn rd: rd
>> shifterOperand: srcReg).
>>         ^machineCodeSize := 4.!
>>
>> Item was changed:
>>   ----- Method: CogARMCompiler>>extractOffsetFromBXAt: (in category
>> 'testing') -----
>> + extractOffsetFromBXAt: addr
>> - extractOffsetFromBXAt: address
>>   "this should return the long call/jump target"
>> +       ^(objectMemory byteAt: addr -4)
>> +               + ((objectMemory byteAt: addr - 8) << 8)
>> +               + ((objectMemory byteAt: addr - 12) << 16)
>> +               + ((objectMemory byteAt: addr - 16) << 24)!
>> -       ^(objectMemory byteAt: address -4)
>> -               + ((objectMemory byteAt: address - 8) << 8)
>> -               + ((objectMemory byteAt: address - 12) << 16)
>> -               + ((objectMemory byteAt: address - 16) << 24)!
>>
>> Item was added:
>> + ----- Method: CogARMCompiler>>saveAndRestoreLinkRegAround: (in category
>> 'abi') -----
>> + saveAndRestoreLinkRegAround: aBlock
>> +       "If the processor's ABI includes a link register, generate
>> instructions
>> +        to save and restore it around aBlock, which is assumed to
>> generate code."
>> +       <inline: true>
>> +       | inst |
>> +       inst := cogit PushR: LinkReg.
>> +       aBlock value.
>> +       cogit PopR: LinkReg.
>> +       ^inst!
>>
>> Item was added:
>> + ----- Method: CogAbstractInstruction>>saveAndRestoreLinkRegAround: (in
>> category 'abi') -----
>> + saveAndRestoreLinkRegAround: aBlock
>> +       "If the processor's ABI includes a link register, generate
>> instructions
>> +        to save and restore it around aBlock, which is assumed to
>> generate code."
>> +       <inline: true>
>> +       self subclassResponsibility!
>>
>> Item was added:
>> + ----- Method: CogIA32Compiler>>saveAndRestoreLinkRegAround: (in
>> category 'abi') -----
>> + saveAndRestoreLinkRegAround: aBlock
>> +       "If the processor's ABI includes a link register, generate
>> instructions
>> +        to save and restore it around aBlock, which is assumed to
>> generate code."
>> +       <inline: true>
>> +       ^aBlock value!
>>
>>
> Hmm, the generater doesn't know how to deal with this one...
> It tries to inline the formal parameter (block) rather than the actual
> block passed by the sender.
>
>
> Hmm... R u sure?  I tried this in a workspace I use for slang testing and
> saw no problem.
>
>
Yes, I do it:
    VMMaker  generateSqueakCogVM.

and get the assertion failure:

CCodeGenerator(Object)>>assert:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
        aBlock:     false
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

CCodeGenerator>>generateValueAsArgument:on:indent:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
        aTSendNode:     aBlock value
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        level:     1
        substitution:     nil
        substitutionDict:     nil
        newLabels:     nil
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

CCodeGenerator>>emitBuiltinConstructAsArgumentFor:on:level:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
        msgNode:     aBlock value
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        level:     1
        action:     #generateValueAsArgument:on:indent:
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

TSendNode>>emitCCodeAsArgumentOn:level:generator:
    Receiver: aBlock value
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        level:     1
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        comment:     nil
        selector:     #value
        receiver:     aBlock
        arguments:     #()
        isBuiltinOperator:     true

TReturnNode>>emitCCodeOn:level:generator:
    Receiver: ^aBlock value
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        level:     1
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        comment:     nil
        expression:     aBlock value

[] in TStmtListNode>>emitCCodeOn:prependToEnd:level:generator:
    Receiver: [^aBlock value]
    Arguments and temporary variables:
        aStream:     ^aBlock value
        aNodeOrNil:     1
        level:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/cogi...etc...
        aCodeGen:     nil
        s:     1
        idx:     a CCodeGenerator
    Receiver's instance variables:
        comment:     nil
        arguments:     #()
        statements:     an OrderedCollection(^aBlock value)

OrderedCollection(SequenceableCollection)>>withIndexDo:
    Receiver: an OrderedCollection(^aBlock value)
    Arguments and temporary variables:
        elementAndIndexBlock:     [closure] in
TStmtListNode>>emitCCodeOn:prependToEnd:leve...etc...
        index:     1
        indexLimiT:     1
    Receiver's instance variables:
        array:     {^aBlock value}
        firstIndex:     1
        lastIndex:     1

TStmtListNode>>emitCCodeOn:prependToEnd:level:generator:
    Receiver: [^aBlock value]
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        aNodeOrNil:     nil
        level:     1
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        comment:     nil
        arguments:     #()
        statements:     an OrderedCollection(^aBlock value)

TStmtListNode>>emitCCodeOn:level:generator:
    Receiver: [^aBlock value]
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        level:     1
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        comment:     nil
        arguments:     #()
        statements:     an OrderedCollection(^aBlock value)

[] in TMethod>>emitCCodeOn:generator:
    Receiver: a TMethod (CogIA32Compiler>>saveAndRestoreLinkRegAround:)
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        selector:     #saveAndRestoreLinkRegAround:
        returnType:     #sqInt
        args:     an
OrderedCollection('self_in_saveAndRestoreLinkRegAround' 'aBlock')
        locals:     a Set()
        declarations:     a
Dictionary('self_in_saveAndRestoreLinkRegAround'->'AbstractInst...etc...
        primitive:     0
        parseTree:     [^aBlock value]
        labels:     a Set()
        writtenToGlobalVarsCache:     nil
        complete:     true
        export:     false
        static:     true
        inline:     true
        sharedLabel:     nil
        sharedCase:     nil
        comment:     an OrderedCollection('If the processor''s ABI includes
a link register...etc...
        definingClass:     CogIA32Compiler
        globalStructureBuildMethodHasFoo:     false
        properties:     an AdditionalMethodState (2682)
        extraVariableNumber:     nil

BlockClosure>>ensure:
    Receiver: [closure] in TMethod>>emitCCodeOn:generator:
    Arguments and temporary variables:
        aBlock:     [closure] in CCodeGenerator>>pushScope:while:
        complete:     nil
        returnValue:     nil
    Receiver's instance variables:
        outerContext:     TMethod>>emitCCodeOn:generator:
        startpc:     87
        numArgs:     0

CCodeGenerator>>pushScope:while:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
        variableToType:     a
Dictionary('self_in_saveAndRestoreLinkRegAround'->'AbstractIn...etc...
        aBlock:     [closure] in TMethod>>emitCCodeOn:generator:
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

TMethod>>emitCCodeOn:generator:
    Receiver: a TMethod (CogIA32Compiler>>saveAndRestoreLinkRegAround:)
    Arguments and temporary variables:
        aStream:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/co...etc...
        aCodeGen:     a CCodeGenerator
    Receiver's instance variables:
        selector:     #saveAndRestoreLinkRegAround:
        returnType:     #sqInt
        args:     an
OrderedCollection('self_in_saveAndRestoreLinkRegAround' 'aBlock')
        locals:     a Set()
        declarations:     a
Dictionary('self_in_saveAndRestoreLinkRegAround'->'AbstractInst...etc...
        primitive:     0
        parseTree:     [^aBlock value]
        labels:     a Set()
        writtenToGlobalVarsCache:     nil
        complete:     true
        export:     false
        static:     true
        inline:     true
        sharedLabel:     nil
        sharedCase:     nil
        comment:     an OrderedCollection('If the processor''s ABI includes
a link register...etc...
        definingClass:     CogIA32Compiler
        globalStructureBuildMethodHasFoo:     false
        properties:     an AdditionalMethodState (2682)
        extraVariableNumber:     nil

[] in [] in CCodeGenerator>>emitCMethods:on:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
<<error during printing>
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

SortedCollection(SequenceableCollection)>>withIndexDo:
    Receiver: a SortedCollection(a TMethod
(CogAbstractInstruction>>abstractRegisterForConcreteRegister:...etc...
    Arguments and temporary variables:
        elementAndIndexBlock:     [closure] in [] in
CCodeGenerator>>emitCMethods:on:
        index:     253
        indexLimiT:     903
    Receiver's instance variables:
        array:     {a TMethod
(CogAbstractInstruction>>abstractRegisterForConcreteRegister:...etc...
        firstIndex:     1
        lastIndex:     903
        sortBlock:     [closure] in CCodeGenerator>>sortMethods:

SortedCollection(SequenceableCollection)>>doWithIndex:
    Receiver: a SortedCollection(a TMethod
(CogAbstractInstruction>>abstractRegisterForConcreteRegister:...etc...
    Arguments and temporary variables:
        elementAndIndexBlock:     [closure] in [] in
CCodeGenerator>>emitCMethods:on:
    Receiver's instance variables:
        array:     {a TMethod
(CogAbstractInstruction>>abstractRegisterForConcreteRegister:...etc...
        firstIndex:     1
        lastIndex:     903
        sortBlock:     [closure] in CCodeGenerator>>sortMethods:

[] in CCodeGenerator>>emitCMethods:on:
    Receiver: a CCodeGenerator
    Arguments and temporary variables:
        methodList:     [closure] in
SystemProgressMorph>>position:label:min:max:
        aStream:     a SortedCollection(a TMethod
(CogAbstractInstruction>>abstractRegister...etc...
        bar:     MultiByteFileStream:
'/Users/nicolas/Smalltalk/Squeak/vm_cog/src/vm/cogit....etc...
    Receiver's instance variables:
        vmClass:     StackToRegisterMappingCogit
        structClasses:     an OrderedCollection(CogAbstractInstruction
CogIA32Compiler CogB...etc...
        translationDict:     a Dictionary(size 111)
        asArgumentTranslationDict:     a
Dictionary(#cCode:->#generateInlineCCodeAsArgument...etc...
        inlineList:     a Set(#concretizeMoveM64rRd #JumpZero: #JumpLess:
#MoveXbr:R:R: #Mo...etc...
        constants:     a Dictionary(size 454)
        variables:     a Set('simStack' 'methodOrBlockNumTemps'
'ceTraceLinkedSendTrampolin...etc...
        variableDeclarations:     a Dictionary('CFramePointer'->'void *
CFramePointer' 'CSt...etc...
        scopeStack:     an OrderedCollection(a
Dictionary('self_in_saveAndRestoreLinkRegAro...etc...
        methods:     a Dictionary(size 903)
        macros:     a Dictionary(#abstractInstructionAt:->'(index)
(&abstractOpcodes[index]...etc...
        apiMethods:     a Dictionary(size 250)
        kernelReturnTypes:     a Dictionary(#byteAt:->#sqInt
#byteAt:put:->#sqInt #byteAtPo...etc...
        currentMethod:     a TMethod
(CogIA32Compiler>>saveAndRestoreLinkRegAround:)
        headerFiles:     an OrderedCollection('"sq.h"' '<stddef.h>'
'"sqCogStackAlignment.h...etc...
        globalVariableUsage:     a Dictionary(size 144)
        useSymbolicConstants:     true
        generateDeadCode:     false
        requiredSelectors:     a Set(#sizePCDependentInstructionAt:
#genPrimitiveMultiply #...etc...
        logger:     a TranscriptStream
        suppressAsmLabels:     false
        asmLabelCounts:     nil
        pools:     an IdentitySet(CogRTLOpcodes CogCompilationConstants
VMSqueakV3ObjectRep...etc...
        selectorTranslations:     an
IdentityDictionary(#AddCq:R:->'gAddCqR' #AddCw:R:->'gA...etc...
        optionsDictionary:     a Dictionary(#BytesPerWord->4
#CheckPrivacyViolations->false...etc...
        breakSrcInlineSelectors:     an IdentitySet()
        breakDestInlineSelectors:     an IdentitySet()
        breakOnInline:     nil
        vmMaker:     a CrossPlatformVMMaker

[] in [] in MorphicUIManager>>displayProgress:at:from:to:during:
    Receiver: a MorphicUIManager
    Arguments and temporary variables:
<<error during printing>
    Receiver's instance variables:
        toolBuilder:     nil

BlockClosure>>on:do:
    Receiver: [closure] in [] in
MorphicUIManager>>displayProgress:at:from:to:during:
    Arguments and temporary variables:
        exception:     ProgressNotification
        handlerAction:     [closure] in [] in
MorphicUIManager>>displayProgress:at:from:to:...etc...
        handlerActive:     true
    Receiver's instance variables:
        outerContext:     [] in
MorphicUIManager>>displayProgress:at:from:to:during:
        startpc:     86
        numArgs:     0


--- The full stack ---
CCodeGenerator(Object)>>assert:
CCodeGenerator>>generateValueAsArgument:on:indent:
CCodeGenerator>>emitBuiltinConstructAsArgumentFor:on:level:
TSendNode>>emitCCodeAsArgumentOn:level:generator:
TReturnNode>>emitCCodeOn:level:generator:
[] in TStmtListNode>>emitCCodeOn:prependToEnd:level:generator:
OrderedCollection(SequenceableCollection)>>withIndexDo:
TStmtListNode>>emitCCodeOn:prependToEnd:level:generator:
TStmtListNode>>emitCCodeOn:level:generator:
[] in TMethod>>emitCCodeOn:generator:
BlockClosure>>ensure:
CCodeGenerator>>pushScope:while:
TMethod>>emitCCodeOn:generator:
[] in [] in CCodeGenerator>>emitCMethods:on:
SortedCollection(SequenceableCollection)>>withIndexDo:
SortedCollection(SequenceableCollection)>>doWithIndex:
[] in CCodeGenerator>>emitCMethods:on:
[] in [] in MorphicUIManager>>displayProgress:at:from:to:during:
BlockClosure>>on:do:
 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
[] in MorphicUIManager>>displayProgress:at:from:to:during:
BlockClosure>>ensure:
MorphicUIManager>>displayProgress:at:from:to:during:
ProgressInitiationException>>defaultResumeValue
ProgressInitiationException(Exception)>>resume
ProgressInitiationException>>defaultAction
UndefinedObject>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
ProgressInitiationException(Exception)>>signal
ProgressInitiationException>>display:at:from:to:during:
ProgressInitiationException class>>display:at:from:to:during:
ByteString(String)>>displayProgressAt:from:to:during:
CCodeGenerator>>emitCMethods:on:
CCodeGenerator>>emitCCodeOn:doInlining:doAssertions:
CCodeGenerator>>storeCodeOnFile:doInlining:doAssertions:
CCodeGenerator>>storeCodeOnFile:doInlining:
CrossPlatformVMMaker(VMMaker)>>generateCogitFile
CrossPlatformVMMaker(VMMaker)>>generateMainVM
CrossPlatformVMMaker(VMMaker)>>generateEntire
VMMaker class>>generate:and:with:to:platformDir:including:
VMMaker class>>generateSqueakCogVMWithInterpreterClass:options:
VMMaker class>>generateSqueakCogVM
UndefinedObject>>DoIt
Compiler>>evaluateCue:ifFail:
Compiler>>evaluateCue:ifFail:logged:
Compiler>>evaluate:in:to:notifying:ifFail:logged:
[] in SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
BlockClosure>>on:do:
SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
SmalltalkEditor(TextEditor)>>evaluateSelection
SmalltalkEditor(TextEditor)>>doIt
SmalltalkEditor(TextEditor)>>doIt:
SmalltalkEditor(TextEditor)>>dispatchOnKeyboardEvent:
SmalltalkEditor(TextEditor)>>keyStroke:
[] in [] in TextMorphForEditView(TextMorph)>>keyStroke:
TextMorphForEditView(TextMorph)>>handleInteraction:fromEvent:
TextMorphForEditView>>handleInteraction:fromEvent:
[] in TextMorphForEditView(TextMorph)>>keyStroke:
StandardToolSet class>>codeCompletionAround:textMorph:keyStroke:
ToolSet class>>codeCompletionAround:textMorph:keyStroke:
TextMorphForEditView(TextMorph)>>keyStroke:
-- and more not shown --

>
> Nicolas
>
>
>> Item was changed:
>>   ----- Method: Cogit>>compileEntry (in category 'compile abstract
>> instructions') -----
>>   compileEntry
>>         "The entry code to a method checks that the class of the current
>> receiver matches
>>          that in the inline cache.  Other non-obvious elements are that
>> its alignment must be
>>          different from the alignment of the noCheckEntry so that the
>> method map machinery
>>          can distinguish normal and super sends (super sends bind to the
>> noCheckEntry).
>>          In Newspeak we also need to distinguish dynSuperSends from
>> normal and super
>>          and so on Nespeak, bind the dynSuperEntry to the preceeding nop
>> (on x86 there
>>          happens to be one anyway)."
>>
>>         self cppIf: NewspeakVM ifTrue:
>>                 [self Nop. "1st nop differentiates dynSuperEntry from
>> no-check entry if using nextMethod"
>>                  dynSuperEntry := self Nop].
>>         entry := objectRepresentation genGetInlineCacheClassTagFrom:
>> ReceiverResultReg into: TempReg forEntry: true.
>>         self CmpR: ClassReg R: TempReg.
>>         self JumpNonZero: sendMiss.
>>         noCheckEntry := self Label.
>>         self compileSendTrace ifTrue:
>> +               [backEnd saveAndRestoreLinkRegAround:
>> +                       [self CallRT: ceTraceLinkedSendTrampoline]]!
>> -               [backEnd hasLinkRegister ifTrue:
>> -                       [self PushR: LinkReg].
>> -                self CallRT: ceTraceLinkedSendTrampoline.
>> -                backEnd hasLinkRegister ifTrue:
>> -                       [self PopR: LinkReg]]!
>>
>> Item was changed:
>>   ----- Method:
>> StackToRegisterMappingCogit>>genFramelessStorePop:ReceiverVariable: (in
>> category 'bytecode generators') -----
>>   genFramelessStorePop: popBoolean ReceiverVariable: slotIndex
>>         <inline: false>
>>         | topReg valueReg constVal |
>>         self assert: needsFrame not.
>>         self ssFlushUpThroughReceiverVariable: slotIndex.
>>         "Avoid store check for immediate values"
>>         constVal := self ssTop maybeConstant.
>>         (self ssTop type = SSConstant
>>          and: [(objectRepresentation shouldAnnotateObjectReference:
>> constVal) not]) ifTrue:
>>                 [self ensureReceiverResultRegContainsSelf.
>>                  self ssStorePop: popBoolean toPreferredReg: TempReg.
>>                  traceStores > 0 ifTrue:
>> +                       [backEnd saveAndRestoreLinkRegAround:
>> +                               [self CallRT: ceTraceStoreTrampoline]].
>> -                       [self CallRT: ceTraceStoreTrampoline].
>>                  ^objectRepresentation
>>                         genStoreImmediateInSourceReg: TempReg
>>                         slotIndex: slotIndex
>>                         destReg: ReceiverResultReg].
>>         (topReg := self ssTop registerOrNil) isNil ifTrue:
>>                 [topReg := ClassReg].
>>         valueReg := self ssStorePop: popBoolean toPreferredReg: topReg.
>>         "Note that ReceiverResultReg remains live after
>> ceStoreCheckTrampoline."
>>         self ensureReceiverResultRegContainsSelf.
>>          traceStores > 0 ifTrue:
>>                 [self MoveR: valueReg R: TempReg.
>> +                backEnd saveAndRestoreLinkRegAround:
>> +                       [self CallRT: ceTraceStoreTrampoline]].
>> -                self CallRT: ceTraceStoreTrampoline].
>>         ^objectRepresentation
>>                 genStoreSourceReg: valueReg
>>                 slotIndex: slotIndex
>>                 destReg: ReceiverResultReg
>>                 scratchReg: TempReg!
>>
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20150321/b740d83d/attachment-0001.htm


More information about the Vm-dev mailing list