VM Maker: FileAttributesPlugin.oscog-akg.48.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.48.mcz

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

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

Name: FileAttributesPlugin.oscog-akg.48
Author: akg
Time: 20 December 2018, 7:50:35.778942 am
UUID: a0562f0c-0958-460c-805b-634eb9dfcdbd
Ancestors: FileAttributesPlugin.oscog-akg.47

FileAttributesPlugin

Add FAPathPtr (subclass of VMStructType) to model the C type of the same name.

This is used to hold the pointer to the fapath while iterating over directories, with a session id to ensure that a stale pointer is never used.

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

Item was added:
+ VMStructType subclass: #FAPathPtr
+ instanceVariableNames: 'sessionId faPath'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'FileAttributesPlugin'!

Item was added:
+ ----- Method: FAPathPtr class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ "Define a CallbackContext, the argument to sendInvokeCallbackContext:
+ self typedef"
+
+ self instVarNames do:
+ [:ivn|
+ aBinaryBlock
+ value: ivn
+ value: (ivn caseOf: {
+ ['sessionId'] -> [#'int'].
+ ['faPath'] -> [#'fapath *']}
+ otherwise: [#'void *'])]!

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

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

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

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

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 *'>
- <var: 'faPathPtr' type: #'fapathptr *'>
 
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)').
- size: (self cCode: 'sizeof(fapathptr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ (self faValidateSessionId: faPathPtr sessionId) ifFalse:
+ [^interpreterProxy primitiveFailForOSError: self badSessionId].
+ faPath := faPathPtr faPath.
- (self faValidateSessionId: (self cCode: 'faPathPtr->sessionId' inSmalltalk: [faPathPtr first])) ifFalse:
- [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- faPath := self cCode: 'faPathPtr->faPath' inSmalltalk: [faPathPtr second].
 
  result := self faCloseDirectory: faPath.
+ self faInvalidateSessionId: (self addressOf: faPathPtr sessionId).
- self faInvalidateSessionId: (self cCode: '&faPathPtr->sessionId' inSmalltalk: [faPathPtr]).
  result = 0 ifFalse:
  [^interpreterProxy primitiveFailForOSError: result].
  self free: faPath.
  interpreterProxy methodReturnValue: dirPointerOop!

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'>
- <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 faInitSessionId: (self addressOf: faPathPtr sessionId).
+ faPathPtr faPath: faPath.
- self faInitSessionId: (self cCode: '&faPathPtr.sessionId' inSmalltalk: [faPathPtr := Array new: 2]).
- self cCode: 'faPathPtr.faPath = faPath'
- inSmalltalk: [faPathPtr at: 2 put: 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>>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 *'>
- <var: 'faPathPtr' type: #'fapathptr *'>
 
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)').
- size: (self cCode: 'sizeof(fapathptr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ (self faValidateSessionId: faPathPtr sessionId) ifFalse:
- (self faValidateSessionId: (self cCode: 'faPathPtr->sessionId' inSmalltalk: [faPathPtr first])) ifFalse:
  [^interpreterProxy primitiveFailForOSError: self badSessionId].
+ faPath := faPathPtr faPath.
- faPath := self cCode: 'faPathPtr->faPath' inSmalltalk: [faPathPtr second].
 
  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 *'>
- <var: 'faPathPtr' type: #'fapathptr *'>
 
  dirPointerOop := interpreterProxy stackValue: 0.
  faPathPtr := self structFromObject: dirPointerOop
+ size: (self cCode: 'sizeof(FAPathPtr)').
- size: (self cCode: 'sizeof(fapathptr)').
  faPathPtr = 0 ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ (self faValidateSessionId: faPathPtr sessionId) ifFalse:
+ [^interpreterProxy primitiveFailForOSError: self badSessionId].
+ faPath := faPathPtr faPath.
- (self faValidateSessionId: (self cCode: 'faPathPtr->sessionId' inSmalltalk: [faPathPtr first])) ifFalse:
- [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- faPath := self cCode: 'faPathPtr->faPath' inSmalltalk: [faPathPtr second].
 
  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>>sizeOfFaPathPtr (in category 'private') -----
  sizeOfFaPathPtr
  "Answer the size of fapathptr.
  The simulation uses a two element array."
 
+ ^self cCode: 'sizeof(FAPathPtr)'
- ^self cCode: 'sizeof(fapathptr)'
  inSmalltalk: [2].!

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.7.1'!
- ^'2.0.7'!