VM Maker: VMMaker.oscog-eem.2742.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
5 messages Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2742.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2742.mcz

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

Name: VMMaker.oscog-eem.2742
Author: eem
Time: 20 April 2020, 7:55:24.339483 pm
UUID: 3931845a-822b-41e2-9db6-4ef3bc9a4e17
Ancestors: VMMaker.oscog-eem.2741

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.

CoInterpreter: rename primitiveArrayBecomeOneWayCopyHash to primitiveArrayBecomeOneWayCopyHashArg to differentiate it from primitiveArrayBecomeOneWayNoCopyHash.

StackInterpeeter: replace the only two uses of option: #SpurMemoryManager with option: #SpurObjectMemory.

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.

=============== Diff against VMMaker.oscog-eem.2741 ===============

Item was added:
+ ----- Method: CCodeGenerator>>optionIsFalse:in: (in category 'utilities') -----
+ optionIsFalse: pragma in: aClass
+ "Answer whether a notOption: pragma is false in the context of aClass.
+ The argument to the option: pragma is interpreted as either a Cogit class name
+ or a class variable name or a variable name in VMBasicConstants."
+ | key |
+ key := pragma argumentAt: 1.
+
+ "If the option is one to be defined at compile time we'll generate a
+ conditional around its declaration and definition."
+ ((vmClass ifNil: [VMBasicConstants]) defineAtCompileTime: key) ifTrue:
+ [^true].
+
+ "If the option is the name of a subclass of Cogit, include it if it dfoesn't inherit from the Cogit class."
+ (Smalltalk classNamed: key) ifNotNil:
+ [:optionClass|
+ aClass cogitClass ifNotNil:
+ [:cogitClass|
+ (optionClass includesBehavior: Cogit) ifTrue:
+ [^(cogitClass includesBehavior: optionClass) not]].
+ aClass objectMemoryClass ifNotNil:
+ [:objectMemoryClass|
+ ((optionClass includesBehavior: ObjectMemory)
+   or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
+ [^(objectMemoryClass includesBehavior: optionClass) not]]].
+ "Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
+ {aClass initializationOptions.
+  aClass.
+  VMBasicConstants.
+  aClass interpreterClass.
+  aClass objectMemoryClass} do:
+ [:scopeOrNil|
+ scopeOrNil ifNotNil:
+ [:scope|
+ (scope bindingOf: key) ifNotNil:
+ [:binding|
+ binding value ~~ true ifTrue: [^true]]]].
+ ^false!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
  "Answer whether a method shoud be translated.  Process optional methods by
  interpreting the argument to the option: pragma as either a Cogit class name
  or a class variable name or a variable name in VMBasicConstants.  Exclude
  methods with the doNotGenerate pragma."
  | optionPragmas notOptionPragmas |
  (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:
  [^false].
 
  "where is pragmasAt: ??"
  optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].
  notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].
  (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:
+ ["We have to include the method if either
+ - any one of the options is false (because we want #if option...)
+ - any one of the notOptions is true (because we want #if !!option...)
+ - all of the options is true and all of the notOptions are false (because they have all been satisfied)"
+ ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])
+    and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])
+   or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
+ and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].
- [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
-   and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].
 
  ^true!

Item was changed:
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
  variableDeclarationStringsForVariable: variableNameString
  "We (have to?) abuse declarations for optionality using #if C preprocessor forms.
  This is ugly, but difficult to avoid.  This routine answers either a single string declaration
  for a variable declared without one of these hacks, or returns the declaration split up into lines."
  | declString |
  declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+ ^((declString includes: $#) and: [declString includes: $\])
- ^(declString includes: $#)
  ifTrue: [declString withCRs findTokens: Character cr]
  ifFalse: [{declString}]!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveFloatSquareRoot
+ <notOption: #BIT_IDENTICAL_FLOATING_POINT>
  <option: #DPFPReg0>
  | jumpFailAlloc |
  <var: #jumpFailAlloc type: #'AbstractInstruction *'>
  cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
  [^UnimplementedPrimitive].
  self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  cogit SqrtRd: DPFPReg0.
  jumpFailAlloc := self
  genAllocFloatValue: DPFPReg0
  into: SendNumArgsReg
  scratchReg: ClassReg
  scratchReg: TempReg.
  cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
  cogit genPrimReturn.
  jumpFailAlloc jmpTarget: cogit Label.
  ^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
+ <notOption: #BIT_IDENTICAL_FLOATING_POINT>
  <option: #Spur64BitMemoryManager>
+ <option: #DPFPReg0>
  | jumpFailAlloc jumpNegative |
  <var: #jumpFailAlloc type: #'AbstractInstruction *'>
  <var: #jumpNegative type: #'AbstractInstruction *'>
  self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
  cogit
  XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"
  CmpRd: DPFPReg0 Rd: DPFPReg1.
  jumpNegative := cogit JumpFPGreater: 0.
  cogit SqrtRd: DPFPReg0.
  jumpFailAlloc := self
  genAllocFloatValue: DPFPReg0
  into: SendNumArgsReg
  scratchReg: ClassReg
  scratchReg: TempReg.
  cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
  cogit genPrimReturn.
  jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).
  ^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
  <doNotGenerate>
+ | first hasCompileTimeOptionPragmas |
+ hasCompileTimeOptionPragmas := false.
+ primitiveGenerator ifNotNil:
+ [:sel|
+ (aCCodeGenerator methodNamed: sel) ifNotNil:
+ [:method|
+ method compileTimeOptionPragmas ifNotEmpty:
+ [:ctop|
+ aStream position: aStream position - 1.
+ method outputConditionalDefineFor: ctop on: aStream.
+ aStream tab.
+ hasCompileTimeOptionPragmas := true]]].
+
- | first |
- first := true.
  aStream nextPut: ${; space.
+ first := true.
  self class instVarNamesAndTypesForTranslationDo:
  [:ivn :type| | value |
  first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
  value := self instVarNamed: ivn.
  aStream nextPutAll: (value
  ifNotNil: [value isSymbol
  ifTrue: [aCCodeGenerator cFunctionNameFor: value]
  ifFalse: [aCCodeGenerator cLiteralFor: value]]
  ifNil: ['0'])].
+ aStream space; nextPut: $}.
+ hasCompileTimeOptionPragmas ifTrue:
+ [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.
+ self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.
+ aStream nextPut: $,; cr; nextPutAll: '#endif']!
- aStream space; nextPut: $}!

Item was changed:
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----
  tableInitializerFor: aTable in: aCCodeGenerator
  ^String streamContents:
  [:s|
  s nextPutAll: ' = {'.
  aTable object
  do: [:gt|
  s crtab.
  gt printCInitializerOn: s in: aCCodeGenerator]
+ separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].
- separatedBy: [s nextPut: $,].
  s cr; nextPut: $}]!

