Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sat, 14 May 2016 09:34:43 +0200
branchjv
changeset 19861 95c7068e30ba
parent 19812 0866264d6eed (current diff)
parent 19830 1e518848efb6 (diff)
child 19862 6c010853ea32
Merge
AbstractOperatingSystem.st
Annotation.st
Behavior.st
CharacterEncoder.st
CharacterEncoderImplementations__ISO8859_1.st
CharacterEncoderImplementations__JIS0208.st
CharacterEncoderImplementations__SingleByteEncoder.st
CharacterEncoderImplementations__TwoByteEncoder.st
Dictionary.st
Filename.st
ProjectDefinition.st
SequenceableCollection.st
UninterpretedBytes.st
UnixFilename.st
UnixOperatingSystem.st
WriteStream.st
--- a/AbstractOperatingSystem.st	Fri May 13 20:17:32 2016 +0200
+++ b/AbstractOperatingSystem.st	Sat May 14 09:34:43 2016 +0200
@@ -2705,13 +2705,23 @@
 caseSensitiveFilenames
     "return true, if the OS has caseSensitive file naming.
      On MSDOS, this will return false;
-     on a real OS, we return true."
+     on a real OS, we return true.
+     Be aware, that OSX can be configured to be either.
+     Also, that it actually depends on the mounted volume"
 
     "/ actually, this query is too general, as it may depend on the mounted volume;
     "/ so we need a query for a particular directory (and/or volume).
     self subclassResponsibility
 !
 
+caseSensitiveFilenamesIn:aFolderPath
+    "return true, if the OS has caseSensitive file naming inside a folderPath.
+     Be aware, that it actually depends on the mounted volume,
+     so some concrete subclass may redefine this query."
+
+    ^ self caseSensitiveFilenames
+!
+
 compressPath:pathName
     "return the pathName compressed - that is, remove all ..-entries
      and . entries. This does not always (in case of symbolic links)
--- a/Annotation.st	Fri May 13 20:17:32 2016 +0200
+++ b/Annotation.st	Sat May 14 09:34:43 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
               All Rights Reserved
@@ -208,27 +206,39 @@
 allNamed:aSymbol
     "Answer a collection of all pragmas found in all methods of all classes whose keyword is aSymbol."
         
-    ^ Array streamContents: [ :stream |
-        Smalltalk allClassesDo:[:eachClass |
-            self withPragmasIn: eachClass do: [ :pragma |
-                    pragma keyword = aSymbol
-                        ifTrue: [ stream nextPut: pragma ] ] ] ].
+    ^ Array 
+        streamContents: [ :stream |
+            Smalltalk allClassesDo:[:eachClass |
+                self withPragmasIn: eachClass do: [ :pragma |
+                    pragma keyword = aSymbol ifTrue: [ 
+                        stream nextPut: pragma 
+                    ] 
+                ] 
+            ] 
+        ].
 
     "
      Annotation allNamed:'worldMenu'
     "
 !
 
-allNamed: aSymbol from: aSubClass to: aSuperClass
-	"Answer a collection of all pragmas found in methods of all classes between aSubClass and aSuperClass (inclusive) whose keyword is aSymbol."
-	
-	^ Array streamContents: [ :stream |
-		aSubClass withAllSuperclassesDo: [ :class |
-			self withPragmasIn: class do:  [ :pragma |
-				pragma keyword = aSymbol
-					ifTrue: [ stream nextPut: pragma ] ].
-			aSuperClass = class
-				ifTrue: [ ^ stream contents ] ] ].
+allNamed:aSymbol from:aSubClass to:aSuperClass
+    "Answer a collection of all pragmas found in methods of all classes 
+     between aSubClass and aSuperClass (inclusive) whose keyword is aSymbol."
+    
+    ^ Array 
+        streamContents:[:stream |
+            aSubClass withAllSuperclassesDo:[:class |
+                self withPragmasIn:class do:[:pragma |
+                    pragma keyword = aSymbol ifTrue: [ 
+                        stream nextPut: pragma 
+                    ] 
+                ].
+                aSuperClass = class ifTrue: [ 
+                    ^ stream contents 
+                ] 
+            ] 
+        ].
 !
 
 allNamed: aSymbol from: aSubClass to: aSuperClass sortedByArgument: anInteger
@@ -244,12 +254,16 @@
 !
 
 allNamed: aSymbol in: aClass
