VM Maker: FileAttributesPlugin.oscog-akg.49.mcz

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

VM Maker: FileAttributesPlugin.oscog-akg.49.mcz

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

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

Name: FileAttributesPlugin.oscog-akg.49
Author: akg
Time: 21 December 2018, 7:21:36.923596 pm
UUID: 00b4eed5-b2a8-454a-90b7-c3662d7c5423
Ancestors: FileAttributesPlugin.oscog-akg.48

FileAttributesPlugin 2.0.8

Get the plugin simulator working again.

Until the first call to #primitiveFailForOSError:, at which point the simulator fails.  Still on the ToDo list...

=============== Diff against FileAttributesPlugin.oscog-akg.48 ===============

Item was changed:
  VMStructType subclass: #FAPathPtr
+ instanceVariableNames: 'sessionId faPath plugin'
- instanceVariableNames: 'sessionId faPath'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'FileAttributesPlugin'!
+
+ !FAPathPtr commentStamp: 'akg 12/21/2018 11:42' prior: 0!
+ FAPathPtr simulates the FAPathPtr structure.  See platforms/Cross/plugins/FileAttributesPlugin/faCommon.h for details.
+
+ Instance Variables
+ faPath: <Array>
+ plugin: <FileAttributesPlugin>
+ sessionId: <Integer>
+
+ faPath
+ - The simulated fapath, currently an Array.
+
+ plugin
+ - The owning FileAttributesPlugin.  In case access to the interpreterProxy is required later on.
+
+ sessionId
+ - As supplied by the VM.
+ !

Item was added:
+ ----- Method: FAPathPtr class>>fromArray:plugin: (in category 'instance creation') -----
+ fromArray: anArray plugin: aFileAttributesPluginSimulator
+
+ ^self new
+ sessionId: anArray first;
+ faPath: anArray second;
+ plugin: aFileAttributesPluginSimulator;
+ yourself!

Item was added:
+ ----- Method: FAPathPtr class>>plugin: (in category 'instance creation') -----
+ plugin: aFileAttributesPlugin
+
+ ^self new
+ plugin: aFileAttributesPlugin;
+ yourself!

Item was added:
+ ----- Method: FAPathPtr>>plugin (in category 'accessing') -----
+ plugin
+
+ ^ plugin!

