2016-04-28 2:35 GMT+02:00 Eliot Miranda <eliot.miranda@gmail.com>:
 
Hi Nicolas,

  I'm looking at this now.  Your recent changes have also caused a huge number of warnings like this:

type mismatch for formal integerValue and actual "pwr - 1" when inlining pushInteger: in primitiveExponent. Use a cast.
type mismatch for formal reasonCode and actual "(objectMemory isIntegerObject: index) ifTrue: [PrimErrBadIndex] ifFalse: [PrimErrBadArgument]" when inlining primitiveFailFor: in primitiveFloatAt. Use a cast.
type mismatch for formal cond and actual "rcvr = arg" when inlining booleanCheat: in bytecodePrimIdentical. Use a cast.
type mismatch for formal cond and actual "rcvr = arg" when inlining booleanCheatSistaV1: in bytecodePrimIdenticalSistaV1. Use a cast.
type mismatch for formal cond and actual "rcvr = arg" when inlining booleanCheatV4: in bytecodePrimIdenticalV4. Use a cast.
type mismatch for formal reasonCode and actual "(objectMemory isIndexable: rcvr) ifTrue: [PrimErrBadIndex] ifFalse: [PrimErrBadReceiver]" when inlining primitiveFailFor: in commonVariable:at:put:cacheIndex:. Use a cast.
type mismatch for formal numSlots and actual "MessageLookupClassIndex + 1" when inlining eeInstantiateSmallClassIndex:format:numSlots: in createActualMessageTo:. Use a cast.
type mismatch for formal successBoolean and actual "integerArg ~= 0" when inlining success: in doPrimitiveDiv:by:. Use a cast.
type mismatch for formal successBoolean and actual "(result >> 60 + 1 bitAnd: 15) <= 1" when inlining success: in doPrimitiveDiv:by:. Use a cast.
type mismatch for formal successBoolean and actual "integerArg ~= 0" when inlining success: in doPrimitiveMod:by:. Use a cast.
type mismatch for formal successBoolean and actual "(integerResult >> 60 + 1 bitAnd: 15) <= 1" when inlining success: in doPrimitiveMod:by:. Use a cast.
type mismatch for formal successBoolean and actual "arg ~= 0.0" when inlining success: in primitiveFloatDivide:byArg:. Use a cast.
type mismatch for formal successBoolean and actual "objectsWritten = 1" when inlining success: in putLong:toFile:. Use a cast.
type mismatch for formal successBoolean and actual "objectsWritten = 1" when inlining success: in putShort:toFile:. Use a cast.
type mismatch for formal successBoolean and actual "objectsWritten = 1" when inlining success: in putWord32:toFile:. Use a cast.

:-(

Great, I didn't know about this type checking. That's usefull.
But isn't the logic inverted?
          self
                    variableOfType: (self typeFor: exprNode in: aTMethod)
                    acceptsValue: exprNode
                    ofType: (targetMethod typeFor: argName in: self)
I would expect
          self
                    variableOfType: (targetMethod typeFor: argName in: self)
                    acceptsValue: exprNode
                    ofType: (self typeFor: exprNode in: aTMethod)

Unfortunately
    someCharArray[i] = someExpressionPromotedToIntLikeBitAndFF & 0xFF;
would now complain because of int promotion...

 
We have to be careful.  Pharo is trying to release.  I would like a stable VM.  I would also like a better-inlined VM, so I support what you're doing.  I'm just worried about timing.


Agree, I committed a bit too soon.
These changes are likely to cause a bit of unstability for a transition period.
Travis-CI bot seems back to green, but i have no idea of coverage.
In last resort we can revert some of the changes and apply only the important fixes.
Let's cross finger and hope it won't be necessary.

 
On Wed, Apr 27, 2016 at 12:47 PM, Nicolas Cellier <nicolas.cellier.aka.nice@gmail.com> wrote:
 
Hi,
I changed the compiler flag -Wno-unused-value to -Wunused-value because there's no reason to carry dead code. Dead code should ring a bell.
it seems it uncovers a problem in code generation.
An example is in code generated for sendInvokeCallbackContext:

       if ((argumentCountOfMethodHeader(methodHeaderOf(GIV(newMethod)))) == 4) {
                /* begin push: */
                value = ((usqInt)((vmCallbackContext->thunkp)));
                /* begin positive32BitIntegerFor: */
                /* begin maybeInlinePositive32BitIntegerFor: */
                assert(!((hasSixtyFourBitImmediates())));
                if ((((unsigned int) value)) <= (MaxSmallInteger)) {
                        ((value << 1) | 1);
                       ^~~~~~~~~~~~~~ PROBLEM HERE: this result should be stored in variable 'object'
                        goto l4;
                }
                /* begin eeInstantiateSmallClassIndex:format:numSlots: */
...snip...
                object = newLargeInteger;
        l4:     /* end maybeInlinePositive32BitIntegerFor: */;
                goto l5;

        l5:     /* end positive32BitIntegerFor: */;

                longAtput((sp = GIV(stackPointer) - BytesPerWord), object);
 
The corresponding Slang code is:

    (self argumentCountOf: newMethod) = 4 ifTrue:
        [self push: (self positiveMachineIntegerFor: vmCallbackContext thunkp asUnsignedInteger).

With push:

    | sp |
    <inline: true>
    <var: #sp type: #'char *'>
    stackPages longAt: (sp := stackPointer - objectMemory wordSize) put: object.
    stackPointer := sp

With positiveMachineIntegerFor:

    <var: #value type: #'unsigned long'>
    <inline: true>
    ^objectMemory wordSize = 8
        ifTrue: [self positive64BitIntegerFor: value]
        ifFalse: [self positive32BitIntegerFor: value]

With positive32BitIntegerFor:

    <inline: true>
    <var: 'integerValue' type: #'unsigned int'>
    objectMemory hasSixtyFourBitImmediates
        ifTrue:
            [^objectMemory integerObjectOf: (integerValue asUnsignedLong bitAnd: 16rFFFFFFFF)]
        ifFalse:
            [^self maybeInlinePositive32BitIntegerFor: integerValue]

With maybeInlinePositive32BitIntegerFor:

    <notOption: #Spur64BitMemoryManager>
    <var: 'integerValue' type: #'unsigned int'>
    | newLargeInteger |
    self deny: objectMemory hasSixtyFourBitImmediates.
       "force coercion because slang inliner sometimes incorrectly pass a signed int without converting to unsigned"
       (self cCode: [self cCoerceSimple: integerValue to: #'unsigned int']
            inSmalltalk: [integerValue bitAnd: 1 << 32 - 1]) <= objectMemory maxSmallInteger ifTrue:
        [^objectMemory integerObjectOf: integerValue].
    newLargeInteger := objectMemory
                            eeInstantiateSmallClassIndex:
    ...snip...
    ^newLargeInteger





--
_,,,^..^,,,_
best, Eliot