[Vm-dev] VM Maker: FileAttributesPlugin.oscog-AlistairGrant.30.mcz

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


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

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

Name: FileAttributesPlugin.oscog-AlistairGrant.30
Author: AlistairGrant
Time: 16 June 2018, 11:06:08.147633 pm
UUID: 943fc170-d5c4-4cfd-846c-c3c937a110b5
Ancestors: FileAttributesPlugin.oscog-AlistairGrant.29

FileAttributesPlugin 1.3.1: clean up type declarations

- Use #var:type: instead of #var:declareC:
- Use symbols for types instead of strings

=============== 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: '<limits.h>'.
  	cg addHeaderFile: '<sys/types.h>'.
  	cg addHeaderFile: '<dirent.h>
  #ifdef _WIN32
  #include <windows.h>
  #include <winbase.h>
  #define FAIL() { return -1; }
  #include "sqWin32File.h"
+ #else
+ #include "sqMemoryAccess.h"
+ extern sqLong convertToLongSqueakTime(time_t unixTime);
  #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)
  #define HAVE_LSTAT 1
  #endif'.
  	cg addHeaderFile: '<unistd.h>
  /* AKG 2017 - ', self moduleName, '.c translated from class ', self name, ' */'!

Item was changed:
  ----- 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 *'>
- 	<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 changed:
  ----- 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 *'>
- 	<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>>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' type: 'char *'>
- 	<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>>fileCreationTimeFor:length:to: (in category 'private - windows') -----
  fileCreationTimeFor: pathString length: pathLength to: creationDate
+ 	"Get the creationDate for the supplied file."
+ 	<inline: #never>
- 	"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>
+ 	| winAttrs status |
+ 	<var: 'pathString' type: #'char *'>
+ 	<var: 'creationDate' type: #'sqLong *'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA'>
- 	| 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].
  
+ 	"Get the file attributes"
+ 	status := self winFileAttributesFor: pathString length: pathLength to: (self addressOf: winAttrs).
+ 	status = 0 ifFalse: [^status].
- 	self cCode: '
- 	tm.tm_year = sysTime.wYear - 1900;
- 	tm.tm_mon = sysTime.wMonth - 1;
- 	tm.tm_mday = sysTime.wDay;
  
+ 	"Set the creationDate"
+ 	status := self winFileCreationTimeFor: (self addressOf: winAttrs) to: creationDate.
+ 	status = 0 ifFalse: [^status].
- 	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 added:
+ ----- Method: FileAttributesPlugin>>fileLastAccessTimeFor:length:to: (in category 'private - windows') -----
+ fileLastAccessTimeFor: pathString length: pathLength to: creationDate
+ 	"Get the creationDate for the supplied file."
+ 	<inline: #never>
+ 	<option: #_WIN32>
+ 	| winAttrs status |
+ 	<var: 'pathString' type: #'char *'>
+ 	<var: 'creationDate' type: #'sqLong *'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA'>
+ 
+ 	"Get the file attributes"
+ 	status := self winFileAttributesFor: pathString length: pathLength to: (self addressOf: winAttrs).
+ 	status = 0 ifFalse: [^status].
+ 
+ 	"Set the creationDate"
+ 	status := self winFileLastAccessTimeFor: (self addressOf: winAttrs) to: creationDate.
+ 	status = 0 ifFalse: [^status].
+ 
+ 	^0!

Item was added:
+ ----- Method: FileAttributesPlugin>>fileLastWriteTimeFor:length:to: (in category 'private - windows') -----
+ fileLastWriteTimeFor: pathString length: pathLength to: creationDate
+ 	"Get the creationDate for the supplied file."
+ 	<inline: #never>
+ 	<option: #_WIN32>
+ 	| winAttrs status |
+ 	<var: 'pathString' type: #'char *'>
+ 	<var: 'creationDate' type: #'sqLong *'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA'>
+ 
+ 	"Get the file attributes"
+ 	status := self winFileAttributesFor: pathString length: pathLength to: (self addressOf: winAttrs).
+ 	status = 0 ifFalse: [^status].
+ 
+ 	"Set the creationDate"
+ 	status := self winFileLastWriteTimeFor: (self addressOf: winAttrs) to: creationDate.
+ 	status = 0 ifFalse: [^status].
+ 
+ 	^0!

Item was changed:
  ----- Method: FileAttributesPlugin>>fileToAttributeArray:mask:array: (in category 'private - file') -----
  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: 'cPathName' type: #'char *'>
+ 	<var: 'attributeArray' type: #'sqInt *'>
+ 	<var: 'statBuf' type: #'struct stat'>
- 	<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].
  		status := useLstat ifFalse:
  					[ self putStatFor: cPathName
  							intoBuffer: (self addressOf: statBuf)
  							targetName:  (self addressOf: fileNameOop) ]
  				ifTrue:
  					[ self putLStatFor: cPathName
  							intoBuffer: (self addressOf: statBuf)
  							targetName:  (self addressOf: fileNameOop) ].
  		status ~= 0 ifTrue: [^status].
  		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 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: 
  		[
  		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>>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'>
- 	<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 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 changed:
  ----- 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' type: #'char *'>
+ 	<var: 'dir' type: #'osdir *'>
+ 	<returnTypeC: #'int'>
- 	<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 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: #'struct stat *'>
+ 	<var: 'attributeDate' type: #'sqLong'>
+ 
+ 	self cppIf: #_WIN32 defined ifTrue: [] ifFalse: [
+ 	attributeDate := self convertToLongSqueakTime: statBufPointer st_atime.
+ 	interpreterProxy
+ 		storePointer: 8
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 	attributeDate := self convertToLongSqueakTime: statBufPointer st_mtime.
+ 	interpreterProxy
+ 		storePointer: 9
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate).
+ 	attributeDate := self convertToLongSqueakTime: statBufPointer st_ctime.
+ 	interpreterProxy
+ 		storePointer: 10
+ 			ofObject: attributeArray
+ 				withValue: (interpreterProxy signed64BitIntegerFor: attributeDate);
+ 		storePointer: 11
+ 			ofObject: attributeArray
+ 				withValue: interpreterProxy nilObject ].
+ 	^0!

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 dirStream result |
  	<export: true>
