<div dir="ltr"><div>Hi Eliot,</div><div>IEEE754 mandates that sqrt be correctly rounded.</div><div>Hence it should be bit identical on every compliant architecture.<br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">Le mar. 21 avr. 2020 à 04:55, <<a href="mailto:commits@source.squeak.org">commits@source.squeak.org</a>> a écrit :<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);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.2742.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2742.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-eem.2742<br>
Author: eem<br>
Time: 20 April 2020, 7:55:24.339483 pm<br>
UUID: 3931845a-822b-41e2-9db6-4ef3bc9a4e17<br>
Ancestors: VMMaker.oscog-eem.2741<br>
<br>
Cogit: mark the floating-point square root generators (the only non-arithmetic primitives) as notOption: #BIT_IDENTICAL_FLOATING_POINT in preparation for making it possioble to link the VM against Nicolas' revamp of fdlibm.  This is for Terf/Croquet.<br>
<br>
CoInterpreter: rename primitiveArrayBecomeOneWayCopyHash to primitiveArrayBecomeOneWayCopyHashArg to differentiate it from primitiveArrayBecomeOneWayNoCopyHash.<br>
<br>
StackInterpeeter: replace the only two uses of option: #SpurMemoryManager with option: #SpurObjectMemory.<br>
<br>
Slang: fix shouldIncludeMethodFor:selector: for combinations of option: and notOption: (e.g. genPrimitiveSmallFloatSquareRoot).  Extend CogPrimitiveDescriptor>>printCInitializerOn:in: to allow optionally defined entries.  Extend namesDefinedAtCompileTime with BIT_IDENTICAL_FLOATING_POINT.  Ideally we'd maintain namesDefinedAtYTranslationTime but I failed to pull off this putch today, at the cost of a good few hours.  It turns out to be tricky.  Slang 1. Eliot 0. once again.<br>
<br>
=============== Diff against VMMaker.oscog-eem.2741 ===============<br>
<br>
Item was added:<br>
+ ----- Method: CCodeGenerator>>optionIsFalse:in: (in category 'utilities') -----<br>
+ optionIsFalse: pragma in: aClass<br>
+       "Answer whether a notOption: pragma is false in the context of aClass.<br>
+        The argument to the option: pragma is interpreted as either a Cogit class name<br>
+        or a class variable name or a variable name in VMBasicConstants."<br>
+       | key |<br>
+       key := pragma argumentAt: 1.<br>
+ <br>
+       "If the option is one to be defined at compile time we'll generate a<br>
+        conditional around its declaration and definition."<br>
+       ((vmClass ifNil: [VMBasicConstants]) defineAtCompileTime: key) ifTrue:<br>
+               [^true].<br>
+ <br>
+       "If the option is the name of a subclass of Cogit, include it if it dfoesn't inherit from the Cogit class."<br>
+       (Smalltalk classNamed: key) ifNotNil:<br>
+               [:optionClass|<br>
+                aClass cogitClass ifNotNil:<br>
+                       [:cogitClass|<br>
+                        (optionClass includesBehavior: Cogit) ifTrue:<br>
+                               [^(cogitClass includesBehavior: optionClass) not]].<br>
+                aClass objectMemoryClass ifNotNil:<br>
+                       [:objectMemoryClass|<br>
+                        ((optionClass includesBehavior: ObjectMemory)<br>
+                          or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:<br>
+                               [^(objectMemoryClass includesBehavior: optionClass) not]]].<br>
+       "Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"<br>
+       {aClass initializationOptions.<br>
+         aClass.<br>
+         VMBasicConstants.<br>
+         aClass interpreterClass.<br>
+         aClass objectMemoryClass} do:<br>
+               [:scopeOrNil|<br>
+                scopeOrNil ifNotNil:<br>
+                       [:scope|<br>
+                        (scope bindingOf: key) ifNotNil:<br>
+                               [:binding|<br>
+                               binding value ~~ true ifTrue: [^true]]]].<br>
+       ^false!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----<br>
  shouldIncludeMethodFor: aClass selector: selector<br>
        "Answer whether a method shoud be translated.  Process optional methods by<br>
         interpreting the argument to the option: pragma as either a Cogit class name<br>
         or a class variable name or a variable name in VMBasicConstants.  Exclude<br>
         methods with the doNotGenerate pragma."<br>
        | optionPragmas notOptionPragmas |<br>
        (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:<br>
                [^false].<br>
<br>
        "where is pragmasAt: ??"<br>
        optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].<br>
        notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].<br>
        (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:<br>
+               ["We have to include the method if either<br>
+                       - any one of the options is false (because we want #if option...)<br>
+                       - any one of the notOptions is true (because we want #if !!option...)<br>
+                       - all of the options is true and all of the notOptions are false (because they have all been satisfied)"<br>
+               ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])<br>
+                   and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])<br>
+                  or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])<br>
+                       and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].<br>
-               [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])<br>
-                  and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].<br>
<br>
        ^true!<br>