-	"Answer a collection of all pragmas found in methods of aClass whose keyword is aSymbol."
-	
-	^ Array streamContents: [ :stream |
-		self withPragmasIn: aClass do: [ :pragma |
-			pragma keyword = aSymbol
-				ifTrue: [ stream nextPut: pragma ] ] ].
+    "Answer a collection of all pragmas found in methods of aClass whose keyword is aSymbol."
+    
+    ^ Array 
+        streamContents: [ :stream |
+            self withPragmasIn: aClass do: [ :pragma |
+                pragma keyword = aSymbol ifTrue: [ 
+                    stream nextPut: pragma 
+                ] 
+            ] 
+        ].
 !
 
 allNamed: aSymbol in: aClass sortedByArgument: anInteger
--- a/Behavior.st	Fri May 13 20:17:32 2016 +0200
+++ b/Behavior.st	Sat May 14 09:34:43 2016 +0200
@@ -1334,7 +1334,8 @@
 !
 
 theNonMetaClass
-    "alias for theNonMetaclass - return the class"
+    "alias for theNonMetaclass (Squeak) - return the class.
+     sigh; in ST/X, it is called theNonMetaclass; please use that."
 
     ^ self theNonMetaclass
 
@@ -1423,6 +1424,7 @@
     ^ self nameWithoutPrefix
 ! !
 
+
 !Behavior methodsFor:'RefactoringBrowser'!
 
 realClass
--- a/CharacterEncoder.st	Fri May 13 20:17:32 2016 +0200
+++ b/CharacterEncoder.st	Sat May 14 09:34:43 2016 +0200
@@ -1487,12 +1487,6 @@
         nextPutAll:(self nameOfEncoding)
 ! !
 
-!CharacterEncoder methodsFor:'private'!
-
-newString:size
-    self subclassResponsibility
-! !
-
 !CharacterEncoder methodsFor:'queries'!
 
 characterSize:codePoint
--- a/CharacterEncoderImplementations__ISO8859_1.st	Fri May 13 20:17:32 2016 +0200
+++ b/CharacterEncoderImplementations__ISO8859_1.st	Sat May 14 09:34:43 2016 +0200
@@ -455,14 +455,9 @@
     ^ unicode.
 ! !
 
-!ISO8859_1 methodsFor:'private'!
-
-newString:size
-    ^ String new:size
-! !
-
 !ISO8859_1 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO8859_1.st,v 1.5 2012-07-11 16:42:55 stefan Exp $'
+    ^ '$Header$'
 ! !
+
--- a/CharacterEncoderImplementations__JIS0208.st	Fri May 13 20:17:32 2016 +0200
+++ b/CharacterEncoderImplementations__JIS0208.st	Sat May 14 09:34:43 2016 +0200
@@ -28637,16 +28637,10 @@
     ] value.
 ! !
 
-!JIS0208 methodsFor:'private'!
-
-newString:size
-    ^ JISEncodedString new:size
-! !
-
 !JIS0208 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208.st,v 1.4 2008/10/30 19:54:58 cg Exp $'
+    ^ '$Header$'
 ! !
 
 
--- a/CharacterEncoderImplementations__SingleByteEncoder.st	Fri May 13 20:17:32 2016 +0200
+++ b/CharacterEncoderImplementations__SingleByteEncoder.st	Sat May 14 09:34:43 2016 +0200
@@ -55,12 +55,6 @@
     ^ 0 
 ! !
 
-!SingleByteEncoder methodsFor:'private'!
-
-newString:size
-    ^ String uninitializedNew:size
-! !
-
 !SingleByteEncoder methodsFor:'queries'!
 
 characterSize:codePoint
@@ -73,9 +67,10 @@
 !SingleByteEncoder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__SingleByteEncoder.st,v 1.9 2009-12-11 16:54:15 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__SingleByteEncoder.st,v 1.9 2009-12-11 16:54:15 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/CharacterEncoderImplementations__TwoByteEncoder.st	Fri May 13 20:17:32 2016 +0200
+++ b/CharacterEncoderImplementations__TwoByteEncoder.st	Sat May 14 09:34:43 2016 +0200
@@ -46,12 +46,6 @@
     ^ 0 
 ! !
 
-!TwoByteEncoder methodsFor:'private'!
-
-newString:size
-    ^ TwoByteString uninitializedNew:size
-! !
-
 !TwoByteEncoder methodsFor:'queries'!
 
 characterSize:codePoint
--- a/Dictionary.st	Fri May 13 20:17:32 2016 +0200
+++ b/Dictionary.st	Sat May 14 09:34:43 2016 +0200
@@ -292,6 +292,8 @@
     ^ true
 ! !
 
+
+
 !Dictionary methodsFor:'accessing'!
 
 associationAt:aKey
@@ -802,6 +804,15 @@
     "Modified: 1.3.1996 / 21:24:03 / cg"
 !
 
+clearContents
+    "remove all elements from the receiver, but do not resize.
+     Returns the receiver."
+
+    keyArray atAllPut:nil.
+    valueArray atAllPut:nil.
+    tally := 0.
+!
+
 declare:key from:aDictionary
     "if the receiver does not include an association for key,
      take the association from aDictionary and add it to the receiver.
