<body><div id="__MailbirdStyleContent" style="font-size: 10pt;font-family: Arial;color: #000000">
                                        Hi all!<div><br></div><div>I will keep this one in the inbox for a few days. If there are no complaints, I will merge it.</div><div><br></div><div>Best,</div><div>Marcel</div><div class="mb_sig"></div><blockquote class="history_container" type="cite" style="border-left-style:solid;border-width:1px; margin-top:20px; margin-left:0px;padding-left:10px;">
                        <p style="color: #AAAAAA; margin-top: 10px;">Am 30.05.2020 18:39:17 schrieb commits@source.squeak.org <commits@source.squeak.org>:</p><div style="font-family:Arial,Helvetica,sans-serif">A new version of FFI-Kernel was added to project FFI Inbox:<br>http://source.squeak.org/FFIinbox/FFI-Kernel-mt.80.mcz<br><br>==================== Summary ====================<br><br>Name: FFI-Kernel-mt.80<br>Author: mt<br>Time: 30 May 2020, 6:39:07.324231 pm<br>UUID: 4750dd07-8701-3146-9348-7a9064273fcf<br>Ancestors: FFI-Kernel-mt.79<br><br>Assure that #pointerSize in an external type can never be nil. Make it more clear that #pointerAt:(put:) is just a shortcut to be used for pointer arithmetic (see ExternalAddress >> #+). Struct field methods must be recompiled because of the field alignment. So, emitting #pointerAt:(put:) is of no use at all. Now we emit #(short|long)PointerAt:(put:).<br><br>Note that we only support 4-byte and 8-byte pointers. Thus, fail as early as possible if -- at some day -- #wordSize would be bigger than 8. <br><br>See discussion on vm-dev: http://forum.world.st/Re-squeak-dev-64-bit-FFI-was-porting-Croquet-to-Squeak6-0-alpha-tp5113318p5117466.html<br><br>=============== Diff against FFI-Kernel-mt.79 ===============<br><br>Item was changed:<br>  ----- Method: ByteArray>>pointerAt: (in category '*FFI-Kernel') -----<br>  pointerAt: byteOffset<br>       "Answer a pointer object stored at the given byte address"<br>+ <br>+     ^ ExternalAddress wordSize caseOf: {<br>+                 [4] -> [self shortPointerAt: byteOffset].<br>+                 [8] -> [self longPointerAt: byteOffset] }!<br>-        | addr |<br>-     addr := ExternalAddress new.<br>-         1 to: ExternalAddress wordSize do:<br>-           [:i|<br>-                 addr basicAt: i put: (self unsignedByteAt: byteOffset+i-1)].<br>-         ^addr!<br><br>Item was changed:<br>  ----- Method: ByteArray>>pointerAt:put: (in category '*FFI-Kernel') -----<br>  pointerAt: byteOffset put: value<br>    "Store a pointer object at the given byte address"<br>+ <br>+     ^ ExternalAddress wordSize caseOf: {<br>+                 [4] -> [self shortPointerAt: byteOffset put: value].<br>+              [8] -> [self longPointerAt: byteOffset put: value] }!<br>-     value isExternalAddress ifFalse:<br>-             [^self error:'Only external addresses can be stored'].<br>-       1 to: ExternalAddress wordSize do:<br>-           [:i|<br>-                 self unsignedByteAt: byteOffset+i-1 put: (value basicAt: i)].<br>-        ^value!<br><br>Item was changed:<br>  ----- Method: ExternalStructure class>>compileFields:withAccessors: (in category 'field definition') -----<br>  compileFields: specArray withAccessors: aSymbol <br>          "Compile a type specification for the FFI machinery.<br>     Return the newly compiled spec.<br>       Eventually generate the field accessors according to following rules:<br>         - aSymbol = #always always generate the accessors<br>     - aSymbol = #never never generate the accessors<br>       - aSymbol = #generated only generate the auto-generated accessors<br>     - aSymbol = #absent only generate the absent accessors"<br>          | newByteAlignment byteOffset typeSpec newCompiledSpec |<br>      (specArray size > 0 and: [specArray first class ~~ Array]) ifTrue:<br>                 [^ self compileAlias: specArray withAccessors: aSymbol].<br>      byteOffset := 0.<br>      newByteAlignment := self minStructureAlignment.<br>       typeSpec := WriteStream on: (WordArray new: 10).<br>      typeSpec nextPut: FFIFlagStructure.<br>   "dummy for size"<br>    specArray do:<br>                 [:spec | | fieldName fieldType isPointerField externalType typeSize fieldAlignment selfRefering |<br>             fieldName := spec first.<br>              fieldType := spec second.<br>             isPointerField := fieldType last = $*.<br>                fieldType := (fieldType findTokens: '*') first withBlanksTrimmed.<br>             externalType := ExternalType atomicTypeNamed: fieldType.<br>              selfRefering := isPointerField and: [externalType isNil and: [fieldType = self asString]].<br>            selfRefering ifTrue: [<br>                        externalType := ExternalType void asPointerType<br>               ] ifFalse:[<br>+                  externalType ifNil: ["non-atomic"<br>+                          (Symbol lookup: fieldType) ifNotNil: [:sym |<br>+                                         externalType := ExternalType structTypeNamed: sym].<br>-                  externalType == nil ifTrue: ["non-atomic"<br>-                          Symbol<br>-                                       hasInterned: fieldType<br>-                                       ifTrue: [:sym | externalType := ExternalType structTypeNamed: sym].<br>                   ].<br>+                   externalType ifNil: [<br>-                        externalType == nil ifTrue:[<br>                                  Transcript show: '(' , fieldType , ' is void)'.<br>                               externalType := ExternalType void.<br>                    ].<br>+                   isPointerField ifTrue: [externalType := externalType asPointerType]].<br>-                        isPointerField ifTrue: [externalType := externalType asPointerType: self pointerSize]].<br>                       typeSize := externalType byteSize.<br>                    fieldAlignment := (externalType byteAlignment max: self minFieldAlignment)<br>                            min: self maxFieldAlignment.<br>                          byteOffset := byteOffset alignedTo: fieldAlignment.<br>                   newByteAlignment := newByteAlignment max: fieldAlignment.<br>                     spec size > 2 ifTrue: ["extra size"<br>                              spec third <><br>                                   ifTrue: [^ self error: 'Explicit type size is less than expected'].<br>                           typeSize := spec third.<br>                       ].<br>                    (fieldName notNil and: [self shouldGenerate: fieldName policy: aSymbol]) ifTrue: [<br>                            self defineFieldAccessorsFor: fieldName startingAt: byteOffset + 1 type: externalType.<br>                        ].<br>                    typeSpec nextPutAll: (externalType embeddedSpecWithSize: typeSize).<br>                   byteOffset := byteOffset + typeSize.<br>                  ].<br>    <br>      newByteAlignment := newByteAlignment min: self maxStructureAlignment.<br>         byteOffset := byteOffset alignedTo: newByteAlignment.<br>         newCompiledSpec := typeSpec contents.<br>         newCompiledSpec at: 1 put: (byteOffset bitOr: FFIFlagStructure).<br>      byteAlignment := newByteAlignment.<br>    ^ newCompiledSpec!<br><br>Item was removed:<br>- ----- Method: ExternalStructure class>>pointerSize (in category 'accessing') -----<br>- pointerSize<br>-   "Answer the size of pointers for this class.  By default answer nil.<br>-     Subclasses that contain pointers must define the size of a pointer if the code is to operate on 64-bit and 32-bit platforms.<br>-         Currently we have no way of converting a type between 32- and 64- bit versions beyond recompiling it."<br>-         ^nil!<br><br>Item was changed:<br>  Object subclass: #ExternalType<br>+         instanceVariableNames: 'compiledSpec referentClass referencedType byteAlignment'<br>-     instanceVariableNames: 'compiledSpec referentClass referencedType pointerSize byteAlignment'<br>          classVariableNames: 'AtomicSelectors AtomicTypeNames AtomicTypes StructTypes'<br>         poolDictionaries: 'FFIConstants'<br>      category: 'FFI-Kernel'!<br>  <br>  !ExternalType commentStamp: 'eem 6/25/2019 10:39' prior: 0!<br>  An external type represents the type of external objects.<br>  <br>  Instance variables:<br>    compiledSpec    <wordarray>               Compiled specification of the external type<br>   referentClass   <behavior |="" nil="">        Class type of argument required<br>       referencedType  <externaltype>    Associated (non)pointer type with the receiver<br>        pointerSize             <integer |="" nil="">         The size of a pointer if the external type is a pointer or is a structure containing a pointer.<br>       byteAlignment   <integer |="" nil="">         The desired alignment for a field of the external type within a structure.  If nil it has yet to be computed.<br>  <br>  Compiled Spec:<br>  The compiled spec defines the type in terms which are understood by the VM. Each word is defined as:<br>   bits 0...15     - byte size of the entity<br>     bit 16          - structure flag (FFIFlagStructure)<br>                             This flag is set if the following words define a structure<br>          bit 17          - pointer flag (FFIFlagPointer)<br>                                 This flag is set if the entity represents a pointer to another object<br>       bit 18          - atomic flag (FFIFlagAtomic)<br>                                   This flag is set if the entity represents an atomic type.<br>                             If the flag is set the atomic type bits are valid.<br>          bits 19...23    - unused<br>      bits 24...27    - atomic type (FFITypeVoid ... FFITypeDoubleFloat)<br>    bits 28...31    - unused<br>  <br>  Note that all combinations of the flags FFIFlagPointer, FFIFlagAtomic, and FFIFlagStructure are invalid, EXCEPT from the following:<br>  <br>       FFIFlagPointer + FFIFlagAtomic:<br>               This defines a pointer to an atomic type (e.g., 'char*', 'int*').<br>             The actual atomic type is represented in the atomic type bits.<br>  <br>    FFIFlagPointer + FFIFlagStructure:<br>            This defines a structure which is a typedef of a pointer type as in<br>                   typedef void* VoidPointer;<br>                    typedef Pixmap* PixmapPtr;<br>            It requires a byte size of four or eight (e.g. a 32-bit or 64-bit pointer) to work correctly.<br>  <br>  [Note: Other combinations may be allowed in the future]<br>  !<br><br>Item was removed:<br>- ----- Method: ExternalType>>asPointerType: (in category 'converting') -----<br>- asPointerType: anotherPointerSize<br>-     "convert the receiver into a pointer type"<br>-         | type |<br>-     type := self asPointerType.<br>-  ^type pointerSize = anotherPointerSize<br>-               ifTrue: [type]<br>-               ifFalse:<br>-                     [type copy pointerSize: anotherPointerSize; yourself]!<br><br>Item was changed:<br>  ----- Method: ExternalType>>pointerSize (in category 'accessing') -----<br>  pointerSize<br>+ <br>+      ^ self asPointerType headerWord bitAnd: FFIStructSizeMask!<br>-   "Answer the pointer size of the receiver, if specified."<br>-   ^pointerSize!<br><br>Item was changed:<br>  ----- Method: ExternalType>>readFieldAt: (in category 'private') -----<br>  readFieldAt: byteOffset<br>         "Answer a string defining the accessor to an entity of the receiver type starting at the given byte offset. <br>      Private. Used for field definition only."<br>       self isPointerType ifTrue:<br>            [| accessor |<br>                 accessor := self pointerSize caseOf: {<br>-                                               [nil]   ->   [#pointerAt:].<br>                                                [4]     ->   [#shortPointerAt:].<br>                                           [8]     ->   [#longPointerAt:] }.<br>                   ^String streamContents:<br>                      [:s|<br>                           referentClass<br>                                ifNil:<br>                                        [s nextPutAll: '^ExternalData fromHandle: (handle ', accessor, ' ';<br>                                           print: byteOffset;<br>                                            nextPutAll: ') type: ExternalType ';<br>                                                  nextPutAll: (AtomicTypeNames at: self atomicType);<br>                                            nextPutAll: ' asPointerType']<br>                                 ifNotNil:<br>                                     [s nextPutAll: '^';<br>                                           print: referentClass;<br>                                                 nextPutAll: ' fromHandle: (handle ', accessor, ' ';<br>                                           print: byteOffset;<br>                                            nextPut: $)]]].<br>  <br>   self isAtomic ifFalse: "structure type"<br>             [^String streamContents:[:s|<br>                          s nextPutAll:'^';<br>                             print: referentClass;<br>                                 nextPutAll:' fromHandle: (handle structAt: ';<br>                                 print: byteOffset;<br>                            nextPutAll:' length: ';<br>                               print: self byteSize;<br>                                 nextPutAll:')']].<br>  <br>         "Atomic non-pointer types"<br>          ^String streamContents:<br>               [:s|<br>                  s nextPutAll:'^handle ';<br>                      nextPutAll: (AtomicSelectors at: self atomicType);<br>                    space; print: byteOffset].!<br><br>Item was changed:<br>  ----- Method: ExternalType>>writeFieldAt:with: (in category 'private') -----<br>  writeFieldAt: byteOffset with: valueName<br>    "Answer a string defining the accessor to an entity of the receiver type starting at the given byte offset. <br>      Private. Used for field definition only."<br>       self isPointerType ifTrue:<br>            [| accessor |<br>                 accessor := self pointerSize caseOf: {<br>-                                               [nil]   ->   [#pointerAt:].<br>                                                [4]     ->   [#shortPointerAt:].<br>                                           [8]     ->   [#longPointerAt:] }.<br>                  ^String streamContents:<br>                       [:s|<br>                          s nextPutAll:'handle ', accessor, ' ';<br>                                print: byteOffset;<br>                            nextPutAll:' put: ';<br>                                  nextPutAll: valueName;<br>                                nextPutAll:' getHandle.']].<br>  <br>       self isAtomic ifFalse:[<br>               ^String streamContents:[:s|<br>                   s nextPutAll:'handle structAt: ';<br>                             print: byteOffset;<br>                            nextPutAll:' put: ';<br>                                  nextPutAll: valueName;<br>                                nextPutAll:' getHandle';<br>                              nextPutAll:' length: ';<br>                               print: self byteSize;<br>                                 nextPutAll:'.']].<br>  <br>         ^String streamContents:[:s|<br>           s nextPutAll:'handle ';<br>                       nextPutAll: (AtomicSelectors at: self atomicType);<br>                    space; print: byteOffset;<br>                     nextPutAll:' put: ';<br>                          nextPutAll: valueName].!<br><br>Item was changed:<br>  ----- Method: ExternalUnion class>>compileFields:withAccessors: (in category 'field definition') -----<br>  compileFields: specArray withAccessors: aSymbol <br>     "Compile a type specification for the FFI machinery.<br>     Return the newly compiled spec.<br>       Eventually generate the field accessors according to the policy defined in aSymbol."<br>     | byteOffset maxByteSize typeSpec newCompiledSpec newByteAlignment |<br>          (specArray size > 0 and: [specArray first class ~~ Array]) ifTrue:<br>                 [^ self error: 'unions must have fields defined by sub-Array'].<br>       byteOffset := 1.<br>      newByteAlignment := 1.<br>        maxByteSize := 0.<br>     typeSpec := WriteStream on: (WordArray new: specArray size + 1).<br>      typeSpec nextPut: FFIFlagStructure.<br>   "dummy for size"<br>    specArray do:<br>                 [:spec |<br>              | fieldName fieldType isPointerField externalType typeSize typeAlignment selfRefering |<br>               fieldName := spec first.<br>              fieldType := spec second.<br>             isPointerField := fieldType last = $*.<br>                fieldType := (fieldType findTokens: '*') first withBlanksTrimmed.<br>             externalType := ExternalType atomicTypeNamed: fieldType.<br>              selfRefering := isPointerField and: [externalType isNil and: [fieldType = self asString]].<br>            selfRefering ifTrue: [<br>                        externalType := ExternalType void asPointerType<br>               ] ifFalse:[<br>+                  externalType ifNil: ["non-atomic"<br>+                          (Symbol lookup: fieldType) ifNotNil: [:sym |<br>+                                         externalType := ExternalType structTypeNamed: sym].<br>-                  externalType == nil ifTrue: ["non-atomic"<br>-                          Symbol<br>-                                       hasInterned: fieldType<br>-                                       ifTrue: [:sym | externalType := ExternalType structTypeNamed: sym].<br>                   ].<br>+                   externalType ifNil: [<br>-                        externalType == nil ifTrue:[<br>                                  Transcript show: '(' , fieldType , ' is void)'.<br>                               externalType := ExternalType void.<br>                    ].<br>+                   isPointerField ifTrue: [externalType := externalType asPointerType]].<br>-                        isPointerField ifTrue: [externalType := externalType asPointerType: self pointerSize]].<br>                       typeSize := externalType byteSize.<br>                    typeAlignment := externalType byteAlignment.<br>                          spec size > 2 ifTrue: ["extra size"<br>                              spec third <><br>                                   ifTrue: [^ self error: 'Explicit type size is less than expected'].<br>                           typeSize := spec third.<br>                       ].<br>                    (fieldName notNil and: [self shouldGenerate: fieldName policy: aSymbol]) ifTrue: [<br>                            self defineFieldAccessorsFor: fieldName startingAt: byteOffset type: externalType.<br>                    ].<br>                    typeSpec nextPutAll: (externalType embeddedSpecWithSize: typeSize).<br>                   maxByteSize := maxByteSize max: typeSize.<br>                     newByteAlignment := newByteAlignment max: typeAlignment<br>               ].<br>    maxByteSize := maxByteSize alignedTo: newByteAlignment.<br>       newCompiledSpec := typeSpec contents.<br>         newCompiledSpec at: 1 put: (maxByteSize bitOr: FFIFlagStructure).<br>     byteAlignment := newByteAlignment.<br>    ^ newCompiledSpec!<br><br>Item was changed:<br>  (PackageInfo named: 'FFI-Kernel') postscript: 'Smalltalk removeFromStartUpList: ExternalAddress.<br>+ Smalltalk removeFromStartUpList: ExternalObject.<br>+ <br>+ "Since #pointerSize in ExternalType is never nil anymore, make the code generated for fields more specific, i.e., #shortPointerAt:(put:) or #longPointerAt:(put:).<br>+ ExternalStructure withAllSubclassesDo: [:cls | cls defineFields].<br>+ '!<br>- Smalltalk removeFromStartUpList: ExternalObject.'!<br><br><br></integer></integer></externaltype></behavior></wordarray></div></blockquote>
                                        </div></body>