Ok.

According to my attempts, Stack and Cog Simulators are working fine (both Spur and SqueakV3). However the VM compiled to C crashes while trying to assign a block into an instance variable.

So something is still wrong. 

2016-01-06 14:46 GMT+01:00 <commits@source.squeak.org>:

Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1617.mcz

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

Name: VMMaker.oscog-cb.1617
Author: cb
Time: 6 January 2016, 2:46:27.798 pm
UUID: 81fe5b89-69de-45b8-9b65-f2f4a8bd187d
Ancestors: VMMaker.oscog-rmacnak.1616

As Eliot ntoed, I made a dumb mistake breking instance variable stores in the interpreter.

This commit fixes the mistake. In addition, storing into an immutable object in a primitive now signals a no modification error instead of inappropriate error.

I checked and the StackVMSimulator is working fine after this commit. Unfortunately, the CogVMSimulator does not work in my machine, likely due to other bugs. I am going to check that it works and that compilation to C works right now.

=============== Diff against VMMaker.oscog-rmacnak.1616 ===============

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
        "Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
        | thisReceiver rawHeader realHeader index newValue |
        newValue := self stackValue: 0.
        index := self stackValue: 1.
        (objectMemory isNonIntegerObject: index) ifTrue:
                [^self primitiveFailFor: PrimErrBadArgument].
        index := objectMemory integerValueOf: index.
        thisReceiver := self stackValue: 2.
        self cppIf: IMMUTABILITY
+               ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
-               ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrInappropriate ] ].
        rawHeader := self rawHeaderOf: thisReceiver.
        realHeader := (self isCogMethodReference: rawHeader)
                                        ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]
                                        ifFalse: [rawHeader].
        (index > 0
         and: [index <= ((objectMemory literalCountOfMethodHeader: realHeader) + LiteralStart)]) ifFalse:
                [^self primitiveFailFor: PrimErrBadIndex].
        index = 1
                ifTrue:
                        [((objectMemory isNonIntegerObject: newValue)
                         or: [(objectMemory literalCountOfMethodHeader: newValue) ~= (objectMemory literalCountOfMethodHeader: realHeader)]) ifTrue:
                                [^self primitiveFailFor: PrimErrBadArgument].
                         (self isCogMethodReference: rawHeader)
                                ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader: newValue]
                                ifFalse: [objectMemory storePointerUnchecked: 0 ofObject: thisReceiver withValue: newValue]]
                ifFalse:
                        [objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue].
        self pop: 3 thenPush: newValue!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatAtPut (in category 'indexing primitives') -----
  primitiveFloatAtPut
        "Provide platform-independent access to 32-bit words comprising
         a Float.  Map index 1 onto the most significant word and index 2
         onto the least significant word."
        | rcvr index oopToStore valueToStore |
        <var: #valueToStore type: #usqInt>
        oopToStore := self stackTop.
        valueToStore := self positive32BitValueOf: oopToStore.
        self successful ifFalse:
                [^self primitiveFailFor: PrimErrBadArgument].
        rcvr := self stackValue: 2.
        index := self stackValue: 1.
        (objectMemory isImmediateFloat: rcvr) ifTrue:
                [^self primitiveFailFor: PrimErrBadReceiver].
        self cppIf: IMMUTABILITY
