<div dir="ltr">Hi Nicolas,<div class="gmail_extra"><br><div class="gmail_quote">On Mon, Mar 13, 2017 at 5:27 PM, Nicolas Cellier <span dir="ltr"><<a href="mailto:nicolas.cellier.aka.nice@gmail.com" target="_blank">nicolas.cellier.aka.nice@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"> <br><div dir="ltr">Hi Eliot,<br><div><div class="gmail_extra"><br><div class="gmail_quote">2017-03-13 21:20 GMT+01:00  <span dir="ltr"><<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>></span>:<br><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"><br>
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2148.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/VMMak<wbr>er/VMMaker.oscog-eem.2148.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-eem.2148<br>
Author: eem<br>
Time: 13 March 2017, 1:19:30.469259 pm<br>
UUID: 7f6e1475-0975-451e-8d17-b827aa<wbr>97c1eb<br>
Ancestors: VMMaker.oscog-dtl.2147<br>
<br>
Slang:<br>
Fix serious bug with inlining expressions such as<br>
        context := ignoreContext<br>
                ifTrue: [objectMemory nilObject ]<br>
                ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].<br>
where the exitVar (context) is lost and ensureFrameIsMarried:SP: is inlined missing the implicit assignment to context in the first ifTrue:.<br>
<br>
Fix bug with type inference for #-.  The difference between two unsigned values is signed.<br>
<br></blockquote><div><br></div><div>Hmm. I'm skeptical about this one.<br></div><div>In C, it ain't so.<br></div><div>What is it usefull to? bind the type inference for having some variable declared as signed?<br></div></div></div></div></div></blockquote><div><br></div><div>Right.</div><div> </div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"><div dir="ltr"><div><div class="gmail_extra"><div class="gmail_quote"><div></div><div>It will fool the type inference when the expression is not stored into a variable, and it does not feel good.<br></div></div></div></div></div></blockquote><div><br></div><div>I hear you.  It's simply that making the difference between two unsigned values signed is by far better usage in our VM given that that's what one gets in the simulator (because if infinite precision arithmetic).  So deciding to type unsigned - unsigned as signed gives better type inference.  For example, in computing the map in generateMapAt:start: mclc and location are both unsigned, but delta should be signed, because if ever the result went negative delta would become massively positive and the system would spin churning out map bytes until it ran off the end of memory.</div><div><br></div><div><span class="gmail-Apple-tab-span" style="white-space:pre">                     </span> [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:<br></div><div><br></div><div>I don't want to have to go through the source manually patching cases like this, adding explicit type declarations.  It's too time consuming, error-prone and ugly.  Instead, having the type inferencer infer the type as signed is, I think, an improvement.  But I'm open to enlightenment :-)</div><div><br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"><div dir="ltr"><div><div class="gmail_extra"><div class="gmail_quote"><div> <br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex">
Fix bug with inferring return types of methods that return unsigned typed variables and positive integer constants.  Don't interpret the type of an integer constant as #sqInt if the method also returns an unsigned.  So defer considering the non-negative integer return values unless no other return type information can be found.<br></blockquote></div></div></div></div></blockquote><div><br></div><div><br></div><div>Related to this I just fixed the type inferencer not to be misled by methods that answer an unsigned variable and an integer constant, as in allocate:</div><div><br></div><div><div>allocate: numBytes</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">     </span>| roundedBytes allocation |</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">    </span>roundedBytes := numBytes + 7 bitAnd: -8.</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">       </span>mzFreeStart + roundedBytes >= (limitAddress - (methodCount * objectMemory wordSize)) ifTrue:</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">                </span>[^0].</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">  </span>allocation := mzFreeStart.</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">     </span>mzFreeStart := mzFreeStart + roundedBytes.</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">     </span>methodCount := methodCount + 1.</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">        </span>self cCode: '' inSmalltalk:</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">            </span>[(cogit breakPC isInteger</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">              </span>   and: [cogit breakPC between: allocation and: mzFreeStart]) ifTrue:</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">                        </span>[cogit singleStep: true]].</div><div><span class="gmail-Apple-tab-span" style="white-space:pre">     </span>^allocation</div></div><div><br></div><div>mzFreeStart is unsigned, hence allocation is inferred as unsigned.  But the ^0 confused the old inferencer into typing allocate: as signed.  This is bogus.  So I modified it to ignore any non-negative integral return values until type inference couldn't determine a type from other returns in the method.<br></div><div><br></div><div>I'm just trying to be pragmatic and have the type inferencer "do the right thing"(tm) as much as possible.</div><div><br></div><div> </div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"><div dir="ltr"><div><div class="gmail_extra"><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex">
<br>
VMMaker:<br>
Add a SpurStackSistaVM configuration (in which the above inlining expressions bug was found).  This is not one of the ones under version control.<br>
<br>
=============== Diff against VMMaker.oscog-dtl.2147 ===============<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator>>harmonizeRetur<wbr>nTypesIn: (in category 'type inference') -----<br>
  harmonizeReturnTypesIn: aSetOfTypes<br>