@@ -2327,6 +2338,7 @@
     ^ aVisitor visitDictionary:self with:aParameter
 ! !
 
+
 !Dictionary class methodsFor:'documentation'!
 
 version
--- a/Filename.st	Fri May 13 20:17:32 2016 +0200
+++ b/Filename.st	Sat May 14 09:34:43 2016 +0200
@@ -1291,10 +1291,13 @@
 
 isCaseSensitive
     "return true, if filenames are case sensitive.
-     We ask the OS about this, to be independent here."
+     We ask the OS about this, to be independent here.
+     This is not really correct, as the sensitivity may depend on
+     the paricular mounted file system (NFS, for example).
+     So we need a query on the instance side"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass isCaseSensitive
+        ^ ConcreteClass isCaseSensitive
     ].
 
     ^ OperatingSystem caseSensitiveFilenames
@@ -1536,7 +1539,7 @@
     |sep f vol rest components|
 
     self isAbstract ifTrue:[
-	^ ConcreteClass components:aString
+        ^ ConcreteClass components:aString
     ].
 
     "/ the following works on Unix & MSDOS (but not on openVMS)
@@ -1547,59 +1550,78 @@
     f := aString asFilename.
     vol := f volume.
     vol size ~~ 0 ifTrue:[
-	rest := f localPathName.
+        rest := f localPathName.
     ] ifFalse:[
-	rest := aString
+        rest := aString
     ].
 
     components := rest asCollectionOfSubstringsSeparatedBy:sep.
     (rest startsWith:sep) ifTrue:[
-	"first was a separator - root directory - restore"
-	(rest size > 1 and:[rest second = sep and:[vol isEmptyOrNil]]) ifTrue:[
-	    "keep \\ for windows network paths"
-	    components at:1 put:(String with:sep with:sep).
-	] ifFalse:[
-	    components at:1 put:sep asString.
-	].
+        "first was a separator - root directory - restore"
+        (rest size > 1 and:[rest second = sep and:[vol isEmptyOrNil]]) ifTrue:[
+            "keep \\ for windows network paths"
+            components at:1 put:(String with:sep with:sep).
+        ] ifFalse:[
+            components at:1 put:sep asString.
+        ].
     ].
     components := components select:[:each| each notEmpty].
 
     "/ prepend volume to first component (the root directory)
     vol size ~~ 0 ifTrue:[
-	components at:1 put:(vol , (components at:1)).
+        components at:1 put:(vol , (components at:1)).
     ].
     ^ components
 
     "
-     Filename components:'/foo/bar/baz'
-     Filename components:'/'
-     Filename components:'//'
-     Filename components:'foo/bar/baz'
-     Filename components:'foo/bar'
-     Filename components:'foo'
-     Filename components:'/foo'
-     Filename components:'//foo'
-     Filename components:''
-
-     Filename components:'\'
-     Filename components:'\foo'
-     Filename components:'\foo\'
-     Filename components:'\foo\bar'
-     Filename components:'\foo\bar\'
-     Filename components:'c:'
-     Filename components:'c:\'
-     Filename components:'c:\foo'
-     Filename components:'c:\foo\'
-     Filename components:'c:\foo\bar'
-     Filename components:'c:\foo\bar\'
-     Filename components:'\\idefix'
-     Filename components:'\\idefix\home'
-     Filename components:'\\idefix\home\bar'
+     Unix:
+     UnixFilename components:'/foo/bar/baz'
+     UnixFilename components:'/'
+     UnixFilename components:'//'
+     UnixFilename components:'foo/bar/baz'
+     UnixFilename components:'foo/bar'
+     UnixFilename components:'foo'
+     UnixFilename components:'/foo'
+     UnixFilename components:'//foo'
+     UnixFilename components:''
+
+     Windows:
+     PCFilename components:'\'
+     PCFilename components:'\foo'
+     PCFilename components:'\foo\'
+     PCFilename components:'\foo\bar'
+     PCFilename components:'\foo\bar\'
+     PCFilename components:'c:'
+     PCFilename components:'c:\'
+     PCFilename components:'c:\foo'
+     PCFilename components:'c:\foo\'
+     PCFilename components:'c:\foo\bar'
+     PCFilename components:'c:\foo\bar\'
+     PCFilename components:'\\idefix'
+     PCFilename components:'\\idefix\home'
+     PCFilename components:'\\idefix\home\bar'
     "
 
     "Modified: / 24.9.1998 / 19:10:52 / cg"
 !
 