+               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [^self primitiveFailFor: PrimErrNoModification] ].
-               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [^self primitiveFailFor: PrimErrBadReceiver] ].
        index = ConstOne ifTrue:
                [objectMemory storeLong32: (VMBIGENDIAN ifTrue: [0] ifFalse: [1])
                        ofObject: rcvr
                        withValue: valueToStore.
                ^self pop: 3 thenPush: oopToStore].
        index = ConstTwo ifTrue:
                [objectMemory storeLong32: (VMBIGENDIAN ifTrue: [1] ifFalse: [0])
                        ofObject: rcvr
                        withValue: valueToStore.
                ^self pop: 3 thenPush: oopToStore].
        self primitiveFailFor: ((objectMemory isIntegerObject: index)
                                                        ifTrue: [PrimErrBadIndex]
                                                        ifFalse: [PrimErrBadArgument])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIntegerAtPut (in category 'sound primitives') -----
  primitiveIntegerAtPut
        "Return the 32bit signed integer contents of a words receiver"
        | index rcvr sz addr value valueOop |
        <var: 'value' type: 'int'>
        valueOop := self stackValue: 0.
        index := self stackIntegerValue: 1.
        value := self signed32BitValueOf: valueOop.
        self successful ifFalse:
                [^self primitiveFailFor: PrimErrBadArgument].
        rcvr := self stackValue: 2.
        (objectMemory isWords: rcvr) ifFalse:
                [^self primitiveFailFor: PrimErrInappropriate].
        self cppIf: IMMUTABILITY "isWords: ensure non immediate"
+               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
-               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrInappropriate ] ].
        sz := objectMemory lengthOf: rcvr.  "number of fields"
        (index >= 1 and: [index <= sz]) ifFalse:
                [^self primitiveFailFor: PrimErrBadIndex].
        "4 = 32 bits / 8"
        addr := rcvr + objectMemory baseHeaderSize + (index - 1 * 4). "for zero indexing"
        value := objectMemory intAt: addr put: value.
        self pop: 3 thenPush: valueOop "pop all; return value"
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
        "Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
        | thisReceiver index newValue |
        newValue := self stackValue: 0.
        index := self stackValue: 1.
        ((objectMemory isNonIntegerObject: index)
         or: [index = ConstOne and: [(objectMemory isNonIntegerObject: newValue)]]) ifTrue:
                [^self primitiveFailFor: PrimErrBadArgument].
        index := objectMemory integerValueOf: index.
        thisReceiver := self stackValue: 2.
        self cppIf: IMMUTABILITY
