[Vm-dev] VM Maker: FileAttributesPlugin.oscog-akg.42.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 29 20:20:35 UTC 2019


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

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

Name: FileAttributesPlugin.oscog-akg.42
Author: akg
Time: 22 October 2018, 9:30:16.185912 pm
UUID: 5efde3da-1231-4285-879c-6ad23a0456f5
Ancestors: FileAttributesPlugin.oscog-AlistairGrant.41

FileAttributesPlugin 2.0.4

Extends support for running in the VM simulator.

This is still a work-in-progress:

- calling #primitiveFailForOSError: causes the simulator to fail.
- FilePlugin has more unicode fixes required.
- #memcpy:_:_: doesn't handle ByteArray's as a destination

=============== Diff against FileAttributesPlugin.oscog-AlistairGrant.28 ===============

Item was changed:
  ----- Method: FileAttributesPlugin class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: cg
  
  	self declareC:  #('sCLPfn' 'sCOFfn')
  		as: #'void *'
  		in: cg.
  	"Assume the security plugin can be loaded until proven otherwise"
  	cg var: 'hasSecurityPlugin' declareC: 'int hasSecurityPlugin = 1'.
  
+ 	cg addHeaderFile: '<errno.h>'.
  	cg addHeaderFile: '<limits.h>'.
  	cg addHeaderFile: '<sys/types.h>'.
+ 	cg addHeaderFile: '<unistd.h>'.
  	cg addHeaderFile: '<dirent.h>
+ #if _WIN32 || _WIN64
+ # include <windows.h>
+ # include <winbase.h>
+ # define FAIL() { return -1; }
+ # include "sqWin32File.h"
+ # if !!defined(PATH_MAX) /* work around bug in 64-bit cygwin; sigh :-( */
+ #	define PATH_MAX 4096
+ # endif
+ # define HAVE_CHMOD 0
+ # define HAVE_CHOWN 0
+ #else
+ #define HAVE_CHMOD 1
+ #define HAVE_CHOWN 1
+ #endif'.
+ 	cg addHeaderFile: '"faCommon.h"'.
- #ifdef _WIN32
- #include <windows.h>
- #include <winbase.h>
- #define FAIL() { return -1; }
- #include "sqWin32File.h"
- #endif
- typedef struct dirptrstruct {
-     		DIR *dp;
- 		int path_len;
-     		char *path_file;
-    		char path[PATH_MAX+4];
-     		} osdir;'.
  	cg addHeaderFile: '<sys/stat.h>
+ #if !!defined(HAVE_LSTAT) && !!defined(_WIN32) && !!defined(_WIN64)
+ # define HAVE_LSTAT 1
- #if !!defined(HAVE_LSTAT) && !!defined(_WIN32)
- #define HAVE_LSTAT 1
  #endif'.
  	cg addHeaderFile: '<unistd.h>
+ /* AKG 2018 - ', self moduleName, '.c translated from class ', self name, ' */'!
- /* AKG 2017 - ', self moduleName, '.c translated from class ', self name, ' */'!

Item was added:
+ ----- Method: FileAttributesPlugin class>>moduleName (in category 'translation') -----
+ moduleName
+ 
+ 	^ 'FileAttributesPlugin'!

Item was added:
+ ----- Method: FileAttributesPlugin class>>primFileAttributeOf:number: (in category 'testing') -----
+ primFileAttributeOf: pathString number: attributeNumber
+ 	"Answer a single file attribute.
+ 	 pathString 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, fail with an error code containing the appropriate OS error code."
+ 
+ 	"(1 to: 16) collect: [:i| self primFileAttributeOf: '.' number: i]"
+ 	"(1 to: 16) collect: [:i| self primFileAttributeOf: 'THIS HAS A GOOD CHANCE OF FAILING' number: i]"
+ 
+ 	<primitive: 'primitiveFileAttribute' module: 'FileAttributesPlugin' error: ec>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: FileAttributesPlugin class>>primFileAttributes:attributeNumber: (in category 'testing') -----
+ primFileAttributes: pathString attributeNumber: attributeNumber
+ 	"Answer a single file attribute.
+ 	primFileAttributes: aString attributeNumber: attributeNumber
+ 	pathString 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, fail with an error code containing the appropriate OS error code."
+ 
+ 	"(1 to: 16) collect: [:i| self installedFileAttributeFor: '.' numbered: i]"
+ 	"(1 to: 16) collect: [:i| self installedFileAttributeFor: 'THIS HAS A GOOD CHANCE OF FAILING' numbered: i]"
+ 
+ 	<primitive: 'primitiveFileAttribute' module: 'FileAttributesPlugin' error: ec>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: FileAttributesPlugin class>>shouldBeTranslated (in category 'translation') -----
+ shouldBeTranslated
+ 	^true!

Item was added:
+ ----- Method: FileAttributesPlugin class>>simulatorClass (in category 'simulation') -----
+ simulatorClass
+ 	^FileAttributesPluginSimulator!

Item was removed:
- ----- Method: FileAttributesPlugin>>accessAttributesForFilename:into:startingAt: (in category 'private - file') -----
- accessAttributesForFilename: cPathName into: attributeArray startingAt: offset
- 	"Call access() for each access type (R, W, X) on the c string cPathName, storing the results in the st array attributeArray."
- 
- 	| index boolean |
- 	<var: 'cPathName' type: 'char *'>
- 	index := offset.
- 	((self acc: cPathName ess: self fileReadableFlag) = 0)
- 		ifTrue: [boolean := interpreterProxy trueObject]
- 		ifFalse: [boolean := interpreterProxy falseObject].
- 	interpreterProxy
- 		storePointer: index
- 		ofObject: attributeArray
- 		withValue: boolean.
- 	index := index + 1.
- 	boolean := ((self acc: cPathName ess: self fileWriteableFlag) = 0)
- 					ifTrue: [interpreterProxy trueObject]
- 					ifFalse: [interpreterProxy falseObject].
- 	interpreterProxy
- 		storePointer: index
- 		ofObject: attributeArray
- 		withValue: boolean.
- 	index := index + 1.
- 	boolean := ((self acc: cPathName ess: self fileExecutableFlag) = 0)
- 					ifTrue: [interpreterProxy trueObject]
- 					ifFalse: [interpreterProxy falseObject].
- 	interpreterProxy
- 		storePointer: index
- 		ofObject: attributeArray
- 		withValue: boolean.
- !

Item was changed:
  ----- Method: FileAttributesPlugin>>addressObjectFor: (in category 'private - directory') -----
  addressObjectFor: aMachineAddress
  	"Answer an ExternalAddress object which represents aMachineAddress"
  
  	| addressOop addressOopArrayPointer addressUnion idx |
+ 	<var: 'aMachineAddress' type: #'void *'>
+ 	<var: 'addressUnion' type: 'union {void *address; unsigned char bytes[sizeof(void *)];}'>
+ 	<var: 'addressOopArrayPointer' type: #'unsigned char *'>
+ 	self touch: addressUnion.
- 	<var: 'aMachineAddress' type: 'void *'>
- 	<var: 'addressUnion' declareC: 'union {void *address; unsigned char bytes[sizeof(void *)];} addressUnion'>
- 	<var: 'addressOopArrayPointer' declareC: 'unsigned char *addressOopArrayPointer'>
  	addressOop := interpreterProxy
  		instantiateClass: interpreterProxy classByteArray
  		indexableSize: self sizeOfPointer.
  	addressOop ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	addressOopArrayPointer := interpreterProxy arrayValueOf: addressOop.
  	self cCode: 'addressUnion.address = aMachineAddress'.
  	idx := 0.
  	[idx < self sizeOfPointer] whileTrue:
  		[self cCode: 'addressOopArrayPointer[idx] = addressUnion.bytes[idx]'.
  		idx := idx + 1].
  	^ addressOop
  !

Item was removed:
- ----- Method: FileAttributesPlugin>>byteArrayFromCString:to: (in category 'private') -----
- byteArrayFromCString: aCString to: byteArrayOop
- 	"Answer a new ByteArray copied from a null-terminated C string.
- 	Caution: This may invoke the garbage collector."
- 
- 	| len newByteArray byteArrayPtr |
- 	<var: 'aCString' type: 'const char *'>
- 	<var: 'byteArrayPtr' type: 'unsigned char *'>
- 	<var: 'byteArrayOop' type: 'sqInt *'>
- 	len := self strlen: aCString.
- 	"We never return strings longer than PATH_MAX"
- 	len > #PATH_MAX ifTrue: [^self stringTooLong].
- 	newByteArray := interpreterProxy
- 		instantiateClass: interpreterProxy classByteArray
- 		indexableSize: len.
- 	newByteArray ifNil:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	byteArrayPtr := interpreterProxy arrayValueOf: newByteArray.
- 	self mem: byteArrayPtr cp: aCString y: len.
- 	byteArrayOop at: 0 put: newByteArray.
- 	^0!

Item was changed:
  ----- Method: FileAttributesPlugin>>canOpenDirectoryStreamFor:length: (in category 'private - directory') -----
  canOpenDirectoryStreamFor: aPathCString length: length
  	"Answer non-zero if security permits the directory to be listed."
  
  	"FIXME: This function has not been tested. -dtl"
  
+ 	<var: 'aPathCString' type: #'char *'>
- 	<var: 'aPathCString' type: 'char *'>
  	"If the security plugin can be loaded, use it to check . 
  	If not, assume it's ok"
  	"The hasSecurityPlugin flag is set to 1 by default"
  	(hasSecurityPlugin = 0) ifTrue: [^ true].
  	sCLPfn ~= 0
  		ifTrue:
  			[^ self cCode: ' ((int (*) (char *, int)) sCLPfn)(aPathCString, length)'
  				inSmalltalk: [true]]
  		ifFalse:
  			[hasSecurityPlugin := 0.	"Reset the flag so we do not try again next time"
  			^ true]
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>canStatFilePath:length: (in category 'private - file') -----
  canStatFilePath: aPathCString length: length
  	"Answer non-zero if security permits the a stat() call on the file path. Allow a
  	stat() call only on files which we are permitted to open."
  
  	"FIXME: This function has not been tested. -dtl"
  
+ 	<var: 'aPathCString' type: #'char *'>
- 	<var: 'aPathCString' type: 'char *'>
  	"If the security plugin can be loaded, use it to check . 
  	If not, assume it's ok"
  	"The hasSecurityPlugin flag is set to 1 by default"
  	(hasSecurityPlugin = 0) ifTrue: [^ true].
  	sCOFfn ~= 0
  		ifTrue:
  			[^ self cCode: ' ((int (*) (char *, int, int)) sCOFfn)(aPathCString, length, 0)'
  				inSmalltalk: [true]]
  		ifFalse: 
  			[hasSecurityPlugin := 0.	"Reset the flag so we do not try again next time"
  			^ true]
  !