<br>
Item was changed:<br>
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----<br>
  variableDeclarationStringsForVariable: variableNameString<br>
        "We (have to?) abuse declarations for optionality using #if C preprocessor forms.<br>
         This is ugly, but difficult to avoid.  This routine answers either a single string declaration<br>
         for a variable declared without one of these hacks, or returns the declaration split up into lines."<br>
        | declString |<br>
        declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].<br>
+       ^((declString includes: $#) and: [declString includes: $\])<br>
-       ^(declString includes: $#)<br>
                ifTrue: [declString withCRs findTokens: Character cr]<br>
                ifFalse: [{declString}]!<br>
<br>
Item was changed:<br>
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----<br>
  genPrimitiveFloatSquareRoot<br>
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT><br>
        <option: #DPFPReg0><br>
        | jumpFailAlloc |<br>
        <var: #jumpFailAlloc type: #'AbstractInstruction *'><br>
        cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:<br>
                [^UnimplementedPrimitive].<br>
        self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.<br>
        cogit SqrtRd: DPFPReg0.<br>
        jumpFailAlloc := self<br>
                                                genAllocFloatValue: DPFPReg0<br>
                                                into: SendNumArgsReg<br>
                                                scratchReg: ClassReg<br>
                                                scratchReg: TempReg.<br>
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.<br>
        cogit genPrimReturn.<br>
        jumpFailAlloc jmpTarget: cogit Label.<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----<br>
  genPrimitiveSmallFloatSquareRoot<br>
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT><br>
        <option: #Spur64BitMemoryManager><br>
+       <option: #DPFPReg0><br>
        | jumpFailAlloc jumpNegative |<br>
        <var: #jumpFailAlloc type: #'AbstractInstruction *'><br>
        <var: #jumpNegative type: #'AbstractInstruction *'><br>
        self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.<br>
        cogit<br>
                XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"<br>
                CmpRd: DPFPReg0 Rd: DPFPReg1.<br>
        jumpNegative := cogit JumpFPGreater: 0.<br>
        cogit SqrtRd: DPFPReg0.<br>
        jumpFailAlloc := self<br>
                                                genAllocFloatValue: DPFPReg0<br>
                                                into: SendNumArgsReg<br>
                                                scratchReg: ClassReg<br>
                                                scratchReg: TempReg.<br>
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.<br>
        cogit genPrimReturn.<br>
        jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----<br>
  printCInitializerOn: aStream in: aCCodeGenerator<br>
        <doNotGenerate><br>
+       | first hasCompileTimeOptionPragmas |<br>
+       hasCompileTimeOptionPragmas := false.<br>
+       primitiveGenerator ifNotNil:<br>
+               [:sel|<br>
+               (aCCodeGenerator methodNamed: sel) ifNotNil:<br>
+                       [:method|<br>
+                        method compileTimeOptionPragmas ifNotEmpty:<br>
+                               [:ctop|<br>
+                                aStream position: aStream position - 1.<br>
+                                method outputConditionalDefineFor: ctop on: aStream.<br>
+                                aStream tab.<br>
+                                hasCompileTimeOptionPragmas := true]]].<br>
+ <br>
-       | first |<br>
-       first := true.<br>
        aStream nextPut: ${; space.<br>
+       first := true.<br>
        self class instVarNamesAndTypesForTranslationDo:<br>
                [:ivn :type| | value |<br>
                first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].<br>
                value := self instVarNamed: ivn.<br>
                aStream nextPutAll: (value<br>
                                                                ifNotNil: [value isSymbol<br>
                                                                                        ifTrue: [aCCodeGenerator cFunctionNameFor: value]<br>
                                                                                        ifFalse: [aCCodeGenerator cLiteralFor: value]]<br>
                                                                ifNil: ['0'])].<br>
+       aStream space; nextPut: $}.<br>
+       hasCompileTimeOptionPragmas ifTrue:<br>
+               [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.<br>
+                self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.<br>
+                aStream nextPut: $,; cr; nextPutAll: '#endif']!<br>
-       aStream space; nextPut: $}!<br>
<br>
Item was changed:<br>
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----<br>
  tableInitializerFor: aTable in: aCCodeGenerator<br>
        ^String streamContents:<br>
                [:s|<br>
                s nextPutAll: ' = {'.<br>
                aTable object<br>
                        do: [:gt|<br>
                                s crtab.<br>
                                gt printCInitializerOn: s in: aCCodeGenerator]<br>
+                       separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].<br>
-                       separatedBy: [s nextPut: $,].<br>
                s cr; nextPut: $}]!<br>
<br>
Item was changed:<br>
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----<br>
(excessive size, no diff calculated)<br>
<br>
Item was removed:<br>
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----<br>
- primitiveArrayBecomeOneWayCopyHash<br>
-       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to<br>
-        copy the receiver's elements identity hashes over the argument's elements identity hashes."<br>
- <br>
-       | copyHashFlag ec |<br>
-       self stackTop = objectMemory trueObject<br>
-               ifTrue: [copyHashFlag := true]<br>
-               ifFalse:<br>
-                       [self stackTop = objectMemory falseObject<br>
-                               ifTrue: [copyHashFlag := false]<br>
-                               ifFalse:<br>
-                                       [self primitiveFailFor: PrimErrBadArgument.<br>
-                                        ^nil]].<br>
-       ec := objectMemory<br>
-                       become: (self stackValue: 2)<br>
-                       with: (self stackValue: 1)<br>
-                       twoWay: false<br>
-                       copyHash: copyHashFlag.<br>
-       ec = PrimNoErr<br>
-               ifTrue: [self pop: argumentCount]<br>
-               ifFalse: [self primitiveFailFor: ec]!<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----<br>
+ primitiveArrayBecomeOneWayCopyHashArg<br>
+       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to<br>
+        copy the receiver's elements identity hashes over the argument's elements identity hashes."<br>
+ <br>
+       | copyHashFlag ec |<br>
+       self stackTop = objectMemory trueObject<br>
+               ifTrue: [copyHashFlag := true]<br>
+               ifFalse:<br>
+                       [self stackTop = objectMemory falseObject<br>
+                               ifTrue: [copyHashFlag := false]<br>
+                               ifFalse:<br>
+                                       [self primitiveFailFor: PrimErrBadArgument.<br>
+                                        ^nil]].<br>
+       ec := objectMemory<br>
+                       become: (self stackValue: 2)<br>
+                       with: (self stackValue: 1)<br>
+                       twoWay: false<br>
+                       copyHash: copyHashFlag.<br>
+       ec = PrimNoErr<br>
+               ifTrue: [self pop: argumentCount]<br>
+               ifFalse: [self primitiveFailFor: ec]!<br>
<br>
Item was added:<br>
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----<br>
+ preGenerationHook: aCCodeGenerator<br>
+       "Define the primitiveTable initializer once all methods have been added."<br>
+       aCCodeGenerator vmClass primitiveTable ifNotNil:<br>
+               [:bytecodeGenTable|<br>
+               aCCodeGenerator<br>
+                       var: #primitiveGeneratorTable<br>
+                               declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',<br>
+                                                       (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable<br>
+                                                               in: aCCodeGenerator)]!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----<br>
(excessive size, no diff calculated)<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----<br>
  literal: offset ofMethod: methodPointer put: oop<br>
