The Trunk: Files-ul.167.mcz

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

The Trunk: Files-ul.167.mcz

commits-2
Levente Uzonyi uploaded a new version of Files to project The Trunk:
http://source.squeak.org/trunk/Files-ul.167.mcz

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

Name: Files-ul.167
Author: ul
Time: 13 March 2017, 4:57:03.092475 am
UUID: c1b507f4-6808-43f3-ae9e-c50360ad43fd
Ancestors: Files-cmm.166

FileDirectory changes:

- implemented #directoryContentsFor:do: in all subclasses of FileDirectory, where #directoryContentsFor: was implemented
- introduced #entriesDo: based on the method above
- rewrote methods sending #entries to use #entriesDo: instead
- simplified DirectoryEntryDirectory >> #asFileDirectory
- introduced #hasEntries
- #directoryEntryForName: signals InvalidDirectoryError as suggested by a comment from 2007
- other minor optimizations
- SortedCollection Whack-a-mole

=============== Diff against Files-cmm.166 ===============

Item was removed:
- ----- Method: AcornFileDirectory>>directoryContentsFor: (in category 'private') -----
- directoryContentsFor: fullPath
- "Return a collection of directory entries for the files and directories in
- the directory with the given path. See primLookupEntryIn:index: for
- further details."
- "FileDirectory default directoryContentsFor: ''"
-
- | entries extraPath |
- entries := super directoryContentsFor: fullPath.
- fullPath isNullPath
- ifTrue: [
- "For Acorn we also make sure that at least the parent of the current dir
- is added - sometimes this is in a filing system that has not been (or
- cannot be) polled for disc root names"
- extraPath := self class default containingDirectory.
- "Only add the extra path if we haven't already got the root of the current dir in the list"
- (entries anySatisfy: [:ent | extraPath fullName beginsWith: ent name])
- ifFalse: [entries := entries
- copyWith: (DirectoryEntryDirectory
- directory: self
- name: extraPath fullName
- creationTime: 0
- modificationTime: 0
- fileSize: 0)]].
- ^ entries
- !

Item was added:
+ ----- Method: AcornFileDirectory>>directoryContentsFor:do: (in category 'private') -----
+ directoryContentsFor: fullPath do: aBlock
+ "Evaluate aBlock with the directory entries for the files and directories in
+ the directory with the given path. See primLookupEntryIn:index: for
+ further details."
+ "FileDirectory default directoryContentsFor: '' do: [ :each | Transcript show: each; cr ]"
+
+ | extraPath extraPathFullName needsExtraPath |
+ fullPath isNullPath ifFalse: [ ^super directoryContentsFor: fullPath do: aBlock ].
+
+ "For Acorn we also make sure that at least the parent of the current dir
+ is added - sometimes this is in a filing system that has not been (or
+ cannot be) polled for disc root names"
+ extraPath := self class default containingDirectory.
+ extraPathFullName := extraPath fullName.
+ needsExtraPath := true.
+ super directoryContentsFor: fullPath do: [ :entry |
+ needsExtraPath := needsExtraPath and: [ (extraPathFullName beginsWith: entry name) not ].
+ aBlock value: entry ].
+
+ needsExtraPath ifFalse: [ ^self ].
+ "Only add the extra path if we haven't already got the root of the current dir in the list"
+ aBlock value: (
+ DirectoryEntryDirectory
+ directory: self
+ name: extraPathFullName
+ creationTime: 0
+ modificationTime: 0
+ fileSize: 0)!

Item was changed:
  ----- Method: DirectoryEntryDirectory>>asFileDirectory (in category 'convert') -----
  asFileDirectory
  "Answer a FileDirectory representing the same directory I represent."
+
+ ^directory on: name!
- ^ self containingDirectory in: [ : cd | cd on: (cd fullNameFor: self name) ]!

Item was changed:
  ----- Method: DirectoryEntryDirectory>>directorySize (in category 'access') -----
  directorySize
 
+ | size |
+ size := 0.
+ self asFileDirectory entriesDo: [ :entry |
+ entry isDirectory
+ ifTrue: [ size := size + entry directorySize ]
+ ifFalse:[ size := size + entry fileSize ] ].
+ ^size!
- ^ self asFileDirectory entries
- inject: 0
- into: [:sum :entry | sum + (entry isDirectory ifTrue: [entry directorySize] ifFalse: [entry fileSize])]!