Item was changed:
+ ----- Method: FileAttributesPlugin>>cantAllocateMemory (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>cantAllocateMemory (in category 'errors') -----
  cantAllocateMemory
  	<inline: #always>
  	^-10!

Item was changed:
+ ----- Method: FileAttributesPlugin>>cantOpenDir (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>cantOpenDir (in category 'errors') -----
  cantOpenDir
  	<inline: #always>
  	^-9!

Item was changed:
+ ----- Method: FileAttributesPlugin>>cantReadlink (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>cantReadlink (in category 'errors') -----
  cantReadlink
  	<inline: #always>
  	^-8!

Item was changed:
+ ----- Method: FileAttributesPlugin>>cantStatPath (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>cantStatPath (in category 'errors') -----
  cantStatPath
  	"SecurityPlugin determined that the requested path cannot be accessed."
  	<inline: #always>
  	^-3!

Item was removed:
- ----- Method: FileAttributesPlugin>>checkAccess:mode:to: (in category 'private - file') -----
- checkAccess: pathString mode: mode to: flag
- 	"Check access to pathString."
- 
- 	| cString len sPtr |
- 	<export: true>
- 	<var: 'cString' declareC: 'char cString[PATH_MAX]'>
- 	<var: 'sPtr' declareC: 'char *sPtr'>
- 	<var: 'flag' type: 'sqInt *'>
- 	len := interpreterProxy stSizeOf: pathString.
- 	"Note: The static sized string buffer is faster than using a Smalltalk allocated
- 	string as the buffer, and is unlikely to fail in practice. In the event that
- 	the buffer turns out to be too small, write an error message to stdout before
- 	failing."
- 	len >= #PATH_MAX ifTrue: [^self stringTooLong].
- 	"Copy pathString to the new string"
- 	sPtr := interpreterProxy arrayValueOf: pathString.
- 	((self canStatFilePath: sPtr length: len) = 0) ifTrue: [^self cantStatPath].
- 	self mem: cString cp: sPtr y: len.
- 	cString at: len put: 0.
- 	flag at: 0 put: (self acc: cString ess: mode).
- 	^0
- !

Item was added:
+ ----- Method: FileAttributesPlugin>>convertWinToSqueakTime: (in category 'private - windows') -----
+ convertWinToSqueakTime: st
+ 	"Convert the supplied Windows SYSTEMTIME to Squeak time"
+ 	<option: #_WIN32>
+ 
+ 	| dy secs nDaysPerMonth |
+ 
+ 	<returnTypeC: #'sqLong'>
+ 	<var: 'st' type: #'SYSTEMTIME'>
+ 	<var: 'dy' type: #'sqLong'>
+ 	<var: 'secs' type: #'sqLong'>
+ 	<var: 'nDaysPerMonth' declareC: 'static sqLong nDaysPerMonth[14] = { 
+ 		0,  0,  31,  59,  90, 120, 151,
+ 		181, 212, 243, 273, 304, 334, 365 }'>
+ 	self touch: nDaysPerMonth.
+ 
+ 	"Squeak epoch is Jan 1, 1901"
+ 	"compute delta year"
+ 	dy := (self cCode: 'st.wYear') - 1901.
+ 	secs := (dy * 365 * 24 * 60 * 60)       "base seconds"
+ 			+ ((dy bitShift: -2) * 24 * 60 * 60).   "seconds of leap years"
+ 	"check if month > 2 and current year is a leap year"
+ 	[ (self cCode: 'st.wMonth') > 2 and: [ (dy bitAnd: 16r0003) = 16r0003 ]] ifTrue: [
+ 		"add one day"
+ 		secs := secs + (24 * 60 * 60) ].
+ 	"add the days from the beginning of the year"
+ 	secs := secs + (self cCode: '(nDaysPerMonth[st.wMonth] + st.wDay - 1) * 24 * 60 * 60').
+ 	"add the hours, minutes, and seconds"
+ 	secs := secs + (self cCode: 'st.wSecond + 60*(st.wMinute + 60*st.wHour)').
+ 	^secs
+ !

Item was changed:
+ ----- Method: FileAttributesPlugin>>corruptValue (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>corruptValue (in category 'errors') -----
  corruptValue
  	<inline: #always>
  	^-7!

Item was removed:
- ----- Method: FileAttributesPlugin>>fileCreationTimeFor:length:to: (in category 'private - windows') -----
- fileCreationTimeFor: pathString length: pathLength to: creationDate
- 	"Get the creationDate for the supplied file.
- 	Linux kernel 4.11 should have statx(), so hopefully there will be a cross-platform
- 	solution soon.  Just dump the c-code and hope to remove it soon."
- 	<option: #_WIN32>
- 	| tm winAttrs win32Path sysTime |
- 	<var: 'pathString' type: 'char *'>
- 	<var: 'creationDate' type: 'time_t *'>
- 	<var: 'tm' type: 'struct tm'>
- 	<var: 'winAttrs' type: 'WIN32_FILE_ATTRIBUTE_DATA'>
- 	<var: 'win32Path' type: 'WCHAR *'>
- 	<var: 'sysTime' type: 'SYSTEMTIME'>
- 	self touch: winAttrs.
- 	self touch: sysTime.
- 	self me: (self addressOf: tm) ms: 0 et: tm sizeof.
- 	"convert the supplied path name into a wide string"
- 	self ALLOC_: win32Path WIN32_: pathString PATH: pathLength.
- 	(self cCode: 'GetFileAttributesExW(win32Path, 0, &winAttrs)') = 0 ifTrue:
-  		[^self getAttributesFailed].
- 	(self cCode: 'FileTimeToSystemTime(&winAttrs.ftCreationTime, &sysTime)') = 0 ifTrue:
-  		[^self timeConversionFailed].
- 
- 	self cCode: '
- 	tm.tm_year = sysTime.wYear - 1900;
- 	tm.tm_mon = sysTime.wMonth - 1;
- 	tm.tm_mday = sysTime.wDay;
- 
- 	tm.tm_hour = sysTime.wHour;
- 	tm.tm_min = sysTime.wMinute;
- 	tm.tm_sec = sysTime.wSecond;
- 	tm.tm_isdst = 0;
- 	*creationDate = mktime(&tm)'.
- 
- 	^0!

Item was changed:
  ----- Method: FileAttributesPlugin>>fileToAttributeArray:mask:array: (in category 'private - file') -----
+ fileToAttributeArray: faPath mask: attributeMask array: attributeArray
- fileToAttributeArray: cPathName mask: attributeMask array: attributeArray
  	"Answer a file attribute array from pathNameOop."
  
  	| getStats useLstat getAccess statArray accessArray combinedArray status fileNameOop statBuf  |
+ 	<returnTypeC: #'int'>
+ 	<var: 'faPath' type: #'fapath *'>
+ 	<var: 'attributeArray' type: #'sqInt *'>
+ 	<var: 'statBuf' type: #'faStatStruct'>
- 	<returnTypeC: 'int'>
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'attributeArray' type: 'sqInt *'>
- 	<var: 'statBuf' type: 'struct stat'>
  
  	"Determine which attributes to retrieve"
  	getStats := attributeMask anyMask: 1.
  	getAccess := attributeMask anyMask: 2.
  	(getStats or: [getAccess]) ifFalse:
  		["No information has been requested, which doesn't make sense"
  		^self invalidArguments].
  	getStats ifTrue: 
  		[
  		useLstat := attributeMask anyMask: 4.
  		statArray := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 12.
  		statArray ifNil:
  			[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 		self cCode: '' inSmalltalk: [
+ 			statBuf := ValueHolder new. "ByteArray new: 1024"
+ 			fileNameOop := ValueHolder new].
  		status := useLstat ifFalse:
+ 					[ self faStat: faPath _: (self addressOf: statBuf ) _: (self addressOf: fileNameOop) ]
- 					[ self putStatFor: cPathName
- 							intoBuffer: (self addressOf: statBuf)
- 							targetName:  (self addressOf: fileNameOop) ]
  				ifTrue:
+ 					[ self faLinkStat: faPath _: (self addressOf: statBuf ) _: (self addressOf: fileNameOop) ].
- 					[ self putLStatFor: cPathName
- 							intoBuffer: (self addressOf: statBuf)
- 							targetName:  (self addressOf: fileNameOop) ].
  		status ~= 0 ifTrue: [^status].
+ 		status := self statArrayFor: faPath toArray: statArray from: (self addressOf: statBuf) fileName: fileNameOop.
- 		status := self statArrayFor: cPathName toArray: statArray from: (self addressOf: statBuf) fileName: fileNameOop.
  		status ~= 0 ifTrue: [^status].
  		"Set attributeArray in case only stat() attributes have been requested"
  		attributeArray at: 0 put: statArray
  		].
  	getAccess ifTrue: 
  		[
  		accessArray := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 3.
  		accessArray ifNil:
  			[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 		self faAccessAttributes: faPath _: accessArray _: 0.
- 		self accessAttributesForFilename: cPathName into: accessArray startingAt: 0.
  		"Set attributeArray in case only access() attributes have been requested"
  		attributeArray at: 0 put: accessArray
  		].
+ 	(getStats and: [getAccess]) ifTrue: 
- 	[getStats and: [getAccess]] ifTrue: 
  		[
  		combinedArray := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
  		combinedArray ifNil:
  			[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  		attributeArray at: 0 put: combinedArray.
  		interpreterProxy
  			storePointer: 0 ofObject: combinedArray withValue: statArray;
  			storePointer: 1 ofObject: combinedArray withValue: accessArray
  		].
  
  	^0!

Item was changed:
+ ----- Method: FileAttributesPlugin>>getAttributesFailed (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>getAttributesFailed (in category 'errors') -----
  getAttributesFailed
  	<inline: #always>
  	^-4!

Item was changed:
+ ----- Method: FileAttributesPlugin>>invalidArguments (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>invalidArguments (in category 'errors') -----
  invalidArguments
  	<inline: #always>
  	^-6!

Item was changed:
+ ----- Method: FileAttributesPlugin>>invalidRequest (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>invalidRequest (in category 'errors') -----
  invalidRequest
  	<inline: #always>
  	^-11!

Item was removed:
- ----- Method: FileAttributesPlugin>>isSymlink:boolean: (in category 'private - file') -----
- isSymlink: cPathName boolean: resultOop
- 	"Set resultOop to a boolean indicating whether cPathName is a symbolic link.
- 	Answer status (0 = success)"
- 
- 	| status statBuf |
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'resultOop' type: 'sqInt *'>
- 	<var: 'statBuf' type: 'struct stat'>
- 	self touch: statBuf.
- 	self cppIf: #HAVE_LSTAT == 1 ifTrue:
- 		[status := self lst: cPathName at: (self addressOf: statBuf).
- 		status ~= 0 ifTrue: [^self cantStatPath].
- 		(self S_ISLNK: statBuf st_mode) = 0
- 			ifFalse: [resultOop at: 0 put: interpreterProxy trueObject]
- 			ifTrue: [resultOop at: 0 put: interpreterProxy falseObject]].
- 	^0!

Item was added:
+ ----- Method: FileAttributesPlugin>>noMoreData (in category 'errors / status') -----
+ noMoreData
+ 	<inline: #always>
+ 	^1!

Item was removed:
- ----- Method: FileAttributesPlugin>>offsetStatBufTimesForWIN32: (in category 'private - windows') -----
- offsetStatBufTimesForWIN32: statBufPointer
- 	"Adjust the statBuffer to UTC, see https://msdn.microsoft.com/en-us/library/windows/desktop/ms725481(v=vs.85).aspx"
- 	<option: #_WIN32>
- 	<var: 'statBufPointer' type: 'struct stat *'>
- 	| status  dtzi offset |
- 	<var: 'offset' type: 'long'>
- 	<var: 'dtzi' type: 'TIME_ZONE_INFORMATION'>
- 	status := self GetTimeZoneInformation: (self addressOf: dtzi).
- 	offset := (self cCode: 'dtzi.Bias' inSmalltalk: [0]) * 60.
- 	"Adjust for DST if required"
- 	status = 2 ifTrue: [offset := offset - 3600].
- 	self cCode: 'statBufPointer->st_atime += offset'.
- 	self cCode: 'statBufPointer->st_mtime += offset'.
- 	self cCode: 'statBufPointer->st_ctime += offset'.!

Item was removed:
- ----- Method: FileAttributesPlugin>>oopFromTimeT: (in category 'private') -----
- oopFromTimeT: posixSeconds
- 	"Answer an object representation of the provided time (time_t).
- 	The size of time_t is platform dependent, so check the size and convert appropriately."
- 
- 	<var: 'posixSeconds' type: 'time_t'>
- 
- 	^(self sizeof: #time_t) = 4 ifTrue:
- 		[interpreterProxy signed32BitIntegerFor: posixSeconds]
- 	ifFalse:
- 		[interpreterProxy signed64BitIntegerFor: posixSeconds].
- !

Item was removed:
- ----- Method: FileAttributesPlugin>>openDirectoryStream:ptr: (in category 'private - directory') -----
- openDirectoryStream: pathOOP ptr: osdirPtr
- 	"Open a new directory stream. Answer a pointer to the directory stream or NULL."
- 
- 	| sPtr len dir |
- 	<var: 'osdirPtr' type: 'osdir **'>
- 	<var: 'sPtr' declareC: 'char *sPtr'>
- 	<var: 'dir' type: 'osdir *'>
- 	<returnTypeC: 'int'>
- 	sPtr := interpreterProxy arrayValueOf: pathOOP.
- 	len := interpreterProxy sizeOfSTArrayFromCPrimitive: sPtr.
- 	"The path buffer needs room for a trailing slash and the file name, so subtracting 2 is conservative"
- 	len > (#PATH_MAX - 2) ifTrue: [^self stringTooLong].
- 	(self canOpenDirectoryStreamFor: sPtr length: len)
- 		ifTrue:
- 			[
- 			dir := self cCode: '(osdir *) malloc(sizeof(osdir))'.
- 			dir = nil ifTrue: [^self cantAllocateMemory].
- 			self mem: dir path cp: sPtr y: len.
- 			"Ensure path has a trailing slash"
- 			self cCode: 'if (dir->path[len-1] !!= ''/'') {
- 				dir->path[len++] = ''/'';
- 				}'.
- 			self cCode: 'dir->path_file = dir->path + len'.
- 			self cCode: 'dir->path_file[0] = ''\0'''.
- 			self cCode: 'dir->path_len = len'.
- 			self cCode: 'dir->dp =  opendir(dir->path)'.
- 			dir dp ifNil:
- 				[self free: dir.
- 				^self cantOpenDir].
- 			osdirPtr at: 0 put: dir.
- 			^0
- 			].
- 	"If we get here, we can't open the directory"
- 	^self cantOpenDir
- !

Item was changed:
  ----- Method: FileAttributesPlugin>>pathOop:toBuffer:maxLen: (in category 'private - file') -----
  pathOop: pathNameOop toBuffer: cPathName maxLen: maxLen
  	"Copy the supplied path name string object to the supplied c string buffer"
  
  	| len sPtr |
+ 	<var: 'cPathName' type: #'char *'>
+ 	<var: 'sPtr' type: #'char *'>
+ 	<returnTypeC: #'int'>
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'sPtr' type: 'char *'>
- 	<returnTypeC: 'int'>
  
  	len := interpreterProxy stSizeOf: pathNameOop.
  	(len >= maxLen) ifTrue: [^self stringTooLong].
  	"Copy pathName to the new string"
  	sPtr := interpreterProxy arrayValueOf: pathNameOop.
  	((self canStatFilePath: sPtr length: len) = 0) ifTrue: [^self cantStatPath].
+ 	self memcpy: cPathName _: sPtr _: len.
- 	self mem: cPathName cp: sPtr y: len.
  	cPathName at: len put: 0.
  	^0.
  !

Item was changed:
  ----- Method: FileAttributesPlugin>>pointerFrom: (in category 'private - directory') -----
  pointerFrom: directoryPointerBytes
  	"Answer the machine address contained in anExternalAddressOop."
  
  	| ptr addressUnion idx |
+ 	<returnTypeC: #'void *'>
+ 	<var: 'ptr' type: #'unsigned char *'>
- 	<returnTypeC: 'void *'>
- 	<var: 'ptr' type: 'unsigned char *'>
  	<var: 'addressUnion' type: 'union {void *address; unsigned char bytes[sizeof(void *)];}'>
  	((interpreterProxy is: directoryPointerBytes KindOf: 'ByteArray') and:
  		[(interpreterProxy stSizeOf: directoryPointerBytes) = self sizeOfPointer])
  		ifFalse: [^ nil].
  	ptr := interpreterProxy arrayValueOf: directoryPointerBytes.
  	idx := 0.
  	[idx < self sizeOfPointer] whileTrue:
  		[self cCode: 'addressUnion.bytes[idx] = ptr[idx]'.
  		idx := idx + 1].
  	^ self cCode: 'addressUnion.address' inSmalltalk: [addressUnion]
  !

Item was added:
+ ----- Method: FileAttributesPlugin>>posixFileTimesFrom:to: (in category 'private - posix') -----
+ posixFileTimesFrom: statBufPointer to: attributeArray
+ 	"Populate attributeArray with the file times from statBufPointer"
+ 
+ 	| attributeDate |
+ 
+ 	<var: 'statBufPointer' type: #'faStatStruct *'>
+ 	<var: 'attributeDate' type: #'sqLong'>
+ 
+ 	self cppIf: #_WIN32 defined ifTrue: [] ifFalse: [
+ 	attributeDate := self faConvertUnixToLongSqueakTime: (self
+ 		cCode: 'statBufPointer->st_atime'
+ 		inSmalltalk: [statBufPointer contents at: 9]).
+ 	interpreterProxy
+ 		storePointer: 8
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 	attributeDate := self faConvertUnixToLongSqueakTime: (self
+ 		cCode: 'statBufPointer->st_mtime'
+ 		inSmalltalk: [statBufPointer contents at: 10]).
+ 	interpreterProxy
+ 		storePointer: 9
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 	attributeDate := self faConvertUnixToLongSqueakTime: (self
+ 		cCode: 'statBufPointer->st_ctime'
+ 		inSmalltalk: [statBufPointer contents at: 11]).
+ 	interpreterProxy
+ 		storePointer: 10
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate);
+ 		storePointer: 11
+ 			ofObject: attributeArray
+ 				withValue: interpreterProxy nilObject ].
+ 	^0!

Item was added:
+ ----- 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: [
+ 		faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 						inSmalltalk: [self simulatedFaPath].
+ 		faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 		self faSetStPathOop: faPath _: fileNameOop.
+ 		interpreterProxy failed ifTrue: [
+ 			self free: faPath.
+ 			^interpreterProxy primitiveFailureCode].
+ 
+ 		status := self chmod: (self faGetPlatPath: faPath) _: newMode.
+ 		self free: faPath.
+ 		status ~= 0 ifTrue: [
+ 			^interpreterProxy primitiveFailForOSError: (self cCode: 'errno')].
+ 		^interpreterProxy methodReturnValue: interpreterProxy nilObject.
+ 		].
+ 	^interpreterProxy primitiveFailForOSError: self unsupportedOperation.
+ !

Item was added:
+ ----- 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: [
+ 		faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 						inSmalltalk: [self simulatedFaPath].
+ 		faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 		self faSetStPathOop: faPath _: fileNameOop.
+ 		interpreterProxy failed ifTrue: [
+ 			self free: faPath.
+ 			^interpreterProxy primitiveFailureCode].
+ 
+ 		status := self chown: (self faGetPlatPath: faPath) _: ownerId _: groupId.
+ 		self free: faPath.
+ 		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 faPath result |
- 	| dirPointerOop dirStream result |
  	<export: true>
+ 	<var: 'fapath' type: #'faPath *'>
+ 
- 	<var: 'dirStream' type: 'osdir *'>
  	dirPointerOop := interpreterProxy stackValue: 0.
+ 	faPath := self pointerFrom: dirPointerOop.
+ 	faPath ifNil:
- 	dirStream := self pointerFrom: dirPointerOop.
- 	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 
+ 	result := self faCloseDirectory: faPath.
- 	result := self closedir: dirStream dp.
  	result = 0 ifFalse:
+ 		[^interpreterProxy primitiveFailForOSError: result].
+ 	self free: faPath.
- 		[^interpreterProxy primitiveFailForOSError: self unableToCloseDir].
- 	self free: dirStream.
  	interpreterProxy pop: 2 thenPush: 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 |
- 	| fileName attributeNumber resultOop fileNameOop statBuf cPathName sizeIfFile mode creationDate status |
  	<export: true>
+ 	<var: 'faPath' type: #'fapath *'>
- 	<var: 'statBuf' type: 'struct stat'>
- 	<var: 'cPathName' declareC: 'char cPathName[PATH_MAX]'>
- 	<var: 'creationDate' type: 'time_t'>
  
  	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].
- 	or: [(attributeNumber between: 1 and: 16) not
- 	or: [(interpreterProxy is: fileName KindOf: 'String') not]]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	status := self pathOop: fileName toBuffer: cPathName maxLen: #PATH_MAX.
- 	status ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailForOSError: status].
- 	resultOop := 0.
  
+ 	faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 				inSmalltalk: [self simulatedFaPath].
+ 	faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 	self faSetStPathOop: faPath _: fileName.
+ 	interpreterProxy failed ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailureCode].
- 	attributeNumber < 12 ifTrue:
- 		"Get requested stat entry"
- 		[
- 		status := self
- 			putStatFor: cPathName
- 			intoBuffer: (self addressOf: statBuf)
- 			targetName: (self addressOf: fileNameOop).
- 		status ~= 0 ifTrue: 
- 			[^interpreterProxy primitiveFailForOSError: status].
- 		"In C, this would naturally be a switch statement,
- 		but I don't know to mix in the smalltalk code"
- 		attributeNumber = 1 ifTrue: [resultOop := fileNameOop].
- 		attributeNumber = 2 ifTrue:
- 			[resultOop := interpreterProxy positiveMachineIntegerFor: statBuf st_mode].
- 		attributeNumber = 3 ifTrue:
- 			[resultOop := interpreterProxy positive64BitIntegerFor: statBuf st_ino].
- 		attributeNumber = 4 ifTrue:
- 			[resultOop := interpreterProxy positive64BitIntegerFor: statBuf st_dev].
- 		attributeNumber = 5 ifTrue:
- 			[resultOop := interpreterProxy positive64BitIntegerFor: statBuf st_nlink].
- 		attributeNumber = 6 ifTrue:
- 			[resultOop := interpreterProxy positiveMachineIntegerFor: statBuf st_uid].
- 		attributeNumber = 7 ifTrue:
- 			[resultOop := interpreterProxy positiveMachineIntegerFor: statBuf st_gid].
- 		attributeNumber = 8 ifTrue:
- 			[
- 			sizeIfFile := ((self S_ISDIR: statBuf st_mode) = 0)
- 							ifTrue: [statBuf st_size]
- 							ifFalse: [0].
- 			resultOop := interpreterProxy positiveMachineIntegerFor: sizeIfFile
- 			].
- 		attributeNumber = 9 ifTrue:
- 			[resultOop := self oopFromTimeT: statBuf st_atime].
- 		attributeNumber = 10 ifTrue:
- 			[resultOop := self oopFromTimeT: statBuf st_mtime].
- 		attributeNumber = 11 ifTrue:
- 			[resultOop := self oopFromTimeT: statBuf st_ctime].
- 		]
- 	ifFalse: [attributeNumber = 12  ifTrue:
- 		[
- 		self cppIf: #_WIN32 defined ifTrue: [
- 			status := self fileCreationTimeFor: cPathName
- 				length: cPathName strlen
- 				to: (self addressOf: creationDate put: [:val| creationDate := val]).
- 			status ~= 0 ifTrue:
- 				[^interpreterProxy primitiveFailForOSError: status].
- 			resultOop := self oopFromTimeT: creationDate ] 
- 		ifFalse: [
- 			resultOop := interpreterProxy nilObject ]
- 		]
- 	ifFalse: [attributeNumber < 16 ifTrue:
- 		"Get requested access entry"
- 		[
- 		attributeNumber = 13 ifTrue: [mode := self fileReadableFlag].
- 		attributeNumber = 14 ifTrue: [mode := self fileWriteableFlag].
- 		attributeNumber = 15 ifTrue: [mode := self fileExecutableFlag].
- 		resultOop := ((self acc: cPathName ess: mode) = 0)
- 						ifTrue: [interpreterProxy trueObject]
- 						ifFalse: [interpreterProxy falseObject].
- 		]
- 	ifFalse: "attributeNumber = 16"
- 		[
- 		status := self isSymlink: cPathName boolean: (self addressOf: resultOop put: [:val| resultOop := val]).
- 		status ~= 0 ifTrue: 
- 			[^interpreterProxy primitiveFailForOSError: status].
- 		]]].
  
+ 	resultOop := self faFileAttribute: faPath _: attributeNumber.
+ 	self free: faPath.
+ 	interpreterProxy failed ifTrue: [
+ 		^interpreterProxy primitiveFailureCode].
+ 
  	resultOop = 0
  		ifTrue: ["It shouldn't be possible to get here"
+ 			interpreterProxy primitiveFailForOSError: self unexpectedError]
+ 		ifFalse: [interpreterProxy methodReturnValue: resultOop]!
- 			interpreterProxy primitiveFail]
- 		ifFalse: [interpreterProxy pop: 3 thenPush: 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 attributeArray faPath status |
- 	| fileName attributeMask attributeArray cPathName status |
  	<export: true>
+ 	<var: 'faPath' type: #'fapath *'>
+ 
- 	<var: 'cPathName' declareC: 'char cPathName[PATH_MAX]'>
  	fileName := interpreterProxy stackObjectValue: 1.
  	attributeMask := interpreterProxy stackIntegerValue: 0.
  	(interpreterProxy failed
+ 	or: [(interpreterProxy isBytes: fileName) not]) ifTrue:
- 	or: [(interpreterProxy is: fileName KindOf: 'String') not]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	status := self pathOop: fileName toBuffer: cPathName maxLen: #PATH_MAX.
- 	status ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailForOSError: status].
  
+ 	faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 				inSmalltalk: [self simulatedFaPath].
+ 	faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 	self faSetStPathOop: faPath _: fileName.
+ 	interpreterProxy failed ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailureCode].
+ 
+ 	status := self fileToAttributeArray: faPath
- 	status := self fileToAttributeArray: cPathName 
  					mask: attributeMask 
  					array: (self addressOf: attributeArray put: [:val| attributeArray := val]).
+ 	self free: faPath.
  	status ~= 0
  		ifTrue: [interpreterProxy primitiveFailForOSError: status]
+ 		ifFalse: [interpreterProxy methodReturnValue: attributeArray]!
- 		ifFalse: [interpreterProxy pop: 3 thenPush: attributeArray]!

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 |
- 	| pathString status accessFlag |
  	<export: true>
+ 	<var: 'faPath'type: #'fapath *'>
+ 
+ 	fileNameOop := interpreterProxy stackObjectValue: 0.
+ 	(interpreterProxy isBytes: fileNameOop) ifFalse:
- 	<var: 'accessFlag' type: 'sqInt'>
- 	pathString := interpreterProxy stackObjectValue: 0.
- 	(interpreterProxy is: pathString KindOf: 'String') ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 
+ 	faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 				inSmalltalk: [self simulatedFaPath].
+ 	faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 	self faSetStPathOop: faPath _: fileNameOop.
+ 	interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode].
+ 
+ 	resultOop := self faExists: faPath.
+ 	self free: faPath.
+ 	^interpreterProxy methodReturnValue: resultOop.
+ !
- 	status := self checkAccess: pathString mode: self fileOKFlag to: (self addressOf: accessFlag).
- 	status = 0 ifFalse: [^interpreterProxy primitiveFailForOSError: status].
- 	interpreterProxy pop: 2 thenPush: (accessFlag = 0
- 									ifTrue: [interpreterProxy trueObject]
- 									ifFalse: [interpreterProxy falseObject])!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveFileMasks (in category 'file primitives') -----
  primitiveFileMasks
  	"Answer an array of well known file masks"
  
  	| masks |
  	<export: true>
  	masks := interpreterProxy instantiateClass: (interpreterProxy classArray) indexableSize: 8.
  	masks ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	interpreterProxy
  		storePointer: 0
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFMT] inSmalltalk: [16rF000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFMT').
  	self cppIf: #_WIN32 defined not
+ 		ifTrue: [
+ 			interpreterProxy
- 		ifTrue:
- 			[interpreterProxy
  				storePointer: 1
  				ofObject: masks
+ 				withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFSOCK] inSmalltalk: [16rC000])).
- 				withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFSOCK').
  			interpreterProxy
  				storePointer: 2
  				ofObject: masks
+ 				withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFLNK] inSmalltalk: [16rA000]))].
- 				withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFLNK')].
  	interpreterProxy
  		storePointer: 3
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFREG] inSmalltalk: [16r8000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFREG').
  	interpreterProxy
  		storePointer: 4
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFBLK] inSmalltalk: [16r6000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFBLK').
  	interpreterProxy
  		storePointer: 5
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFDIR] inSmalltalk: [16r4000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFDIR').
  	interpreterProxy
  		storePointer: 6
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFCHR] inSmalltalk: [16r2000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFCHR').
  	interpreterProxy
  		storePointer: 7
  		ofObject: masks
+ 		withValue: (interpreterProxy positive32BitIntegerFor: (self cCode: [#S_IFIFO] inSmalltalk: [16r1000])).
- 		withValue: (interpreterProxy positiveMachineIntegerFor: #'S_IFIFO').
  	interpreterProxy pop: 1 thenPush: masks!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveLogicalDrives (in category 'file primitives') -----
  primitiveLogicalDrives
  	"Answer the logical drive mask on windows"
  
+ 	| mask |
  	<export: true>
  	<var: 'mask' type: #'unsigned int'>
  	self cppIf: #_WIN32 defined
  		ifTrue:
+ 			[
- 			[| mask |
  			 mask := self GetLogicalDrives.
  			 mask ~= 0 ifTrue:
  				[^interpreterProxy pop: 1 thenPush: (interpreterProxy positive32BitIntegerFor: mask)]].
  	interpreterProxy primitiveFail!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveOpendir (in category 'file primitives') -----
  primitiveOpendir
  
  	"self primOpendir: '/etc'"
  
+ 	| dirName faPath dirOop status resultOop |
- 	| dirName dir dirOop status |
  	<export: true>
+ 	<var: 'faPath' type: #'fapath *'>
+ 
- 	<var: 'dir' type: 'osdir *'>
  	dirName := interpreterProxy stackObjectValue: 0.
+ 	(interpreterProxy isBytes: dirName) ifFalse:
- 	(interpreterProxy is: dirName KindOf: 'String') ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 
+ 	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].
+ 
+ 	status := self faOpenDirectory: faPath.
+ 	status = self noMoreData ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy pop: 2 thenPush: interpreterProxy nilObject].
+ 	status < 0 ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailForOSError: status].
+ 	resultOop := self processDirectory: faPath.
+ 	interpreterProxy failed ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailureCode ].
+ 
+ 	self remapOop: resultOop in:
+ 		[ dirOop := self addressObjectFor: faPath ].
+ 	^interpreterProxy 
+ 		storePointer: 2 ofObject: resultOop withValue: dirOop;
+ 		methodReturnValue: resultOop.!
- 	status := self openDirectoryStream: dirName ptr: (self addressOf: dir).
- 	status ~= 0 ifTrue: [^interpreterProxy primitiveFailForOSError: status].
- 	dirOop := self addressObjectFor: dir.
- 	interpreterProxy pop: 2 thenPush: dirOop!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitivePathMax (in category 'file primitives') -----
  primitivePathMax
  	"Answer the value of PATH_MAX for the current VM"
  
  	<export: true>
+ 	^interpreterProxy pop: 1 thenPush: (interpreterProxy integerObjectOf: #FA_PATH_MAX)!
- 	^interpreterProxy pop: 1 thenPush: (interpreterProxy integerObjectOf: #PATH_MAX)!

Item was added:
+ ----- 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].
+ 
+ 	faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 				inSmalltalk: [self simulatedFaPath].
+ 	faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 	self faSetPlatPathOop: faPath _: fileName.
+ 	interpreterProxy failed ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailureCode].
+ 
+ 	resultOop := interpreterProxy
+ 		instantiateClass: interpreterProxy classByteArray
+ 		indexableSize: (self faGetStPathLen: faPath).
+ 	resultOop ifNil: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 	byteArrayPtr := interpreterProxy arrayValueOf: resultOop.
+ 	self memcpy: byteArrayPtr _: (self faGetStPath: faPath) _: (self faGetStPathLen: faPath).
+ 	self free: 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)"
- 	nil for the end of the directory stream."
  
+ 	| dirPointerOop faPath resultArray status |
- 	| dirPointerOop dirStream ent entryName attributeArray resultArray haveEntry entry_len status |
  	<export: true>
+ 	<var: 'faPath' type: #'fapath *'>
- 	<var: 'ent' type: 'struct dirent *'>
- 	<var: 'dirStream' type: 'osdir *'>
- 	<var: 'haveEntry' type: #int>
  
  	dirPointerOop := interpreterProxy stackValue: 0.
+ 	faPath := self pointerFrom: dirPointerOop.
+ 	faPath ifNil:
- 	dirStream := self pointerFrom: dirPointerOop.
- 	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 
+ 	status := self faReadDirectory: faPath.
+ 	status = self noMoreData ifTrue:
- 	haveEntry := 0.
- 	[ent := self readdir: dirStream dp.
- 	 self cCode: 'if (ent == NULL ||
-                  		((!! (ent->d_name[0] == ''.'' && strlen(ent->d_name) == 1)) && strcmp(ent->d_name, "..")))
-                      		haveEntry = 1'.
- 	 haveEntry = 0] whileTrue.
- 	ent ifNil: "This is the normal case for the end of a directory stream,
- 			although it may indicate other error conditions for which errno would be updated.
- 			Assume the normal case here."
  		[^interpreterProxy pop: 2 thenPush: interpreterProxy nilObject].