Item was added:
+ ----- Method: FAPathPtr>>plugin: (in category 'accessing') -----
+ plugin: anObject
+
+ ^ plugin := anObject.!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveChangeMode (in category 'file primitives') -----
  primitiveChangeMode
  "Set the mode of the supplied file using chmod()."
 
  | fileNameOop newMode status faPath |
  <export: true>
  <var: 'newMode' type: #'sqInt'>
  <var: 'faPath' type: #'fapath'>
 
  fileNameOop := interpreterProxy stackObjectValue: 1.
  newMode := interpreterProxy stackIntegerValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileNameOop) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  self cppIf: #HAVE_CHMOD ifTrue: [
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileNameOop.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  status := self chmod: (self faGetPlatPath: (self addressOf: faPath)) _: newMode.
  status ~= 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: (self cCode: 'errno')].
  ^interpreterProxy methodReturnValue: interpreterProxy nilObject.
  ].
  ^interpreterProxy primitiveFailForOSError: self unsupportedOperation.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveChangeOwner (in category 'file primitives') -----
  primitiveChangeOwner
  "Set the owner of the supplied file using chown()."
 
  | fileNameOop ownerId groupId faPath status |
  <export: true>
  <var: 'faPath' type: #'fapath'>
 
  fileNameOop := interpreterProxy stackObjectValue: 2.
  ownerId := interpreterProxy stackIntegerValue: 1.
  groupId := interpreterProxy stackIntegerValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileNameOop) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  self cppIf: #HAVE_CHOWN ifTrue: [
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileNameOop.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  status := self chown: (self faGetPlatPath: (self addressOf: faPath)) _: ownerId _: groupId.
  status ~= 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: (self cCode: 'errno')].
  ^interpreterProxy methodReturnValue: interpreterProxy nilObject.
  ].
  ^interpreterProxy primitiveFailForOSError: self unsupportedOperation.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveClosedir (in category 'file primitives') -----
  primitiveClosedir
  "Close the directory stream for dirPointerOop. Answer dirPointerOop on success.
  Raise PrimErrBadArgument if the parameter is not a ByteArray length size(void *).
  If closedir() returns an error raise PrimitiveOSError."
 
  | dirPointerOop faPathPtr faPath result |
  <export: true>
  <var: 'faPath' type: #'fapath *'>
  <var: 'faPathPtr' type: #'FAPathPtr *'>
 
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)' inSmalltalk: [self sizeOfFaPathPtr]).
- size: (self cCode: 'sizeof(FAPathPtr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ self cCode: '' inSmalltalk: [faPathPtr := FAPathPtr fromArray: faPathPtr plugin: self].
  (self faValidateSessionId: faPathPtr sessionId) ifFalse:
  [^interpreterProxy primitiveFailForOSError: self badSessionId].
  faPath := faPathPtr faPath.
 
  result := self faCloseDirectory: faPath.
+ self faInvalidateSessionId: (self cCode: '&faPathPtr->sessionId' inSmalltalk: [faPathPtr]).
- self faInvalidateSessionId: (self addressOf: faPathPtr sessionId).
  result = 0 ifFalse:
  [^interpreterProxy primitiveFailForOSError: result].
  self free: faPath.
  interpreterProxy methodReturnValue: dirPointerOop!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveFileAttribute (in category 'file primitives') -----
  primitiveFileAttribute
  "Answer a single file attribute.
  primFileAttributes: aString attributeNumber: attributeNumber
  aString is the path to the file
  attributeNumber identifies which attribute to return:
  1 - 12: stat(): name, mode, ino, dev, nlink, uid, gid, size, accessDate, modifiedDate, changeDate, creationDate
  13 - 15: access(): R_OK, W_OK, X_OK
  16: isSymlink
  On error, answer a single element array containing the appropriate error code."
 
  | fileName attributeNumber resultOop faPath |
  <export: true>
  <var: 'faPath' type: #'fapath'>
 
  fileName := interpreterProxy stackObjectValue: 1.
  attributeNumber := interpreterProxy stackIntegerValue: 0.
  (interpreterProxy failed
  or: [(attributeNumber between: 1 and: 16) not
  or: [(interpreterProxy isBytes: fileName) not]]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileName.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  resultOop := self faFileAttribute: (self addressOf: faPath) _: attributeNumber.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  resultOop = 0
  ifTrue: ["It shouldn't be possible to get here"
  interpreterProxy primitiveFailForOSError: self unexpectedError]
  ifFalse: [interpreterProxy methodReturnValue: resultOop]!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveFileAttributes (in category 'file primitives') -----
  primitiveFileAttributes
  "Answer an array of file attributes.
  primFileAttributes: aString mask: attributeMask
  aString is the path to the file
  attributeMask indicates which attributes to retrieve:
  bit 0 - get stat() attributes
  bit 1 - get access() attributes
  bit 2 - use lstat() instead of stat()
  On error answer the appropriate error code (Integer)"
 
  | fileName attributeMask faPath status resultOop  |
  <export: true>
  <var: 'faPath' type: #'fapath'>
 
  fileName := interpreterProxy stackObjectValue: 1.
  attributeMask := interpreterProxy stackIntegerValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileName) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileName.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  status := self attributeArray: (self addressOf: resultOop put: [ :val | resultOop := val])
  for: (self addressOf: faPath)
  mask: attributeMask.
  status ~= 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: status].
  ^interpreterProxy methodReturnValue: resultOop!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveFileExists (in category 'file primitives') -----
  primitiveFileExists
  "Check for existence of a file with a call to access()."
 
  | fileNameOop faPath resultOop |
  <export: true>
  <var: 'faPath'type: #'fapath'>
 
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  fileNameOop := interpreterProxy stackObjectValue: 0.
  (interpreterProxy isBytes: fileNameOop) ifFalse:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
  self faSetStPathOop: (self addressOf: faPath) _: fileNameOop.
  interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode].
 
  resultOop := self faExists: (self addressOf: faPath).
  ^interpreterProxy methodReturnValue: resultOop.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveOpendir (in category 'file primitives') -----
  primitiveOpendir
  "Open the supplied directory and answer the first entry and directory pointer.
  If the directory is empty, answer nil as the first entry.
  If the directory can't be opened, answer an error (cantOpenDir)"
  "self primOpendir: '/etc'"
 
  | dirName faPath faPathPtr dirOop status resultOop |
  <export: true>
  <var: 'faPath' type: #'fapath *'>
  <var: 'faPathPtr' type: #'FAPathPtr'>