+filesMatchingGLOB:pattern
+    "does a GLOB filename expansion.
+     Generates and returns a possibly empty list of files which match
+     the given glob pattern"
+
+    ^ OrderedCollection withCollectedContents:[:coll |
+        pattern asFilename filesMatchingGLOBDo:[:each | coll add:each]
+      ]
+
+    "
+     Filename filesMatchingGLOB:'./A*'
+     Filename filesMatchingGLOB:'/etc/A*'
+     Filename filesMatchingGLOB:'/*/A*'
+     '.' asFilename filesMatchingGLOB:'A*'
+    "
+!
+
 nameFromComponents:aCollectionOfDirectoryNames
     "return a filenameString from components given in aCollectionOfDirectoryNames.
      If the first component is the name of the root directory (i.e. '/'),
@@ -2176,16 +2198,8 @@
 directories
     "return a collection of directories contained in the directory represented by the receiver."
 
-    |collection|
-
-    collection := OrderedCollection new.
-    self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-	eachFileOrDirectory isDirectory ifTrue:[
-	    collection add:eachFileOrDirectory.
-	].
-    ].
-
-    ^ collection
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self directoriesDo:[:eachDirectory | coll add:eachDirectory]]
 
     "
      '.' asFilename directories.
@@ -2253,25 +2267,25 @@
     s := DirectoryStream directoryNamed:self osNameForDirectoryContents.
     "check for nil, in order to allow to proceed from an OpenError"
     s notNil ifTrue:[
-	[
-	    [s atEnd] whileFalse:[
-		|fn|
-
-		fn := s nextLine.
-		(fn ~= '.' and:[fn ~= '..']) ifTrue:[
-		    aBlock value:fn
-		].
-	    ].
-	] ensure:[
-	    s close.
-	].
+        [
+            [s atEnd] whileFalse:[
+                |fn|
+
+                fn := s nextLine.
+                (fn notNil and:[fn ~= '.' and:[fn ~= '..']]) ifTrue:[
+                    aBlock value:fn
+                ].
+            ].
+        ] ensure:[
+            s close.
+        ].
     ].
 
     "
      '.' asFilename directoryContentsDo:[:fn | Transcript showCR:fn].
      'doeSnotExIST' asFilename directoryContentsDo:[:fn | Transcript showCR:fn].
      [
-	'doeSnotExIST' asFilename directoryContentsDo:[:fn | Transcript showCR:fn].
+        'doeSnotExIST' asFilename directoryContentsDo:[:fn | Transcript showCR:fn].
      ] on:OpenError do:[:ex| ex proceed]
     "
 
@@ -2283,11 +2297,8 @@
     "return a collection of regular files
      contained in the directory represented by the receiver."
 
-    |collection|
-
-    collection := OrderedCollection new.
-    self filesDo:[:eachFileName | collection add:eachFileName].
-    ^ collection.
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self filesDo:[:eachFileName | coll add:eachFileName]].
 
     "
      '.' asFilename files.
@@ -2314,19 +2325,140 @@
     "Modified: / 29-05-2007 / 12:02:46 / cg"
 !
 