Item was changed:
  ----- Method: FileDirectory>>directoryContentsFor:do: (in category 'private') -----
  directoryContentsFor: fullPath do: aBlock
+ "Do aBlock for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details."
+ "FileDirectory default directoryContentsFor: '' do: [ :each | Transcript show: each; cr ]"
- "Do aBlock for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details."
 
  | f entryArray index |
  f := fullPath asVmPathName.
  index := 1.
  [(entryArray := self primLookupEntryIn: f index: index) == nil] whileFalse: [
  #badDirectoryPath == entryArray ifTrue: [
  ^(InvalidDirectoryError pathName: pathName) signal].
  index := index + 1.
  aBlock value: (DirectoryEntry fromArray: entryArray directory: self) convertFromSystemName]!

Item was changed:
  ----- Method: FileDirectory>>directoryEntryForName: (in category 'private') -----
  directoryEntryForName: aFileName
 
  "Return a single DirectoryEntry for the given (non-path) entry name,
  or nil if the entry could not be found.
  Raises InvalidDirectoryError if this directory's path does not identify a directory."
 
  | entryArray sysPath sysName |
 
  sysPath := pathName asVmPathName.
  sysName := aFileName asVmPathName.
 
  "New linear-time primitive."
  entryArray := self primLookupEntryIn: sysPath name: sysName.
  entryArray == #primFailed ifFalse:[
  ^ entryArray ifNotNil: [(DirectoryEntry fromArray: entryArray directory: self) convertFromSystemName]
  ].
 
