<div dir="ltr"><div><div>Hi Eliot,</div><div>if we have a certified arithmetic right shift that preserves integer kind</div><div> - not something like (((usqint) x) >> 32), which is a logical right shift</div><div>- nor (((sqint) x) >> 32)<br></div><div>then what we could do is use a signed long long to store intermediate result:</div><div>(I call it arithmeticRightShift: because I don't have a VMMaker handy to verify the right name</div><div>maybe it was >>> ? but then that's the reverse meaning of java!)</div></div><div><br></div><div>
        <var: #pWordSmall type: #'unsigned int *'><br>
        <var: #pWordLarge type: #'unsigned int *'><br>
        <var: #pWordRes type: #'unsigned int *'><br>
        <var: #z type: #'long long'><br>
<br>
        z := 0.<br>
        0 to: smallLen - 1 do:<br>
                [:i |</div><div>                z := z + (self cDigitOf: pWordLarge at: i) - (self cDigitOf: pWordSmall at: i).<br>
                self cDigitOf: pWordRes at: i put: (z bitAnd: 16rFFFFFFFF).</div><div>
                z := z arithmeticRightShift: 32].<br>
        smallLen to: largeLen - 1 do:<br>
                [:i |</div><div>                z := z + (self cDigitOf: pWordLarge at: i).<br>
                self cDigitOf: pWordRes at: i put: (z bitAnd: 16rFFFFFFFF).</div><div>
                z := z arithmeticRightShift: 32].<br>
        ^0!<br>