+filesMatchingGLOB:pattern do:aBlock
+    "Interpreting pattern as a GLOB pattern,
+     evaluate aBlock for each file in me, which matches.
+     Returns the number of matches."
+
+    self assert:(pattern asFilename isAbsolute not).
+    ^ self filesMatchingGLOBComponents:(Filename components:pattern) do:aBlock
+    
+    "
+     '..' asFilename filesMatchingGLOB:'A*' do:[:fn | Transcript showCR:fn].
+     '../..' asFilename filesMatchingGLOB:'lib*/*.st' do:[:fn | Transcript showCR:fn].
+    "
+!
+
+filesMatchingGLOBComponents:patternComponents do:aBlock
+    "patternComponents is a component-collection with possible GLOB patterns.
+     Evaluate aBlock for each file in me, which matches.
+     Returns the number of matches"
+
+    |dirPath subComponents count|
+    
+    dirPath := patternComponents first.
+    subComponents := patternComponents copyFrom:2.
+
+    dirPath includesMatchCharacters ifFalse:[
+        | sub |
+        
+        sub := (self / dirPath).
+        subComponents isEmpty ifTrue:[
+            "/ I am a leaf
+            sub exists ifTrue:[
+                aBlock value:sub.
+                ^ 1.
+            ].    
+            ^ 0
+        ] ifFalse:[    
+            ^ sub filesMatchingGLOBComponents:subComponents do:aBlock
+        ].
+    ] ifTrue:[
+        count := 0.
+        subComponents isEmpty ifTrue:[
+            "/ I am a leaf
+            self isDirectory ifTrue:[
+                self filesMatching:dirPath do:[:eachMatchingFile |
+                    aBlock value:(self / eachMatchingFile).
+                    count := count + 1.
+                ]
+            ]
+        ] ifFalse:[    
+            self filesMatching:dirPath do:[:eachMatchingSubDir |
+                |sub|
+                sub := (self / eachMatchingSubDir).
+                sub isDirectory ifTrue:[
+                    count := count + (sub filesMatchingGLOBComponents:subComponents do:aBlock)
+                ].
+            ].
+        ].
+        ^ count
+    ].    
+
+    "
+     '/etc/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../lib*/*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+    "
+!
+
+filesMatchingGLOBDo:aBlock
+    "Interpreting myself as a GLOB pattern,
+     evaluate aBlock for each file which matches."
+
+    |parts dirPath subComponents count top|
+    
+    parts := self components.
+    dirPath := parts first.
+    subComponents := parts copyFrom:2.
+
+    OpenError handle:[:ex |
+        ('%1 [info]: failed to open %2: %3'
+                bindWith:self class name
+                with:ex pathName 
+                with:ex description) infoPrintCR. 
+        self breakPoint:#cg.
+        ex proceed.
+    ] do:[
+        top := dirPath asFilename.
+
+        dirPath includesMatchCharacters ifFalse:[
+            top isAbsolute ifFalse:[
+                top := Filename currentDirectory construct:dirPath.
+            ].
+            ^ top filesMatchingGLOBComponents:subComponents do:aBlock
+        ].
+        
+        top isAbsolute ifFalse:[
+            top := Filename currentDirectory.
+        ].
+        count := 0.
+        top filesMatching:dirPath do:[:sub |
+            count := count + ((self / sub) filesMatchingGLOBComponents:subComponents do:aBlock)
+        ].
+        ^ count
+    ].
+    
+    "
+     '/etc/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '/etc/a*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../lib*/*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../lib*/[A-D]*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../*/[A-D]*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../*/*/[A-D]*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../*java*/*/[A-D]*.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../../*java*/*/Ary.st' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '/*/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '*/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '../*/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     './*/A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     './*/*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+     '././A*' asFilename filesMatchingGLOBDo:[:fn | Transcript showCR:fn].
+    "
+!
+
 filesWithSuffix:suffix
     "return a collection of regular files (i.e. not subdirectories)
      with a given suffix which are contained in the directory
      represented by the receiver."
 
-    |collection|
-
-    collection := OrderedCollection new.
-    self filesWithSuffix:suffix do:[:eachFileName | collection add:eachFileName].
-    ^ collection.
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self filesWithSuffix:suffix do:[:eachFileName | coll add:eachFileName]].
 
     "
      '.' asFilename filesWithSuffix:'so'.
+     'packages' asFilename filesWithSuffix:'so'.
     "
 !
 
@@ -4358,14 +4490,8 @@
      The pattern may be a simple matchPattern, or a set of
      multiple patterns separated by semicolons."
 
-    |matchers caseSensitive|
-
-    matchers := aPattern asCollectionOfSubstringsSeparatedBy:$;.
-    caseSensitive := self species isCaseSensitive.
-    ^ self directoryContents
-	select:[:name |
-		(matchers detect:[:p | p match:name caseSensitive:caseSensitive] ifNone:0) ~~ 0
-	       ]
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self filesMatching:aPattern do:[:fn | coll add:fn]]
 
     "
      '/etc' asFilename filesMatching:'a*;c*'
@@ -4375,6 +4501,45 @@
     "Modified: / 3.8.1998 / 21:22:15 / cg"
 !
 
+filesMatching:aPattern caseSensitive:caseSensitive do:aBlock
+    "given the receiver, representing a directory;
+     evaluate aBlock for files which match a pattern.
+     The pattern may be a simple matchPattern, or a set of
+     multiple patterns separated by semicolons."
+
+    |matchers|
+
+    matchers := aPattern asCollectionOfSubstringsSeparatedBy:$;.
+    self directoryContentsDo:[:name |
+        (matchers contains:[:p | p match:name caseSensitive:caseSensitive]) ifTrue:[
+            aBlock value:name
+        ]
+    ].    
+
+    "
+     '/etc' asFilename filesMatching:'a*;c*' do:[:f | Transcript showCR:f]
+    "
+
+    "Created: / 15.4.1997 / 15:40:02 / cg"
+    "Modified: / 3.8.1998 / 21:22:15 / cg"
+!
+
+filesMatching:aPattern do:aBlock
+    "given the receiver, representing a directory;
+     evaluate aBlock for files which match a pattern.
+     The pattern may be a simple matchPattern, or a set of
+     multiple patterns separated by semicolons."
+
+    self filesMatching:aPattern caseSensitive:self species isCaseSensitive do:aBlock
+
+    "
+     '/etc' asFilename filesMatching:'a*;c*' do:[:f | Transcript showCR:f]
+    "
+
+    "Created: / 15.4.1997 / 15:40:02 / cg"
+    "Modified: / 3.8.1998 / 21:22:15 / cg"
+!
+
 filesMatchingWithoutDotDirs:aPattern
     "given the receiver, representing a directory;
      return a collection of files matching a pattern.