+ (InvalidDirectoryError pathName: pathName) signal.
+ ^nil
+
  "If the new primitive fails, use the old slow method.
  (This fallback can be changed to signal InvalidDirectoryError once
   VM's with FilePlugin #primitiveDirectoryEntry have been distributed everywhere;
+  the new primitive was introduced 6/13/2007.
-  the new primitive was introduced 6/13/2007."
 
+ self isCaseSensitive
+ ifTrue: [ self entriesDo: [ :entry | entry name = aFileName ifTrue: [ ^entry ] ] ]
+ ifFalse: [ self entriesDo: [ :entry | (entry name sameAs: aFileName) ifTrue: [ ^entry ] ] ].
+ ^nil"!
- ^self isCaseSensitive ifTrue: [
- self entries detect: [:entry | entry name = aFileName ] ifNone: [ nil ]
- ] ifFalse: [
- self entries detect: [:entry | entry name sameAs: aFileName ] ifNone: [ nil ]
- ]
- !

Item was changed:
  ----- Method: FileDirectory>>directoryNames (in category 'enumeration') -----
  directoryNames
  "Return a collection of names for the subdirectories of this directory."
  "FileDirectory default directoryNames"
 
+ ^Array streamContents: [ :stream |
+ self entriesDo: [ :entry |
+ entry isDirectory ifTrue: [
+ stream nextPut: entry name ] ] ]!
- ^ (self entries select: [:entry | entry isDirectory ])
- collect: [:entry | entry name]
- !

Item was changed:
  ----- Method: FileDirectory>>directoryTreeDo:entries: (in category 'enumeration') -----
  directoryTreeDo: oneArgBlock entries: entriesCollection
  "Value oneArgBlock with the path (an OrderedCollection of FileDirectory's) to each DirectoryEntry and the DirectoryEntry itself."
+
+ self entriesDo:  [ :entry |
+ entriesCollection addLast: entry.
- self entries do:
- [ : each |
- entriesCollection add: each.
  oneArgBlock value: entriesCollection.
+ entry isDirectory ifTrue: [
+ entry asFileDirectory
- each isDirectory ifTrue:
- [ | subdir |
- subdir := each asFileDirectory.
- subdir
  directoryTreeDo: oneArgBlock
  entries: entriesCollection ].
  entriesCollection removeLast ]!

Item was added:
+ ----- Method: FileDirectory>>entriesDo: (in category 'enumeration') -----
+ entriesDo: aBlock
+ "Evaluate aBlock with DirectoryEntry's for the files and directories in this directory.  See primLookupEntryIn:index: for further details."
+
+ ^self directoryContentsFor: pathName do: aBlock
+ !

Item was changed:
  ----- Method: FileDirectory>>fileAndDirectoryNames (in category 'enumeration') -----
  fileAndDirectoryNames
  "FileDirectory default fileAndDirectoryNames"
+
+ ^Array streamContents: [ :stream |
+ self entriesDo: [ :entry |
+ stream nextPut: entry name ] ]!
- ^ self entries collect: [ : entry | entry name ]!

Item was changed:
  ----- Method: FileDirectory>>fileNames (in category 'enumeration') -----
  fileNames
  "Return a collection of names for the files (but not directories) in this directory."
  "FileDirectory default fileNames"
+
+ ^Array streamContents: [ :stream |
+ self entriesDo: [ :entry |
+ entry isDirectory ifFalse: [
+ stream nextPut: entry name ] ] ]!
- ^ (self entries reject: [ : entry | entry isDirectory ])
- collect: [ : entry | entry name ]!

Item was changed:
  ----- Method: FileDirectory>>fileOrDirectoryExists: (in category 'file operations') -----
  fileOrDirectoryExists: filenameOrPath
  "Answer true if either a file or a directory file of the given name exists. The given name may be either a full path name or a local name within this directory."
  "FileDirectory default fileOrDirectoryExists: Smalltalk sourcesName"
 
  | fName dir |
  DirectoryClass splitName: filenameOrPath to:
  [:filePath :name |
  fName := name.
  filePath isEmpty
  ifTrue: [dir := self]
  ifFalse: [dir := FileDirectory on: filePath]].
 
+ ^(dir includesKey: fName) or: [ fName = '' and: [ dir hasEntries ] ]!
- ^ (dir includesKey: fName) or: [ fName = '' and:[ dir entries size > 1]]!

Item was added:
+ ----- Method: FileDirectory>>hasEntries (in category 'private') -----
+ hasEntries
+ "Return true if this directory has entries or false."
+ "FileDirectory default hasEntries"
+
+ ^(self primLookupEntryIn: pathName asVmPathName index: 1) ~~ nil!

Item was changed:
  ----- Method: FileDirectory>>lastNameFor:extension: (in category 'file name utilities') -----
  lastNameFor: baseFileName extension: extension
  "Assumes a file name includes a version number encoded as '.' followed by digits
  preceding the file extension.  Increment the version number and answer the new file name.
  If a version number is not found, set the version to 1 and answer a new file name"
 
  | files splits |
 
  files := self fileNamesMatching: (baseFileName,'*', self class dot, extension).
  splits := files
  collect: [:file | self splitNameVersionExtensionFor: file]
  thenSelect: [:split | (split at: 1) = baseFileName].
+ splits isEmpty ifTrue: [ ^nil ].
+ ^(baseFileName, '.', ((splits detectMax: [ :each | each at: 2]) at: 2) asString, self class dot, extension) asFileName!
- splits := splits asSortedCollection: [:a :b | (a at: 2) < (b at: 2)].
- ^splits isEmpty
- ifTrue: [nil]
- ifFalse: [(baseFileName, '.', (splits last at: 2) asString, self class dot, extension) asFileName]!

Item was changed:
  ----- Method: FileDirectory>>nextNameFor:extension: (in category 'file name utilities') -----
  nextNameFor: baseFileName extension: extension
  "Assumes a file name includes a version number encoded as '.' followed by digits
  preceding the file extension.  Increment the version number and answer the new file name.
  If a version number is not found, set the version to 1 and answer a new file name"
 
  | files splits version |
 
  files := self fileNamesMatching: (baseFileName,'*', self class dot, extension).
  splits := files
  collect: [:file | self splitNameVersionExtensionFor: file]
  thenSelect: [:split | (split at: 1) = baseFileName].
- splits := splits asSortedCollection: [:a :b | (a at: 2) < (b at: 2)].
  splits isEmpty
  ifTrue: [version := 1]
+ ifFalse: [version := ((splits detectMax: [ :each | each at: 2 ]) at: 2) + 1].
- ifFalse: [version := (splits last at: 2) + 1].
  ^ (baseFileName, '.', version asString, self class dot, extension) asFileName!