</div></div><div class="gmail_extra"><br><div class="gmail_quote">2017-12-22 6:18 GMT+01:00  <span dir="ltr"><<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>></span>:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2299.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/<wbr>VMMaker/VMMaker.oscog-eem.<wbr>2299.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-eem.2299<br>
Author: eem<br>
Time: 21 December 2017, 9:17:52.747344 pm<br>
UUID: 53b6a352-dbde-430a-9ec1-<wbr>cb56154fe2c5<br>
Ancestors: VMMaker.oscog-eem.2298<br>
<br>
Get the StackInterpreterSimulator to a state where it can correctly simulate the DoubleByteArray, WordArray, DoubleWordArray and MemoryTests.  Principally allow the SqueakFFIPrims plugin (ThreadedFFIPlugin) to load and make primitiveFFIIntegerAt[Put] function correctly in simulation.  Change the two primitives to use unalignedShortAt:[put:], unalignedLong32At:[put:] & unalignedLong64At:[put:] and implement these in SpurMemoryManager (ObjectMemory can wait) and have the preambleCCode map these to the original shortAt[put],  long32At[put] & long32At[put] C functions/macros.<br>
<br>
Fix a bug in the simulation of LargeIntegersPlugin>><wbr>cDigitSub:len:with:len:into: (Nicolas, there may be similar signedness issues in other functions.  If you have time and energy please consider taking a look at the code in the simulator).<br>
<br>
Fix a slip in the range comparison for 64-bit integer arguments in genPrimitiveAtPut.<br>
<br>
=============== Diff against VMMaker.oscog-eem.2298 ===============<br>
<br>
Item was added:<br>
+ ----- Method: CoInterpreter>>ISA (in category 'simulation') -----<br>
+ ISA<br>
+       <doNotGenerate><br>
+       ^cogit backEnd class ISA!<br>
<br>
Item was changed:<br>
  ----- Method: CogClass>>cCoerceSimple:to: (in category 'translation support') -----<br>
  cCoerceSimple: value to: cTypeString<br>
        <doNotGenerate><br>
        "Type coercion for translation and simulation.<br>
         For simulation answer a suitable surrogate for the struct types"<br>
        ^cTypeString caseOf:<br>
           {    [#'unsigned long']                                                      ->      [value].<br>
                [#'unsigned int']                                                       ->      [value].<br>
+               [#'unsigned short']                                                     ->      [value].<br>
+               [#sqInt]                                                                        ->      [value].<br>
-               [#sqInt]                                                                                ->      [value].<br>
                [#'sqIntptr_t']                                                         ->      [value].<br>
                [#'usqIntptr_t']                                                                ->      [value].<br>
                [#usqInt]                                                                       ->      [value].<br>
                [#sqLong]                                                                       ->      [value].<br>
+               [#usqLong]                                                              ->      [value].<br>
-               [#usqLong]                                                                      ->      [value].<br>
                [#'AbstractInstruction *']                                      ->      [value].<br>
                [#'BytecodeFixup *']                                            ->      [value].<br>
                [#'CogMethod *']                                                        ->      [value].<br>
                [#'char *']                                                                     ->      [value].<br>
                [#'sqInt *']                                                                    ->      [value].<br>
                [#'void *']                                                                     ->      [value].<br>
                [#void]                                                                         ->      [value].<br>
                [#'void (*)()']                                                         ->      [value].<br>
                [#'void (*)(void)']                                                     ->      [value].<br>
                [#'unsigned long (*)(void)']                                    ->      [value].<br>
                [#'void (*)(unsigned long,unsigned long)']      ->      [value].<br>
                [#'usqIntptr_t (*)(void)']                                      ->      [value] }!<br>
<br>
Item was changed:<br>
  ----- Method: CogObjectRepresentationFor64Bi<wbr>tSpur>>genPrimitiveAtPut (in category 'primitive generators') -----<br>
(excessive size, no diff calculated)<br>
<br>
Item was changed:<br>
  ----- Method: FFIPlugin class>>moduleName (in category 'translation') -----<br>
  moduleName "FFIPlugin translate"<br>
        "IMPORTANT: IF YOU CHANGE THE NAME OF THIS PLUGIN YOU MUST CHANGE<br>
                Interpreter>><wbr>primitiveCalloutToFFI<br>
        TO REFLECT THE CHANGE."<br>
+       ^'SqueakFFIPrims (Obsolete)'!<br>
-       ^'SqueakFFIPrims'!<br>
<br>
Item was changed:<br>
  ----- Method: FilePluginSimulator>><wbr>sqFileDeleteName:Size: (in category 'simulation') -----<br>
  sqFileDeleteName: nameIndex Size: nameSize<br>
        | path |<br>
+       path := interpreterProxy asString: nameIndex size: nameSize.<br>
-       path := interpreterProxy interpreter asString: nameIndex size: nameSize.<br>
        (StandardFileStream isAFileNamed: path) ifFalse:<br>
                [^interpreterProxy primitiveFail].<br>
        [FileDirectory deleteFilePath: path]<br>
                on: Error<br>
                do: [:ex| interpreterProxy primitiveFail]!<br>
<br>
Item was changed:<br>
  ----- Method: LargeIntegersPlugin>><wbr>cDigitSub:len:with:len:into: (in category 'C core') -----<br>
  cDigitSub: pWordSmall<br>
                len: smallLen<br>
                with: pWordLarge<br>
                len: largeLen<br>
                into: pWordRes<br>
        | z |<br>
        <var: #pWordSmall type: #'unsigned int *'><br>
        <var: #pWordLarge type: #'unsigned int *'><br>
        <var: #pWordRes type: #'unsigned int *'><br>
        <var: #z type: #'unsigned long long'><br>
<br>
        z := 0.<br>
        0 to: smallLen - 1 do:<br>
                [:i |<br>
                z := z + (self cDigitOf: pWordLarge at: i) - (self cDigitOf: pWordSmall at: i).<br>
                self cDigitOf: pWordRes at: i put: (z bitAnd: 16rFFFFFFFF).<br>
+               z := 0 - (self cCode: [z >> 63] inSmalltalk: [z >> 63 bitAnd: 1])].<br>
-               z := 0 - (z >> 63)].<br>
        smallLen to: largeLen - 1 do:<br>
                [:i |<br>
                z := z + (self cDigitOf: pWordLarge at: i) .<br>
                self cDigitOf: pWordRes at: i put: (z bitAnd: 16rFFFFFFFF).<br>
+               z := 0 - (self cCode: [z >> 63] inSmalltalk: [z >> 63 bitAnd: 1])].<br>
-               z := 0 - (z >> 63)].<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: Spur64BitMMLECoSimulatorFor64B<wbr>its>>long64At: (in category 'memory access') -----<br>
  long64At: byteAddress<br>
+       "memory is a DoubleWordArray, a 64-bit indexable array of bits"<br>
-       "memory is a DobleWordArray, a 64-bit indexable array of bits"<br>
        byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].<br>
        ^memory at: byteAddress // 8 + 1!<br>
<br>
Item was changed:<br>
  ----- Method: Spur64BitMMLECoSimulatorFor64B<wbr>its>>long64At:put: (in category 'memory access') -----<br>
  long64At: byteAddress put: a64BitValue<br>
+       "memory is a DoubleWordArray, a 64-bit indexable array of bits"<br>
-       "memory is a DobleWordArray, a 64-bit indexable array of bits"<br>
        byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].<br>
        ^memory at: byteAddress // 8 + 1 put: a64BitValue!<br>
<br>
Item was changed:<br>
  ----- Method: Spur64BitMMLESimulatorFor64Bit<wbr>s>>long32At:put: (in category 'memory access') -----<br>
  long32At: byteAddress put: a32BitValue<br>
        "Store the 32-bit word at byteAddress which must be a multiple of four."<br>
        | lowBits long longAddress |<br>
+       a32BitValue < 0 ifTrue:<br>
+               [self long32At: byteAddress put: (a32BitValue bitAnd: 16rFFFFFFFF).<br>
+                ^a32BitValue].<br>
        lowBits := byteAddress bitAnd: 4.<br>
        lowBits = 0<br>
                ifTrue: "storing into LS word"<br>
                        [long := self long64At: byteAddress.<br>
                         self long64At: byteAddress<br>
                                put: ((long bitAnd: 16rFFFFFFFF00000000) bitOr: a32BitValue)]<br>
                ifFalse: "storing into MS word"<br>
                        [longAddress := byteAddress - 4.<br>
                        long := self long64At: longAddress.<br>
                        self long64At: longAddress<br>
                                put: ((long bitAnd: 16rFFFFFFFF) bitOr: (a32BitValue bitShift: 32))].<br>
        ^a32BitValue!<br>
<br>
Item was changed:<br>
  ----- Method: Spur64BitMMLESimulatorFor64Bit<wbr>s>>long64At:put: (in category 'memory access') -----<br>
  long64At: byteAddress put: a64BitValue<br>
+       "memory is a DoubleWordArray, a 64-bit indexable array of bits"<br>
-       "memory is a DobleWordArray, a 64-bit indexable array of bits"<br>
        byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].<br>
        ^memory at: byteAddress // 8 + 1 put: a64BitValue!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>>ISA (in category 'simulation only') -----<br>
+ ISA<br>
+       "hack around the CoInterpreter/ObjectMemory split refactoring"<br>
+       <doNotGenerate><br>
+       ^coInterpreter ISA!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>signed64BitIntegerFor: (in category 'simulation only') -----<br>
+ signed64BitIntegerFor: integerValue<br>
+       "hack around the CoInterpreter/ObjectMemory split refactoring"<br>
+       <doNotGenerate><br>
+       ^coInterpreter signed64BitIntegerFor: integerValue!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>signed64BitValueOf: (in category 'simulation only') -----<br>
+ signed64BitValueOf: oop<br>
+       "hack around the CoInterpreter/ObjectMemory split refactoring"<br>
+       <doNotGenerate><br>
+       ^coInterpreter signed64BitValueOf: oop!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedLong32At: (in category 'simulation') -----<br>
+ unalignedLong32At: index<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       | odd hi lo |<br>
+       (odd := index bitAnd: 3) = 0 ifTrue:<br>
+               [^self long32At: index].<br>
+       lo := self long32At: index - odd.<br>
+       hi := self long32At: index + 4 - odd.<br>
+       ^lo >> (odd * 8) + ((hi bitAnd: 1 << (odd * 8) - 1) << (4 - odd * 8))!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedLong32At:put: (in category 'simulation') -----<br>
+ unalignedLong32At: index put: aValue<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       | odd hi lo mask |<br>
+       aValue < 0 ifTrue:<br>
+               [self unalignedLong64At: index put: (aValue bitAnd: 16rFFFFFFFF).<br>
+                ^aValue].<br>
+       (odd := index bitAnd: 3) = 0 ifTrue:<br>
+               [^self long32At: index put: aValue].<br>
+       mask := 1 << (odd * 8) - 1.<br>
+       lo := self long32At: index - odd.<br>
+       self long32At: index - odd<br>
+               put: (lo bitAnd: mask)<br>
+                       + ((aValue bitAnd: 1 << (4 - odd * 8) - 1) << (odd * 8)).<br>
+       hi := self long32At: index + 4 - odd.<br>
+       self long32At: index + 4 - odd<br>
+               put: (hi bitClear: mask) + (aValue >> (4 - odd * 8) bitAnd: mask).<br>
+       ^aValue!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedLong64At: (in category 'simulation') -----<br>
+ unalignedLong64At: index<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       | odd hi lo |<br>
+       (odd := index bitAnd: 7) = 0 ifTrue:<br>
+               [^self long64At: index].<br>
+       lo := self long64At: index - odd.<br>
+       hi := self long64At: index + 8 - odd.<br>
+       ^lo >> (odd * 8) + ((hi bitAnd: 1 << (odd * 8) - 1) << (8 - odd * 8))!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedLong64At:put: (in category 'simulation') -----<br>
+ unalignedLong64At: index put: aValue<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       | odd hi lo mask |<br>
+       aValue < 0 ifTrue:<br>
+               [self unalignedLong64At: index put: (aValue bitAnd: 16rFFFFFFFFFFFFFFFF).<br>
+                ^aValue].<br>
+       (odd := index bitAnd: 7) = 0 ifTrue:<br>
+               [^self long64At: index put: aValue].<br>
+       mask := 1 << (odd * 8) - 1.<br>
+       lo := self long64At: index - odd.<br>
+       self long64At: index - odd<br>
+               put: (lo bitAnd: mask)<br>
+                       + ((aValue bitAnd: 1 << (8 - odd * 8) - 1) << (odd * 8)).<br>
+       hi := self long64At: index + 8 - odd.<br>
+       self long64At: index + 8 - odd<br>
+               put: (hi bitClear: mask) + (aValue >> (8 - odd * 8) bitAnd: mask).<br>
+       ^aValue!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedShortAt: (in category 'simulation') -----<br>
+ unalignedShortAt: index<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       | hi lo |<br>
+       (index bitAnd: 1) = 0 ifTrue:<br>
+               [^self shortAt: index].<br>
+       lo := self shortAt: index - 1.<br>
+       hi := self shortAt: index + 1.<br>
+       ^lo >> 8 + ((hi bitAnd: 16rFF) << 8)!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>><wbr>unalignedShortAt:put: (in category 'simulation') -----<br>
+ unalignedShortAt: index put: aValue<br>
+       "Support for primitiveFFIIntegerAt[Put]"<br>
+       <doNotGenerate><br>
+       (index bitAnd: 1) = 0 ifTrue:<br>
+               [^self shortAt: index put: aValue].<br>
+       self shouldBeImplemented.<br>
+       ^aValue!<br>
<br>
Item was added:<br>
+ ----- Method: StackInterpreter>>ISA (in category 'simulation') -----<br>
+ ISA<br>
+       <doNotGenerate><br>
+       ^self class initializationOptions<br>
+               at: #ISA<br>
+               ifAbsent: [Smalltalk wordSize = 8<br>
+                                       ifTrue: [#X64]<br>
+                                       ifFalse: [#IA32]]!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter>><wbr>ioLoadExternalFunction:<wbr>OfLength:FromModule:OfLength:<wbr>AccessorDepthInto: (in category 'primitive support') -----<br>
  ioLoadExternalFunction: functionName OfLength: functionLength FromModule: moduleName OfLength: moduleLength AccessorDepthInto: accessorDepthPtr<br>
        "Load and return the requested function from a module.  Assign the accessor depth through accessorDepthPtr.<br>
         N.B. The actual code lives in platforms/Cross/vm/<wbr>sqNamedPrims.h"<br>
        <doNotGenerate><br>
        | pluginString functionString |<br>
        pluginString := String new: moduleLength.<br>
+       (1 to: moduleLength) do:[:i| pluginString byteAt: i put: (objectMemory byteAt: moduleName+i-1)].<br>
-       1 to: moduleLength do:[:i| pluginString byteAt: i put: (objectMemory byteAt: moduleName+i-1)].<br>
        functionString := String new: functionLength.<br>
+       (1 to: functionLength) do:[:i| functionString byteAt: i put: (objectMemory byteAt: functionName+i-1)].<br>
+       "We used to ignore loads of the SqueakFFIPrims plugin, but that means doing without integerAt:[put:]size:signed:<br>
+        which is too much of a limitation (not that these simulate unaligned accesses yet)."<br>
-       1 to: functionLength do:[:i| functionString byteAt: i put: (objectMemory byteAt: functionName+i-1)].<br>
-       "Pharo images as of 2016 use the FFI plugin (for getenv:?).  We can't simulate such function loads.  So ignore"<br>
-       pluginString = 'SqueakFFIPrims' ifTrue:<br>
-               ["self halt."<br>
-                true ifTrue:<br>
-                       [self transcript cr; show: 'ignoring function load from SqueakFFIPrims'.<br>
-                        ^0]].<br>
        ^self ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin class>>preambleCCode (in category 'translation') -----<br>
  preambleCCode<br>
        "For a source of builtin defines grep for builtin_define in a gcc release config directory."<br>
        ^'<br>
  #include "sqAssert.h" /* for assert */<br>
  #define ThreadedFFIPlugin 1 /* to filter-out unwanted declarations from sqFFI.h */<br>
  #include "sqFFI.h" /* for logging and surface functions */<br>
  #include "sqCogStackAlignment.h" /* for STACK_ALIGN_BYTES and getsp() */<br>
<br>
  #ifdef _MSC_VER<br>
  # define alloca _alloca<br>
  #endif<br>
  #if defined(__GNUC__) && (defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__))<br>
  # define setsp(sp) asm volatile ("movl %0,%%esp" : : "m"(sp))<br>
  # elif defined(__GNUC__) && (defined(__amd64__) || defined(__x86_64__) ||  defined(__amd64) || defined(__x86_64))<br>
  # define setsp(sp) asm volatile ("movq %0,%%rsp" : : "m"(sp))<br>
  # elif defined(__GNUC__) && (defined(__arm__))<br>
  # define setsp(sp) asm volatile ("ldr %%sp, %0" : : "m"(sp))<br>
  #endif<br>
  #if !!defined(getsp)<br>
  # define getsp() 0<br>
  #endif<br>
  #if !!defined(setsp)<br>
  # define setsp(ignored) 0<br>
  #endif<br>
<br>
  #if !!defined(STACK_ALIGN_BYTES)<br>
  #  define STACK_ALIGN_BYTES 0<br>
  #endif /* !!defined(STACK_ALIGN_BYTES) */<br>
<br>
  /* For ABI that require stack alignment greater than natural word size */<br>
  #define MUST_ALIGN_STACK (STACK_ALIGN_BYTES > sizeof(void*))<br>
<br>
  #if defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__)<br>
  /* Both Mac OS X x86 and Win32 x86 return structs of a power of two in size<br>
   * less than or equal to eight bytes in length in registers. Linux never does so.<br>
   */<br>
  # if __linux__<br>
  #     define WIN32_X86_STRUCT_RETURN 0<br>
  # else<br>
  #     define WIN32_X86_STRUCT_RETURN 1<br>
  # endif<br>
  # if _WIN32<br>
  #     define PLATFORM_API_USES_CALLEE_POPS_<wbr>CONVENTION 1<br>
  # endif<br>
  # elif defined(__amd64__) || defined(__x86_64__) ||  defined(__amd64) || defined(__x86_64)<br>
  # if _WIN32 | _WIN64<br>
  #     define PLATFORM_API_USES_CALLEE_POPS_<wbr>CONVENTION 1<br>
  # endif<br>
  #endif /* defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__) */<br>
<br>
  #if !!defined(ALLOCA_LIES_SO_<wbr>SETSP_BEFORE_CALL)<br>
  # if defined(__MINGW32__) && !!defined(__clang__) && (__GNUC__ >= 3) && (defined(_X86_) || defined(i386) || defined(__i386) || defined(__i386__))<br>
      /*<br>
       * cygwin -mno-cygwin (MinGW) gcc 3.4.x''s alloca is a library routine that answers<br>
       * %esp + xx, so the outgoing stack is offset by one or more word if uncorrected.<br>
       * Grab the actual stack pointer to correct.<br>
       */<br>
  #     define ALLOCA_LIES_SO_SETSP_BEFORE_<wbr>CALL 1<br>
  # else<br>
  #     define ALLOCA_LIES_SO_SETSP_BEFORE_<wbr>CALL 0<br>
  # endif<br>
  #endif /* !!defined(ALLOCA_LIES_SO_<wbr>SETSP_BEFORE_CALL) */<br>
<br>
  #if !!defined(PLATFORM_API_USES_<wbr>CALLEE_POPS_CONVENTION)<br>
  # define PLATFORM_API_USES_CALLEE_POPS_<wbr>CONVENTION 0<br>
  #endif<br>
<br>
+ /* This alignment stuff is a hack for integerAt:put:size:signed:/<wbr>primitiveFFIIntegerAt[Put].<br>
+  * The assumption right now is that all processors suppoprt unaligned access.  That only<br>
+  * holds true for x86, x86-64 & ARMv6 & later.  But this keeps us going until we can addresws it properly.<br>
+  */<br>
+ #define unalignedShortAt(a) shortAt(a)<br>
+ #define unalignedShortAtput(a) shortAtput(a)<br>
+ #define unalignedLong32At(a) long32At(a)<br>
+ #define unalignedLong32Atput(a) long32Atput(a)<br>
+ #define unalignedLong64At(a) long64At(a)<br>
+ #define unalignedLong64Atput(a) long64Atput(a)<br>
+<br>
  /* The dispatchOn:in:with:with: generates an unwanted call on error.  Just squash it. */<br>
  #define error(foo) 0<br>
  #ifndef SQUEAK_BUILTIN_PLUGIN<br>
  /* but print assert failures. */<br>
  void<br>
  warning(char *s) { /* Print an error message but don''t exit. */<br>
        printf("\n%s\n", s);<br>
  }<br>
  #endif<br>
<br>
  /* sanitize */<br>
  #ifdef SQUEAK_BUILTIN_PLUGIN<br>
  # define EXTERN<br>
  #else<br>
  # define EXTERN extern<br>
  #endif<br>
  '!<br>
<br>
Item was added:<br>
+ ----- Method: ThreadedFFIPlugin>><wbr>initSurfacePluginFunctionPoint<wbr>ers (in category 'simulation') -----<br>
+ initSurfacePluginFunctionPoint<wbr>ers<br>
+       "This is a simulation-only stub.  The real code is in<br>
+               platforms/Cross/plugins/<wbr>SqueakFFIPrims/<wbr>sqManualSurface.c"<br>
+       <doNotGenerate>!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin>><wbr>initialiseModule (in category 'initialize') -----<br>
  initialiseModule<br>
        <export: true><br>
        "By default, disable logging"<br>
        ffiLogEnabled := false.<br>
        "Get the instSize of ExternalFunction to know whether it contains a cache of the stackSize,<br>
         and what the offset of ExternalLibraryFunction's functionName and moduleName slots are."<br>
        externalFunctionInstSize := interpreterProxy instanceSizeOf: interpreterProxy classExternalFunction.<br>
        self initSurfacePluginFunctionPoint<wbr>ers.<br>
+       ^true!<br>
-       ^1!<br>
<br>
Item was added:<br>
+ ----- Method: ThreadedFFIPlugin>><wbr>morphIntoConcreteSubclass: (in category 'simulation') -----<br>
+ morphIntoConcreteSubclass: aCoInterpreter<br>
+       <doNotGenerate><br>
+       | concreteClass |<br>
+       concreteClass :=<br>
+               aCoInterpreter ISA caseOf: {<br>
+                       [#X64]          ->      [(Smalltalk platformName beginsWith: 'Win')<br>
+                                                               ifTrue: [ThreadedX64Win64FFIPlugin]<br>
+                                                               ifFalse: [ThreadedX64SysVFFIPlugin]].<br>
+                       [#IA32] ->      [ThreadedIA32FFIPlugin].<br>
+                       [#ARMv5]        ->      [ThreadedARMFFIPlugin] }<br>
+                       otherwise: [self error: 'simulation not set up for this ISA'].<br>
+       self changeClassTo: concreteClass!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin>><wbr>primitiveFFIIntegerAt (in category 'primitives') -----<br>
  primitiveFFIIntegerAt<br>
        "Answer a (signed or unsigned) n byte integer from the given byte offset<br>
         in the receiver, using the platform's endianness."<br>
        | isSigned byteSize byteOffset rcvr addr value mask valueOop |<br>
        <var: 'value' type: #usqLong><br>
        <var: 'mask' type: #usqLong><br>
        <export: true><br>
        <inline: false><br>
        isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).<br>
        byteSize := interpreterProxy stackIntegerValue: 1.<br>
        byteOffset := interpreterProxy stackIntegerValue: 2.<br>
        rcvr := interpreterProxy stackObjectValue: 3.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        (byteOffset > 0<br>
         and: [(byteSize between: 1 and: 8)<br>
         and: [(byteSize bitAnd: byteSize - 1) = 0 "a.k.a. isPowerOfTwo"]]) ifFalse:<br>
                [^interpreterProxy primitiveFail].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        byteSize <= 2<br>
                ifTrue:<br>
                        [byteSize = 1<br>
                                ifTrue: [value := self cCoerceSimple: (interpreterProxy byteAt: addr) to: #'unsigned char']<br>
+                               ifFalse: [value := self cCoerceSimple: (interpreterProxy unalignedShortAt: addr) to: #'unsigned short']]<br>
-                               ifFalse: [value := self cCoerceSimple: (interpreterProxy shortAt: addr) to: #'unsigned short']]<br>
                ifFalse:<br>
                        [byteSize = 4<br>
+                               ifTrue: [value := self cCoerceSimple: (interpreterProxy unalignedLong32At: addr) to: #'unsigned int']<br>
+                               ifFalse: [value := interpreterProxy unalignedLong64At: addr]].<br>
-                               ifTrue: [value := self cCoerceSimple: (interpreterProxy long32At: addr) to: #'unsigned int']<br>
-                               ifFalse: [value := interpreterProxy long64At: addr]].<br>
        byteSize < BytesPerWord<br>
                ifTrue:<br>
                        [isSigned ifTrue: "sign extend value"<br>
                                [mask := 1 asUnsignedLongLong << (byteSize * 8 - 1).<br>
                                value := (value bitAnd: mask-1) - (value bitAnd: mask)].<br>
                         "note: byte/short (&long if BytesPerWord=8) never exceed SmallInteger range"<br>
                         valueOop := interpreterProxy integerObjectOf: value]<br>
                ifFalse: "general 64 bit integer; note these never fail"<br>
                        [isSigned<br>
                                ifTrue:<br>
                                        [byteSize < 8 ifTrue: "sign extend value"<br>
                                                [mask := 1 asUnsignedLongLong << (byteSize * 8 - 1).<br>
                                                value := (value bitAnd: mask-1) - (value bitAnd: mask)].<br>
+                                        self cCode: [] inSmalltalk:<br>
+                                               [(byteSize = 8 and: [(value bitShift: -56) >= 128]) ifTrue:<br>
+                                                       [value := value - (1 bitShift: 64)]].<br>
                                         valueOop := interpreterProxy signed64BitIntegerFor: value]<br>
                                ifFalse:[valueOop := interpreterProxy positive64BitIntegerFor: value]].<br>
        ^interpreterProxy pop: 4 thenPush: valueOop!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin>><wbr>primitiveFFIIntegerAtPut (in category 'primitives') -----<br>
  primitiveFFIIntegerAtPut<br>
        "Store a (signed or unsigned) n byte integer at the given byte offset<br>
         in the receiver, using the platform's endianness."<br>
        | isSigned byteSize byteOffset rcvr addr value max valueOop |<br>
        <var: 'value' type: #sqLong><br>
        <var: 'max' type: #sqLong><br>
        <export: true><br>
        <inline: false><br>
        isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).<br>
        byteSize := interpreterProxy stackIntegerValue: 1.<br>
        valueOop := interpreterProxy stackValue: 2.<br>
        byteOffset := interpreterProxy stackIntegerValue: 3.<br>
        rcvr := interpreterProxy stackObjectValue: 4.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        (byteOffset > 0<br>
         and: [(byteSize between: 1 and: 8)<br>
         and: [(byteSize bitAnd: byteSize - 1) = 0 "a.k.a. isPowerOfTwo"]]) ifFalse:<br>
                [^interpreterProxy primitiveFail].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        isSigned<br>
                ifTrue:[value := interpreterProxy signed64BitValueOf: valueOop]<br>
                ifFalse:[value := interpreterProxy positive64BitValueOf: valueOop].<br>
        interpreterProxy failed ifTrue:[^0].<br>
        byteSize < 8 ifTrue:<br>
                [isSigned<br>
                        ifTrue:<br>
                                [max := 1 asUnsignedLongLong << (8 * byteSize - 1).<br>
                                (value >= (0 - max) and: [value < max]) ifFalse: [^interpreterProxy primitiveFail]]<br>
                        ifFalse:<br>
                                [value asUnsignedLongLong < (1 asUnsignedLongLong << (8 * byteSize)) ifFalse: [^interpreterProxy primitiveFail]]].<br>
        byteSize <= 2<br>
                ifTrue:<br>
                        [byteSize = 1<br>
                                ifTrue: [interpreterProxy byteAt: addr put: value]<br>
+                               ifFalse: [interpreterProxy unalignedShortAt: addr put: value]]<br>
-                               ifFalse: [interpreterProxy shortAt: addr put: value]]<br>
                ifFalse:<br>
                        [byteSize = 4<br>
+                               ifTrue: [interpreterProxy unalignedLong32At: addr put: value]<br>
+                               ifFalse: [interpreterProxy unalignedLong64At: addr put: value]].<br>
-                               ifTrue: [interpreterProxy long32At: addr put: value]<br>
-                               ifFalse: [interpreterProxy long64At: addr put: value]].<br>
        ^interpreterProxy pop: 5 thenPush: valueOop!<br>
<br>
Item was added:<br>
+ ----- Method: ThreadedFFIPlugin>><wbr>setInterpreter: (in category 'simulation') -----<br>
+ setInterpreter: anInterpreter<br>
+       "Initialization of the plugin in the simulator.<br>
+        The real routine is in the superclass."<br>
+       self cCode: []<br>
+               inSmalltalk: [self class == thisContext method methodClass ifTrue:<br>
+                                               [self morphIntoConcreteSubclass: anInterpreter]].<br>
+       ^super setInterpreter: anInterpreter!<br>
<br>
</blockquote></div><br></div>