+       "Eliminate signed/unsigned conflicts in aSetOfTypes. Non-negative integers can be either<br>
+        signed or unsigned. Ignore them unless there are no types, in which case default to sqInt."<br>
+       | constantIntegers sqs usqs |<br>
+       constantIntegers := aSetOfTypes select: [:element| element isInteger].<br>
+       aSetOfTypes removeAll: constantIntegers.<br>
+       "N.B. Because of LP64 vs LLP64 issues do *not* rename #long to #sqInt or #'unsigned long' to #usqInt"<br>
+       #(char short int #'long long' #'unsigned char' #'unsigned short' #'unsigned int' #'unsigned long long')<br>
+               with: #(sqInt sqInt sqInt sqLong usqInt usqInt usqInt usqLong)<br>
-       "Eliminate signed/unsigned conflicts in aSetOfTypes"<br>
-       | sqs usqs |<br>
-       #(char short int #'unsigned char' #'unsigned short' #'unsigned int' #'unsigned long')<br>
-               with: #(sqInt sqInt sqInt #usqInt #usqInt #usqInt #usqInt)<br>
                do: [:type :replacement|<br>
                        (aSetOfTypes includes: type) ifTrue:<br>
                                [aSetOfTypes remove: type; add: replacement]].<br>
        sqs := aSetOfTypes select: [:t| t beginsWith: 'sq'].<br>
        usqs := aSetOfTypes select: [:t| t beginsWith: 'usq'].<br>
        ^(sqs size + usqs size = aSetOfTypes size<br>
           and: [sqs notEmpty<br>
           and: [sqs allSatisfy: [:t| usqs includes: 'u', t]]])<br>
                ifTrue: [sqs]<br>