@@ -4382,17 +4547,57 @@
      The pattern may be a simple matchPattern, or a set of
      multiple patterns separated by semicolons."
 
-    |matchers caseSensitive|
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self filesMatchingWithoutDotDirs:aPattern do:[:fn | coll add:fn]]
+
+    "
+     Filename currentDirectory filesMatching:'.*'
+     Filename currentDirectory filesMatchingWithoutDotDirs:'*.*'
+     '/etc' asFilename filesMatchingWithoutDotDirs:'*'
+    "
+
+    "Created: / 15.4.1997 / 12:52:10 / cg"
+    "Modified: / 3.8.1998 / 21:22:30 / cg"
+!
+
+filesMatchingWithoutDotDirs:aPattern caseSensitive:caseSensitive do:aBlock
+    "given the receiver, representing a directory;
+     evaluate aBlock for files matching a pattern.
+     Exclude '.' and '..'.
+     The pattern may be a simple matchPattern, or a set of
+     multiple patterns separated by semicolons."
+
+    |matchers|
 
     matchers := aPattern asCollectionOfSubstringsSeparatedBy:$;.
-    caseSensitive := self species isCaseSensitive.
-
-    ^ self directoryContents
-	select:[:name |
-		name ~= '.'
-		and:[name ~= '..'
-		and:[(matchers detect:[:p | p match:name caseSensitive:caseSensitive] ifNone:0) ~~ 0]]
-      ]
+
+    self directoryContentsDo:[:name |
+        (name ~= '.'
+            and:[ name ~= '..'
+            and:[ (matchers contains:[:p | p match:name caseSensitive:caseSensitive]) ]])
+        ifTrue:[
+            aBlock value:name
+        ]
+    ].
+    
+    "
+     Filename currentDirectory filesMatching:'M*'
+     '/etc' asFilename filesMatching:'[a-z]*'
+     '../../libbasic' asFilename filesMatching:'[A-D]*.st'
+    "
+
+    "Created: / 15.4.1997 / 12:52:10 / cg"
+    "Modified: / 3.8.1998 / 21:22:30 / cg"
+!
+
+filesMatchingWithoutDotDirs:aPattern do:aBlock
+    "given the receiver, representing a directory;
+     evaluate aBlock for files matching a pattern.
+     Exclude '.' and '..'.
+     The pattern may be a simple matchPattern, or a set of
+     multiple patterns separated by semicolons."
+
+    self filesMatchingWithoutDotDirs:aPattern caseSensitive:self species isCaseSensitive do:aBlock
 
     "
      Filename currentDirectory filesMatching:'M*'
@@ -4405,6 +4610,10 @@
 !
 
 fullAlternativePathName
+    "some filesystems (aka: windows) have alternative (short) filenames.
+     Those systems redefine this method to return it.
+     Otherwise, the same as the regular name is returned here"
+     
     ^ nameString
 !
 
@@ -5521,29 +5730,11 @@
      may be changed in the near future, to raise an exception instead.
      So users of this method better test for existing directory before.
      Notice:
-	this returns the file-names as strings;
-	see also #directoryContentsAsFilenames, which returns fileName instances."
-
-    |directoryStream contents|
-
-    contents := OrderedCollection new.
-    directoryStream := DirectoryStream directoryNamed:(self osNameForDirectoryContents).
-    directoryStream isNil ifTrue:[^ nil].
-
-    [
-	[directoryStream atEnd] whileFalse:[
-	    |entry|
-
-	    entry := directoryStream nextLine.
-	    (entry notNil and:[entry ~= '.' and:[entry ~= '..']]) ifTrue:[
-		contents add:entry
-	    ].
-	].
-    ] ensure:[
-	directoryStream close
-    ].
-
-    ^ contents.
+        this returns the file-names as strings;
+        see also #directoryContentsAsFilenames, which returns fileName instances."
+
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self directoryContentsDo:[:each | coll add:each]] 
 
     "
      '.' asFilename directoryContents
@@ -5561,14 +5752,11 @@
      may be changed in the near future, to raise an exception instead.
      So users of this method better test for existing directory before.
      Notice:
-	this returns the file-names as fileName instances;
-	see also #directoryContents, which returns strings."
-
-    |names|
-
-    names := self directoryContents.
-    names isNil ifTrue:[^ nil].
-    ^ names collect:[:entry | self construct:entry].
+        this returns the file-names as fileName instances;
+        see also #directoryContents, which returns strings."
+
+    ^ OrderedCollection withCollectedContents:[:coll |
+        self directoryContentsAsFilenamesDo:[:each | coll add:each]] 
 
     "
      '.' asFilename directoryContentsAsFilenames
--- a/OSXOperatingSystem.st	Fri May 13 20:17:32 2016 +0200
+++ b/OSXOperatingSystem.st	Sat May 14 09:34:43 2016 +0200
@@ -61,7 +61,9 @@
 caseSensitiveFilenames
     "return true, if the OS has caseSensitive file naming.
      On MSDOS, this will return false;
-     on a real OS, we return true."
+     on a real OS, we return true.
+     Be aware, that OSX can be configured to be either.
+     Also, that it actually depends on the mounted volume"
 
     "/ actually, this is wrong and depends on the mounted volume;
     "/ so we need a query for a particular directory (and/or volume).
@@ -133,9 +135,10 @@
 !OSXOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.17 2015-04-24 08:18:41 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.17 2015-04-24 08:18:41 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/OrderedDictionary.st	Fri May 13 20:17:32 2016 +0200
+++ b/OrderedDictionary.st	Sat May 14 09:34:43 2016 +0200
@@ -892,6 +892,13 @@
 
 !OrderedDictionary methodsFor:'removing'!
 
+clearContents
+    "remove all elements from the receiver, but do not shrink. Returns the receiver."
+
+    super clearContents.
+    order clearContents.
+!
+
 removeFirst
     |key|
 
--- a/ProjectDefinition.st	Fri May 13 20:17:32 2016 +0200
+++ b/ProjectDefinition.st	Sat May 14 09:34:43 2016 +0200
@@ -2746,6 +2746,7 @@
     "Created: / 18-08-2006 / 12:51:38 / cg"
 ! !
 
+
 !ProjectDefinition class methodsFor:'description - project information'!
 
 applicationAdditionalIconFileNames
@@ -4789,6 +4790,7 @@
     ^ self subProjectMakeCallsUsing:'call vcmake %1 %2'.
 ! !
 
+
 !ProjectDefinition class methodsFor:'file templates'!
 
 autopackage_default_dot_apspec
@@ -7721,7 +7723,7 @@
     |className|
 
     className := aClassOrClassName isBehavior 
-                    ifTrue:[ aClassOrClassName theNonMetaClass name ]
+                    ifTrue:[ aClassOrClassName theNonMetaclass name ]
                     ifFalse:[ aClassOrClassName ].
     ^ self autoloaded_classNames includes:className
 
--- a/SequenceableCollection.st	Fri May 13 20:17:32 2016 +0200
+++ b/SequenceableCollection.st	Sat May 14 09:34:43 2016 +0200
@@ -299,6 +299,26 @@
     ^ stream contents
 !
 
+new:initialSize withCollectedContents:blockWithArg
+    "create an instance of the receiver-class,
+     evaluate blockWithArg, passing that instance,
+     return the instance.
+     Similar to streamContents, but passes the collection to the block,
+     instead of a stream."
+
+    |inst|
+
+    inst := self new:initialSize.
+    blockWithArg value:inst.
+    ^ inst
+
+    "
+     |rslt|
+
+     rslt := OrderedCollection new:10 withCollectedContents:[:c | c add:'hello'; add:'world']
+    "
+!
+
 streamContents:blockWithArg
     "create a write-stream on an instance of the receiver-class,
      evaluate blockWithArg, passing that stream,
@@ -374,6 +394,26 @@
     "Created: / 29-03-2007 / 15:05:30 / cg"
 !
 
+withCollectedContents:blockWithArg
+    "create an instance of the receiver-class,
+     evaluate blockWithArg, passing that instance,
+     return the instance.
+     Similar to streamContents, but passes the collection to the block,
+     instead of a stream."
+
+    |inst|
+
+    inst := self new.
+    blockWithArg value:inst.
+    ^ inst
+
+    "
+     |rslt|
+
+     rslt := OrderedCollection withCollectedContents:[:c | c add:'hello'; add:'world']
+    "
+!
+
 writeStream
     "create a write-stream on an instance of the receiver-class"
 
--- a/UninterpretedBytes.st	Fri May 13 20:17:32 2016 +0200
+++ b/UninterpretedBytes.st	Sat May 14 09:34:43 2016 +0200
@@ -1764,10 +1764,9 @@
         __fetchBytePointerAndSize__(self, &cp, &sz);
         if (cp) {
             unsigned INT idx = ((unsigned INT)__intVal(byteIndex)) - 1;
-            char ch;
 
             if (idx < sz) {
-                ch = cp[idx] & 0xFF;
+                unsigned char ch = cp[idx] & 0xFF;
                 RETURN (__mkSmallInteger( ch ));
             }
         }