+               ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
-               ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrInappropriate ] ].
        (index > 0 and: [index <= ((objectMemory literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
                [^self primitiveFailFor: PrimErrBadIndex].
        objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue.
        self pop: 3 thenPush: newValue!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveShortAtPut (in category 'sound primitives') -----
  primitiveShortAtPut
        "Treat the receiver, which can be indexible by either bytes or words, as an array
         of signed 16-bit values. Set the contents of the given index to the given value.
         Note that the index specifies the i-th 16-bit entry, not the i-th byte or word."

        | index rcvr value |
        value := self stackTop.
        index := self stackValue: 1.
        ((objectMemory isIntegerObject: value)
         and: [(objectMemory isIntegerObject: index)
         and: [value := objectMemory integerValueOf: value.
                  (value >= -32768) and: [value <= 32767]]]) ifFalse:
                [^self primitiveFailFor: PrimErrBadArgument].
        rcvr := self stackValue: 2.
        (objectMemory isWordsOrBytes: rcvr) ifFalse:
                [^self primitiveFailFor: PrimErrInappropriate].
        self cppIf: IMMUTABILITY "isWordsOrBytes ensure non immediate"
+               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
-               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrInappropriate ] ].
        index := objectMemory integerValueOf: index.
        (index >= 1 and: [index <= (objectMemory num16BitUnitsOf: rcvr)]) ifFalse:
                [^self primitiveFailFor: PrimErrBadIndex].
        objectMemory storeShort16: index - 1 ofObject: rcvr withValue: value.
        self pop: 3 thenPush: (objectMemory integerObjectOf: value)!

Item was changed:
  ----- Method: SpurMemoryManager>>isOopValidBecome: (in category 'become implementation') -----
  isOopValidBecome: oop
        "Answers 0 if the oop can be become.
        Answers an error code in the other case"
        (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
        (self isPinned: oop) ifTrue: [^PrimErrObjectIsPinned].
        self
                cppIf: IMMUTABILITY
+               ifTrue: [ (self isImmutable: oop) ifTrue: [^PrimErrNoModification] ].
-               ifTrue: [ (self isImmutable: oop) ifTrue: [^PrimErrInappropriate] ].
        ^ 0!

Item was changed:
  ----- Method: StackInterpreter>>extendedStoreAndPopBytecode (in category 'stack bytecodes') -----
  extendedStoreAndPopBytecode
        <inline: true>
        self extendedStoreBytecodePop: true
+       "may not be reached (immutable receiver)"!
- !

Item was changed:
  ----- Method: StackInterpreter>>extendedStoreBytecode (in category 'stack bytecodes') -----
  extendedStoreBytecode
        <inline: true>
+       self extendedStoreBytecodePop: false
+       "may not be reached (immutable receiver)"!
-       self extendedStoreBytecodePop: false!

Item was changed:
  ----- Method: StackInterpreter>>storeAndPopReceiverVariableBytecode (in category 'stack bytecodes') -----
  storeAndPopReceiverVariableBytecode
        "Note: This code uses
        storePointerUnchecked:ofObject:withValue: and does the
        store check explicitely in order to help the translator
        produce better code."
        | rcvr top |
        rcvr := self receiver.
        top := self internalStackTop.
        self internalPop: 1.
+       self
+               cCode: "Slang will inline currentBytecode to a constant so this will work in C"
+                       [self fetchNextBytecode.
+                        objectMemory
+                               storePointerImmutabilityCheck: (currentBytecode bitAnd: 7)
+                               ofObject: rcvr
+                               withValue: top]
+               inSmalltalk: "But in Smalltalk we must use the currentBytecode's value, not the next.
+                       We cant use the following code when generating C code as slang
+                       won't inline currentBytecode correctly due to the extra temp."
+                       [ | instVarIndex |
+                        instVarIndex := currentBytecode bitAnd: 7.
+                        self fetchNextBytecode.
+                        objectMemory
+                               storePointerImmutabilityCheck: instVarIndex
+                               ofObject: rcvr
+                               withValue: top]!
-       self fetchNextBytecode.
-       objectMemory storePointerImmutabilityCheck: (currentBytecode bitAnd: 7) ofObject: rcvr withValue: top.!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
  primitiveInstVarAtPut
        | newValue index rcvr hdr fmt totalLength fixedFields |
        newValue := self stackTop.
        index := self stackValue: 1.
        rcvr := self stackValue: 2.
        ((objectMemory isNonIntegerObject: index)
         or: [argumentCount > 2 "e.g. object:instVarAt:put:"
                and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
                [^self primitiveFailFor: PrimErrBadArgument].
+       (objectMemory isImmediate: rcvr) ifTrue: [ ^ self primitiveFailFor: PrimErrInappropriate].
+       self
+               cppIf: IMMUTABILITY
+               ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^ self primitiveFailFor: PrimErrNoModification] ].
-       self cppIf: IMMUTABILITY
-               ifTrue: [ (objectMemory isOopImmutable: rcvr) ifTrue: [^self primitiveFailFor: PrimErrInappropriate] ]
-               ifFalse: [ (objectMemory isImmediate: rcvr) ifTrue: [^self primitiveFailFor: PrimErrInappropriate] ].
        index := objectMemory integerValueOf: index.
        hdr := objectMemory baseHeader: rcvr.
        fmt := objectMemory formatOfHeader: hdr.
        totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
        fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
        (index >= 1 and: [index <= fixedFields]) ifFalse:
                [^self primitiveFailFor: PrimErrBadIndex].
        (fmt = objectMemory indexablePointersFormat
         and: [objectMemory isContextHeader: hdr])
                ifTrue: [self externalInstVar: index - 1 ofContext: rcvr put: newValue]
                ifFalse: [self subscript: rcvr with: index storing: newValue format: fmt].
        self pop: argumentCount + 1 thenPush: newValue!