Item was changed:
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----
- primitiveArrayBecomeOneWayCopyHash
- "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
- copy the receiver's elements identity hashes over the argument's elements identity hashes."
-
- | copyHashFlag ec |
- self stackTop = objectMemory trueObject
- ifTrue: [copyHashFlag := true]
- ifFalse:
- [self stackTop = objectMemory falseObject
- ifTrue: [copyHashFlag := false]
- ifFalse:
- [self primitiveFailFor: PrimErrBadArgument.
- ^nil]].
- ec := objectMemory
- become: (self stackValue: 2)
- with: (self stackValue: 1)
- twoWay: false
- copyHash: copyHashFlag.
- ec = PrimNoErr
- ifTrue: [self pop: argumentCount]
- ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
+ primitiveArrayBecomeOneWayCopyHashArg
+ "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+ copy the receiver's elements identity hashes over the argument's elements identity hashes."
+
+ | copyHashFlag ec |
+ self stackTop = objectMemory trueObject
+ ifTrue: [copyHashFlag := true]
+ ifFalse:
+ [self stackTop = objectMemory falseObject
+ ifTrue: [copyHashFlag := false]
+ ifFalse:
+ [self primitiveFailFor: PrimErrBadArgument.
+ ^nil]].
+ ec := objectMemory
+ become: (self stackValue: 2)
+ with: (self stackValue: 1)
+ twoWay: false
+ copyHash: copyHashFlag.
+ ec = PrimNoErr
+ ifTrue: [self pop: argumentCount]
+ ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGenerator
+ "Define the primitiveTable initializer once all methods have been added."
+ aCCodeGenerator vmClass primitiveTable ifNotNil:
+ [:bytecodeGenTable|
+ aCCodeGenerator
+ var: #primitiveGeneratorTable
+ declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+ (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+ in: aCCodeGenerator)]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----
  literal: offset ofMethod: methodPointer put: oop
+ <option: #SpurObjectMemory>
- <option: #SpurMemoryManager>
  <inline: true>
  objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop
  !

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
  "N.B. will *not* cause a GC.
  integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
  <notOption: #Spur64BitMemoryManager>
+ <inline: #always>
  <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: ClassLargePositiveIntegerCompactIndex
  format: (objectMemory byteFormatForNumBytes: 4)
  numSlots: 1.
  SPURVM
  ifTrue:
  ["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"
  objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
  objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
  ifFalse:
  [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
  ^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----
  unfollow: litVar atIndex: literalIndex
+ <option: #SpurObjectMemory>
- <option: #SpurMemoryManager>
  <inline: #never> "So rare it mustn't bulk up the common path"
  | followed |
  followed := objectMemory followForwarded: litVar.
  self literal: literalIndex ofMethod: method put: followed.
  ^followed!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
  "Answer the set of names for variables that should be defined at compile time.
  Some of these get default values during simulation, and hence get defaulted in
  the various initializeMiscConstants methods.  But that they have values should
  /not/ cause the code generator to do dead code elimination based on their
  default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
  will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
  ^#( VMBIGENDIAN
  IMMUTABILITY
  STACKVM COGVM COGMTVM SPURVM
  PharoVM "Pharo vs Squeak"
  TerfVM "Terf vs Squeak"
  EnforceAccessControl "Newspeak"
  CheckRememberedInTrampoline "IMMUTABILITY"
+ BIT_IDENTICAL_FLOATING_POINT
+ 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>"
- 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>"
 
  "processor related"
  __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
  _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
  x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64
 
  "Compiler brand related"
  __GNUC__
  _MSC_VER
  __ICC
 
  "os related"
  ACORN
  __linux__
  __MINGW32__
  __OpenBSD__
  __osf__
  UNIX
  WIN32 _WIN32 _WIN32_WCE
  WIN64 _WIN64 _WIN64_WCE)!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2742.mcz

Nicolas Cellier
 
Hi Eliot,
IEEE754 mandates that sqrt be correctly rounded.
Hence it should be bit identical on every compliant architecture.

Le mar. 21 avr. 2020 à 04:55, <[hidden email]> a écrit :
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2742.mcz

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

Name: VMMaker.oscog-eem.2742
Author: eem
Time: 20 April 2020, 7:55:24.339483 pm
UUID: 3931845a-822b-41e2-9db6-4ef3bc9a4e17
Ancestors: VMMaker.oscog-eem.2741

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.

CoInterpreter: rename primitiveArrayBecomeOneWayCopyHash to primitiveArrayBecomeOneWayCopyHashArg to differentiate it from primitiveArrayBecomeOneWayNoCopyHash.

StackInterpeeter: replace the only two uses of option: #SpurMemoryManager with option: #SpurObjectMemory.

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.

=============== Diff against VMMaker.oscog-eem.2741 ===============

Item was added:
+ ----- Method: CCodeGenerator>>optionIsFalse:in: (in category 'utilities') -----
+ optionIsFalse: pragma in: aClass
+       "Answer whether a notOption: pragma is false in the context of aClass.
+        The argument to the option: pragma is interpreted as either a Cogit class name
+        or a class variable name or a variable name in VMBasicConstants."
+       | key |
+       key := pragma argumentAt: 1.
+
+       "If the option is one to be defined at compile time we'll generate a
+        conditional around its declaration and definition."
+       ((vmClass ifNil: [VMBasicConstants]) defineAtCompileTime: key) ifTrue:
+               [^true].
+
+       "If the option is the name of a subclass of Cogit, include it if it dfoesn't inherit from the Cogit class."
+       (Smalltalk classNamed: key) ifNotNil:
+               [:optionClass|
+                aClass cogitClass ifNotNil:
+                       [:cogitClass|
+                        (optionClass includesBehavior: Cogit) ifTrue:
+                               [^(cogitClass includesBehavior: optionClass) not]].
+                aClass objectMemoryClass ifNotNil:
+                       [:objectMemoryClass|
+                        ((optionClass includesBehavior: ObjectMemory)
+                          or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
+                               [^(objectMemoryClass includesBehavior: optionClass) not]]].
+       "Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
+       {aClass initializationOptions.
+         aClass.
+         VMBasicConstants.
+         aClass interpreterClass.
+         aClass objectMemoryClass} do:
+               [:scopeOrNil|
+                scopeOrNil ifNotNil:
+                       [:scope|
+                        (scope bindingOf: key) ifNotNil:
+                               [:binding|
+                               binding value ~~ true ifTrue: [^true]]]].
+       ^false!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
        "Answer whether a method shoud be translated.  Process optional methods by
         interpreting the argument to the option: pragma as either a Cogit class name
         or a class variable name or a variable name in VMBasicConstants.  Exclude
         methods with the doNotGenerate pragma."
        | optionPragmas notOptionPragmas |
        (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:
                [^false].

        "where is pragmasAt: ??"
        optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].
        notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].
        (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:
+               ["We have to include the method if either
+                       - any one of the options is false (because we want #if option...)
+                       - any one of the notOptions is true (because we want #if !!option...)
+                       - all of the options is true and all of the notOptions are false (because they have all been satisfied)"
+               ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])
+                   and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])
+                  or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
+                       and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].
-               [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
-                  and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].

        ^true!