-
  "Process the parameters"
  dirName := interpreterProxy stackObjectValue: 0.
  (interpreterProxy isBytes: dirName) ifFalse:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
  "Allocate and initialise faPath"
  faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
  inSmalltalk: [self simulatedFaPath].
  faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
  self faSetStDirOop: faPath _: dirName.
  interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode].
 
  (self canOpenDirectoryStreamFor: (self faGetStPath: faPath) length: (self faGetStPathLen: faPath)) ifFalse: [
  self free: faPath.
  ^interpreterProxy primitiveFailForOSError: self cantOpenDir].
 
  "Open the directory and process the first entry"
  status := self faOpenDirectory: faPath.
  status = self noMoreData ifTrue: [
  self free: faPath.
  ^interpreterProxy methodReturnValue: interpreterProxy nilObject].
  status < 0 ifTrue: [
  self free: faPath.
  ^interpreterProxy primitiveFailForOSError: status].
  resultOop := self processDirectory: faPath.
  interpreterProxy failed ifTrue: [
  self free: faPath.
  ^interpreterProxy primitiveFailureCode ].
 
  "Set the faPathPtr"
+ self cCode: '' inSmalltalk: [faPathPtr := FAPathPtr plugin: self].
+ self faInitSessionId: (self cCode: '&faPathPtr.sessionId' inSmalltalk: [faPathPtr]).
- self faInitSessionId: (self addressOf: faPathPtr sessionId).
  faPathPtr faPath: faPath.
  self remapOop: resultOop in:
  [ dirOop := self objectFromStruct: (self addressOf: faPathPtr) size: self sizeOfFaPathPtr ].
 
  ^interpreterProxy
  storePointer: 2 ofObject: resultOop withValue: dirOop;
  methodReturnValue: resultOop.!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitivePlatToStPath (in category 'file primitives') -----
  primitivePlatToStPath
  "Convert the supplied file name (platform encoded) to the St UTF8 encoded byte array"
 
  | fileName faPath resultOop byteArrayPtr |
  <export: true>
  <var: 'faPath' type: #'fapath'>
  <var: 'byteArrayPtr' type: #'unsigned char *'>
 
  fileName := interpreterProxy stackObjectValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileName) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetPlatPathOop: (self addressOf: faPath) _: fileName.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  resultOop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: (self faGetStPathLen: (self addressOf: faPath)).
  resultOop ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  byteArrayPtr := interpreterProxy arrayValueOf: resultOop.
  self memcpy: byteArrayPtr
  _: (self faGetStPath: (self addressOf: faPath))
  _: (self faGetStPathLen: (self addressOf: faPath)).
 
  ^interpreterProxy methodReturnValue: resultOop.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveReaddir (in category 'file primitives') -----
  primitiveReaddir
  "Get the next entry in the directory stream. Answer the name of the entry, or
  nil for the end of the directory stream.
  Arguments:
  - directoryPointer (ByteArray)"
 
  | dirPointerOop faPathPtr faPath resultArray status |
  <export: true>
  <var: 'faPath' type: #'fapath *'>
  <var: 'faPathPtr' type: #'FAPathPtr *'>