+               ifFalse: [(aSetOfTypes isEmpty and: [constantIntegers notEmpty])<br>
+                                       ifTrue: [Set with: #sqInt]<br>
+                                       ifFalse: [aSetOfTypes]]!<br>
-               ifFalse: [aSetOfTypes]!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator>>typeForArithme<wbr>tic:in: (in category 'type inference') -----<br>
  typeForArithmetic: sendNode in: aTMethod<br>
        "Answer the return type for an arithmetic sendThis is so that the inliner can still<br>
         inline simple expressions.  Deal with pointer arithmetic, floating point arithmetic<br>
         and promotion."<br>
+       | rcvrType argType arg promotedType |<br>
-       | rcvrType argType |<br>
        rcvrType := self typeFor: sendNode receiver in: aTMethod.<br>
+       argType := self typeFor: (arg := sendNode args first) in: aTMethod.<br>
-       argType := self typeFor: sendNode args first in: aTMethod.<br>
        "deal with pointer arithmetic"<br>
+       ((rcvrType notNil and: [rcvrType last == $*]) or: [argType notNil and: [argType last == $*]]) ifTrue:<br>
-       ((rcvrType notNil and: [rcvrType last = $*]) or: [argType notNil and: [argType last = $*]]) ifTrue:<br>
                [(rcvrType isNil or: [argType isNil]) ifTrue:<br>
                        [^nil].<br>
+                (rcvrType last == $* and: [argType last == $*]) ifTrue:<br>
-                (rcvrType last = $* and: [argType last = $*]) ifTrue:<br>
                        [sendNode selector == #- ifTrue:<br>
                                [^#int].<br>
                         self error: 'invalid pointer arithmetic'].<br>
+                ^rcvrType last == $*<br>
-                ^rcvrType last = $*<br>
                        ifTrue: [rcvrType]<br>
                        ifFalse: [argType]].<br>
+       promotedType := self promoteArithmeticTypes: rcvrType and: argType.<br>
+       "We have to be very careful with subtraction.  The difference between two unsigned types is signed.<br>
+        But we don't want unsigned - constant to be signed.  We almost always want this to stay unsigned."<br>
+       ^(sendNode selector == #- and: [promotedType first == $u and: [(arg isConstant and: [arg value isInteger]) not]])<br>
+               ifTrue: [promotedType allButFirst: ((promotedType beginsWith: 'unsigned') ifTrue: [9] ifFalse: [1])]<br>
+               ifFalse: [promotedType]!<br>
-       ^self promoteArithmeticTypes: rcvrType and: argType!<br>
<br>
Item was changed:<br>
  ----- Method: TMethod>>addTypesFor:to:in: (in category 'type inference') -----<br>
  addTypesFor: node to: typeSet in: aCodeGen<br>
        "Add the value types for the node to typeSet.<br>
         Answer if any type was derived from an as-yet-untyped method, which allows us to abort<br>
         inferReturnTypeFromReturnsIn: if the return type depends on a yet-to-be-typed method."<br>
        | expr |<br>
        expr := node.<br>
        [expr isAssignment or: [expr isStmtList]] whileTrue:<br>
                [expr isAssignment ifTrue:<br>
                        [expr := expr variable].<br>
                 expr isStmtList ifTrue:<br>
                        [expr := expr statements last]].<br>
        expr isSend ifTrue:<br>
                [(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: expr selector) ifTrue:<br>
                        [^expr args<br>
                                inject: false<br>
                                into: [:asYetUntyped :block|<br>
                                        asYetUntyped | (self addTypesFor: block to: typeSet in: aCodeGen)]].<br>
                (aCodeGen returnTypeForSend: expr in: self ifNil: nil)<br>
                        ifNil: [^(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]<br>
                        ifNotNil:<br>
                                [:type |<br>
                                typeSet add: type.<br>
                                ^false].].<br>
        expr isVariable ifTrue:<br>
                [(aCodeGen typeOfVariable: expr name)<br>
                        ifNotNil: [:type| typeSet add: type]<br>
                        ifNil: [typeSet add: (expr name = 'self'<br>
                                                                                ifTrue: [#void]<br>
                                                                                ifFalse: [#sqInt])]].<br>
        expr isConstant ifTrue:<br>
+               [(expr value isInteger and: [expr value >= 0]) "cannot determine if signed or unsigned yet..."<br>
+                       ifTrue: [typeSet add: expr value]<br>
+                       ifFalse:<br>
+                               [(expr typeOrNilFrom: aCodeGen in: self) ifNotNil:<br>
+                                       [:type | typeSet add: type]]].<br>
-               [(expr typeOrNilFrom: aCodeGen in: self) ifNotNil:<br>
-                       [:type | typeSet add: type]]..<br>
        ^false!<br>
<br>
Item was changed:<br>
  ----- Method: TMethod>>inferTypesForImplicit<wbr>lyTypedVariablesIn: (in category 'type inference') -----<br>
  inferTypesForImplicitlyTypedVa<wbr>riablesIn: aCodeGen<br>
        "infer types for untyped variables from assignments and arithmetic uses.<br>
         For debugging answer a Dictionary from var to the nodes that determined types<br>
         This for debugging:<br>
                (self copy inferTypesForImplicitlyTypedVa<wbr>riablesIn: aCodeGen)"<br>
+       | alreadyExplicitlyTypedOrNotToB<wbr>eTyped asYetUntyped effectiveNodes |<br>
-       | alreadyExplicitlyTypedOrNotToB<wbr>eTyped effectiveNodes |<br>
        aCodeGen maybeBreakForTestToInline: selector in: self.<br>
        alreadyExplicitlyTypedOrNotToB<wbr>eTyped := declarations keys asSet.<br>
+       asYetUntyped := locals copyWithoutAll: alreadyExplicitlyTypedOrNotToB<wbr>eTyped.<br>
        effectiveNodes := Dictionary new. "this for debugging"<br>
        parseTree nodesDo:<br>
                [:node| | type var |<br>
                "If there is something of the form i >= 0, then i should be signed, not unsigned."<br>
                (node isSend<br>
                 and: [(locals includes: (var := node receiver variableNameOrNil))<br>
                 and: [(alreadyExplicitlyTypedOrNotT<wbr>oBeTyped includes: var) not "don't be fooled by inferred unsigned types"<br>
                 and: [(#(<= < >= >) includes: node selector)<br>
                 and: [node args first isConstant<br>
                 and: [node args first value = 0<br>
                 and: [(type := self typeFor: var in: aCodeGen) notNil<br>
                 and: [type first == $u]]]]]]]) ifTrue:<br>
                        [self declarationAt: var put: (aCodeGen signedTypeForIntegralType: type), ' ', var.<br>
                         effectiveNodes at: var put: { declarations at: var. node }].<br>
                "if an assignment to an untyped local of a known type, set the local's type to that type.<br>
                 Only observe known sends (methods in the current set) and typed local variables."<br>
                (node isAssignment<br>
                 and: [(locals includes: (var := node variable name))<br>
                 and: [(alreadyExplicitlyTypedOrNotT<wbr>oBeTyped includes: var) not]]) ifTrue: "don't be fooled by previously inferred types"<br>
                        [type := node expression isSend<br>
                                                ifTrue: [aCodeGen returnTypeForSend: node expression in: self ifNil: nil]<br>
                                                ifFalse: [self typeFor: node expression in: aCodeGen].<br>
                         type "If untyped, then cannot type the variable yet. A subsequent assignment may assign a subtype of what this type ends up being"<br>
                                ifNil: [alreadyExplicitlyTypedOrNotTo<wbr>BeTyped add: var]<br>
+                               ifNotNil: "Merge simple types (but *don't* merge untyped vars); complex types must be defined by the programmer."<br>
-                               ifNotNil: "Merge simple types; complex types must be defined by the programmer."<br>
                                        [(aCodeGen isSimpleType: type) ifTrue:<br>
+                                               [(asYetUntyped includes: var)<br>
+                                                       ifTrue: [declarations at: var put: type, ' ', var. asYetUntyped remove: var]<br>
+                                                       ifFalse:<br>
+                                                               [aCodeGen mergeTypeOf: var in: declarations with: type method: self].<br>
-                                               [aCodeGen mergeTypeOf: var in: declarations with: type method: self.<br>
                                                 effectiveNodes at: var put: { declarations at: var. node }, (effectiveNodes at: var ifAbsent: [#()])]]]].<br>
        ^effectiveNodes!<br>
<br>
Item was changed:<br>
  ----- Method: TMethod>>tryToInlineMethodStat<wbr>ementsIn:statementListsInto: (in category 'inlining') -----<br>
  tryToInlineMethodStatementsIn: aCodeGen statementListsInto: aBlock<br>
        "Expand any (complete) inline methods sent by this method as top-level statements.<br>
         Answer if anything was inlined."<br>
<br>
        | stmtLists didSomething newStatements returningNodes |<br>
        didSomething := false.<br>
        returningNodes := Set new.<br>
+       stmtLists := self statementsListsForInliningIn: aCodeGen.<br>
+       "stmtLists may include expressions that are used for value but the exitVar is distant because its in an ifTrue:ifTrue:,<br>
+        e.g. in<br>
+                       context := ignoreContext<br>
+                                                       ifTrue: [objectMemory nilObject ]<br>
+                                                       ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].<br>
+       ensureFrameIsMarried:SP: *does* have an exitVar, context, but it is the exitVar for the ifTrue:ifFalse:.  So<br>
+       inlineCodeOrNilForStatement:r<wbr>eturningNodes:in: should not consider inlining these in its last phrase where exitVar is nil."<br>
        parseTree nodesDo:<br>
                [:node|<br>
                node isReturn ifTrue:<br>
                        [returningNodes add: node expression.<br>
                         node expression isConditionalSend ifTrue:<br>
+                               [returningNodes addAll: (node expression args collect: [:stmtList| stmtList statements last])]].<br>
+               node isAssignment ifTrue:<br>
+                       [node expression nodesDo:<br>
+                               [:assignmentSubNode|<br>
+                               (stmtLists includes: assignmentSubNode) ifTrue:<br>
+                                       [stmtLists remove: assignmentSubNode]]]].<br>
+<br>
-                               [returningNodes addAll: (node expression args collect: [:stmtList| stmtList statements last])]]].<br>
-       stmtLists := self statementsListsForInliningIn: aCodeGen.<br>
        stmtLists do:<br>
                [:stmtList|<br>
                newStatements := OrderedCollection new: stmtList statements size.<br>
                stmtList statements do:<br>
                        [:stmt|<br>
                        (self inlineCodeOrNilForStatement: stmt returningNodes: returningNodes in: aCodeGen)<br>
                                ifNil: [newStatements addLast: stmt]<br>
                                ifNotNil: [:inlinedStmts|<br>
                                        didSomething := true.<br>
                                        newStatements addAllLast: inlinedStmts]].<br>
                stmtList setStatements: newStatements asArray].<br>
<br>
        "This is a hack; forgive me. The inlining above tends to keep return statements in statement lists.<br>
         In the case of returning ifs we don't want the returns in case the returning if is generated as an expression."<br>
        returningNodes do:<br>
                [:returningNode|<br>
                 (returningNode isConditionalSend<br>
                  and: [returningNode args anySatisfy: [:alternativeNode| alternativeNode endsWithReturn]]) ifTrue:<br>
                        [returningNode args withIndexDo:<br>
                                [:alternativeNode :index|<br>
                                 alternativeNode endsWithReturn ifTrue:<br>
                                        [returningNode args at: index put: alternativeNode copyWithoutReturn]]]].<br>
<br>
        aBlock value: stmtLists.<br>
<br>
        ^didSomething!<br>
<br>
Item was added:<br>
+ ----- Method: VMMaker class>>generateSqueakSpurStack<wbr>SistaVM (in category 'configurations') -----<br>
+ generateSqueakSpurStackSistaVM<br>
+       "No primitives since we can use those for the Cog VM"<br>
+       ^VMMaker<br>
+               generate: StackInterpreter<br>
+               with: #(SistaVM true<br>
+                               ObjectMemory Spur32BitMemoryManager<br>
+                               FailImbalancedPrimitives false<br>
+                               MULTIPLEBYTECODESETS true<br>
+                               bytecodeTableInitializer initializeBytecodeTableForSque<wbr>akV3PlusClosuresSistaV1Hybrid)<br>
+               to: (FileDirectory default pathFromURI: self sourceTree, '/spursistastacksrc')<br>
+               platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')<br>
+               including:#()!<br>
<br>
</blockquote></div><br></div></div></div>
<br></blockquote></div><br><br clear="all"><div><br></div>-- <br><div class="gmail_signature"><div dir="ltr"><div><span style="font-size:small;border-collapse:separate"><div>_,,,^..^,,,_<br></div><div>best, Eliot</div></span></div></div></div>
</div></div>