[PATCH] move lots of methods up to File

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

[PATCH] move lots of methods up to File

Paolo Bonzini-2
Again for the same reason, a lot of methods in the Directory class
are moved up to File.  At the same time, users do not need anymore
to use "Directory name: x" and can use "File name: x".

---
 kernel/Directory.st                  |  214 +---------------------------------
 kernel/File.st                       |  197 ++++++++++++++++++++++++++++++-
 kernel/PkgLoader.st                  |    2 +-
 packages/httpd/FileServer.st         |    6 +-
 packages/httpd/WikiServer.st         |    2 +-
 packages/net/URIResolver.st          |    2 +-
 packages/seaside/core/Seaside-GST.st |    2 +-
 scripts/Package.st                   |   48 ++++----
 8 files changed, 226 insertions(+), 247 deletions(-)

diff --git a/kernel/Directory.st b/kernel/Directory.st
index 9372af8..4372407 100644
--- a/kernel/Directory.st
+++ b/kernel/Directory.st
@@ -115,7 +115,7 @@ virtual one).'>
  (d := self home) isNil
     ifFalse:
  [d := d , '/tmp'.
- (Directory exists: d) ifTrue: [^d]].
+ (File name: d) isDirectory ifTrue: [^d]].
  ^'/tmp'
     ]
 
@@ -189,13 +189,13 @@ virtual one).'>
  name := prefix asString , 'XXXXXX'.
  self primCreateTemporary: name.
  self checkError.
- ^Directory name: name
+ ^File name: name
     ]
 
     Directory class >> allFilesMatching: aPattern do: aBlock [
  "Invoke #allFilesMatching:do: on the current working directory."
  <category: 'file operations'>
- (self name: self working) allFilesMatching: aPattern do: aBlock
+ (File name: self working) allFilesMatching: aPattern do: aBlock
     ]
 
     Directory class >> create: dirName [
@@ -206,213 +206,7 @@ virtual one).'>
  parent := File pathFor: dirName asString ifNone: [Directory working].
  handler := VFS.VFSHandler for: parent.
  handler createDir: (File stripPathFrom: dirName).
- ^Directory name: dirName
+ ^File name: dirName
     ]
 