-
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)' inSmalltalk: [self sizeOfFaPathPtr]).
- size: (self cCode: 'sizeof(FAPathPtr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ self cCode: '' inSmalltalk: [faPathPtr := FAPathPtr fromArray: faPathPtr plugin: self].
  (self faValidateSessionId: faPathPtr sessionId) ifFalse:
  [^interpreterProxy primitiveFailForOSError: self badSessionId].
  faPath := faPathPtr faPath.
 
  status := self faReadDirectory: faPath.
  status = self noMoreData ifTrue:
  [^interpreterProxy methodReturnValue: interpreterProxy nilObject].
  status < 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: status].
  resultArray := self processDirectory: faPath.
  "no need to check the status of #processDirectory: as it will have flagged an error with interpreterProxy"
  ^interpreterProxy methodReturnValue: resultArray.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveRewinddir (in category 'file primitives') -----
  primitiveRewinddir
  "Set directoryStream to first entry. Answer dirPointerOop."
 
  | dirPointerOop faPathPtr faPath status resultOop |
  <export: true>
  <var: 'faPath' type: #'fapath *'>
  <var: 'faPathPtr' type: #'FAPathPtr *'>
 
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)' inSmalltalk: [self sizeOfFaPathPtr]).
- size: (self cCode: 'sizeof(FAPathPtr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ self cCode: '' inSmalltalk: [faPathPtr := FAPathPtr fromArray: faPathPtr plugin: self].
  (self faValidateSessionId: faPathPtr sessionId) ifFalse:
  [^interpreterProxy primitiveFailForOSError: self badSessionId].
  faPath := faPathPtr faPath.
 
  status := self faRewindDirectory: faPath.
  status < 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: status].
  resultOop := self processDirectory: faPath.
  "no need to check the status of #processDirectory: as it will have flagged an error with interpreterProxy"
  ^interpreterProxy methodReturnValue: resultOop.!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveStToPlatPath (in category 'file primitives') -----
  primitiveStToPlatPath
  "Convert the supplied file name (UTF8 encoded) to the platform encoded byte array"
 
  | fileName faPath resultOop byteArrayPtr |
  <export: true>
  <var: 'faPath' type: #'fapath'>
  <var: 'byteArrayPtr' type: #'unsigned char *'>
 
  fileName := interpreterProxy stackObjectValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileName) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
 
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileName.
  interpreterProxy failed ifTrue:
  [^interpreterProxy primitiveFailureCode].
 
  resultOop := interpreterProxy
  instantiateClass: interpreterProxy classByteArray
  indexableSize: (self faGetPlatPathByteCount: (self addressOf: faPath)).
  resultOop ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  byteArrayPtr := interpreterProxy arrayValueOf: resultOop.
  self memcpy: byteArrayPtr
  _: (self faGetPlatPath: (self addressOf: faPath))
  _: (self faGetPlatPathByteCount: (self addressOf: faPath)).
 
  ^interpreterProxy methodReturnValue: resultOop.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveSymlinkChangeOwner (in category 'file primitives') -----
  primitiveSymlinkChangeOwner
  "Set the owner of the supplied file using chown()."
 
  | fileNameOop ownerId groupId faPath status |
  <export: true>
  <var: 'faPath' type: #'fapath'>
 
  fileNameOop := interpreterProxy stackObjectValue: 2.
  ownerId := interpreterProxy stackIntegerValue: 1.
  groupId := interpreterProxy stackIntegerValue: 0.
  (interpreterProxy failed
  or: [(interpreterProxy isBytes: fileNameOop) not]) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  self cppIf: #HAVE_CHOWN ifTrue: [
+ self cCode: '' inSmalltalk: [faPath := self simulatedFaPath].
  self faSetStPathOop: (self addressOf: faPath) _: fileNameOop.
  interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode].
 
  status := self lchown: (self faGetPlatPath: (self addressOf: faPath)) _: ownerId _: groupId.
  status ~= 0 ifTrue:
  [^interpreterProxy primitiveFailForOSError: (self cCode: 'errno')].
  ^interpreterProxy methodReturnValue: interpreterProxy nilObject.
  ].
  ^interpreterProxy primitiveFailForOSError: self unsupportedOperation.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>versionString (in category 'version string') -----
  versionString
  "Answer a string containing the version string for this plugin."
  <inline: #always>
+ ^'2.0.8'!
- ^'2.0.7.1'!

Item was changed:
  ----- Method: FileAttributesPluginSimulator>>faFileAttribute:_: (in category 'simulation') -----
  faFileAttribute: faPath _: attributeNumber
  "Simulate the the call by actually calling the primitive."
 