Item was changed:
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
  variableDeclarationStringsForVariable: variableNameString
        "We (have to?) abuse declarations for optionality using #if C preprocessor forms.
         This is ugly, but difficult to avoid.  This routine answers either a single string declaration
         for a variable declared without one of these hacks, or returns the declaration split up into lines."
        | declString |
        declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+       ^((declString includes: $#) and: [declString includes: $\])
-       ^(declString includes: $#)
                ifTrue: [declString withCRs findTokens: Character cr]
                ifFalse: [{declString}]!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #DPFPReg0>
        | jumpFailAlloc |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
                [^UnimplementedPrimitive].
        self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpFailAlloc jmpTarget: cogit Label.
        ^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #Spur64BitMemoryManager>
+       <option: #DPFPReg0>
        | jumpFailAlloc jumpNegative |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        <var: #jumpNegative type: #'AbstractInstruction *'>
        self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
        cogit
                XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"
                CmpRd: DPFPReg0 Rd: DPFPReg1.
        jumpNegative := cogit JumpFPGreater: 0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).
        ^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
        <doNotGenerate>
+       | first hasCompileTimeOptionPragmas |
+       hasCompileTimeOptionPragmas := false.
+       primitiveGenerator ifNotNil:
+               [:sel|
+               (aCCodeGenerator methodNamed: sel) ifNotNil:
+                       [:method|
+                        method compileTimeOptionPragmas ifNotEmpty:
+                               [:ctop|
+                                aStream position: aStream position - 1.
+                                method outputConditionalDefineFor: ctop on: aStream.
+                                aStream tab.
+                                hasCompileTimeOptionPragmas := true]]].
+
-       | first |
-       first := true.
        aStream nextPut: ${; space.
+       first := true.
        self class instVarNamesAndTypesForTranslationDo:
                [:ivn :type| | value |
                first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
                value := self instVarNamed: ivn.
                aStream nextPutAll: (value
                                                                ifNotNil: [value isSymbol
                                                                                        ifTrue: [aCCodeGenerator cFunctionNameFor: value]
                                                                                        ifFalse: [aCCodeGenerator cLiteralFor: value]]
                                                                ifNil: ['0'])].
+       aStream space; nextPut: $}.
+       hasCompileTimeOptionPragmas ifTrue:
+               [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.
+                self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.
+                aStream nextPut: $,; cr; nextPutAll: '#endif']!
-       aStream space; nextPut: $}!

Item was changed:
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----
  tableInitializerFor: aTable in: aCCodeGenerator
        ^String streamContents:
                [:s|
                s nextPutAll: ' = {'.
                aTable object
                        do: [:gt|
                                s crtab.
                                gt printCInitializerOn: s in: aCCodeGenerator]
+                       separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].
-                       separatedBy: [s nextPut: $,].
                s cr; nextPut: $}]!

Item was changed:
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----
- primitiveArrayBecomeOneWayCopyHash
-       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
-        copy the receiver's elements identity hashes over the argument's elements identity hashes."
-
-       | copyHashFlag ec |
-       self stackTop = objectMemory trueObject
-               ifTrue: [copyHashFlag := true]
-               ifFalse:
-                       [self stackTop = objectMemory falseObject
-                               ifTrue: [copyHashFlag := false]
-                               ifFalse:
-                                       [self primitiveFailFor: PrimErrBadArgument.
-                                        ^nil]].
-       ec := objectMemory
-                       become: (self stackValue: 2)
-                       with: (self stackValue: 1)
-                       twoWay: false
-                       copyHash: copyHashFlag.
-       ec = PrimNoErr
-               ifTrue: [self pop: argumentCount]
-               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
+ primitiveArrayBecomeOneWayCopyHashArg
+       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+        copy the receiver's elements identity hashes over the argument's elements identity hashes."
+
+       | copyHashFlag ec |
+       self stackTop = objectMemory trueObject
+               ifTrue: [copyHashFlag := true]
+               ifFalse:
+                       [self stackTop = objectMemory falseObject
+                               ifTrue: [copyHashFlag := false]
+                               ifFalse:
+                                       [self primitiveFailFor: PrimErrBadArgument.
+                                        ^nil]].
+       ec := objectMemory
+                       become: (self stackValue: 2)
+                       with: (self stackValue: 1)
+                       twoWay: false
+                       copyHash: copyHashFlag.
+       ec = PrimNoErr
+               ifTrue: [self pop: argumentCount]
+               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGenerator
+       "Define the primitiveTable initializer once all methods have been added."
+       aCCodeGenerator vmClass primitiveTable ifNotNil:
+               [:bytecodeGenTable|
+               aCCodeGenerator
+                       var: #primitiveGeneratorTable
+                               declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+                                                       (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+                                                               in: aCCodeGenerator)]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----
  literal: offset ofMethod: methodPointer put: oop
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: true>
        objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop
  !

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
        "N.B. will *not* cause a GC.
         integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
        <notOption: #Spur64BitMemoryManager>
+       <inline: #always>
        <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: ClassLargePositiveIntegerCompactIndex
                                                        format: (objectMemory byteFormatForNumBytes: 4)
                                                        numSlots: 1.
        SPURVM
                ifTrue:
                        ["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"
                        objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
                        objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
                ifFalse:
                        [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
        ^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----
  unfollow: litVar atIndex: literalIndex
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: #never> "So rare it mustn't bulk up the common path"
        | followed |
        followed := objectMemory followForwarded: litVar.
        self literal: literalIndex ofMethod: method put: followed.
        ^followed!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
        "Answer the set of names for variables that should be defined at compile time.
         Some of these get default values during simulation, and hence get defaulted in
         the various initializeMiscConstants methods.  But that they have values should
         /not/ cause the code generator to do dead code elimination based on their
         default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
         will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
        ^#(     VMBIGENDIAN
                IMMUTABILITY
                STACKVM COGVM COGMTVM SPURVM
                PharoVM                                                         "Pharo vs Squeak"
                TerfVM                                                                  "Terf vs Squeak"
                EnforceAccessControl                                    "Newspeak"
                CheckRememberedInTrampoline             "IMMUTABILITY"
+               BIT_IDENTICAL_FLOATING_POINT
+               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>"
-               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>"

                "processor related"
                __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
                _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
                x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64

                "Compiler brand related"
                __GNUC__
                _MSC_VER
                __ICC

                "os related"
                ACORN
                __linux__
                __MINGW32__
                __OpenBSD__
                __osf__
                UNIX
                WIN32 _WIN32 _WIN32_WCE
                WIN64 _WIN64 _WIN64_WCE)!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2742.mcz

Eliot Miranda-2
 
Hi Nicoilas,

On Tue, Apr 21, 2020 at 6:16 AM Nicolas Cellier <[hidden email]> wrote:
 
Hi Eliot,
IEEE754 mandates that sqrt be correctly rounded.
Hence it should be bit identical on every compliant architecture.

That's good to know.! I c an change thin gas back soon.  First I want to see that I can link the VM against https://github.com/nicolas-cellier-aka-nice/fdlibm.git.  I have modified the Mac makefile to build libm.a from your fdlibm, and link against it but so far I'm not sure if the m is actually using the code.  Would you have time for us to discuss in a video chat, say on Discord, some times this week?  I'm simply not confident with the math side of things.  You're the expert and I need your input.

+         aClass interpreterClass.
+         aClass objectMemoryClass} do:
+               [:scopeOrNil|
+                scopeOrNil ifNotNil:
+                       [:scope|
+                        (scope bindingOf: key) ifNotNil:
+                               [:binding|
+                               binding value ~~ true ifTrue: [^true]]]].
+       ^false!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
        "Answer whether a method shoud be translated.  Process optional methods by
         interpreting the argument to the option: pragma as either a Cogit class name
         or a class variable name or a variable name in VMBasicConstants.  Exclude
         methods with the doNotGenerate pragma."
        | optionPragmas notOptionPragmas |
        (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:
                [^false].

        "where is pragmasAt: ??"
        optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].
        notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].
        (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:
+               ["We have to include the method if either
+                       - any one of the options is false (because we want #if option...)
+                       - any one of the notOptions is true (because we want #if !!option...)
+                       - all of the options is true and all of the notOptions are false (because they have all been satisfied)"
+               ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])
+                   and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])
+                  or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
+                       and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].
-               [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
-                  and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].

        ^true!

Item was changed:
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
  variableDeclarationStringsForVariable: variableNameString
        "We (have to?) abuse declarations for optionality using #if C preprocessor forms.
         This is ugly, but difficult to avoid.  This routine answers either a single string declaration
         for a variable declared without one of these hacks, or returns the declaration split up into lines."
        | declString |
        declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+       ^((declString includes: $#) and: [declString includes: $\])
-       ^(declString includes: $#)
                ifTrue: [declString withCRs findTokens: Character cr]
                ifFalse: [{declString}]!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #DPFPReg0>
        | jumpFailAlloc |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
                [^UnimplementedPrimitive].
        self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpFailAlloc jmpTarget: cogit Label.
        ^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #Spur64BitMemoryManager>
+       <option: #DPFPReg0>
        | jumpFailAlloc jumpNegative |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        <var: #jumpNegative type: #'AbstractInstruction *'>
        self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
        cogit
                XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"
                CmpRd: DPFPReg0 Rd: DPFPReg1.
        jumpNegative := cogit JumpFPGreater: 0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).
        ^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
        <doNotGenerate>
+       | first hasCompileTimeOptionPragmas |
+       hasCompileTimeOptionPragmas := false.
+       primitiveGenerator ifNotNil:
+               [:sel|
+               (aCCodeGenerator methodNamed: sel) ifNotNil:
+                       [:method|
+                        method compileTimeOptionPragmas ifNotEmpty:
+                               [:ctop|
+                                aStream position: aStream position - 1.
+                                method outputConditionalDefineFor: ctop on: aStream.
+                                aStream tab.
+                                hasCompileTimeOptionPragmas := true]]].
+
-       | first |
-       first := true.
        aStream nextPut: ${; space.
+       first := true.
        self class instVarNamesAndTypesForTranslationDo:
                [:ivn :type| | value |
                first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
                value := self instVarNamed: ivn.
                aStream nextPutAll: (value
                                                                ifNotNil: [value isSymbol
                                                                                        ifTrue: [aCCodeGenerator cFunctionNameFor: value]
                                                                                        ifFalse: [aCCodeGenerator cLiteralFor: value]]
                                                                ifNil: ['0'])].
+       aStream space; nextPut: $}.
+       hasCompileTimeOptionPragmas ifTrue:
+               [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.
+                self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.
+                aStream nextPut: $,; cr; nextPutAll: '#endif']!
-       aStream space; nextPut: $}!

Item was changed:
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----
  tableInitializerFor: aTable in: aCCodeGenerator
        ^String streamContents:
                [:s|
                s nextPutAll: ' = {'.
                aTable object
                        do: [:gt|
                                s crtab.
                                gt printCInitializerOn: s in: aCCodeGenerator]
+                       separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].
-                       separatedBy: [s nextPut: $,].
                s cr; nextPut: $}]!

Item was changed:
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----
- primitiveArrayBecomeOneWayCopyHash
-       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
-        copy the receiver's elements identity hashes over the argument's elements identity hashes."
-
-       | copyHashFlag ec |
-       self stackTop = objectMemory trueObject
-               ifTrue: [copyHashFlag := true]
-               ifFalse:
-                       [self stackTop = objectMemory falseObject
-                               ifTrue: [copyHashFlag := false]
-                               ifFalse:
-                                       [self primitiveFailFor: PrimErrBadArgument.
-                                        ^nil]].
-       ec := objectMemory
-                       become: (self stackValue: 2)
-                       with: (self stackValue: 1)
-                       twoWay: false
-                       copyHash: copyHashFlag.
-       ec = PrimNoErr
-               ifTrue: [self pop: argumentCount]
-               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
+ primitiveArrayBecomeOneWayCopyHashArg
+       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+        copy the receiver's elements identity hashes over the argument's elements identity hashes."
+
+       | copyHashFlag ec |
+       self stackTop = objectMemory trueObject
+               ifTrue: [copyHashFlag := true]
+               ifFalse:
+                       [self stackTop = objectMemory falseObject
+                               ifTrue: [copyHashFlag := false]
+                               ifFalse:
+                                       [self primitiveFailFor: PrimErrBadArgument.
+                                        ^nil]].
+       ec := objectMemory
+                       become: (self stackValue: 2)
+                       with: (self stackValue: 1)
+                       twoWay: false
+                       copyHash: copyHashFlag.
+       ec = PrimNoErr
+               ifTrue: [self pop: argumentCount]
+               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGenerator
+       "Define the primitiveTable initializer once all methods have been added."
+       aCCodeGenerator vmClass primitiveTable ifNotNil:
+               [:bytecodeGenTable|
+               aCCodeGenerator
+                       var: #primitiveGeneratorTable
+                               declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+                                                       (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+                                                               in: aCCodeGenerator)]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----
  literal: offset ofMethod: methodPointer put: oop
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: true>
        objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop
  !

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
        "N.B. will *not* cause a GC.
         integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
        <notOption: #Spur64BitMemoryManager>
+       <inline: #always>
        <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: ClassLargePositiveIntegerCompactIndex
                                                        format: (objectMemory byteFormatForNumBytes: 4)
                                                        numSlots: 1.
        SPURVM
                ifTrue:
                        ["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"
                        objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
                        objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
                ifFalse:
                        [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
        ^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----
  unfollow: litVar atIndex: literalIndex
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: #never> "So rare it mustn't bulk up the common path"
        | followed |
        followed := objectMemory followForwarded: litVar.
        self literal: literalIndex ofMethod: method put: followed.
        ^followed!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
        "Answer the set of names for variables that should be defined at compile time.
         Some of these get default values during simulation, and hence get defaulted in
         the various initializeMiscConstants methods.  But that they have values should
         /not/ cause the code generator to do dead code elimination based on their
         default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
         will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
        ^#(     VMBIGENDIAN
                IMMUTABILITY
                STACKVM COGVM COGMTVM SPURVM
                PharoVM                                                         "Pharo vs Squeak"
                TerfVM                                                                  "Terf vs Squeak"
                EnforceAccessControl                                    "Newspeak"
                CheckRememberedInTrampoline             "IMMUTABILITY"
+               BIT_IDENTICAL_FLOATING_POINT
+               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>"
-               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>"

                "processor related"
                __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
                _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
                x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64

                "Compiler brand related"
                __GNUC__
                _MSC_VER
                __ICC

                "os related"
                ACORN
                __linux__
                __MINGW32__
                __OpenBSD__
                __osf__
                UNIX
                WIN32 _WIN32 _WIN32_WCE
                WIN64 _WIN64 _WIN64_WCE)!



--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2742.mcz

Nicolas Cellier
 
Hi Eliot,
I don't know if I can help you wrt to Mac library system which is a bit opaque to me (I never took time to inquire this framework thing).
But I can try setting tests to verify which version is used.
On 64 bits macos, I still have this libm bug: https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/383
So we have at least one easy test case telling us if we effectively link against fdlibm or not: the regular Squeak FloatTest fails if we link ldexp against apple's libm.

Otherwisen we can compile the FloatMathPlugin and compare results of regular primitives vs FloatMathPlugin primitives on some well chosen cases... (or a big list of  random cases...).
We can contact on Discord tomorrow around 19h00 UTC if you want.

Le mer. 22 avr. 2020 à 02:45, Eliot Miranda <[hidden email]> a écrit :
 
Hi Nicoilas,

On Tue, Apr 21, 2020 at 6:16 AM Nicolas Cellier <[hidden email]> wrote:
 
Hi Eliot,
IEEE754 mandates that sqrt be correctly rounded.
Hence it should be bit identical on every compliant architecture.

That's good to know.! I c an change thin gas back soon.  First I want to see that I can link the VM against https://github.com/nicolas-cellier-aka-nice/fdlibm.git.  I have modified the Mac makefile to build libm.a from your fdlibm, and link against it but so far I'm not sure if the m is actually using the code.  Would you have time for us to discuss in a video chat, say on Discord, some times this week?  I'm simply not confident with the math side of things.  You're the expert and I need your input.

+         aClass interpreterClass.
+         aClass objectMemoryClass} do:
+               [:scopeOrNil|
+                scopeOrNil ifNotNil:
+                       [:scope|
+                        (scope bindingOf: key) ifNotNil:
+                               [:binding|
+                               binding value ~~ true ifTrue: [^true]]]].
+       ^false!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
        "Answer whether a method shoud be translated.  Process optional methods by
         interpreting the argument to the option: pragma as either a Cogit class name
         or a class variable name or a variable name in VMBasicConstants.  Exclude
         methods with the doNotGenerate pragma."
        | optionPragmas notOptionPragmas |
        (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:
                [^false].

        "where is pragmasAt: ??"
        optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].
        notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].
        (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:
+               ["We have to include the method if either
+                       - any one of the options is false (because we want #if option...)
+                       - any one of the notOptions is true (because we want #if !!option...)
+                       - all of the options is true and all of the notOptions are false (because they have all been satisfied)"
+               ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])
+                   and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])
+                  or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
+                       and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].
-               [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
-                  and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].

        ^true!

Item was changed:
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
  variableDeclarationStringsForVariable: variableNameString
        "We (have to?) abuse declarations for optionality using #if C preprocessor forms.
         This is ugly, but difficult to avoid.  This routine answers either a single string declaration
         for a variable declared without one of these hacks, or returns the declaration split up into lines."
        | declString |
        declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+       ^((declString includes: $#) and: [declString includes: $\])
-       ^(declString includes: $#)
                ifTrue: [declString withCRs findTokens: Character cr]
                ifFalse: [{declString}]!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #DPFPReg0>
        | jumpFailAlloc |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
                [^UnimplementedPrimitive].
        self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpFailAlloc jmpTarget: cogit Label.
        ^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #Spur64BitMemoryManager>
+       <option: #DPFPReg0>
        | jumpFailAlloc jumpNegative |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        <var: #jumpNegative type: #'AbstractInstruction *'>
        self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
        cogit
                XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"
                CmpRd: DPFPReg0 Rd: DPFPReg1.
        jumpNegative := cogit JumpFPGreater: 0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).
        ^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
        <doNotGenerate>
+       | first hasCompileTimeOptionPragmas |
+       hasCompileTimeOptionPragmas := false.
+       primitiveGenerator ifNotNil:
+               [:sel|
+               (aCCodeGenerator methodNamed: sel) ifNotNil:
+                       [:method|
+                        method compileTimeOptionPragmas ifNotEmpty:
+                               [:ctop|
+                                aStream position: aStream position - 1.
+                                method outputConditionalDefineFor: ctop on: aStream.
+                                aStream tab.
+                                hasCompileTimeOptionPragmas := true]]].
+
-       | first |
-       first := true.
        aStream nextPut: ${; space.
+       first := true.
        self class instVarNamesAndTypesForTranslationDo:
                [:ivn :type| | value |
                first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
                value := self instVarNamed: ivn.
                aStream nextPutAll: (value
                                                                ifNotNil: [value isSymbol
                                                                                        ifTrue: [aCCodeGenerator cFunctionNameFor: value]
                                                                                        ifFalse: [aCCodeGenerator cLiteralFor: value]]
                                                                ifNil: ['0'])].
+       aStream space; nextPut: $}.
+       hasCompileTimeOptionPragmas ifTrue:
+               [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.
+                self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.
+                aStream nextPut: $,; cr; nextPutAll: '#endif']!
-       aStream space; nextPut: $}!

Item was changed:
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----
  tableInitializerFor: aTable in: aCCodeGenerator
        ^String streamContents:
                [:s|
                s nextPutAll: ' = {'.
                aTable object
                        do: [:gt|
                                s crtab.
                                gt printCInitializerOn: s in: aCCodeGenerator]
+                       separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].
-                       separatedBy: [s nextPut: $,].
                s cr; nextPut: $}]!

Item was changed:
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----
- primitiveArrayBecomeOneWayCopyHash
-       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
-        copy the receiver's elements identity hashes over the argument's elements identity hashes."
-
-       | copyHashFlag ec |
-       self stackTop = objectMemory trueObject
-               ifTrue: [copyHashFlag := true]
-               ifFalse:
-                       [self stackTop = objectMemory falseObject
-                               ifTrue: [copyHashFlag := false]
-                               ifFalse:
-                                       [self primitiveFailFor: PrimErrBadArgument.
-                                        ^nil]].
-       ec := objectMemory
-                       become: (self stackValue: 2)
-                       with: (self stackValue: 1)
-                       twoWay: false
-                       copyHash: copyHashFlag.
-       ec = PrimNoErr
-               ifTrue: [self pop: argumentCount]
-               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
+ primitiveArrayBecomeOneWayCopyHashArg
+       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+        copy the receiver's elements identity hashes over the argument's elements identity hashes."
+
+       | copyHashFlag ec |
+       self stackTop = objectMemory trueObject
+               ifTrue: [copyHashFlag := true]
+               ifFalse:
+                       [self stackTop = objectMemory falseObject
+                               ifTrue: [copyHashFlag := false]
+                               ifFalse:
+                                       [self primitiveFailFor: PrimErrBadArgument.
+                                        ^nil]].
+       ec := objectMemory
+                       become: (self stackValue: 2)
+                       with: (self stackValue: 1)
+                       twoWay: false
+                       copyHash: copyHashFlag.
+       ec = PrimNoErr
+               ifTrue: [self pop: argumentCount]
+               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGenerator
+       "Define the primitiveTable initializer once all methods have been added."
+       aCCodeGenerator vmClass primitiveTable ifNotNil:
+               [:bytecodeGenTable|
+               aCCodeGenerator
+                       var: #primitiveGeneratorTable
+                               declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+                                                       (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+                                                               in: aCCodeGenerator)]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----
  literal: offset ofMethod: methodPointer put: oop
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: true>
        objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop
  !

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
        "N.B. will *not* cause a GC.
         integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
        <notOption: #Spur64BitMemoryManager>
+       <inline: #always>
        <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: ClassLargePositiveIntegerCompactIndex
                                                        format: (objectMemory byteFormatForNumBytes: 4)
                                                        numSlots: 1.
        SPURVM
                ifTrue:
                        ["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"
                        objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
                        objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
                ifFalse:
                        [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
        ^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----
  unfollow: litVar atIndex: literalIndex
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: #never> "So rare it mustn't bulk up the common path"
        | followed |
        followed := objectMemory followForwarded: litVar.
        self literal: literalIndex ofMethod: method put: followed.
        ^followed!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
        "Answer the set of names for variables that should be defined at compile time.
         Some of these get default values during simulation, and hence get defaulted in
         the various initializeMiscConstants methods.  But that they have values should
         /not/ cause the code generator to do dead code elimination based on their
         default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
         will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
        ^#(     VMBIGENDIAN
                IMMUTABILITY
                STACKVM COGVM COGMTVM SPURVM
                PharoVM                                                         "Pharo vs Squeak"
                TerfVM                                                                  "Terf vs Squeak"
                EnforceAccessControl                                    "Newspeak"
                CheckRememberedInTrampoline             "IMMUTABILITY"
+               BIT_IDENTICAL_FLOATING_POINT
+               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>"
-               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>"

                "processor related"
                __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
                _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
                x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64

                "Compiler brand related"
                __GNUC__
                _MSC_VER
                __ICC

                "os related"
                ACORN
                __linux__
                __MINGW32__
                __OpenBSD__
                __osf__
                UNIX
                WIN32 _WIN32 _WIN32_WCE
                WIN64 _WIN64 _WIN64_WCE)!



--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2742.mcz

Eliot Miranda-2
 
Hi Nicolas,

On Wed, Apr 22, 2020 at 12:27 PM Nicolas Cellier <[hidden email]> wrote:
 
Hi Eliot,
I don't know if I can help you wrt to Mac library system which is a bit opaque to me (I never took time to inquire this framework thing).
But I can try setting tests to verify which version is used.
On 64 bits macos, I still have this libm bug: https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/383
So we have at least one easy test case telling us if we effectively link against fdlibm or not: the regular Squeak FloatTest fails if we link ldexp against apple's libm.

OK, good, that's a useful test.   So far I have your fork of fdlibm compiling and linking against the VM on 64-bit Mac, and am working on 64-bit Windows (cygwin).  Once I have that working I'll commit and you can review.  I'll commit on Cog because it doesn't affect normal builds, being dead code to any build that doesn't set BIT_IDENTICAL_FLOATING_POINT in the Makefile (you'll see what I mean when you view the commit).


Otherwisen we can compile the FloatMathPlugin and compare results of regular primitives vs FloatMathPlugin primitives on some well chosen cases... (or a big list of  random cases...).
We can contact on Discord tomorrow around 19h00 UTC if you want.

Yes, please.  I want to discuss this with you to see if I have the right idea/misunderastand something fundamental, am doing the right thing/wasting effort, etc.  Hopefully there will be code for is to look at in Cog by then.

Cheers!


Le mer. 22 avr. 2020 à 02:45, Eliot Miranda <[hidden email]> a écrit :
 
Hi Nicoilas,

On Tue, Apr 21, 2020 at 6:16 AM Nicolas Cellier <[hidden email]> wrote:
 
Hi Eliot,
IEEE754 mandates that sqrt be correctly rounded.
Hence it should be bit identical on every compliant architecture.

That's good to know.! I c an change thin gas back soon.  First I want to see that I can link the VM against https://github.com/nicolas-cellier-aka-nice/fdlibm.git.  I have modified the Mac makefile to build libm.a from your fdlibm, and link against it but so far I'm not sure if the m is actually using the code.  Would you have time for us to discuss in a video chat, say on Discord, some times this week?  I'm simply not confident with the math side of things.  You're the expert and I need your input.

+         aClass interpreterClass.
+         aClass objectMemoryClass} do:
+               [:scopeOrNil|
+                scopeOrNil ifNotNil:
+                       [:scope|
+                        (scope bindingOf: key) ifNotNil:
+                               [:binding|
+                               binding value ~~ true ifTrue: [^true]]]].
+       ^false!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
        "Answer whether a method shoud be translated.  Process optional methods by
         interpreting the argument to the option: pragma as either a Cogit class name
         or a class variable name or a variable name in VMBasicConstants.  Exclude
         methods with the doNotGenerate pragma."
        | optionPragmas notOptionPragmas |
        (aClass >> selector pragmaAt: #doNotGenerate) ifNotNil:
                [^false].

        "where is pragmasAt: ??"
        optionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #option:].
        notOptionPragmas := (aClass >> selector) pragmas select: [:p| p keyword == #notOption:].
        (optionPragmas notEmpty or: [notOptionPragmas notEmpty]) ifTrue:
+               ["We have to include the method if either
+                       - any one of the options is false (because we want #if option...)
+                       - any one of the notOptions is true (because we want #if !!option...)
+                       - all of the options is true and all of the notOptions are false (because they have all been satisfied)"
+               ^((optionPragmas anySatisfy: [:pragma| (self optionIsTrue: pragma in: aClass) not])
+                   and: [notOptionPragmas anySatisfy: [:pragma| (self optionIsFalse: pragma in: aClass) not]])
+                  or: [(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
+                       and: [notOptionPragmas allSatisfy: [:pragma| self optionIsFalse: pragma in: aClass]]]].
-               [^(optionPragmas allSatisfy: [:pragma| self optionIsTrue: pragma in: aClass])
-                  and: [notOptionPragmas noneSatisfy: [:pragma| self optionIsTrue: pragma in: aClass]]].

        ^true!

Item was changed:
  ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
  variableDeclarationStringsForVariable: variableNameString
        "We (have to?) abuse declarations for optionality using #if C preprocessor forms.
         This is ugly, but difficult to avoid.  This routine answers either a single string declaration
         for a variable declared without one of these hacks, or returns the declaration split up into lines."
        | declString |
        declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+       ^((declString includes: $#) and: [declString includes: $\])
-       ^(declString includes: $#)
                ifTrue: [declString withCRs findTokens: Character cr]
                ifFalse: [{declString}]!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #DPFPReg0>
        | jumpFailAlloc |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        cogit processorHasDoublePrecisionFloatingPointSupport ifFalse:
                [^UnimplementedPrimitive].
        self genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpFailAlloc jmpTarget: cogit Label.
        ^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
+       <notOption: #BIT_IDENTICAL_FLOATING_POINT>
        <option: #Spur64BitMemoryManager>
+       <option: #DPFPReg0>
        | jumpFailAlloc jumpNegative |
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        <var: #jumpNegative type: #'AbstractInstruction *'>
        self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
        cogit
                XorRd: DPFPReg1 Rd: DPFPReg1; "+0.0 is all zeros"
                CmpRd: DPFPReg0 Rd: DPFPReg1.
        jumpNegative := cogit JumpFPGreater: 0.
        cogit SqrtRd: DPFPReg0.
        jumpFailAlloc := self
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
        cogit genPrimReturn.
        jumpNegative jmpTarget: (jumpFailAlloc jmpTarget: cogit Label).
        ^0!

Item was changed:
  ----- Method: CogPrimitiveDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
        <doNotGenerate>
+       | first hasCompileTimeOptionPragmas |
+       hasCompileTimeOptionPragmas := false.
+       primitiveGenerator ifNotNil:
+               [:sel|
+               (aCCodeGenerator methodNamed: sel) ifNotNil:
+                       [:method|
+                        method compileTimeOptionPragmas ifNotEmpty:
+                               [:ctop|
+                                aStream position: aStream position - 1.
+                                method outputConditionalDefineFor: ctop on: aStream.
+                                aStream tab.
+                                hasCompileTimeOptionPragmas := true]]].
+
-       | first |
-       first := true.
        aStream nextPut: ${; space.
+       first := true.
        self class instVarNamesAndTypesForTranslationDo:
                [:ivn :type| | value |
                first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
                value := self instVarNamed: ivn.
                aStream nextPutAll: (value
                                                                ifNotNil: [value isSymbol
                                                                                        ifTrue: [aCCodeGenerator cFunctionNameFor: value]
                                                                                        ifFalse: [aCCodeGenerator cLiteralFor: value]]
                                                                ifNil: ['0'])].
+       aStream space; nextPut: $}.
+       hasCompileTimeOptionPragmas ifTrue:
+               [aStream nextPut: $,; cr; nextPutAll: '#else'; crtab.
+                self copy primitiveGenerator: nil; primNumArgs: -1; printCInitializerOn: aStream in: aCCodeGenerator.
+                aStream nextPut: $,; cr; nextPutAll: '#endif']!
-       aStream space; nextPut: $}!

Item was changed:
  ----- Method: Cogit class>>tableInitializerFor:in: (in category 'translation') -----
  tableInitializerFor: aTable in: aCCodeGenerator
        ^String streamContents:
                [:s|
                s nextPutAll: ' = {'.
                aTable object
                        do: [:gt|
                                s crtab.
                                gt printCInitializerOn: s in: aCCodeGenerator]
+                       separatedBy: [s peekLast == $} ifTrue: [s nextPut: $,]].
-                       separatedBy: [s nextPut: $,].
                s cr; nextPut: $}]!

Item was changed:
  ----- Method: Interpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHash (in category 'object access primitives') -----
- primitiveArrayBecomeOneWayCopyHash
-       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
-        copy the receiver's elements identity hashes over the argument's elements identity hashes."
-
-       | copyHashFlag ec |
-       self stackTop = objectMemory trueObject
-               ifTrue: [copyHashFlag := true]
-               ifFalse:
-                       [self stackTop = objectMemory falseObject
-                               ifTrue: [copyHashFlag := false]
-                               ifFalse:
-                                       [self primitiveFailFor: PrimErrBadArgument.
-                                        ^nil]].
-       ec := objectMemory
-                       become: (self stackValue: 2)
-                       with: (self stackValue: 1)
-                       twoWay: false
-                       copyHash: copyHashFlag.
-       ec = PrimNoErr
-               ifTrue: [self pop: argumentCount]
-               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
+ primitiveArrayBecomeOneWayCopyHashArg
+       "Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+        copy the receiver's elements identity hashes over the argument's elements identity hashes."
+
+       | copyHashFlag ec |
+       self stackTop = objectMemory trueObject
+               ifTrue: [copyHashFlag := true]
+               ifFalse:
+                       [self stackTop = objectMemory falseObject
+                               ifTrue: [copyHashFlag := false]
+                               ifFalse:
+                                       [self primitiveFailFor: PrimErrBadArgument.
+                                        ^nil]].
+       ec := objectMemory
+                       become: (self stackValue: 2)
+                       with: (self stackValue: 1)
+                       twoWay: false
+                       copyHash: copyHashFlag.
+       ec = PrimNoErr
+               ifTrue: [self pop: argumentCount]
+               ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>preGenerationHook: (in category 'translation') -----
+ preGenerationHook: aCCodeGenerator
+       "Define the primitiveTable initializer once all methods have been added."
+       aCCodeGenerator vmClass primitiveTable ifNotNil:
+               [:bytecodeGenTable|
+               aCCodeGenerator
+                       var: #primitiveGeneratorTable
+                               declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
+                                                       (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
+                                                               in: aCCodeGenerator)]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>literal:ofMethod:put: (in category 'compiled methods') -----
  literal: offset ofMethod: methodPointer put: oop
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: true>
        objectMemory storePointer: offset + LiteralStart ofObject: methodPointer withValue: oop
  !

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
        "N.B. will *not* cause a GC.
         integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
        <notOption: #Spur64BitMemoryManager>
+       <inline: #always>
        <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: ClassLargePositiveIntegerCompactIndex
                                                        format: (objectMemory byteFormatForNumBytes: 4)
                                                        numSlots: 1.
        SPURVM
                ifTrue:
                        ["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"
                        objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
                        objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
                ifFalse:
                        [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
        ^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>unfollow:atIndex: (in category 'compiled methods') -----
  unfollow: litVar atIndex: literalIndex
+       <option: #SpurObjectMemory>
-       <option: #SpurMemoryManager>
        <inline: #never> "So rare it mustn't bulk up the common path"
        | followed |
        followed := objectMemory followForwarded: litVar.
        self literal: literalIndex ofMethod: method put: followed.
        ^followed!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
        "Answer the set of names for variables that should be defined at compile time.
         Some of these get default values during simulation, and hence get defaulted in
         the various initializeMiscConstants methods.  But that they have values should
         /not/ cause the code generator to do dead code elimination based on their
         default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
         will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
        ^#(     VMBIGENDIAN
                IMMUTABILITY
                STACKVM COGVM COGMTVM SPURVM
                PharoVM                                                         "Pharo vs Squeak"
                TerfVM                                                                  "Terf vs Squeak"
                EnforceAccessControl                                    "Newspeak"
                CheckRememberedInTrampoline             "IMMUTABILITY"
+               BIT_IDENTICAL_FLOATING_POINT
+               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>"
-               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>"

                "processor related"
                __ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
                _M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
                x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64

                "Compiler brand related"
                __GNUC__
                _MSC_VER
                __ICC

                "os related"
                ACORN
                __linux__
                __MINGW32__
                __OpenBSD__
                __osf__
                UNIX
                WIN32 _WIN32 _WIN32_WCE
                WIN64 _WIN64 _WIN64_WCE)!



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


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