-    pathTo: destName [
- "Compute the relative path from the receiver to destName."
-
- <category: 'accessing'>
- | destFullName |
- destFullName := File fullNameFor: destName asString.
- vfsHandler realFileName = destFullName ifTrue: [^'.'].
- ^File computePathFrom: vfsHandler realFileName , '/somefile'
-    to: destFullName
-    ]
-
-    fileAt: aName [
- "Answer a File object for a file named `aName' residing in the
- directory represented by the receiver."
-
- <category: 'accessing'>
- ^File on: (vfsHandler at: aName)
-    ]
-
-    / aName [
- "Answer a File or Directory object as appropriate for a file named
- 'aName' in the directory represented by the receiver."
-
- ^self at: aName
-    ]
-
-    at: aName [
- "Answer a File or Directory object as appropriate for a file named
- 'aName' in the directory represented by the receiver."
-
- <category: 'accessing'>
- | f |
- f := vfsHandler at: aName.
- ^((f exists and: [f isDirectory]) ifTrue: [Directory] ifFalse: [File])
-    on: f
-    ]
-
-    directoryAt: aName [
- "Answer a Directory object for a file named `aName' residing in the
- directory represented by the receiver."
-
- <category: 'accessing'>
- ^Directory on: (vfsHandler at: aName)
-    ]
-
-    includes: aName [
- "Answer whether a file named `aName' exists in the directory represented
- by the receiver."
-
- <category: 'accessing'>
- ^(vfsHandler at: aName) exists
-    ]
-
-    fullNameAt: aName [
- "Answer a String containing the full path to a file named `aName' which
- resides in the directory represented by the receiver."
-
- <category: 'accessing'>
- ^Directory append: aName to: self fullName
-    ]
-
-    nameAt: aName [
- "Answer a String containing the path to a file named `aName' which
- resides in the directory represented by the receiver."
-
- <category: 'accessing'>
- ^Directory append: aName to: self name
-    ]
-
-    allFilesMatching: aPattern do: aBlock [
- "Evaluate aBlock on the File objects that match aPattern (according to
- String>>#match:) in the directory named by the receiver. Recursively
- descend into directories."
-
- <category: 'enumerating'>
- self do:
- [:name |
- | f |
- f := self at: name.
- (aPattern match: name) ifTrue: [aBlock value: f].
- f isDirectory
-    ifTrue:
- [((#('.' '..') includes: name) or: [f isSymbolicLink])
-    ifFalse: [f allFilesMatching: aPattern do: aBlock]]]
-    ]
-
-    files [
- "Answer an Array with File objects for the contents of the directory
- represented by the receiver."
-
- <category: 'enumerating'>
- ^self select: [ :each | each isFile ]
-    ]
-
-    directories [
- "Answer an Array with Directory objects for the subdirectories
- of the directory represented by the receiver."
-
- <category: 'enumerating'>
- ^self select: [ :each | each isDirectory ]
-    ]
-
-    entries [
- "Answer an Array with File or Directory objects for the contents
- of the directory represented by the receiver."
-
- <category: 'enumerating'>
- | ws |
- ws := WriteStream on: (Array new: 50).
- self do: [:each | ws nextPut: each].
- ^ws contents
-    ]
-
-    entryNames [
- "Answer an Array with the names of the files in the directory
- represented by the receiver."
-
- <category: 'enumerating'>
- | ws |
- ws := WriteStream on: (Array new: 50).
- self namesDo: [:each | ws nextPut: each].
- ^ws contents
-    ]
-
-    do: aBlock [
- "Evaluate aBlock once for each file in the directory represented by the
- receiver, passing its name."
-
- <category: 'enumerating'>
- self namesDo: [ :name |
-    aBlock value: (self at: name) ]
-    ]
-
-    namesDo: aBlock [
- "Evaluate aBlock once for each file in the directory represented by the
- receiver, passing its name."
-
- <category: 'enumerating'>
- vfsHandler do: [ :name | aBlock value: name ]
-    ]
-
-    filesMatching: aPattern [
- "Evaluate aBlock once for each file in the directory represented by the
- receiver, passing a File or Directory object to aBlock. Returns the
- *names* of the files for which aBlock returns true."
-
- <category: 'enumerating'>
- | ws |
- ws := WriteStream on: (Array new: 50).
- self namesDo: [ :name |
-    (aPattern match: name) ifTrue: [ ws nextPut: (self at: name) ] ].
- ^ws contents
-    ]
-
-    reject: aBlock [
- "Evaluate aBlock once for each file in the directory represented by the
- receiver, passing a File or Directory object to aBlock. Returns the
- *names* of the files for which aBlock returns true."
-
- <category: 'enumerating'>
- | ws |
- ws := WriteStream on: (Array new: 50).
- self do: [ :each |
-    (aBlock value: each) ifFalse: [ ws nextPut: each ] ].
- ^ws contents
-    ]
-
-    select: aBlock [
- "Evaluate aBlock once for each file in the directory represented by the
- receiver, passing a File or Directory object to aBlock. Returns the
- *names* of the files for which aBlock returns true."
-
- <category: 'enumerating'>
- | ws |
- ws := WriteStream on: (Array new: 50).
- self do: [ :each |
-    (aBlock value: each) ifTrue: [ ws nextPut: each ] ].
- ^ws contents
-    ]
-
-    filesMatching: aPattern do: block [
- "Evaluate block on the File objects that match aPattern (according to
- String>>#match:) in the directory named by the receiver."
-
- <category: 'enumerating'>
- self namesDo: [:name |
-    (aPattern match: name) ifTrue: [block value: (self at: name)]]
-    ]
-
-    namesMatching: aPattern do: block [
- "Evaluate block on the file names that match aPattern (according to
- String>>#match:) in the directory named by the receiver."
-
- <category: 'enumerating'>
- vfsHandler
-    do: [:name | (aPattern match: name) ifTrue: [block value: (self nameAt: name)]]
-    ]
-]
-
-String extend [
-    / aName [
- "Answer a File or Directory object as appropriate for a file named
- 'aName' in the directory represented by the receiver."
-
- ^(Directory name: self) at: aName
-    ]
 ]
diff --git a/kernel/File.st b/kernel/File.st
index 0bc8f5c..730b485 100644
--- a/kernel/File.st
+++ b/kernel/File.st
@@ -569,7 +569,7 @@ size and timestamps.'>
  "Answer the Directory object for the receiver's path"
 
  <category: 'file name management'>
- ^Directory name: (File pathFor: self name)
+ ^File name: (File pathFor: self name)
     ]
 
     path [
@@ -608,11 +608,6 @@ size and timestamps.'>
  ^contents
     ]
 