+ 	status < 0 ifTrue:
- 	status := self byteArrayFromCString: ent d_name to: (self addressOf: entryName put: [:val| entryName := val]).
- 	status ~= 0 ifTrue:
  		[^interpreterProxy primitiveFailForOSError: status].
+ 	resultArray := self processDirectory: faPath.
+ 	interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode].
  
- 	"Build the path name (append the entry name to the path name)"
- 	entry_len := self strlen: ent d_name.
- 	[dirStream path_len + entry_len > (#PATH_MAX - 1)] ifTrue:
- 		[^interpreterProxy primitiveFailForOSError: self stringTooLong].
- 	self mem: dirStream path_file cp: ent d_name y: entry_len.
- 	dirStream path_file at: entry_len put: 0.
- 
- 	status := self fileToAttributeArray: dirStream path mask: 1 array: (self addressOf: attributeArray put: [:val| attributeArray := val]).
- 	"If the stat() fails, still return the filename, just no attributes"
- 	status ~= 0 ifTrue: [attributeArray := interpreterProxy nilObject].
- 
- 	self remapOop: #(entryName attributeArray)
- 		in: [resultArray := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2].
- 	resultArray ifNil:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	interpreterProxy
- 		storePointer: 0 ofObject: resultArray withValue: entryName;
- 		storePointer: 1 ofObject: resultArray withValue: attributeArray;
  		pop: 2 thenPush: resultArray!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveRewinddir (in category 'file primitives') -----
  primitiveRewinddir
  	"Set directoryStream to first entry. Answer dirPointerOop."
  
+ 	| dirPointerOop faPath status resultOop |
- 	| dirPointerOop dirStream |
  	<export: true>
+ 	<var: 'faPath' type: #'fapath *'>
- 	<var: 'dirStream' declareC: 'osdir *dirStream'>
  	dirPointerOop := interpreterProxy stackValue: 0.
+ 	faPath := self pointerFrom: dirPointerOop.
+ 	faPath ifNil:
- 	dirStream := self pointerFrom: dirPointerOop.
- 	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 
+ 	status := self faRewindDirectory: faPath.
+ 	status < 0 ifTrue: [^interpreterProxy primitiveFailForOSError: status].
+ 	resultOop := self processDirectory: faPath.
+ 	interpreterProxy failed ifTrue: [^interpreterProxy primitiveFailureCode ].
+ 	^interpreterProxy methodReturnValue: resultOop.!
- 	self rewinddir: dirStream dp.
- 	interpreterProxy pop: 2 thenPush: dirPointerOop!

Item was added:
+ ----- 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].
+ 
+ 	faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 				inSmalltalk: [self simulatedFaPath].
+ 	faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 	self faSetStPathOop: faPath _: fileName.
+ 	interpreterProxy failed ifTrue: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailureCode].
+ 
+ 	resultOop := interpreterProxy
+ 		instantiateClass: interpreterProxy classByteArray
+ 		indexableSize: (self faGetPlatPathByteCount: faPath).
+ 	resultOop ifNil: [
+ 		self free: faPath.
+ 		^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 	byteArrayPtr := interpreterProxy arrayValueOf: resultOop.
+ 	self memcpy: byteArrayPtr _: (self faGetPlatPath: faPath) _: (self faGetPlatPathByteCount: faPath).
+ 	self free: faPath.
+ 
+ 	^interpreterProxy methodReturnValue: resultOop.
+ !

Item was added:
+ ----- 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: [
+ 		faPath := self cCode: '(fapath *) calloc(1, sizeof(fapath))'
+ 						inSmalltalk: [self simulatedFaPath].
+ 		faPath = nil ifTrue: [^interpreterProxy primitiveFailForOSError: self cantAllocateMemory].
+ 		self faSetStPathOop: faPath _: fileNameOop.
+ 		interpreterProxy failed ifTrue: [
+ 			self free: faPath.
+ 			^interpreterProxy primitiveFailureCode].
+ 
+ 		status := self lchown: (self faGetPlatPath: faPath) _: ownerId _: groupId.
+ 		self free: faPath.
+ 		status ~= 0 ifTrue:
+ 			[^interpreterProxy primitiveFailForOSError: (self cCode: 'errno')].
+ 		^interpreterProxy methodReturnValue: interpreterProxy nilObject.
+ 		].
+ 	^interpreterProxy primitiveFailForOSError: self unsupportedOperation.
+ !

Item was added:
+ ----- Method: FileAttributesPlugin>>processDirectory: (in category 'private') -----
+ processDirectory: faPath
+ 	"The supplied faPath contains the full path to the current entry while iterating over a directory.
+ 	Convert the file name to an object, get the attributes and answer the resulting array."
+ 
+ 	| status entryName attributeArray resultArray |
+ 	<var: 'faPath' type: #'fapath *'>
+ 
+ 	status := self faCharToByteArray: (self faGetStFile: faPath) 
+ 				_: (self addressOf: entryName put: [:val | entryName := val]).
+ 	status ~= 0 ifTrue:
+ 		[ ^interpreterProxy primitiveFailForOSError: status].
+ 
+ 	status := self fileToAttributeArray: faPath mask: 1 array: (self addressOf: attributeArray put: [:val| attributeArray := val]).
+ 	"If the stat() fails, still return the filename, just no attributes"
+ 	status ~= 0 ifTrue: [attributeArray := interpreterProxy nilObject].
+ 
+ 	"resultArray: entryName, attributeArray, dirPtrOop"
+ 	self remapOop: #(entryName attributeArray)
+ 		in: [resultArray := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 3].
+ 	resultArray ifNil:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 	interpreterProxy
+ 		storePointer: 0 ofObject: resultArray withValue: entryName;
+ 		storePointer: 1 ofObject: resultArray withValue: attributeArray.
+ 	^resultArray!

Item was removed:
- ----- Method: FileAttributesPlugin>>putLStatFor:intoBuffer:targetName: (in category 'private - file') -----
- putLStatFor: cPathName intoBuffer: statBufPointer targetName: fileNameOop
- 	"Call stat() on cPathName, storing the results in
- 	the buffer at statBufPointer."
- 
- 	| cLinkName len status |
- 	<returnTypeC: 'sqInt'>
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'statBufPointer' type: 'struct stat *'>
- 	<var: 'cLinkName' declareC: 'char cLinkName[PATH_MAX]'>
- 	<var: 'fileNameOop' type: 'sqInt *'>
- 
- 	self cppIf: #HAVE_LSTAT = 1 ifTrue: [
- 		status := self lst: cPathName at: statBufPointer.
- 		status ~= 0 ifTrue: [^self cantStatPath].
- 		(self S_ISLNK: statBufPointer st_mode) = 0
- 			ifFalse: [
- 				len := self readLink: cPathName into: cLinkName maxLength: #PATH_MAX.
- 				len < 0 ifTrue: [^len].
- 				status := self byteArrayFromCString: cLinkName to: fileNameOop]
- 			ifTrue:
- 				[fileNameOop at: 0 put: interpreterProxy nilObject].
- 	] ifFalse: [ "#HAVE_LSTAT = 1"
- 		status := self invalidRequest.
- 	].
- 	^status
- !