+ 	<var: 'dirStream' type: #'osdir *'>
- 	<var: 'dirStream' type: 'osdir *'>
  	dirPointerOop := interpreterProxy stackValue: 0.
  	dirStream := self pointerFrom: dirPointerOop.
  	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	result := self closedir: dirStream dp.
  	result = 0 ifFalse:
  		[^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 fileNameOop statBuf cPathName sizeIfFile mode attributeDate status |
- 	| fileName attributeNumber resultOop fileNameOop statBuf cPathName sizeIfFile mode creationDate status |
  	<export: true>
+ 	<var: 'statBuf' type: #'struct stat'>
- 	<var: 'statBuf' type: 'struct stat'>
  	<var: 'cPathName' declareC: 'char cPathName[PATH_MAX]'>
+ 	<var: 'attributeDate' type: #'sqLong'>
- 	<var: 'creationDate' type: 'time_t'>
  
  	fileName := interpreterProxy stackObjectValue: 1.
  	attributeNumber := interpreterProxy stackIntegerValue: 0.
  	(interpreterProxy failed
  	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.
  
  	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: [ "Access Time"
+ 			self cppIf: #_WIN32 defined ifTrue: [
+ 				status := self fileLastAccessTimeFor: cPathName
+ 					length: cPathName strlen
+ 					to: (self addressOf: attributeDate put: [:val| attributeDate := val]).
+ 				status ~= 0 ifTrue:
+ 					[^interpreterProxy primitiveFailForOSError: status].
+ 				resultOop := interpreterProxy signed64BitIntegerFor: attributeDate ] 
+ 			ifFalse: [
+ 				attributeDate := self convertToLongSqueakTime: statBuf st_atime.
+ 				resultOop := interpreterProxy signed64BitIntegerFor: attributeDate]].
+ 		attributeNumber = 10 ifTrue: [ "Modified Time"
+ 			self cppIf: #_WIN32 defined ifTrue: [
+ 				status := self fileLastWriteTimeFor: cPathName
+ 					length: cPathName strlen
+ 					to: (self addressOf: attributeDate put: [:val| attributeDate := val]).
+ 				status ~= 0 ifTrue:
+ 					[^interpreterProxy primitiveFailForOSError: status].
+ 				resultOop := interpreterProxy signed64BitIntegerFor: attributeDate ] 
+ 			ifFalse: [
+ 				attributeDate := self convertToLongSqueakTime: statBuf st_mtime.
+ 				resultOop := interpreterProxy signed64BitIntegerFor: attributeDate]].
+ 		attributeNumber = 11 ifTrue: [ "Change Time"
+ 			self cppIf: #_WIN32 defined ifTrue: 
+ 				[resultOop := interpreterProxy nilObject]
+ 			ifFalse: [
+ 				attributeDate := self convertToLongSqueakTime: statBuf st_ctime.
+ 				resultOop := interpreterProxy signed64BitIntegerFor: attributeDate]].
- 		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: [ "Creation Time"
- 	ifFalse: [attributeNumber = 12  ifTrue:
- 		[
  		self cppIf: #_WIN32 defined ifTrue: [
  			status := self fileCreationTimeFor: cPathName
  				length: cPathName strlen
+ 				to: (self addressOf: attributeDate put: [:val| attributeDate := val]).
- 				to: (self addressOf: creationDate put: [:val| creationDate := val]).
  			status ~= 0 ifTrue:
  				[^interpreterProxy primitiveFailForOSError: status].
+ 			resultOop := interpreterProxy signed64BitIntegerFor: attributeDate ] 
- 			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, #isSymlink"
- 	ifFalse: "attributeNumber = 16"
  		[
  		status := self isSymlink: cPathName boolean: (self addressOf: resultOop put: [:val| resultOop := val]).
  		status ~= 0 ifTrue: 
  			[^interpreterProxy primitiveFailForOSError: status].
  		]]].
  
  	resultOop = 0
  		ifTrue: ["It shouldn't be possible to get here"
  			interpreterProxy primitiveFail]
  		ifFalse: [interpreterProxy pop: 3 thenPush: resultOop]!

Item was changed:
  ----- Method: FileAttributesPlugin>>primitiveFileExists (in category 'file primitives') -----
  primitiveFileExists
  	"Check for existence of a file with a call to access()."
  
  	| pathString status accessFlag |
  	<export: true>
+ 	<var: 'accessFlag' type: #'sqInt'>
- 	<var: 'accessFlag' type: 'sqInt'>
  	pathString := interpreterProxy stackObjectValue: 0.
  	(interpreterProxy is: pathString KindOf: 'String') ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	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>>primitiveOpendir (in category 'file primitives') -----
  primitiveOpendir
  
  	"self primOpendir: '/etc'"
  
  	| dirName dir dirOop status |
  	<export: true>
+ 	<var: 'dir' type: #'osdir *'>
- 	<var: 'dir' type: 'osdir *'>
  	dirName := interpreterProxy stackObjectValue: 0.
  	(interpreterProxy is: dirName KindOf: 'String') ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	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>>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."
  
  	| dirPointerOop dirStream ent entryName attributeArray resultArray haveEntry entry_len status |
  	<export: true>
+ 	<var: 'ent' type: #'struct dirent *'>
+ 	<var: 'dirStream' type: #'osdir *'>
- 	<var: 'ent' type: 'struct dirent *'>
- 	<var: 'dirStream' type: 'osdir *'>
  	<var: 'haveEntry' type: #int>
  
  	dirPointerOop := interpreterProxy stackValue: 0.
  	dirStream := self pointerFrom: dirPointerOop.
  	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	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 := self byteArrayFromCString: ent d_name to: (self addressOf: entryName put: [:val| entryName := val]).
  	status ~= 0 ifTrue:
  		[^interpreterProxy primitiveFailForOSError: status].
  
  	"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 dirStream |
  	<export: true>