-    includes: aString [
- "Return false, regular files do not include other paths."
- ^false
-    ]
-
     touch [
  "Update the timestamp of the file corresponding to the receiver."
 
@@ -746,5 +741,195 @@ size and timestamps.'>
  <category: 'private'>
  vfsHandler := aVFSHandler
     ]
+
+    pathTo: destName [
+ "Compute the relative path from the receiver to destName."
+
+ <category: 'accessing'>
+ | destFullName |
+ destFullName := File fullNameFor: destName asString.
+ vfsHandler realFileName = destFullName ifTrue: [^'.'].
+ ^File computePathFrom: vfsHandler realFileName , '/somefile'
+    to: destFullName
+    ]
+
+    / aName [
+ "Answer a File or Directory object as appropriate for a file named
+ 'aName' in the directory represented by the receiver."
+
+ ^self at: aName
+    ]
+
+    at: aName [
+ "Answer a File or Directory object as appropriate for a file named
+ 'aName' in the directory represented by the receiver."
+
+ <category: 'accessing'>
+ | f |
+ f := vfsHandler at: aName.
+ ^self class on: f
+    ]
+
+    includes: aName [
+        "Answer whether a file named `aName' exists in the directory represented
+         by the receiver."
+
+        <category: 'accessing'>
+        ^(vfsHandler at: aName) exists
+    ]
+
+    fullNameAt: aName [
+ "Answer a String containing the full path to a file named `aName' which
+ resides in the directory represented by the receiver."
+
+ <category: 'accessing'>
+ ^Directory append: aName to: self fullName
+    ]
+
+    nameAt: aName [
+ "Answer a String containing the path to a file named `aName' which
+ resides in the directory represented by the receiver."
+
+ <category: 'accessing'>
+ ^Directory append: aName to: self name
+    ]
+
+    allFilesMatching: aPattern do: aBlock [
+ "Evaluate aBlock on the File objects that match aPattern (according to
+ String>>#match:) in the directory named by the receiver. Recursively
+ descend into directories."
+
+ <category: 'enumerating'>
+ self do:
+ [:name |
+ | f |
+ f := self at: name.
+ (aPattern match: name) ifTrue: [aBlock value: f].
+ f isDirectory
+    ifTrue:
+ [((#('.' '..') includes: name) or: [f isSymbolicLink])
+    ifFalse: [f allFilesMatching: aPattern do: aBlock]]]
+    ]
+
+    files [
+ "Answer an Array with File objects for the contents of the directory
+ represented by the receiver."
+
+ <category: 'enumerating'>
+ ^self select: [ :each | each isFile ]
+    ]
+
+    directories [
+ "Answer an Array with Directory objects for the subdirectories
+ of the directory represented by the receiver."
+
+ <category: 'enumerating'>
+ ^self select: [ :each | each isDirectory ]
+    ]
+
+    entries [
+ "Answer an Array with File or Directory objects for the contents
+ of the directory represented by the receiver."
+
+ <category: 'enumerating'>
+ | ws |
+ ws := WriteStream on: (Array new: 50).
+ self do: [:each | ws nextPut: each].
+ ^ws contents
+    ]
+
+    entryNames [
+ "Answer an Array with the names of the files in the directory
+ represented by the receiver."
+
+ <category: 'enumerating'>
+ | ws |
+ ws := WriteStream on: (Array new: 50).
+ self namesDo: [:each | ws nextPut: each].
+ ^ws contents
+    ]
+
+    do: aBlock [
+ "Evaluate aBlock once for each file in the directory represented by the
+ receiver, passing its name."
+
+ <category: 'enumerating'>
+ self namesDo: [ :name |
+    aBlock value: (self at: name) ]
+    ]
+
+    namesDo: aBlock [
+ "Evaluate aBlock once for each file in the directory represented by the
+ receiver, passing its name."
+
+ <category: 'enumerating'>
+ vfsHandler do: [ :name | aBlock value: name ]
+    ]
+
+    filesMatching: aPattern [
+ "Evaluate aBlock once for each file in the directory represented by the
+ receiver, passing a File or Directory object to aBlock. Returns the
+ *names* of the files for which aBlock returns true."
+
+ <category: 'enumerating'>
+ | ws |
+ ws := WriteStream on: (Array new: 50).
+ self namesDo: [ :name |
+    (aPattern match: name) ifTrue: [ ws nextPut: (self at: name) ] ].
+ ^ws contents
+    ]
+
+    reject: aBlock [
+ "Evaluate aBlock once for each file in the directory represented by the
+ receiver, passing a File or Directory object to aBlock. Returns the
+ *names* of the files for which aBlock returns true."
+
+ <category: 'enumerating'>
+ | ws |
+ ws := WriteStream on: (Array new: 50).
+ self do: [ :each |
+    (aBlock value: each) ifFalse: [ ws nextPut: each ] ].
+ ^ws contents
+    ]
+
+    select: aBlock [
+ "Evaluate aBlock once for each file in the directory represented by the
+ receiver, passing a File or Directory object to aBlock. Returns the
+ *names* of the files for which aBlock returns true."
+
+ <category: 'enumerating'>
+ | ws |
+ ws := WriteStream on: (Array new: 50).
+ self do: [ :each |
+    (aBlock value: each) ifTrue: [ ws nextPut: each ] ].
+ ^ws contents
+    ]
+
+    filesMatching: aPattern do: block [
+ "Evaluate block on the File objects that match aPattern (according to
+ String>>#match:) in the directory named by the receiver."
+
+ <category: 'enumerating'>
+ self namesDo: [:name |
+    (aPattern match: name) ifTrue: [block value: (self at: name)]]
+    ]
+
+    namesMatching: aPattern do: block [
+ "Evaluate block on the file names that match aPattern (according to
+ String>>#match:) in the directory named by the receiver."
+
+ <category: 'enumerating'>
+ vfsHandler
+    do: [:name | (aPattern match: name) ifTrue: [block value: (self nameAt: name)]]
+    ]
 ]
 
+
+String extend [
+    / aName [
+ "Answer a File or Directory object as appropriate for a file named
+ 'aName' in the directory represented by the receiver."
+
+ ^(File name: self) at: aName
+    ]
+]
diff --git a/kernel/PkgLoader.st b/kernel/PkgLoader.st
index 6ed4b84..1bf5d17 100644
--- a/kernel/PkgLoader.st
+++ b/kernel/PkgLoader.st
@@ -318,7 +318,7 @@ XML.'>
  <category: 'refreshing'>
  | dir file allDirs |
  file := File name: fileName.
- dir := Directory name: file path.
+ dir := file directory.
  allDirs := Smalltalk imageLocal
     ifTrue: [{Directory image} , baseDirectories value]
     ifFalse: [baseDirectories value].
diff --git a/packages/httpd/FileServer.st b/packages/httpd/FileServer.st
index ee1dc14..22e2b94 100644
--- a/packages/httpd/FileServer.st
+++ b/packages/httpd/FileServer.st
@@ -111,7 +111,7 @@ A DirectoryResponse formats output of the contents of a Directory object.'>
     nl;
     << '<hr>';
     nl.
- (Directory name: file name) entryNames asSortedCollection
+ (File name: file name) entryNames asSortedCollection
     do: [:each | self sendFileProperties: each].
  self << '</pre><hr><FORM ACTION="' << request uri.
  self
@@ -814,7 +814,7 @@ and DirectoryResponses.'>
 
     directory: aDirectory [
  <category: 'accessing'>
- initialDirectory := Directory name: aDirectory
+ initialDirectory := File name: aDirectory
     ]
 
     indexFileNames [
@@ -824,7 +824,7 @@ and DirectoryResponses.'>
 
     initialize [
  <category: 'initialize-release'>
- initialDirectory := Directory name: Directory working.
+ initialDirectory := File name: Directory working.
  uploadAuthorizer := WebAuthorizer new.
  name := 'File'
     ]
diff --git a/packages/httpd/WikiServer.st b/packages/httpd/WikiServer.st
index 0faf394..9046301 100644
--- a/packages/httpd/WikiServer.st
+++ b/packages/httpd/WikiServer.st
@@ -2275,7 +2275,7 @@ WikiPersistanceManager subclass: FlatFileWiki [
 
     directory: aFilename [
  <category: 'accessing'>
- directory := Directory name: aFilename
+ directory := File name: aFilename
     ]
 
     addPage: aPage [
diff --git a/packages/net/URIResolver.st b/packages/net/URIResolver.st
index 593c34c..9d900c2 100644
--- a/packages/net/URIResolver.st
+++ b/packages/net/URIResolver.st
@@ -285,7 +285,7 @@ Copyright (c) Kazuki Yasumatsu, 1995. All rights reserved.
  file exists not ifTrue: [^self errorContents: 'No such file'].
  file isReadable ifFalse: [^self errorContents: 'Cannot read'].
  file isDirectory
-    ifTrue: [^self getDirectoryContentsOf: (Directory name: file name)].
+    ifTrue: [^self getDirectoryContentsOf: (File name: file name)].
  ^(WebEntity new)
     url: url;
     canCache: false;
diff --git a/packages/seaside/core/Seaside-GST.st b/packages/seaside/core/Seaside-GST.st
index 0f2e2c9..5d04ee6 100644
--- a/packages/seaside/core/Seaside-GST.st
+++ b/packages/seaside/core/Seaside-GST.st
@@ -554,7 +554,7 @@ Object subclass: WAGNUSmalltalkPlatform [
  "Return a collection of absolute paths for all the files (no directories) in the directory given by aPathString
  must not include file names that start with ."
  | directory |
- directory := Directory name: aPathString.
+ directory := File name: aPathString.
  ^(directory entryNames
  reject: [ :each | each first = $. ])
  collect: [ :each | Directory append: each to: directory name ]
diff --git a/scripts/Package.st b/scripts/Package.st
index d3c5048..f195839 100644
--- a/scripts/Package.st
+++ b/scripts/Package.st
@@ -107,7 +107,7 @@ Kernel.PackageDirectories subclass: PackageFiles [
  "See if the file is in srcdir or builddir.  In any case, we want to
  look for files first in the builddir, and secondarily in srcdir."
  srcdirPath := file pathFrom: srcdir.
- builddirPrefix := (Directory name: Directory working) pathFrom: srcdir.
+ builddirPrefix := (File name: Directory working) pathFrom: srcdir.
  ^(srcdirPath startsWith: builddirPrefix, Directory pathSeparatorString)
     ifFalse: [
  "file is in srcdir."
@@ -182,7 +182,7 @@ File extend [
     ]
 ]
 
-Directory extend [
+File extend [
     emitMkdir [
  | doThat |
  self exists ifTrue: [ ^self ].
@@ -230,7 +230,7 @@ Object subclass: Command [
 
     validateDestDir: destdir installDir: instDir [
  instDir isNil ifTrue: [ ^self ].
- ((Directory name: instDir) name ~= instDir
+ ((File name: instDir) name ~= instDir
     and: [ destdir notEmpty ]) ifTrue: [
  self error: '--destdir used with relative target directory' ]
     ]
@@ -238,7 +238,7 @@ Object subclass: Command [
     destDir: destdir installDir: instDir [
  self validateDestDir: destdir installDir: instDir.
  installDir :=
-    Directory name:
+    File name:
         destdir, (instDir ifNil: [ self defaultInstallDir ])
     ]
 
@@ -272,7 +272,7 @@ Object subclass: Command [
  source := self isOption: 'load'.
  test := self isOption: 'test'.
  base := self installDir.
- vpathBase := Directory name: self srcdir.
+ vpathBase := File name: self srcdir.
 
         listFiles do: [ :each || package files |
     package := self packages at: each.
@@ -323,7 +323,7 @@ Command subclass: PkgDist [
     distribute: srcFile as: file in: dir [
  | destName baseDir |
  baseDir := self installDir.
- dir isNil ifFalse: [ baseDir := baseDir directoryAt: dir ].
+ dir isNil ifFalse: [ baseDir := baseDir / dir ].
  destName := baseDir nameAt: file.
  (self isOption: 'copy')
     ifTrue: [ srcFile emitInstall: destName ]
@@ -343,7 +343,7 @@ Command subclass: PkgDist [
     dirs := dirs collect: [ :dir | aPackage relativeDirectory / dir ] ].
 
         dirs do: [ :dir || destName |
-    (self installDir directoryAt: dir name) emitMkdir ].
+    (self installDir / dir name) emitMkdir ].
 
         files do: [ :file || srcFile destName |
     srcFile := File name: (aPackage fullPathOf: file).
@@ -399,7 +399,7 @@ Command subclass: PkgInstall [
  gstLoad := gstPackage.
  pat := '%1 gst-load -I %2 --kernel-directory %3 %4 %5' ]
     ifFalse: [
- gstLoad := gstPackage directory fileAt: 'gst-load'.
+ gstLoad := gstPackage directory / 'gst-load'.
  pat := '%1 -I %2 --kernel-directory %3 %4 %5' ].
 
  packageList := ''.
@@ -423,35 +423,35 @@ Command subclass: PkgInstall [
 
     runOnPackage: aPackage [
  | pkg destFile dirs files baseDir |
- baseDir := self tmpDir directoryAt: aPackage name.
+ baseDir := self tmpDir / aPackage name.
  pkg := aPackage copy.
  pkg relativeDirectory: nil.
 
  baseDir emitMkdir.
  Command
     execute: [
-        (baseDir fileAt: 'package.xml') withWriteStreamDo: [ :s |
+        (baseDir / 'package.xml') withWriteStreamDo: [ :s |
             pkg printOn: s ].
 
         files := pkg allFiles.
                 dirs := files collect: [ :file | File pathFor: file ].
         dirs asSet asSortedCollection do: [ :dir |
-            (baseDir directoryAt: dir) emitMkdir ].
+            (baseDir / dir) emitMkdir ].
 
                 files do: [ :file || srcFile |
             srcFile := File name: (aPackage fullPathOf: file).
             srcFile emitSymlink: (baseDir nameAt: file) ].
 
-        (self installDir fileAt: aPackage name, '.star')
+        (self installDir / aPackage name, '.star')
     emitZipDir: baseDir
     ]
     ensure: [
         "Clean up our mess."
-        (baseDir fileAt: 'package.xml') remove.
+        (baseDir / 'package.xml') remove.
                 files do: [ :file |
-            (baseDir fileAt: file) remove ].
+            (baseDir / file) remove ].
         dirs asSet asSortedCollection do: [ :dir |
-            (baseDir directoryAt: dir) remove ]
+            (baseDir / dir) remove ]
     ].
     ]
 
@@ -472,10 +472,10 @@ Command subclass: PkgUninstall [
  | baseDir |
  baseDir := self installDir.
  aPackage relativeDirectory isNil ifFalse: [
-    baseDir := baseDir directoryAt: aPackage relativeDirectory ].
+    baseDir := baseDir / aPackage relativeDirectory ].
 
  aPackage allFiles do: [ :file |
-    (baseDir fileAt: file) emitRemove ]
+    (baseDir / file) emitRemove ]
     ]
 
     runOnStar: aPackage [ ]
@@ -517,11 +517,11 @@ Command subclass: PkgPrepare [
  srcFile isNil ifTrue: [
     f := self srcdir / aCollection first.
             (File exists: f)
-        ifTrue: [ srcFile := (Directory name: self srcdir) pathTo: f ].
+        ifTrue: [ srcFile := (File name: self srcdir) pathTo: f ].
 
     f := f, '.in'.
             (File exists: f)
-        ifTrue: [ srcFile := (Directory name: self srcdir) pathTo: f ]
+        ifTrue: [ srcFile := (File name: self srcdir) pathTo: f ]
  ].
 
  super addAllFiles: aCollection.
@@ -529,7 +529,7 @@ Command subclass: PkgPrepare [
 
     run [
         | base configureAC makefileAM gstIN |
- base := Directory name: self srcdir.
+ base := File name: self srcdir.
  configureAC := base at: 'configure.ac'.
  makefileAM := base at: 'Makefile.am'.
  gstIN := base at: 'gst.in'.
@@ -591,14 +591,14 @@ AC_OUTPUT
 
     writeConfigureEntry: each to: ws [
  | pkgName buildPath srcPath pkgSrcDir relPkgSrcDir generated |
- buildPath := (Directory name: Directory working) pathTo: each.
- srcPath := (Directory name: self srcdir) pathTo: each.
+ buildPath := Directory working pathTo: each.
+ srcPath := (File name: self srcdir) pathTo: each.
 
  pkgSrcDir := srcPath size < buildPath size
     ifTrue: [ File pathFor: srcPath ifNone: [ self srcdir ] ]
     ifFalse: [ Directory append: (File pathFor: buildPath) to: self srcdir ].
 
- relPkgSrcDir := (Directory name: self srcdir) pathTo: pkgSrcDir.
+ relPkgSrcDir := (File name: self srcdir) pathTo: pkgSrcDir.
 
  ('*.in' match: each)
     ifTrue: [
@@ -620,7 +620,7 @@ AC_OUTPUT
 
  generated ifTrue: [
     ws nextPutAll: (', , , [%1]' % {
- (Directory name: relPkgSrcDir) pathTo: srcPath }) ].
+ (File name: relPkgSrcDir) pathTo: srcPath }) ].
 
  ws nextPutAll: ')'; nl.
     ]
--
1.5.3.4.910.gc5122-dirty



_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk