VM Maker Inbox: VMMaker.oscog-nice.2762.mcz

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

VM Maker Inbox: VMMaker.oscog-nice.2762.mcz

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

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

Name: VMMaker.oscog-nice.2762
Author: nice
Time: 21 June 2020, 8:04:31.580691 pm
UUID: be5f88fb-cafe-4654-ab95-4f5bafe5de16
Ancestors: VMMaker.oscog-nice.2761

Cosmetic changes
- move some smart syntax method FloatArray -> Float32Array
  requires a recent Squeak trunk image or a compatibility layer
- recategorize some FFI methods
- remove some unused var:type:

=============== Diff against VMMaker.oscog-nice.2761 ===============

Item was added:
+ ----- Method: Float32Array class>>ccg:prolog:expr:index: (in category '*VMMaker-plugin generation') -----
+ ccg: cg prolog: aBlock expr: aString index: anInteger
+
+ ^cg ccgLoad: aBlock expr: aString asWBFloatPtrFrom: anInteger!

Item was added:
+ ----- Method: Float32Array class>>ccgDeclareCForVar: (in category '*VMMaker-plugin generation') -----
+ ccgDeclareCForVar: aSymbolOrString
+
+ ^'float *', aSymbolOrString!

Item was removed:
- ----- Method: FloatArray class>>ccg:prolog:expr:index: (in category '*VMMaker-plugin generation') -----
- ccg: cg prolog: aBlock expr: aString index: anInteger
-
- ^cg ccgLoad: aBlock expr: aString asWBFloatPtrFrom: anInteger!

Item was removed:
- ----- Method: FloatArray class>>ccgDeclareCForVar: (in category '*VMMaker-plugin generation') -----
- ccgDeclareCForVar: aSymbolOrString
-
- ^'float *', aSymbolOrString!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling-struct') -----
- ----- Method: ThreadedFFIPlugin>>canReturnInRegistersStructOfSize: (in category 'marshalling') -----
  canReturnInRegistersStructOfSize: returnStructSize
  "Answer if a struct result of a given size can be returned via registers or not.
  Size is a necessary condition, but it might not be a sufficient condition.
  For example, SysV X64 also require that struct fields be properly aligned."
  ^self subclassResponsibility!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>ffiPushSignedLongLongOop:in: (in category 'marshalling') -----
- ----- Method: ThreadedFFIPlugin>>ffiPushSignedLongLongOop:in: (in category 'callout support') -----
  ffiPushSignedLongLongOop: oop in: calloutState
  <var: #calloutState type: #'CalloutState *'>
  "Push a longlong type (e.g., a 64bit integer).
  Note: Coercions from float are *not* supported."
  | value |
  <var: #value type: #sqLong>
  (oop = interpreterProxy nilObject
  or: [oop = interpreterProxy falseObject])
  ifTrue:[value := 0] ifFalse:
  [oop = interpreterProxy trueObject
  ifTrue:[value := 1] ifFalse:
  [value := interpreterProxy signed64BitValueOf: oop.
  interpreterProxy failed ifTrue:
  [^FFIErrorCoercionFailed]]].
  ^self ffiPushSignedLongLong: value in: calloutState!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>ffiPushStructure:ofSize:typeSpec:ofLength:in: (in category 'marshalling-struct') -----
- ----- Method: ThreadedFFIPlugin>>ffiPushStructure:ofSize:typeSpec:ofLength:in: (in category 'marshalling') -----
  ffiPushStructure: pointer ofSize: structSize typeSpec: argSpec ofLength: argSpecSize in: calloutState
  <var: #pointer type: #'void *'>
  <var: #argSpec type: #'sqInt *'>
  <var: #calloutState type: #'CalloutState *'>
  <inline: true>
  self subclassResponsibility!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>ffiPushStructureContentsOf:in: (in category 'marshalling-struct') -----
- ----- Method: ThreadedFFIPlugin>>ffiPushStructureContentsOf:in: (in category 'callout support') -----
  ffiPushStructureContentsOf: oop in: calloutState
  <var: #calloutState type: #'CalloutState *'>
  "Push the contents of the given external structure"
  | ptrClass ptrAddress |
  <inline: true>
  ptrClass := interpreterProxy fetchClassOf: oop.
  ptrClass = interpreterProxy classExternalAddress ifTrue: "ExternalAddress is bytes"
  [ptrAddress := (interpreterProxy fetchPointer: 0 ofObject: oop) asVoidPointer.
  "There is no way we can make sure the structure is valid.
  But we can at least check for attempts to pass pointers to ST memory."
  (interpreterProxy isInMemory: ptrAddress) ifTrue:
  [^FFIErrorInvalidPointer].
  ^self ffiPushStructure: ptrAddress
  ofSize: (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  typeSpec: calloutState ffiArgSpec
  ofLength: calloutState ffiArgSpecSize
  in: calloutState].
  ptrClass = interpreterProxy classByteArray ifTrue:
  ["The following is a somewhat pessimistic test but I like being sure..."
  (interpreterProxy byteSizeOf: oop) = (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  ifFalse:[^FFIErrorStructSize].
  ptrAddress := interpreterProxy firstIndexableField: oop.
  (calloutState ffiArgHeader anyMask: FFIFlagPointer) ifFalse:
  "Since this involves passing the address of the first indexable field we need to fail
   the call if it is threaded and the object is young, since it may move during the call."
  [self cppIf: COGMTVM ifTrue:
  [((calloutState callFlags anyMask: FFICallFlagThreaded)
  and: [interpreterProxy isYoung: oop]) ifTrue:
  [^PrimErrObjectMayMove negated]].
  ^self ffiPushStructure: ptrAddress
  ofSize: (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  typeSpec: calloutState ffiArgSpec
  ofLength: calloutState ffiArgSpecSize
  in: calloutState].
  "If FFIFlagPointer + FFIFlagStructure is set use ffiPushPointer on the contents"
  (calloutState ffiArgHeader bitAnd: FFIStructSizeMask) = BytesPerWord ifFalse:
  [^FFIErrorStructSize].
  ptrAddress := (interpreterProxy fetchPointer: 0 ofObject: oop) asVoidPointer.
  (interpreterProxy isInMemory: ptrAddress) ifTrue:
  [^FFIErrorInvalidPointer].
  ^self ffiPushPointer: ptrAddress in: calloutState].
  ^FFIErrorBadArg!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedLongLongOop:in: (in category 'marshalling') -----
- ----- Method: ThreadedFFIPlugin>>ffiPushUnsignedLongLongOop:in: (in category 'callout support') -----
  ffiPushUnsignedLongLongOop: oop in: calloutState
  <var: #calloutState type: #'CalloutState *'>
  "Push an unsigned longlong type (e.g., a 64bit integer).
  Note: Coercions from float are *not* supported."
  | value |
  <var: #value type: #usqLong>
  (oop = interpreterProxy nilObject
  or: [oop = interpreterProxy falseObject])
  ifTrue:[value := 0] ifFalse:
  [oop = interpreterProxy trueObject
  ifTrue:[value := 1] ifFalse:
  [value := interpreterProxy positive64BitValueOf: oop.
  interpreterProxy failed ifTrue:
  [^FFIErrorCoercionFailed]]].
  ^self ffiPushUnsignedLongLong: value in: calloutState!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>ffiPushVoid:in: (in category 'marshalling') -----
- ----- Method: ThreadedFFIPlugin>>ffiPushVoid:in: (in category 'callout support') -----
  ffiPushVoid: ignored in: calloutState
  <var: #calloutState type: #'CalloutState *'>
  "This is a fallback in case somebody tries to pass a 'void' value.
  We could simply ignore the argument but I think it's better to let
  the caller know what he did"
  ^FFIErrorAttemptToPassVoid!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>nonRegisterStructReturnIsViaImplicitFirstArgument (in category 'marshalling-struct') -----
- ----- Method: ThreadedFFIPlugin>>nonRegisterStructReturnIsViaImplicitFirstArgument (in category 'marshalling') -----
  nonRegisterStructReturnIsViaImplicitFirstArgument
  "Answer if a struct returned in memory is returned to the
  referent of a pointer passed as an implciit first argument.
  It almost always is.  Subclasses can override if not."
  ^true!

Item was changed:
+ ----- Method: ThreadedFFIPlugin>>returnStructInRegisters: (in category 'marshalling-struct') -----
- ----- Method: ThreadedFFIPlugin>>returnStructInRegisters: (in category 'marshalling') -----
  returnStructInRegisters: calloutState
  "Answer if struct result is returned in registers or not.
  Use the OS specific encoding stored in structReturnType.
  Since it is OS dependent, leave the responsibility to subclass"
  <var: #calloutState type: #'CalloutState *'>
  ^self subclassResponsibility!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>registerType:ForUnionSpecs:OfLength:StartingAt:ByteOffset:EightbyteOffset: (in category 'marshalling') -----
  registerType: initialRegisterType ForUnionSpecs: specs OfLength: specSize StartingAt: indexPtr ByteOffset: byteOffset EightbyteOffset: eightbyteOffset
  "Answer with a number characterizing the register type for passing a union of size <= 16 bytes.
  On input, the index points to the structure header (the one with FFIFlagStructure + structSize)
  On output, the index points to the structure trailer (the FFIFlagStructure)."
 
  <var: #specs type: #'unsigned int*'>
  <var: #indexPtr type: #'unsigned int*'>
- <var: #subIndex type: #'unsigned int'>
  <inline: false>
  | registerType spec atomic isInt recurse subLevel |
  registerType := initialRegisterType.
  [indexPtr at: 0 put: (indexPtr at: 0) + 1.
  subLevel := 0.
  (indexPtr at: 0) < specSize]
  whileTrue:
  [spec := specs at: (indexPtr at: 0).
  isInt := false.
  recurse := false.
  spec = FFIFlagStructure "this marks end of structure/union"
  ifTrue:
  [subLevel = 0 ifTrue: [^registerType].
  subLevel := subLevel - 1]
  ifFalse:
  [(spec anyMask: FFIFlagPointer)
  ifTrue:
  [isInt := true]
  ifFalse:
  [(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
  caseOf:
  {[FFIFlagStructure] ->
  [recurse := (self isUnionSpec: specs OfLength: specSize StartingAt: (indexPtr at: 0))not.
  recurse ifFalse: [subLevel := subLevel + 1]].
  [FFIFlagAtomic] ->
  [atomic := self atomicTypeOf: spec.
  isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
  otherwise: ["invalid spec" ^-1]].
  isInt
  ifTrue:
  ["If this eightbyte contains an int field, then we must use an int register"
  registerType := registerType bitOr: 1 << eightbyteOffset].
  recurse ifTrue:
  ["struct in union require a recursive form, because we handle byteOffset/eightbyteOffset differently"
  registerType := self
  registerType: registerType
  ForStructSpecs: specs
  OfLength: specSize
  StartingAt: indexPtr
  ByteOffset: byteOffset
  EightbyteOffset: eightbyteOffset]]].
  self assert: subLevel = 0.
  ^registerType!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>registerTypeForStructSpecs:OfLength: (in category 'marshalling') -----
  registerTypeForStructSpecs: specs OfLength: specSize
  "Answer with a number characterizing the register type for passing a struct of size <= 16 bytes.
  The bit at offset i of registerType is set to 1 if eightbyte at offset i is a int register (RAX ...)
  The bit at offset 2 indicates if there is a single eightbyte (struct size <= 8)
  * 2r00 for float float (XMM0 XMM1)
  * 2r01 for int float (RAX XMM0)
  * 2r10 for float int (XMM0 RAX)
  * 2r11 for int int (RAX RDX)
  * 2r100 for float (XMM0)
  * 2r101 for int (RAX)
  * 2r110 INVALID (not aligned)
  Beware, the bits must be read from right to left for decoding register type.
  Note: this method reconstructs the struct layout according to X64 alignment rules.
  Therefore, it will not work for packed struct or other exotic alignment."
 
  <var: #specs type: #'unsigned int*'>
- <var: #subIndex type: #'unsigned int'>
  <inline: false>
  | index byteSize registerType |
  index := 0.
  byteSize := (specs at: index) bitAnd: FFIStructSizeMask.
  byteSize > 16 ifTrue: [^2r110].
  (self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)
  ifFalse: [^2r110].
  registerType := byteSize <= 8 ifTrue: [2r100] ifFalse: [0].
  ^(self isUnionSpec: specs OfLength: specSize StartingAt: 0)
  ifTrue: [ self
  registerType: registerType
  ForUnionSpecs: specs
  OfLength: specSize
  StartingAt: (self addressOf: index)
  ByteOffset: 0
  EightbyteOffset: 0 ]
  ifFalse: [ self
  registerType: registerType
  ForStructSpecs: specs
  OfLength: specSize
  StartingAt: (self addressOf: index)
  ByteOffset: 0
  EightbyteOffset: 0 ]!