--- a/UnixFilename.st	Fri May 13 20:17:32 2016 +0200
+++ b/UnixFilename.st	Sat May 14 09:34:43 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Filename subclass:#UnixFilename
 	instanceVariableNames:''
 	classVariableNames:''
@@ -89,7 +91,9 @@
 !
 
 isCaseSensitive
-    "return true, if filenames are case sensitive.return true, if filenames are case sensitive."
+    "return true, if filenames are case sensitive.
+     This is not really correct, as the sensitivity may depend on
+     the paricular mounted file system (NFS, for example)"
 
     ^ OperatingSystem caseSensitiveFilenames
 !
@@ -226,10 +230,10 @@
 !UnixFilename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UnixFilename.st,v 1.25 2014-11-18 18:59:35 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/UnixFilename.st,v 1.25 2014-11-18 18:59:35 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/UnixOperatingSystem.st	Fri May 13 20:17:32 2016 +0200
+++ b/UnixOperatingSystem.st	Sat May 14 09:34:43 2016 +0200
@@ -4706,7 +4706,9 @@
 caseSensitiveFilenames
     "return true, if the OS has caseSensitive file naming.
      On MSDOS, this will return false;
-     on a real OS, we return true."
+     on a real OS, we return true.
+     Be aware, that some OSs can be configured to be either.
+     Also, that it actually depends on the mounted volume"
 
     "/ actually, this is wrong and may depend on the mounted volume;
     "/ so we need a query for a particular directory (and/or volume).
--- a/WriteStream.st	Fri May 13 20:17:32 2016 +0200
+++ b/WriteStream.st	Sat May 14 09:34:43 2016 +0200
@@ -551,38 +551,26 @@
 %{  /* NOCONTEXT */
 
 #ifndef NO_PRIM_STREAM
-    REGISTER int pos;
-    OBJ coll;
-    OBJ p, wL, rL;
-    int __readLimit = -1;
-
-    coll = __INST(collection);
-    p = __INST(position);
+    OBJ coll = __INST(collection);
+    OBJ p = __INST(position);
 
     if (__isNonNilObject(coll) && __isSmallInteger(p) && __isSmallInteger(anObject)) {
-        unsigned ch;
-
-        ch = __intVal(anObject);
+        OBJ wL  = __INST(writeLimit);
+        INT pos = __intVal(p) + 1;    /* make 1-based and usable for update below */
+        unsigned int ch = __intVal(anObject);
 
-        pos = __intVal(p);
-        /* make 1-based and usable for update below */
-        pos = pos + 1;
-        wL = __INST(writeLimit);
+        if (ch <= 0xFF &&  /* ch is unsigned */
+            ((wL == nil) || (__isSmallInteger(wL) && (pos <= __intVal(wL))))) {
+            OBJ cls = __qClass(coll);
+            OBJ rL = __INST(readLimit);
+            INT __readLimit = -1;
 
-        if ((wL == nil)
-         || (__isSmallInteger(wL) && (pos <= __intVal(wL)))) {
-            OBJ cls;
-
-            cls = __qClass(coll);
-
-            rL = __INST(readLimit);
             if (__isSmallInteger(rL)) {
                 __readLimit = __intVal(rL);
             }
 
             if (cls == @global(String)) {
-                if ((pos <= __stringSize(coll))
-                 && (ch <= 0xFF)) { /* ch is unsigned */
+                if (pos <= __stringSize(coll)) { 
                     __StringInstPtr(coll)->s_element[pos-1] = ch;
     advancePositionAndReturn: ;
                     if ((__readLimit >= 0) && (pos > __readLimit)) {
@@ -592,8 +580,7 @@
                     RETURN ( anObject );
                 }
             } else if (cls == @global(ByteArray)) {
-                if ((pos <= __byteArraySize(coll))
-                 && (ch <= 0xFF)) { /* ch is unsigned */
+                if (pos <= __byteArraySize(coll)) { 
                     __ByteArrayInstPtr(coll)->ba_element[pos-1] = ch;
                     goto advancePositionAndReturn;
                 }
@@ -602,7 +589,13 @@
     }
 #endif
 %}.
-    ^ super nextPutByte:anObject
+    ((writeLimit isNil or:[(position + 1) <= writeLimit])
+      and:[position >= collection size]) ifTrue:[
+        self growCollection.
+        ^ self nextPutByte:anObject.  "try again"                    
+    ] ifFalse:[
+        ^ super nextPutByte:anObject
+    ].
 !
 
 nextPutBytes:count from:anObject startingAt:start