Item was removed:
- ----- Method: FileAttributesPlugin>>putStatFor:intoBuffer:targetName: (in category 'private - file') -----
- putStatFor: cPathName intoBuffer: statBufPointer targetName: fileNameOop
- 	"Call stat() on cPathName, storing the results in
- 	the buffer at statBufPointer."
- 
- 	| status |
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'statBufPointer' type: 'struct stat *'>
- 	<var: 'fileNameOop' type: 'sqInt *'>
- 
- 	status := self st: cPathName at: statBufPointer.
- 	status ~= 0 ifTrue: [^self cantStatPath].
- 	self cppIf: #_WIN32 defined
- 		ifTrue: [self offsetStatBufTimesForWIN32: statBufPointer].
- 	fileNameOop at: 0 put: interpreterProxy nilObject.
- 	^0!

Item was changed:
  ----- Method: FileAttributesPlugin>>readLink:into:maxLength: (in category 'private - file') -----
  readLink: cPathName into: cLinkPtr maxLength: maxLength
  	"Get the target filename of the supplied symbolic link."
  
  	| len |
+ 	<var: 'cPathName' type: #'char *'>
+ 	<var: 'cLinkPtr' type: #'char *'>
+ 	<var: 'maxLength' type: #'size_t'>
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'cLinkPtr' type: 'char *'>
- 	<var: 'maxLength' type: 'size_t'>
  	<var: 'len' type: #sqInt> "len must be signed so that -1 can be communicated as an error."
  
  	len := self cppIf: #_WIN32 defined
  				ifTrue: [-1]
  				ifFalse: [self read: cPathName li: cLinkPtr nk: maxLength].
  	len < 0 ifTrue:
  		[self cppIf: #'INDEBUG' defined ifTrue: 
  			[self cCode: 'fprintf(stderr, "FileAttributesPlugin: unable to readlink(): %d, errno=%d\n", len, errno)'].
  		^self cantReadlink].
  	cLinkPtr at: len put: 0.
  	^len!

Item was changed:
  ----- Method: FileAttributesPlugin>>statArrayFor:toArray:from:fileName: (in category 'private - file') -----
+ statArrayFor: faPath toArray: attributeArray from: statBufPointer fileName: fileNameOop
- statArrayFor: cPathName toArray: attributeArray from: statBufPointer fileName: fileNameOop
  	"Answer a file entry array from the supplied statBufPointer"
  
+ 	| sizeIfFile status isDir |
+ 	<var: 'faPath' type: #'fapath *'>
+ 	<var: 'statBufPointer' type: #'faStatStruct *'>
- 	| sizeIfFile creationDate status |
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'statBufPointer' type: 'struct stat *'>
- 	<var: 'creationDate' type: 'time_t'>
  
+ 	isDir := self
+ 		cCode: 'S_ISDIR(statBufPointer->st_mode)'
+ 		inSmalltalk: [
+ 			((statBufPointer contents at: 2) bitAnd: self s_IFMT) = self s_IFDIR
+ 				ifTrue: [1]
+ 				ifFalse: [0]].
+ 	sizeIfFile := isDir = 0
+ 					ifTrue: [self cCode: 'statBufPointer->st_size'
+ 								inSmalltalk: [self
+ 									cCode: 'statBufPointer->st_size'
+ 									inSmalltalk: [statBufPointer contents at: 8]]]
- 	sizeIfFile := (self S_ISDIR: statBufPointer st_mode) = 0
- 					ifTrue: [statBufPointer st_size]
  					ifFalse: [0].
  	interpreterProxy
  		storePointer: 0
  			ofObject: attributeArray
+ 				withValue: (self cCode: 'fileNameOop' inSmalltalk: [self toOop: fileNameOop contents]);
- 				withValue: fileNameOop;
  		storePointer: 1
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_mode'
+ 					inSmalltalk: [statBufPointer contents at: 2]));
- 				withValue: (interpreterProxy positiveMachineIntegerFor: statBufPointer st_mode);
  		storePointer: 2
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_ino'
+ 					inSmalltalk: [statBufPointer contents at: 3]));
- 				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_ino);
  		storePointer: 3
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_dev'
+ 					inSmalltalk: [statBufPointer contents at: 4]));
- 				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_dev);
  		storePointer: 4
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_nlink'
+ 					inSmalltalk: [statBufPointer contents at: 5]));
- 				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_nlink);
  		storePointer: 5
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_uid'
+ 					inSmalltalk: [statBufPointer contents at: 6]));
- 				withValue: (interpreterProxy positiveMachineIntegerFor: statBufPointer st_uid);
  		storePointer: 6
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: (self
+ 					cCode: 'statBufPointer->st_gid'
+ 					inSmalltalk: [statBufPointer contents at: 7]));
- 				withValue: (interpreterProxy positiveMachineIntegerFor: statBufPointer st_gid);
  		storePointer: 7
  			ofObject: attributeArray
+ 				withValue: (interpreterProxy positive64BitIntegerFor: sizeIfFile).
+ 
- 				withValue: (interpreterProxy positive64BitIntegerFor: sizeIfFile);
- 		storePointer: 8
- 			ofObject: attributeArray
- 				withValue: (self oopFromTimeT:	statBufPointer st_atime);
- 		storePointer: 9
- 			ofObject: attributeArray
- 				withValue: (self oopFromTimeT:	statBufPointer st_mtime);
- 		storePointer: 10
- 			ofObject: attributeArray
- 				withValue: (self oopFromTimeT: statBufPointer st_ctime).
  	self cppIf: #_WIN32 defined
+ 		ifTrue: [ status := self winFileTimesFor: faPath to: attributeArray ]
+ 		ifFalse: [ status := self posixFileTimesFrom: statBufPointer to: attributeArray ].
+ 
+ 	^status
+ !
- 		ifTrue:
- 			[status := self	fileCreationTimeFor: cPathName
- 							length: cPathName strlen
- 							to: (self addressOf: creationDate put: [:val| creationDate := val]).
- 			interpreterProxy
- 				storePointer: 11
- 				ofObject: attributeArray
- 				withValue: (status = 0
- 							ifTrue:  [self oopFromTimeT: creationDate]
- 							ifFalse: [interpreterProxy nilObject])]
- 		ifFalse:
- 			[interpreterProxy
- 				storePointer: 11
- 				ofObject: attributeArray
- 				withValue: interpreterProxy nilObject].
- 	^0!