+ | result |
+
+ result := self primFileAttribute: (self faGetStPath: faPath) number: attributeNumber.
+ result isNumber ifTrue: [interpreterProxy primitiveFailForOSError: result].
+ ^self toOop: result!
- ^self toOop: (self primFileAttribute: (self faGetStPath: faPath) number: attributeNumber)!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faFileStatAttributes:_:_: (in category 'simulation') -----
+ faFileStatAttributes: faPath _: getLinkStats _: attributeArray
+ "Simulate the call to faFileStatAttributes().
+ The simulator uses a dictionary with keys named after the stat structure members."
+
+ | path primArray mask |
+
+ path := self faGetStPath: faPath.
+ mask := getLinkStats
+ ifTrue: [5] "lstat()"
+ ifFalse: [1]. "stat()"
+ primArray := self primFileAttributes: path mask: 1.
+ primArray isNumber ifTrue: [^primArray].
+ primArray doWithIndex: [ :entry :index |
+ interpreterProxy
+ storePointer: index - 1
+ ofObject: attributeArray
+ withValue: (self toOop: entry)].
+ ^0!

Item was changed:
  ----- Method: FileAttributesPluginSimulator>>faInitSessionId: (in category 'simulation') -----
  faInitSessionId: faPathPtr
+ "Set the session id in the supplied pointer"
- "Set the session id in the supplied pointer (a 2 element array in the simulation)"
 
+ faPathPtr sessionId: interpreterProxy getThisSessionID.
- faPathPtr at: 1 put: interpreterProxy getThisSessionID.
  ^self faSuccess!

Item was changed:
  ----- Method: FileAttributesPluginSimulator>>faInvalidateSessionId: (in category 'simulation') -----
  faInvalidateSessionId: faPathPtr
  "Clear the session ID in the faPathPtr, marking it invalid"
 
+ faPathPtr sessionId: nil.
- faPathPtr at: 1 put: nil.
  ^self faSuccess!

Item was changed:
  ----- Method: FileAttributesPluginSimulator>>toOop: (in category 'simulation support') -----
  toOop: anObject
  "Convert the supplied simulation object to an object in the simulated image (oop).
  Use a horrible series of class comparisons to keep it all local for now"
 
  | resultOop resultBytes |
 
  anObject class == Array ifTrue: [
  resultOop := interpreterProxy
+ instantiateClass: interpreterProxy classArray
- instantiateClass: (interpreterProxy classArray)
  indexableSize: anObject size.
  1 to: anObject size do: [ :i |
  interpreterProxy
  storePointer: i-1
  ofObject: resultOop
  withValue: (self toOop: (anObject at: i))].
  ^resultOop].
  anObject class == ByteArray ifTrue: [
  resultOop := interpreterProxy
+ instantiateClass: interpreterProxy classByteArray
- instantiateClass: (interpreterProxy classByteArray)
  indexableSize: anObject size.
  resultBytes := interpreterProxy arrayValueOf: resultOop.
  1 to: anObject size do: [ :i |
  interpreterProxy byteAt: resultBytes+i-1 put: (anObject at: i)].
  ^resultOop].
  (anObject isKindOf: Boolean) ifTrue: [
  ^anObject
  ifTrue: [interpreterProxy trueObject]
  ifFalse: [interpreterProxy falseObject].
  ].
  anObject isInteger ifTrue: [
  (anObject between: -2147483648 and: 2147483648) ifTrue:
  [^interpreterProxy signed32BitIntegerFor: anObject].
  ^anObject > 0
  ifTrue: [interpreterProxy positive64BitIntegerFor: anObject]
  ifFalse: [interpreterProxy signed64BitIntegerFor: anObject]].
  anObject == nil ifTrue:
  [^interpreterProxy nilObject].
+ anObject class == FAPathPtr ifTrue: [
+ resultOop := interpreterProxy
+ instantiateClass: interpreterProxy classArray
+ indexableSize: 2.
+ interpreterProxy
+ storePointer: 0
+ ofObject: resultOop
+ withValue: (self toOop: anObject sessionId).
+ interpreterProxy
+ storePointer: 1
+ ofObject: resultOop
+ withValue: (self toOop: anObject faPath).
+ ^resultOop].
  self error: 'unknown object type'.!