Skip to content

Commit

Permalink
Modify File Attributes to reflect updated windows attributes
Browse files Browse the repository at this point in the history
  • Loading branch information
akgrant committed Feb 1, 2019
1 parent 7175ee6 commit 74c7f15
Show file tree
Hide file tree
Showing 5 changed files with 14 additions and 5 deletions.
3 changes: 2 additions & 1 deletion src/FileSystem-Core/DiskDirectoryEntry.class.st
Expand Up @@ -307,7 +307,8 @@ DiskDirectoryEntry >> modificationUnixTime [
DiskDirectoryEntry >> numberOfHardLinks [
"Answer the number of hard links to the receiver"

^self statAttributes at: 5
^(self statAttributes at: 5) ifNil:
[ FileAttributeNotSupported signalWith: reference ]
]

{ #category : #accessing }
Expand Down
Expand Up @@ -224,7 +224,10 @@ DiskFileAttributesTests >> testModificationTime [
DiskFileAttributesTests >> testNLink [
"Assume that there is only one hard link to the just created temporary file"

self collectionAssert: [ :each | each numberOfHardLinks ] equals: 1.
OSPlatform current name = #'Win32' ifTrue:
[ self should: [ self tempFileResource file numberOfHardLinks ] raise: FileAttributeNotSupported ]
ifFalse:
[ self collectionAssert: [ :each | each numberOfHardLinks ] equals: 1 ].
]

{ #category : #tests }
Expand Down
Expand Up @@ -57,7 +57,7 @@ FileAttributesPluginPrimsTests >> testPrimCloseDirString [
"FileAttributesPluginPrims>>primClosedir: only accepts a ByteArray, anything else should raise an error"

self
should: [ primitives primClosedir: 'a string' ]
should: [ primitives primClosedir: 'not a buffer' ]
raise: PrimitiveFailed
withExceptionDo: [ :exception |
self assert: exception selector equals: #'bad argument' ].
Expand Down
Expand Up @@ -180,8 +180,11 @@ FileReferenceAttributeTests >> testModificationTime [
FileReferenceAttributeTests >> testNLink [
"Assume that there is only one hard link to the just created temporary file"

self assert: self tempFileResource file numberOfHardLinks equals: 1.
self assert: self tempFileResource file entry numberOfHardLinks equals: self tempFileResource file numberOfHardLinks.
OSPlatform current name = #'Win32' ifTrue:
[ self should: [ self tempFileResource file numberOfHardLinks ] raise: FileAttributeNotSupported ]
ifFalse:
[ self assert: self tempFileResource file numberOfHardLinks equals: 1.
self assert: self tempFileResource file entry numberOfHardLinks equals: 1 ].
]

{ #category : #tests }
Expand Down
2 changes: 2 additions & 0 deletions src/Files/File.class.st
Expand Up @@ -949,6 +949,8 @@ File class >> signalError: error for: aByteArray [
[ ^FileDoesNotExistException signalWith: pathString ].
errorNumber = self getAttributesFailed ifTrue:
[ ^FileDoesNotExistException signalWith: pathString ].
errorNumber = self unsupportedOperation ifTrue:
[ ^FileAttributeNotSupported signalWith: pathString ].
^FileException signalWith: pathString.
]

Expand Down

0 comments on commit 74c7f15

Please sign in to comment.