Item was changed:
+ ----- Method: FileAttributesPlugin>>statFailed (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>statFailed (in category 'errors') -----
  statFailed
  	"A call to stat() failed"
  	<inline: #always>
  	^-2!

Item was changed:
  ----- Method: FileAttributesPlugin>>stringFromCString: (in category 'private') -----
  stringFromCString: aCString
  	"Answer a new String copied from a null-terminated C string.
  	Caution: This may invoke the garbage collector."
  
  	| len newString |
+ 	<var: 'aCString' type: #'const char *'>
- 	<var: 'aCString' type: 'const char *'>
  	len := self strlen: aCString.
  	newString := interpreterProxy
  		instantiateClass: interpreterProxy classString
  		indexableSize: len.
  	newString ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
+ 	self strncpy: (interpreterProxy arrayValueOf: newString)
+ 		_: aCString
+ 		_: len. "(char *)strncpy()"
- 	self st: (interpreterProxy arrayValueOf: newString)
- 		rn: aCString
- 		cpy: len. "(char *)strncpy()"
  	^ newString
  !

Item was changed:
+ ----- Method: FileAttributesPlugin>>stringTooLong (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>stringTooLong (in category 'errors') -----
  stringTooLong
  	"String too long.  A file path name was longer than PATH_MAX"
  	<inline: #always>
  	^-1!

Item was changed:
+ ----- Method: FileAttributesPlugin>>timeConversionFailed (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>timeConversionFailed (in category 'errors') -----
  timeConversionFailed
  	<inline: #always>
  	^-5!

Item was changed:
+ ----- Method: FileAttributesPlugin>>unableToCloseDir (in category 'errors / status') -----
- ----- Method: FileAttributesPlugin>>unableToCloseDir (in category 'errors') -----
  unableToCloseDir
  	"The call to closedir() failed"
  	<inline: #always>
  	^-12!

Item was added:
+ ----- Method: FileAttributesPlugin>>unexpectedError (in category 'errors / status') -----
+ unexpectedError
+ 	"This is normally used where a catch-all is placed, but not expected to be used"
+ 	<inline: #always>
+ 	^-14!

Item was added:
+ ----- Method: FileAttributesPlugin>>unsupportedOperation (in category 'errors / status') -----
+ unsupportedOperation
+ 	"The requested operation is not supported on the current platform"
+ 	<inline: #always>
+ 	^-13!

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.4'!
- 	^'1.2.6'!

Item was added:
+ ----- Method: FileAttributesPlugin>>winFileCreationTimeFor:to: (in category 'private - windows') -----
+ winFileCreationTimeFor: winAttrs to: creationDate
+ 	"Set the file creation time from the supplied attributes."
+ 	<option: #_WIN32>
+ 
+ 	| sysTime fileTime |
+ 
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA *'>
+ 	<var: 'creationDate' type: #'sqLong *'>
+ 	<var: 'fileTime' type: #'FILETIME'>
+ 	<var: 'sysTime' type: #'SYSTEMTIME'>
+ 
+ 	self touch: sysTime.
+ 	self touch: fileTime.
+ 
+ 	(self cCode: 'FileTimeToLocalFileTime(&winAttrs->ftCreationTime, &fileTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	(self cCode: 'FileTimeToSystemTime(&fileTime, &sysTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	self cCode: '*creationDate = convertWinToSqueakTime(sysTime)'.
+ 
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPlugin>>winFileLastAccessTimeFor:to: (in category 'private - windows') -----
+ winFileLastAccessTimeFor: winAttrs to: accessDate
+ 	"Set the file creation time from the supplied attributes."
+ 	<option: #_WIN32>
+ 
+ 	| sysTime fileTime |
+ 
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA *'>
+ 	<var: 'accessDate' type: #'sqLong *'>
+ 	<var: 'fileTime' type: #'FILETIME'>
+ 	<var: 'sysTime' type: #'SYSTEMTIME'>
+ 
+ 	self touch: sysTime.
+ 	self touch: fileTime.
+ 
+ 	(self cCode: 'FileTimeToLocalFileTime(&winAttrs->ftLastAccessTime, &fileTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	(self cCode: 'FileTimeToSystemTime(&fileTime, &sysTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	self cCode: '*accessDate = convertWinToSqueakTime(sysTime)'.
+ 
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPlugin>>winFileLastWriteTimeFor:to: (in category 'private - windows') -----
+ winFileLastWriteTimeFor: winAttrs to: writeDate
+ 	"Set the file write time from the supplied attributes."
+ 	<option: #_WIN32>
+ 
+ 	| sysTime fileTime |
+ 
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA *'>
+ 	<var: 'writeDate' type: #'sqLong *'>
+ 	<var: 'fileTime' type: #'FILETIME'>
+ 	<var: 'sysTime' type: #'SYSTEMTIME'>
+ 
+ 	self touch: sysTime.
+ 	self touch: fileTime.
+ 
+ 	(self cCode: 'FileTimeToLocalFileTime(&winAttrs->ftLastWriteTime, &fileTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	(self cCode: 'FileTimeToSystemTime(&fileTime, &sysTime)') = 0 ifTrue:
+  		[^self timeConversionFailed].
+ 	self cCode: '*writeDate = convertWinToSqueakTime(sysTime)'.
+ 
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPlugin>>winFileTimesFor:to: (in category 'private - windows') -----
+ winFileTimesFor: faPath to: attributeArray
+ 	<inline: #never>
+ 	<option: #_WIN32>
+ 
+ 	| winAttrs attributeDate status |
+ 	<var: 'faPath' type: #'fapath *'>
+ 	<var: 'attributeDate' type: #'sqLong'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA'>
+ 
+ 	"Get the file attributes"
+ 	status := self cCode: 'GetFileAttributesExW(faGetPlatPath(faPath), GetFileExInfoStandard, &winAttrs)'.
+ 	status = 0 ifTrue: [^self getAttributesFailed].
+ 
+ 	"Set the accessDate"
+ 	status := self winFileLastAccessTimeFor: (self addressOf: winAttrs) to: (self addressOf: attributeDate).
+ 	status = 0 ifFalse: [^status].
+ 	interpreterProxy
+ 		storePointer: 8
+ 		ofObject: attributeArray
+ 		withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 
+ 	"Set the modifiedDate"
+ 	status := self winFileLastWriteTimeFor: (self addressOf: winAttrs) to: (self addressOf: attributeDate).
+ 	status = 0 ifFalse: [^status].
+ 	interpreterProxy
+ 		storePointer: 9
+ 		ofObject: attributeArray
+ 		withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 
+ 	"Set the changeDate"
+ 	interpreterProxy
+ 		storePointer: 10
+ 		ofObject: attributeArray
+ 		withValue: interpreterProxy nilObject.
+ 
+ 	"Set the creationDate"
+ 	status := self winFileCreationTimeFor: (self addressOf: winAttrs) to: (self addressOf: attributeDate).
+ 	status = 0 ifFalse: [^status].
+ 	interpreterProxy
+ 		storePointer: 11
+ 		ofObject: attributeArray
+ 		withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 
+ 	^0
+ !

Item was added:
+ FileAttributesPlugin subclass: #FileAttributesPluginSimulator
+ 	instanceVariableNames: 'maxPathLen'
+ 	classVariableNames: 'FA_PATH_MAX HAVE_CHMOD HAVE_CHOWN HAVE_LSTAT PATH_MAX S_IFBLK S_IFCHR S_IFDIR S_IFIFO S_IFLNK S_IFMT S_IFREG S_IFSOCK'
+ 	poolDictionaries: ''
+ 	category: 'FileAttributesPlugin'!
+ 
+ !FileAttributesPluginSimulator commentStamp: 'akg 10/19/2018 16:12' prior: 0!
+ FileAttributesPluginSimulator provides support functions to allow the FilePluginsAttribute to run in the VM simulator.
+ 
+ faPath is opaque to the VM, but normally stores:
+ 
+ 1. The file path being interagated in the format provided by the image (precomposed UTF8).
+ 2. The file path in platform specific format, e.g. wide strings for Windows, decomposed UTF8 for Mac.
+ 3. Platform specific directory iteration information when required, e.g. primOpendir.
+ 
+ The simulator stores an Array with:
+ 
+ 1. The input path in precomposed UTF8.
+ 2. The file name when iterating over directories.
+ 3. The input path with platform specific encoding
+ 4. The file name when iterating over directories with platform specific encoding
+ 5. The pointer to the real faPath used by the plugin.
+ 
+ The third and fourth entries (platform specific encoding) are only valid in specific cases, e.g. primitivePlatToStPath and primitiveStToPlatPath.
+ 
+ 
+ Instance Variables
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator class>>shouldBeTranslated (in category 'translation') -----
+ shouldBeTranslated
+ "This class should not be translated"
+ 	^false!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>addressObjectFor: (in category 'simulation support') -----
+ addressObjectFor: aByteArray
+ 	"The simulation passes around ByteArrays in place of malloc'd memory.
+ 	Copy the supplied ByteArray to the simulations memory and answer the address."
+ 
+ 	^self toOop: aByteArray!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>arrayFromOop: (in category 'simulation support') -----
+ arrayFromOop: anOop
+ 	"Answer a copy of the supplied array Oop"
+ 
+ 	| sz array |
+ 
+ 	sz := interpreterProxy stSizeOf: anOop.
+ 	array := Array new: sz.
+ 	1 to: sz do: [ :i |
+ 		array at: i put: (self fromOop: (interpreterProxy fetchPointer: i-1 ofObject: anOop))].
+ 	^array!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>byteArrayFromOop: (in category 'simulation support') -----
+ byteArrayFromOop: anOop
+ 	"Answer a copy of the supplied byte array Oop"
+ 
+ 	| sz array ptr |
+ 
+ 	sz := interpreterProxy stSizeOf: anOop.
+ 	ptr := interpreterProxy arrayValueOf: anOop.
+ 	array := ByteArray new: sz.
+ 	1 to: sz do: [ :i |
+ 		array at: i put: (interpreterProxy byteAt: ptr+i-1)].
+ 	^array!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>chmod:_: (in category 'simulation') -----
+ chmod: pathByteArray _: newMode
+ 	"Set the mode of pathByateArray to anInteger (as defined by chmod())"
+ 
+ 	| status |
+ 
+ 	status := self primFile: pathByteArray posixPermissions: newMode.
+ 	"The real primitive answers nil on success, convert to C integer status"
+ 	^status ifNil: [0]!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>chown:_:_: (in category 'simulation') -----
+ chown: pathByteArray _: uidInteger _: gidInteger
+ 	"Set the owner and group of path by numeric id."
+ 
+ 	| status |
+ 
+ 	status := self primFile: pathByteArray uid: uidInteger gid: gidInteger.
+ 	"The real primitive answers nil on success, convert to C integer status"
+ 	^status ifNil: [0]!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>classOf: (in category 'simulation support') -----
+ classOf: anOop
+ 
+ 	| clsOop |
+ 	
+ 	anOop = interpreterProxy nilObject ifTrue: [^UndefinedObject].
+ 	clsOop := interpreterProxy fetchClassOf: anOop.
+ 	clsOop = interpreterProxy classArray ifTrue: [^Array].
+ 	clsOop = interpreterProxy classByteArray ifTrue: [^ByteArray].
+ 	self error: 'unknown class'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faAccessAttributes:_:_: (in category 'simulation') -----
+ faAccessAttributes: faPath _: accessArray _: offset
+ 	"Set the access attributes in the supplied array (size 3) at the supplied offset.
+ 	Simulated by calling primFileAttributes:mask:."
+ 
+ 	| access |
+ 
+ 	access := self primFileAttributes: (self faGetStPath: faPath) mask: 2r10.
+ 	interpreterProxy
+ 		storePointer: offset+0
+ 			ofObject: accessArray
+ 			withValue: (self toOop: (access at: 1));
+ 		storePointer: offset+1
+ 			ofObject: accessArray
+ 			withValue: (self toOop: (access at: 2));
+ 		storePointer: offset+2
+ 			ofObject: accessArray
+ 			withValue: (self toOop: (access at: 3)).
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faCharToByteArray:_: (in category 'simulation') -----
+ faCharToByteArray: filePtr _: byteArrayPtr
+ 	"Copy the supplied file name to the simulation and set the pointer"
+ 
+ 	byteArrayPtr at: 0 put: (self toOop: filePtr).
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faCloseDirectory: (in category 'simulation') -----
+ faCloseDirectory: faPath
+ 	"Simulate the the call by actually calling the primitive and discarding the stat information (which will be retrieved again later in the simulation)."
+ 
+ 	| result status |
+ 
+ 	result := self primClosedir: (self faPathPtr: faPath).
+ 	result ifNotNil: [
+ 		faPath at: 3 put: nil.
+ 		status := 0 ]
+ 	ifNil: [status := self unexpectedError].
+ 	^status
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faConvertUnixToLongSqueakTime: (in category 'simulation') -----
+ faConvertUnixToLongSqueakTime: anInteger
+ 	"In the simulation the primitive returns the value already converted, so this is a no-op"
+ 
+ 	^anInteger!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faExists: (in category 'simulation') -----
+ faExists: faPath
+ 	"Simulate the the call by actually calling the primitive."
+ 
+ 	^(self primExists: faPath first)
+ 		ifTrue: [interpreterProxy trueObject]
+ 		ifFalse: [interpreterProxy falseObject].
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faFileAttribute:_: (in category 'simulation') -----
+ faFileAttribute: faPath _: attributeNumber
+ 	"Simulate the the call by actually calling the primitive."
+ 
+ 	^self toOop: (self primFileAttribute: faPath first number: attributeNumber)!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faGetPlatPath: (in category 'simulation') -----
+ faGetPlatPath: faPath
+ 	"Answer the Plat format of the path.
+ 	Horrible kludge: Within the simulation: if the platform encoding hasn't been set we're about to call the real primitive, which means that actually the St form is required."
+ 
+ 	| path |
+ 
+ 	path := (faPath at: 3) ifNil:
+ 		[faPath 
+ 			at: 4 put: nil;
+ 			at: 3 put: (self primToPlatformPath: (self faGetStPath: faPath))].
+ 	(faPath at: 4) ifNotNil: [
+ 		path := path, (faPath at: 4)].
+ 	^path!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faGetPlatPathByteCount: (in category 'simulation') -----
+ faGetPlatPathByteCount: faPath
+ 	"Answer the number of bytes in the platform specific encoding"
+ 	
+ 	^(self faGetPlatPath: faPath) size!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faGetStFile: (in category 'simulation') -----
+ faGetStFile: faPath
+ 	"Answer the basename of the path.
+ 	The simulated faPath contains the basename as the second entry in the Array."
+ 
+ 	^faPath at: 2!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faGetStPath: (in category 'simulation') -----
+ faGetStPath: faPath
+ 	"Answer the St format of the path."
+ 
+ 	| path |
+ 
+ 	path := faPath first.
+ 	faPath second ifNotNil: [
+ 		path := path, faPath second].
+ 	^path!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faGetStPathLen: (in category 'simulation') -----
+ faGetStPathLen: faPath
+ 	"Answer the length of the path."
+ 
+ 	^faPath first size
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faOpenDirectory: (in category 'simulation') -----
+ faOpenDirectory: faPath
+ 	"Simulate the the call by actually calling the primitive and discarding the stat information (which will be retrieved again later in the simulation)."
+ 
+ 	| result status |
+ 
+ 	result := self primOpendir: faPath first.
+ 	result ifNotNil: [
+ 		faPath 
+ 			at: 2 put: (result at: 1);
+ 			at: 3 put: (result at: 3).
+ 		status := 0 ]
+ 	ifNil: [status := self noMoreData].
+ 	^status
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faPathPtr: (in category 'simulation') -----
+ faPathPtr: faPathSimulation
+ 	"Given the simulation faPath, answer the ByteArray pointing to the actual faPath"
+ 
+ 	^faPathSimulation at: 3!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faReadDirectory: (in category 'simulation') -----
+ faReadDirectory: faPath
+ 	"Simulate the the call by actually calling the primitive and discarding the stat information (which will be retrieved again later in the simulation)."
+ 
+ 	| result status |
+ 
+ 	result := self primReaddir: (self faPathPtr: faPath).
+ 	result ifNotNil: [
+ 		faPath at: 2 put: (result at: 1).
+ 		status := 0 ]
+ 	ifNil: [status := self noMoreData].
+ 	^status
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faSetPlatPathOop:_: (in category 'simulation') -----
+ faSetPlatPathOop: faPath _: fileNameOop
+ 	"Simulate setting the platform encoded file name in the supplied faPath."
+ 
+ 	| fileNameBytes len path stPath |
+ 
+ 	fileNameBytes := interpreterProxy arrayValueOf: fileNameOop.
+ 	len := self strlen: fileNameBytes.
+ 	path := ByteArray new: len.
+ 	self strncpy: path _: fileNameBytes _: len.
+ 	self simFaPathPlatPath: faPath set: path.
+ 	stPath := self primFromPlatformPath: path.
+ 	self simFaPathStPath: faPath set: stPath!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faSetStDirOop:_: (in category 'simulation') -----
+ faSetStDirOop: faPath _: dirOop
+ 	"Simulate setting the dir name in the supplied faPath."
+ 
+ 	self faSetStPathOop: faPath _: dirOop.
+ 	faPath first last = FileDirectory pathNameDelimiter asciiValue ifFalse:
+ 		[faPath at: 1 put: (faPath first copyWith: FileDirectory pathNameDelimiter asciiValue)].
+ 	faPath at: 2 put: nil.!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faSetStPathOop:_: (in category 'simulation') -----
+ faSetStPathOop: faPath _: fileNameOop
+ 	"Simulate setting the file name in the supplied faPath.
+ 	The simulated faPath is simply the file name as a C string (null-terminated)."
+ 
+ 	| fileNameBytes len path |
+ 
+ 	fileNameBytes := interpreterProxy arrayValueOf: fileNameOop.
+ 	self assert: faPath class == Array.
+ 	len := self strlen: fileNameBytes.
+ 	path := ByteArray new: len.
+ 	self strncpy: path _: fileNameBytes _: len.
+ 	faPath 
+ 		at: 1 put: path;
+ 		at: 2 put: nil.!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>faStat:_:_: (in category 'simulation') -----
+ faStat: faPath _: statBuf _: fileNameOop
+ 	"Simulate the call to faStat().
+ 	The simulator uses a dictionary with keys named after the stat structure members."
+ 
+ 	| path primArray |
+ 
+ 	path := self faGetStPath: faPath.
+ 	primArray := self primFileAttributes: path mask: 1.
+ 	primArray isNumber ifTrue: [^primArray].
+ 	"First entry is fileName: **TODO**"
+ 	statBuf contents: primArray.
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>fromOop: (in category 'simulation support') -----
+ fromOop: anOop
+ 
+ 	| cls |
+ 
+ 	cls := self classOf: anOop.
+ 	cls = UndefinedObject ifTrue: [^nil].
+ 	cls = Array ifTrue: [^self arrayFromOop: anOop].
+ 	cls = ByteArray ifTrue: [^self byteArrayFromOop: anOop].
+ 	self error: 'Unknown class'.!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>initialize (in category 'initialize-release') -----
+ initialize
+ 	"Initialise the receiver for the current platform"
+ 
+ 	| masks |
+ 
+ 	masks := self primFileMasks.
+ 	S_IFMT := masks at: 1.
+ 	S_IFSOCK := masks at: 2.
+ 	S_IFLNK := masks at: 3.
+ 	S_IFREG := masks at: 4.
+ 	S_IFBLK := masks at: 5.
+ 	S_IFDIR := masks at: 6.
+ 	S_IFCHR := masks at: 7.
+ 	S_IFIFO := masks at: 8.
+ 
+ 	"Simulation has only been tested on Unix"
+ 	HAVE_LSTAT := true.
+ 	HAVE_CHMOD := true.
+ 	HAVE_CHOWN := true.
+ 	PATH_MAX := FA_PATH_MAX := self primPathMax.!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>lchown:_:_: (in category 'simulation') -----
+ lchown: pathByteArray _: uidInteger _: gidInteger
+ 	"Set the symlink owner and group of path by numeric id."
+ 
+ 	| status |
+ 
+ 	status := self primFile: pathByteArray symlinkUid: uidInteger gid: gidInteger.
+ 	"The real primitive answers nil on success, convert to C integer status"
+ 	^status ifNil: [0]!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>maxPathLen (in category 'simulation support') -----
+ maxPathLen
+ 	"Answer the maximum supported path length for the current platform"
+ 
+ 	^maxPathLen ifNil: [maxPathLen := self primPathMax]!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>pointerFrom: (in category 'simulation support') -----
+ pointerFrom: arrayOop
+ 	"For the simulation, convert the supplied address to a ByteArray"
+ 
+ 	^self fromOop: arrayOop!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primClosedir: (in category 'primitives') -----
+ primClosedir: directoryPointerBytes
+ 	"Close the directory stream associated with directoryPointerBytes.
+ 	Caution: do not call this twice on the same externalAddress."
+ 
+ 	"self primClosedir: (self primOpendir: '/etc')"
+ 	"self primClosedir: (self primOpendir: '/no/such/directory')"
+ 
+ 	<primitive: 'primitiveClosedir' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primClosedir'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primExists: (in category 'primitives') -----
+ primExists: aByteArray
+ 	"Answer a boolean indicating whether the supplied file exists."
+ 
+ 	<primitive: 'primitiveFileExists' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: aByteArray.
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFile:posixPermissions: (in category 'primitives') -----
+ primFile: pathByteArray posixPermissions: anInteger
+ 	"Set the mode of pathByateArray to anInteger (as defined by chmod())"
+ 
+ 	<primitive: 'primitiveChangeMode' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: pathByteArray!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFile:symlinkUid:gid: (in category 'primitives') -----
+ primFile: pathByteArray symlinkUid: uidInteger gid: gidInteger
+ 	"Set the owner and group of path by numeric id."
+ 
+ 	<primitive: 'primitiveSymlinkChangeOwner' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: pathByteArray!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFile:uid:gid: (in category 'primitives') -----
+ primFile: pathByteArray uid: uidInteger gid: gidInteger
+ 	"Set the owner and group of path by numeric id."
+ 
+ 	<primitive: 'primitiveChangeOwner' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: pathByteArray!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFileAttribute:number: (in category 'primitives') -----
+ primFileAttribute: aByteArray number: attributeNumber
+ 	"Answer a single attribute for the supplied file.
+ 	For backward compatibility (on Unix) with FileReference if the file doesn't exist, and the specified path is a (broken) symbolic link, answer the requested attribute for the symbolic link.
+ 
+ stat() information:
+ 	
+ 	1: name
+ 	2: mode
+ 	3: ino
+ 	4: dev
+ 	5: nlink
+ 	6: uid
+ 	7: gid
+ 	8: size
+ 	9: accessDate
+ 	10: modifiedDate
+ 	11: changeDate
+ 	12: creationDate
+ 
+ access() information
+ 
+ 	13: is readable
+ 	14: is writeable
+ 	15: is executable
+ 
+ symbolic link information
+ 
+ 	16: is symbolic link
+ 	"
+ 	<primitive: 'primitiveFileAttribute' module: 'FileAttributesPlugin' error: error>
+ 	"FilePlugin>>primitiveDirectoryEntry would return the symbolic link attributes if the symbolic link was broken.  This was due to the incorrect implementation of attempting to retrieve symbolic link information.
+ 	If the old behaviour is required, the logic is:
+ 	
+ 		(error isPrimitiveError and: [attributeNumber ~= 16 and: [error errorCode = self cantStatPath and: [
+ 					self platformSupportsSymbolicLinksEgUnix]]]) ifTrue:
+ 						[DiskSymlinkDirectoryEntry fileSystem: DiskStore currentFileSystem path: aString asPath]"
+ 	error isPrimitiveError ifTrue: [ 
+ 		(attributeNumber = 16 and: [ error errorCode = self unsupportedOperation ]) ifTrue: 
+ 			"If symlinks aren't supported, answer false"
+ 			[ ^false ]].
+ 	^self signalError: error for: aByteArray
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFileAttributes:mask: (in category 'primitives') -----
+ primFileAttributes: aByteArray mask: attributeMask
+ 	"Answer an array of attributes for the supplied file.  The size and contents of the array are determined by the attributeMask:
+ 
+ Bit 0: stat() information
+ Bit 1: access() information
+ Bit 2: use lstat() (instead of stat())
+ 
+ On error, answer an error code (Integer).
+ 
+ stat() information:
+ 	
+ 	1: name
+ 	2: mode
+ 	3: ino
+ 	4: dev
+ 	5: nlink
+ 	6: uid
+ 	7: gid
+ 	8: size
+ 	9: accessDate
+ 	10: modifiedDate
+ 	11: creationDate
+ 
+ access() information
+ 
+ 	1: is readable
+ 	2: is writeable
+ 	3: is executable
+ 	"
+ 	<primitive: 'primitiveFileAttributes' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: aByteArray
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFileMasks (in category 'primitives') -----
+ primFileMasks
+ 	"Answer an array of well known masks:
+ 	
+ 	1: S_IFMT
+ 	2: S_IFSOCK
+ 	3: S_IFLNK
+ 	4: S_IFREG
+ 	5: S_IFBLK
+ 	6: S_IFDIR
+ 	7: S_IFCHR
+ 	8: S_IFIFO
+ 
+ 	For more information, see: http://man7.org/linux/man-pages/man2/stat.2.html
+ 	"
+ 	<primitive: 'primitiveFileMasks' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primFileMasks'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primFromPlatformPath: (in category 'primitives') -----
+ primFromPlatformPath: aByteArray
+ 	"Convert the supplied platform encoded string to the native (UTF8) equivalent"
+ 
+ 	<primitive: 'primitivePlatToStPath' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primToPlatformPath:'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primOpendir: (in category 'primitives') -----
+ primOpendir: pathString
+ 	"Answer an ExternalAddress for a directory stream on pathString, or nil if
+ 	the directory cannot be opened"
+ 
+ 	"self primOpendir: '/etc'"
+ 	"self primOpendir: '.'"
+ 	"self primOpendir: '/no/such/directory'"
+ 
+ 	<primitive: 'primitiveOpendir' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: pathString!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primPathMax (in category 'primitives') -----
+ primPathMax
+ 	"Answer the VMs FA_PATH_MAX value"
+ 
+ 	<primitive: 'primitivePathMax' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primPathMax'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primReaddir: (in category 'primitives') -----
+ primReaddir: directoryPointerBytes
+ 	"Read the next directory entry from the directory stream associated with
+ 	directoryPointerBytes. Answer the name of the entry, ornil for end of directory stream."
+ 
+ 	"self primReaddir: (self primOpendir: '/etc')"
+ 	"self primReaddir: (self primOpendir: '/no/such/directory')"
+ 
+ 	<primitive: 'primitiveReaddir' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primReaddir:'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primToPlatformPath: (in category 'primitives') -----
+ primToPlatformPath: aByteArray
+ 	"Convert the supplied UTF8 encoded string to the platform encoded equivalent"
+ 
+ 	<primitive: 'primitiveStToPlatPath' module: 'FileAttributesPlugin' error: error>
+ 	^self signalError: error for: 'primToPlatformPath:'!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>primitivePathMax (in category 'simulation') -----
+ primitivePathMax
+ 	"Answer the value of FA_PATH_MAX for the current VM.
+ 	It doesn't make sense to simulate this, just call the primitive"
+ 
+ 	^self primPathMax!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>s_IFDIR (in category 'simulation support') -----
+ s_IFDIR
+ 
+ 	^S_IFDIR!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>s_IFMT (in category 'simulation support') -----
+ s_IFMT
+ 
+ 	^S_IFMT!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>signalError:for: (in category 'primitives') -----
+ signalError: error for: aByteArray
+ 	"In the simulation, just return the error code"
+ 
+ 	error ifNil: [ ^self primitiveFailed ].
+ 	error isSymbol ifTrue: [ ^self primitiveFailed: error ].
+ 	error isPrimitiveError ifFalse: [ 
+ 		"We shouldn't ever get here"
+ 		^self primitiveFailed. ].
+ 
+ 	^error errorCode.
+ !

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathPlatDir: (in category 'faPath simulation') -----
+ simFaPathPlatDir: faPath
+ 	"Answer the directory name"
+ 
+ 	^faPath at: 3!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathPlatFIleName: (in category 'faPath simulation') -----
+ simFaPathPlatFIleName: faPath
+ 	"Answer the file name, nil if not present"
+ 
+ 	^faPath at: 4!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathPlatPath: (in category 'faPath simulation') -----
+ simFaPathPlatPath: faPath
+ 	"Answer the full path name, i.e. combine the directory and file name (if present)"
+ 
+ 	| path |
+ 
+ 	path := faPath at: 3.
+ 	(faPath at: 4) ifNotNil:
+ 		[path := path, (faPath at: 4)].
+ 	^path!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathPlatPath:set: (in category 'faPath simulation') -----
+ simFaPathPlatPath: faPath set: pathName
+ 	"Set the full path name"
+ 
+ 	faPath
+ 		at: 3 put: pathName;
+ 		at: 4 put: nil.
+ 	^pathName!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathPtr: (in category 'faPath simulation') -----
+ simFaPathPtr: faPath
+ 	"Answer the address of the actual faPath buffer"
+ 
+ 	^faPath at: 5!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathStDir: (in category 'faPath simulation') -----
+ simFaPathStDir: faPath
+ 	"Answer the directory name"
+ 
+ 	^faPath at: 1!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathStFIleName: (in category 'faPath simulation') -----
+ simFaPathStFIleName: faPath
+ 	"Answer the file name, nil if not present"
+ 
+ 	^faPath at: 2!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathStPath: (in category 'faPath simulation') -----
+ simFaPathStPath: faPath
+ 	"Answer the full path name, i.e. combine the directory and file name (if present)"
+ 
+ 	| path |
+ 
+ 	path := faPath at: 1.
+ 	(faPath at: 2) ifNotNil:
+ 		[path := path, (faPath at: 2)].
+ 	^path!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simFaPathStPath:set: (in category 'faPath simulation') -----
+ simFaPathStPath: faPath set: path
+ 	"Set the full path name"
+ 
+ 	faPath
+ 		at: 1 put: path;
+ 		at: 2 put: nil.
+ 	^path!

Item was added:
+ ----- Method: FileAttributesPluginSimulator>>simulatedFaPath (in category 'simulation support') -----
+ simulatedFaPath
+ 	"Answer the simulated faPath.
+ 	See class comments for details."
+ 
+ 	^Array new: 5.!

Item was added:
+ ----- 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)
+ 						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)
+ 						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].
+ 	self error: 'unknown object type'.!




More information about the Vm-dev mailing list