+ 	<var: 'dirStream' type: #'osdir *'>
- 	<var: 'dirStream' declareC: 'osdir *dirStream'>
  	dirPointerOop := interpreterProxy stackValue: 0.
  	dirStream := self pointerFrom: dirPointerOop.
  	dirStream ifNil:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	self rewinddir: dirStream dp.
  	interpreterProxy pop: 2 thenPush: dirPointerOop!

Item was changed:
  ----- 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 *'>
- 	<returnTypeC: 'sqInt'>
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'statBufPointer' type: 'struct stat *'>
  	<var: 'cLinkName' declareC: 'char cLinkName[PATH_MAX]'>
+ 	<var: 'fileNameOop' type: #'sqInt *'>
- 	<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 changed:
  ----- 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 *'>
- 	<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: cPathName toArray: attributeArray from: statBufPointer fileName: fileNameOop
  	"Answer a file entry array from the supplied statBufPointer"
  
+ 	| sizeIfFile status |
+ 	<var: 'cPathName' type: #'char *'>
+ 	<var: 'statBufPointer' type: #'struct stat *'>
- 	| sizeIfFile creationDate status |
- 	<var: 'cPathName' type: 'char *'>
- 	<var: 'statBufPointer' type: 'struct stat *'>
- 	<var: 'creationDate' type: 'time_t'>
  
  	sizeIfFile := (self S_ISDIR: statBufPointer st_mode) = 0
  					ifTrue: [statBufPointer st_size]
  					ifFalse: [0].
  	interpreterProxy
  		storePointer: 0
  			ofObject: attributeArray
  				withValue: fileNameOop;
  		storePointer: 1
  			ofObject: attributeArray
  				withValue: (interpreterProxy positiveMachineIntegerFor: statBufPointer st_mode);
  		storePointer: 2
  			ofObject: attributeArray
  				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_ino);
  		storePointer: 3
  			ofObject: attributeArray
  				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_dev);
  		storePointer: 4
  			ofObject: attributeArray
  				withValue: (interpreterProxy positive64BitIntegerFor: statBufPointer st_nlink);
  		storePointer: 5
  			ofObject: attributeArray
  				withValue: (interpreterProxy positiveMachineIntegerFor: statBufPointer st_uid);
  		storePointer: 6
  			ofObject: attributeArray
  				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: cPathName 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>>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 st: (interpreterProxy arrayValueOf: newString)
  		rn: aCString
  		cpy: len. "(char *)strncpy()"
  	^ newString
  !

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

Item was added:
+ ----- Method: FileAttributesPlugin>>winFileAttributesFor:length:to: (in category 'private - windows') -----
+ winFileAttributesFor: pathString length: pathLength to: winAttrs
+ 	"Populate the supplied Win32 file attribute structure"
+ 
+ 	<option: #_WIN32>
+ 
+ 	| win32Path |
+ 	<var: 'pathString' type: #'char *'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA *'>
+ 	<var: 'win32Path' type: #'WCHAR *'>
+ 
+ 	self touch: winAttrs.
+ 	"convert the supplied path name into a wide string"
+ 	self ALLOC_: win32Path WIN32_: pathString PATH: pathLength.
+ 	"Populate the supplied winAttrs structure"
+ 	(self cCode: 'GetFileAttributesExW(win32Path, GetFileExInfoStandard, winAttrs)') = 0 ifTrue:
+  		[^self getAttributesFailed].
+ 	^0!

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: cPathName to: attributeArray
+ 	<inline: #never>
+ 	<option: #_WIN32>
+ 
+ 	| winAttrs attributeDate status |
+ 	<var: 'cPathName' type: #'char *'>
+ 	<var: 'attributeDate' type: #'sqLong'>
+ 	<var: 'winAttrs' type: #'WIN32_FILE_ATTRIBUTE_DATA'>
+ 
+ 	"Get the file attributes"
+ 	status := self winFileAttributesFor: cPathName 
+ 					length: cPathName strlen 
+ 					to: (self addressOf: winAttrs put: [ :val | winAttrs := val ]).
+ 	status = 0 ifFalse: [^status].
+ 
+ 	"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 accessDate"
+ 	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
+ !




More information about the Vm-dev mailing list