+       <option: #SpurObjectMemory><br>
-       <option: #SpurMemoryManager><br>
        <inline: true><br>
        objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----<br>
  maybeInlinePositive32BitIntegerFor: integerValue<br>
        "N.B. will *not* cause a GC.<br>
         integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."<br>
        <notOption: #Spur64BitMemoryManager><br>
+       <inline: #always><br>
        <var: 'integerValue' type: #'unsigned int'><br>
        | newLargeInteger |<br>
        self deny: objectMemory hasSixtyFourBitImmediates.<br>
         "force coercion because slang inliner sometimes incorrectly pass a signed int without converting to unsigned"<br>
         (self cCode: [self cCoerceSimple: integerValue to: #'unsigned int']<br>
                        inSmalltalk: [integerValue bitAnd: 1 << 32 - 1]) <= objectMemory maxSmallInteger ifTrue:<br>
                [^objectMemory integerObjectOf: integerValue].<br>
        newLargeInteger := objectMemory<br>
                                                        eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex<br>
                                                        format: (objectMemory byteFormatForNumBytes: 4)<br>
                                                        numSlots: 1.<br>
        SPURVM<br>
                ifTrue:<br>
                        ["Memory is 8 byte aligned in Spur, make sure that oversized bytes are set to zero" "eem 4/28/2016 questionable; they should never be read"<br>
                        objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).<br>
                        objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]<br>
                ifFalse: <br>
                        [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].<br>
        ^newLargeInteger!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----<br>
  unfollow: litVar atIndex: literalIndex<br>
+       <option: #SpurObjectMemory><br>
-       <option: #SpurMemoryManager><br>
        <inline: #never> "So rare it mustn't bulk up the common path"<br>
        | followed |<br>
        followed := objectMemory followForwarded: litVar.<br>
        self literal: literalIndex ofMethod: method put: followed.<br>
        ^followed!<br>
<br>
Item was changed:<br>
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----<br>
  namesDefinedAtCompileTime<br>
        "Answer the set of names for variables that should be defined at compile time.<br>
         Some of these get default values during simulation, and hence get defaulted in<br>
         the various initializeMiscConstants methods.  But that they have values should<br>
         /not/ cause the code generator to do dead code elimination based on their<br>
         default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime><br>
         will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."<br>
        ^#(     VMBIGENDIAN<br>
                IMMUTABILITY<br>
                STACKVM COGVM COGMTVM SPURVM<br>
                PharoVM                                                         "Pharo vs Squeak"<br>
                TerfVM                                                                  "Terf vs Squeak"<br>
                EnforceAccessControl                                    "Newspeak"<br>
                CheckRememberedInTrampoline             "IMMUTABILITY"<br>
+               BIT_IDENTICAL_FLOATING_POINT<br>
+               LLDB                                                                    "As of lldb-370.0.42 Swift-3.1, passing function parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"<br>
-               LLDB                                                                    "As of lldb-370.0.42 Swift-3.1, passing funciton parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"<br>
<br>
                "processor related"<br>
                __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64<br>
                _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386<br>
                x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64<br>
<br>
                "Compiler brand related"<br>
                __GNUC__<br>
                _MSC_VER<br>
                __ICC<br>
<br>
                "os related"<br>
                ACORN<br>
                __linux__<br>
                __MINGW32__<br>
                __OpenBSD__<br>
                __osf__<br>
                UNIX<br>
                WIN32 _WIN32 _WIN32_WCE<br>
                WIN64 _WIN64 _WIN64_WCE)!<br>
<br>
</blockquote></div>