Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 18 Nov 2016 21:28:24 +0000
branchjv
changeset 4213 739af6adeb3a
parent 4212 532eccd8b51b (current diff)
parent 4202 88ea818849fa (diff)
child 4214 5654b7964b47
Merge
BitArray.st
BooleanArray.st
IntegerArray.st
LongIntegerArray.st
Make.proto
Make.spec
SignedIntegerArray.st
SignedLongIntegerArray.st
Socket.st
UnboxedIntegerArray.st
WordArray.st
ZipArchive.st
bc.mak
libInit.cc
stx_libbasic2.st
--- a/AATree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/AATree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2009 by eXept Software AG
               All Rights Reserved
@@ -50,13 +48,24 @@
 
     Usage:
         As seen in the performance charts, AA trees offer better average and worst case
-        performance, with a lower best case performance. 
-        Thus providing a more predictable performance (within a factor of 2, as opposed to
-        a much wider range for sortedCollections)
+        performance, with a slightly lower best case performance. 
+        Thus providing a more predictable performance 
+        (within a factor of 2, as opposed to a much wider range for sortedCollections)
+
+    [instance variables:]
+        treeRoot             TreeNode        the top node
+        sortBlock            Block           sorter; 
+                                             gets two args a,b and should return true if a is
+                                             to come before b in the collection    
 
     [author:]
         Original algorithm by Arne Andersson
-        ported from wikipedia to smalltalk code by Claus Gittinger
+        ported from wikipedia to Smalltalk code by Claus Gittinger
+
+    [see also:]
+        BTree
+        SortedCollection
+        https://en.wikipedia.org/wiki/AA_tree
 "
 !
 
@@ -97,7 +106,7 @@
 
     timing 1:
                                                                 [exBegin]
-    |N randomNumbers coll1_BT coll2_AT coll3_SC t1_BT t2_AT t3_SC|
+    |N randomNumbers coll1_BT coll2_AT coll3_SC coll4_AVL t1_BT t2_AT t3_SC t4_AVL|
 
     N := 1000000.
     randomNumbers := (1 to:N) collect:[:i | Random nextInteger].
@@ -123,11 +132,20 @@
     ].
     coll3_SC := nil.
     ObjectMemory garbageCollect.
+
+    t4_AVL := Time millisecondsToRun:[
+        coll4_AVL := AVLTree new.
+        coll4_AVL addAll:randomNumbers
+    ].
+    coll4_AVL := nil.
+    ObjectMemory garbageCollect.
+
     randomNumbers := nil.
 
     Transcript show:'Time to insert random '; show:N; show:' into SortedCollection: '; show:t3_SC; showCR:'ms'.
     Transcript show:'Time to insert random '; show:N; show:' into BinaryTree: '; show:t1_BT; showCR:'ms'.
     Transcript show:'Time to insert random '; show:N; show:' into AATree: '; show:t2_AT; showCR:'ms'.
+    Transcript show:'Time to insert random '; show:N; show:' into AVLTree: '; show:t4_AVL; showCR:'ms'.
 
     ObjectMemory garbageCollect.
     t1_BT := Time millisecondsToRun:[
@@ -151,9 +169,17 @@
     coll3_SC := nil.
     ObjectMemory garbageCollect.
 
+    t4_AVL := Time millisecondsToRun:[
+        coll4_AVL := AVLTree new.
+        coll4_AVL addAll:(1 to:100000)
+    ].
+    coll4_AVL := nil.
+    ObjectMemory garbageCollect.
+
     Transcript show:'Time to insert ordered '; show:N; show:' into SortedCollection: '; show:t3_SC; showCR:'ms'.
     Transcript show:'Time to insert ordered '; show:N; show:' into BinaryTree: '; show:t1_BT; showCR:'ms'.
     Transcript show:'Time to insert ordered '; show:N; show:' into AATree: '; show:t2_AT; showCR:'ms'.
+    Transcript show:'Time to insert ordered '; show:N; show:' into AVLTree: '; show:t4_AVL; showCR:'ms'.
 
     ObjectMemory garbageCollect.
     t1_BT := Time millisecondsToRun:[
@@ -177,9 +203,17 @@
     coll3_SC := nil.
     ObjectMemory garbageCollect.
 
+    t4_AVL := Time millisecondsToRun:[
+        coll4_AVL := AVLTree new.
+        coll4_AVL addAll:(100000 downTo:1)
+    ].
+    coll4_AVL := nil.
+    ObjectMemory garbageCollect.
+
     Transcript show:'Time to insert reverse ordered '; show:N; show:' into SortedCollection: '; show:t3_SC; showCR:'ms'.
     Transcript show:'Time to insert reverse ordered '; show:N; show:' into BinaryTree: '; show:t1_BT; showCR:'ms'.
     Transcript show:'Time to insert reverse ordered '; show:N; show:' into AATree: '; show:t2_AT; showCR:'ms'.
+    Transcript show:'Time to insert reverse ordered '; show:N; show:' into AVLTree: '; show:t4_AVL; showCR:'ms'.
                                                                 [exEnd]
 
   timing 2:  
@@ -264,35 +298,52 @@
 
 performance
 "
-    Time to insert random 100000 individually into SortedCollection: 6037ms
-    Time to insert random 100000 en-bloque into SortedCollection: 172ms
-    Time to insert in order 100000 individually into SortedCollection: 31ms
-    Time to insert in order 100000 en-bloque into SortedCollection: 125ms
-    Time to insert in reverse order 100000 individually into SortedCollection: 93ms
-    Time to insert in reverse order 100000 en-bloque into SortedCollection: 125ms
-    Time to remove in random order 100000 from SortedCollection: 6380ms
-    Time to remove in order 100000 from SortedCollection: 109ms
-    Time to remove in reverse order 100000 from SortedCollection: 125ms
+    warning: the times below are very old, taken on a pentium-class machine.
+    Your times will be much shorter, so only look at the ratios.
+    
+    SortedCollection keeps the collection sorted and dense.
+    It is super fast, when adding in 'almost sorted' or almost reverse-sorted order, 
+    or when only a few elements are to be added later.
+    To create a big sorted collection, it is better to first collect them all unsorted in
+    an orderedCollection, then convert in one operation using asSortedCollection.
+
+        Time to insert random 100000 individually into SortedCollection: 6037ms
+        Time to insert random 100000 en-bloque into SortedCollection: 172ms
+        Time to insert in order 100000 individually into SortedCollection: 31ms
+        Time to insert in order 100000 en-bloque into SortedCollection: 125ms
+        Time to insert in reverse order 100000 individually into SortedCollection: 93ms
+        Time to insert in reverse order 100000 en-bloque into SortedCollection: 125ms
+        Time to remove in random order 100000 from SortedCollection: 6380ms
+        Time to remove in order 100000 from SortedCollection: 109ms
+        Time to remove in reverse order 100000 from SortedCollection: 125ms
+
+    BinaryTree (which is not balancing) degenerates to a linear list, 
+    if elements come in already sorted or reverse sorted,
+    but behaves better than AATree if they come in randomly:
 
-    Time to insert random 100000 individually into AATree: 281ms
-    Time to insert random 100000 en-bloque into AATree: 265ms
-    Time to insert in order 100000 individually into AATree: 281ms
-    Time to insert in order 100000 en-bloque into AATree: 328ms
-    Time to insert in reverse order 100000 individually into AATree: 203ms
-    Time to insert in reverse order 100000 en-bloque into AATree: 218ms
-    Time to remove in random order 100000 from AATree: 452ms
-    Time to remove in order 100000 from AATree: 312ms
-    Time to remove in reverse order 100000 from AATree: 499ms
+        Time to insert random 100000 individually into BinaryTree: 156ms
+        Time to insert random 100000 en-bloque into BinaryTree: 156ms
+        Time to insert in order 100000 individually into BinaryTree: 195921ms
+        Time to insert in order 100000 en-bloque into BinaryTree: 205266ms
+        Time to insert in reverse order 100000 individually into BinaryTree: 202271ms
+        Time to insert in reverse order 100000 en-bloque into BinaryTree: 197684ms
+        Time to remove in random order 100000 from BinaryTree: 234ms
+        Time to remove in order 100000 from BinaryTree: 78ms
+        Time to remove in reverse order 100000 from BinaryTree: 78ms
 
-    Time to insert random 100000 individually into BinaryTree: 156ms
-    Time to insert random 100000 en-bloque into BinaryTree: 156ms
-    Time to insert in order 100000 individually into BinaryTree: 195921ms
-    Time to insert in order 100000 en-bloque into BinaryTree: 205266ms
-    Time to insert in reverse order 100000 individually into BinaryTree: 202271ms
-    Time to insert in reverse order 100000 en-bloque into BinaryTree: 197684ms
-    Time to remove in random order 100000 from BinaryTree: 234ms
-    Time to remove in order 100000 from BinaryTree: 78ms
-    Time to remove in reverse order 100000 from BinaryTree: 78ms
+    AATree is slower than the best-case above (because it keeps the tre balanced), 
+    but has a much better worst case performance.
+    Thus providing a more predictable performance (all roughly within a factor of 2):
+
+        Time to insert random 100000 individually into AATree: 281ms
+        Time to insert random 100000 en-bloque into AATree: 265ms
+        Time to insert in order 100000 individually into AATree: 281ms
+        Time to insert in order 100000 en-bloque into AATree: 328ms
+        Time to insert in reverse order 100000 individually into AATree: 203ms
+        Time to insert in reverse order 100000 en-bloque into AATree: 218ms
+        Time to remove in random order 100000 from AATree: 452ms
+        Time to remove in order 100000 from AATree: 312ms
+        Time to remove in reverse order 100000 from AATree: 499ms
 "
 ! !
 
@@ -324,10 +375,10 @@
 !AATree class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/AATree.st,v 1.9 2015-04-10 06:55:43 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/AATree.st,v 1.9 2015-04-10 06:55:43 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/AVLTree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/AVLTree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -18,6 +18,8 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 SequenceableCollection subclass:#AVLTree
 	instanceVariableNames:'rootNode orderBlock'
 	classVariableNames:''
@@ -64,8 +66,23 @@
 
 documentation
 "
-    AVLTree -- balanced trees
+    AVLTree -- balanced trees.
+
+    This implements another kind of self-balancing tree, named after their inventors,
+    AVLTree is obsoleted by AATree, which has the same best/worst/average characteristics 
+    (it is also self-balancing), but is always faster (roughly by a factor of 1.5 to 2).
+    
+    Consider using an AATree instead.
+    (unless a special situation arises, of which we don't know yet)
 
+    [see also:]
+        AATree
+        BTree
+        SortedCollection
+        https://en.wikipedia.org/wiki/AVL_tree
+
+    Examples:
+    
     |t|
 
     t := AVLTree new.
@@ -109,6 +126,25 @@
     tree addAll: words.
     tree printOn:Transcript. Transcript cr; cr.
 "
+!
+
+performance
+"
+    Time to insert random 1000000 into SortedCollection: 840ms
+    Time to insert random 1000000 into BinaryTree: 2040ms
+    Time to insert random 1000000 into AATree: 3060ms
+    Time to insert random 1000000 into AVLTree: 3780ms
+    
+    Time to insert ordered 1000000 into SortedCollection: 30ms
+    Time to insert ordered 1000000 into BinaryTree: 72200ms
+    Time to insert ordered 1000000 into AATree: 110ms
+    Time to insert ordered 1000000 into AVLTree: 180ms
+
+    Time to insert reverse ordered 1000000 into SortedCollection: 30ms
+    Time to insert reverse ordered 1000000 into BinaryTree: 73880ms
+    Time to insert reverse ordered 1000000 into AATree: 80ms
+    Time to insert reverse ordered 1000000 into AVLTree: 160ms
+"
 ! !
 
 !AVLTree class methodsFor:'instance creation'!
@@ -401,5 +437,10 @@
 !AVLTree class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/AVLTree.st,v 1.2 2012-08-05 09:30:47 cg Exp $'
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
 ! !
+
--- a/AppletalkSocketAddress.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/AppletalkSocketAddress.st	Fri Nov 18 21:28:24 2016 +0000
@@ -42,7 +42,6 @@
     Instances of AppletalkSocketAddress represent appletalk socket addresses.
     These consist of a network (2 bytes), a node (1 byte) and a port number.
 
-
     [author:]
         Claus Gittinger (cg@exept)
 
--- a/AutoResizingOrderedCollection.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/AutoResizingOrderedCollection.st	Fri Nov 18 21:28:24 2016 +0000
@@ -15,9 +15,14 @@
 "
     I am an ordered collection which automatically resizes if elements
     are added beyond the size. 
-    I.e. if at:put: is sent for indexes > the current size, the receiver grows to
+    I.e. if #at:put: is sent for indexes > the current size, the receiver grows to
     the required index and missing fields are implicitly filled with nils.
     Queries for non-existing elements are anwered with nil.
+
+    [see also:]
+        OrderedCollection
+        Array
+        SparseArray
 "
 !
 
--- a/AutoResizingOrderedCollectionWithDefault.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/AutoResizingOrderedCollectionWithDefault.st	Fri Nov 18 21:28:24 2016 +0000
@@ -15,9 +15,14 @@
 "
     I am an ordered collection which automatically resizes if elements
     are added beyond the size. 
-    I.e. if at:put: is sent for indexes > the current size, the receiver grows to
+    I.e. if #at:put: is sent for indexes > the current size, the receiver grows to
     the required index and missing fields are implicitly filled with a default value.
     Queries for non-existing elements are anwered with the default value.
+
+    [see also:]
+        OrderedCollection
+        Array
+        SparseArray
 "
 !
 
--- a/BIG5EncodedString.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/BIG5EncodedString.st	Fri Nov 18 21:28:24 2016 +0000
@@ -9,9 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
+"{ Package: 'stx:libbasic2' }"
 
-"{ Package: 'stx:libbasic2' }"
+"{ NameSpace: Smalltalk }"
 
 TwoByteString variableWordSubclass:#BIG5EncodedString
 	instanceVariableNames:''
@@ -50,6 +50,7 @@
         Claus Gittinger
 
     [see also:]
+        Unicode16String
         GBEncodedString JISEncodedString 
         TwoByteString String CharacterArray
         StringCollection
@@ -130,7 +131,8 @@
 !BIG5EncodedString class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/BIG5EncodedString.st,v 1.11 2004-03-15 14:10:51 cg Exp $'
+    ^ '$Header$'
 ! !
 
+
 BIG5EncodedString initialize!
--- a/BTree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/BTree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "{ Package: 'stx:libbasic2' }"
 
 "{ NameSpace: Smalltalk }"
@@ -57,6 +55,8 @@
 
 documentation
 "
+    BTree and TSTree
+    
     A bunch of collection classes that are useful for building large indices of things. 
     It's especially geared towards people using OODBs like GOODS, but can be used it in the image too: 
     the BTree class is great for when you need to select numeric keys by range, 
@@ -706,9 +706,10 @@
 
 commonKeysWith: aNode keysAndValuesDo: aBlock flip: aBoolean
         | index key block leaf advanceKey last |
-        block := aBoolean 
-                    ifTrue: [[:k :v1 :v2 | aBlock value: k value: v2 value: v1]] 
-                    ifFalse: [aBlock].
+
+        aBoolean 
+             ifTrue: [ block := [:k :v1 :v2 | aBlock value: k value: v2 value: v1] ] 
+             ifFalse: [ block := aBlock ].
 
         index := 0.
         advanceKey :=
@@ -897,6 +898,10 @@
 
 !BTree class methodsFor:'documentation'!
 
+version
+    ^ '$Header$'
+!
+
 version_CVS
     ^ '$Header$'
 ! !
--- a/BinaryTree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/BinaryTree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -42,17 +42,19 @@
 
     WARNING:
         This tree does not reorganize itself. 
-        Thus, its performance might degenerate to that of a linked list (see performance).
-        The performance is OK, if elements are added in random order and the tree is therefore balanced.
+        Thus, its performance might degenerate to that of a linked list (see performance) when elements
+        are added in 'already sorted' or reverse order.
+        The performance is OK, if elements are added in random order and the tree is therefore more or less
+        balanced.
         The worst case is to add elements in order, reverseOrder or zig-zag order.
         Use instances of my subclasses, which balance the tree if in doubt.
 
     EXTRA WARNING:
         the inherited storeString will generate the elements in sorted order,
-        which generates exactly the generated case when read-back.
+        which generates exactly the generated worst case when read-back.
         If you use this class and need textual persistency, you should consider rewriting
         the storeOn: method, to enumerate elements in a binary segmentation fashion.
-        Otherwise, please use one of the balanced trees instead,
+        Otherwise, please use one of the self-balancing trees instead,
         for example AATree or BTree.
         
     Changes:
--- a/BitArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,522 +0,0 @@
-"{ Encoding: utf8 }"
-
-"
- COPYRIGHT (c) 1997 by eXept Software AG / Claus Gittinger
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-
- This is a demo example:
-
- THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
- SUCH DAMAGE.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-ArrayedCollection variableByteSubclass:#BitArray
-	instanceVariableNames:'tally'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!BitArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG / Claus Gittinger
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-
- This is a demo example:
-
- THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
- SUCH DAMAGE.
-"
-
-!
-
-documentation
-"
-    useful for bulk bit/boolean data 
-    Requires only 1/32th (32bit machines) or 1/64th (64bit machines) of the memory 
-    compared to an array of booleans.
-
-    This one stores 8 bits per byte. Since instances store bits in multiples
-    of 8, we have to keep the real size of the collection in an extra instance
-    variable (tally).
-    It may be useful if huge boolean arrays are to be used.
-
-    There are 10 types of people in this world: 
-        Those who understand binary, & those who don't.
-
-    ATTENTION:
-    Bits 1 to 8 of the BooleanArray are stored in bits 8 to 1 of the
-    corresponding byte, to allow easy mapping to ASN.1 BIT STRING encoding
-    in the BER. (i.e. MSB-first)
-
-    [memory requirements:]
-        OBJ-HEADER + ((size + 7) // 8)
-
-    [author:]
-        Claus Gittinger
-
-    [see also:]
-        BooleanArray ByteArray WordArray Array
-"
-!
-
-examples
-"
-                                                                        [exBegin]
-    (BitArray new:7) inspect
-                                                                        [exEnd]
-                                                                        [exBegin]
-    (BitArray new:7) basicInspect
-                                                                        [exEnd]
-                                                                        [exBegin]
-    |bits|
-
-    bits := BitArray new:1000000.
-    (bits at:9999) printCR.
-    bits at:9999 put:1.
-    (bits at:9999) printCR.
-                                                                        [exEnd]
-"
-! !
-
-!BitArray class methodsFor:'instance creation'!
-
-fromBytes:aByteArray
-    "return a new instance, capable of holding aByteArray size*8 bits, initialized from aByteArray"
-
-    |a|
-
-    a := self new: aByteArray size*8.
-    1 to:aByteArray size do:[:i | a byteAt:i put:(aByteArray at:i)].
-    ^ a
-
-    "
-     BitArray fromBytes:#[ 2r00001111 2r10101010 2r01010101]
-    "
-!
-
-new
-    "return a new instance, capable of holding size bits"
-
-    ^ self new:0
-
-    "
-     BitArray new
-    "
-!
-
-new:size
-    "return a new instance, capable of holding size bits"
-
-    |nBytes|
-
-    nBytes := (size + 7) // 8.
-    ^ (super new:nBytes) setTally:size
-
-    "
-     BitArray new:10
-    "
-!
-
-uninitializedNew:size
-    ^ self new:size
-! !
-
-!BitArray class methodsFor:'queries'!
-
-maxVal
-    "the minimum value which can be stored in instances of me.
-     For BitArrays, this is 1"
-
-    ^ 1
-!
-
-minVal
-    "the minimum value which can be stored in instances of me.
-     For BitArrays, this is 0"
-
-    ^ 0
-! !
-
-!BitArray methodsFor:'accessing'!
-
-at:index
-    "retrieve the bit at index (1..)"
-
-    |byte mask i0|
-
-    (index between:1 and:tally) ifFalse:[
-        ^ self subscriptBoundsError:index
-    ].
-    i0 := index - 1.
-    byte := super basicAt:(i0 // 8)+1.
-    mask := 1 bitShift:(7 - (i0 \\ 8)).
-    ^ (byte bitTest:mask) ifTrue:[1] ifFalse:[0]
-
-    "
-     (BitArray new:1000) at:555
-     (BitArray new:1000) at:400 put:1; at:400
-    "
-
-    "
-     |b|
-
-     b := BitArray new:1000.
-     b at:555 put:1.
-     b at:555   
-    "
-!
-
-at:index put:aNumber
-    "store the argument, aNumber at index (1..);    
-     return the argument, aNumber (sigh)."
-
-    |byte mask idx i0|
-
-    (index between:1 and:tally) ifFalse:[
-        ^ self subscriptBoundsError:index
-    ].
-
-    i0 := index - 1.
-    idx := (i0 // 8) + 1.
-    byte := super basicAt:idx.
-    mask := 1 bitShift:(7 - (i0 \\ 8)).
-    aNumber == 1 ifTrue:[
-        byte := byte bitOr:mask
-    ] ifFalse:[
-        aNumber == 0 ifTrue:[
-            byte := byte bitAnd:(mask bitInvert)
-        ] ifFalse:[
-            "/ not 0 or 1
-            ^ self elementBoundsError:aNumber
-        ]
-    ].
-    super basicAt:idx put:byte.
-    ^ aNumber.
-
-    "
-     |b|
-
-     b := BitArray new:1000.
-     b at:555 put:1.
-     b at:555    
-    "
-!
-
-byteAt:index
-    "retrieve 8 bits at index; the index is 1 for the first 8 bits, 2 for the next 8 bits etc."
-
-    ^ self basicAt:index
-
-    "
-     ((BitArray new:8) at:1 put:1); byteAt:1
-    "
-!
-
-byteAt:index put:aByte
-    "store 8 bits at index; the index is 1 for the first 8 bits, 2 for the next 8 bits etc."
-
-    ^ self basicAt:index put:aByte
-
-    "
-     ((BitArray new:8) byteAt:1 put:128); at:1     
-    "
-!
-
-occurrencesOf:anElement
-    "count the occurrences of the argument, anElement in the receiver"
-
-    |nOnes|
-
-    nOnes := self countOnes.
-    anElement == 1 ifTrue:[
-        ^ nOnes
-    ].
-    anElement == 0 ifTrue:[
-        ^ tally - nOnes
-    ].
-    ^ 0
-
-    "
-     (BitArray new:10)
-        at:4 put:1;
-        at:6 put:1;
-        at:7 put:1;
-        occurrencesOf:1 
-
-     (BitArray new:10)
-        at:4 put:1;
-        at:6 put:1;
-        at:7 put:1;
-        occurrencesOf:0    
-    "
-! !
-
-!BitArray methodsFor:'converting'!
-
-bytes
-    "answer myself as a ByteArray containing my bytes"
-
-    |size bytes|
-
-    size := self basicSize.
-    bytes := ByteArray new:size.
-    1 to:size do:[:index|
-        bytes at:index put:(self byteAt:index)
-    ].
-    ^ bytes
-! !
-
-!BitArray methodsFor:'filling & replacing'!
-
-atAllPut:aNumber
-    "replace all elements of the collection by the argument, aNumber.
-     The argument, aBoolean must be 0 or 1.
-     Notice: This operation modifies the receiver, NOT a copy;
-     therefore the change may affect all others referencing the receiver."
-
-    |v lastIndex|
-
-    lastIndex := self basicSize.
-    lastIndex == 0 ifTrue:[^ self].
-
-    aNumber == 1 ifTrue:[
-        v := 255
-    ] ifFalse:[
-        aNumber == 0 ifTrue:[
-            v := 0
-        ] ifFalse:[
-            "/
-            "/ booleanArrays can only hold true and false
-            "/
-            ^ self elementBoundsError:aNumber
-        ]
-    ].
-    1 to:lastIndex-1 do:[:i |
-        self basicAt:i put:v
-    ].
-
-    "/ ensure 0-bits above tally
-    v := #[ 2r11111111
-            2r10000000
-            2r11000000
-            2r11100000
-            2r11110000
-            2r11111000
-            2r11111100
-            2r11111110 ] at:(tally\\8)+1. 
-    self basicAt:lastIndex put:v.
-
-    "
-     ((self new:10) atAllPut:1) countOnes  
-     ((self new:8) atAllPut:1) countOnes   
-    "
-! !
-
-!BitArray methodsFor:'logical operations'!
-
-bitOr:aBitArray
-    |new mySize "{ Class: SmallInteger }" otherSize "{ Class: SmallInteger }"|
-
-    mySize := self basicSize.
-    otherSize := aBitArray basicSize.
-
-    new := self class basicNew:(mySize max:otherSize).
-    new setTally:(self size max:aBitArray size).
-
-    1 to:mySize do:[:i|
-        new basicAt:i put:(self basicAt:i).
-    ].
-    1 to:otherSize do:[:i|
-        new basicAt:i put:((new basicAt:i) bitOr:(aBitArray basicAt:i)).
-    ].
-    
-    ^ new
-
-    "
-        ((BitArray new:5) at:3 put:1; yourself) bitOr:((BitArray new:8) at:5 put:1; yourself)
-    "
-! !
-
-!BitArray methodsFor:'private'!
-
-countOnes
-    "count the 1-bits in the receiver"
-
-    |sz bI count|
-
-    count := 0.
-
-    "/ because remaining bits in the highest byte are always 0,
-    "/ we can simply count the 1-bits in ALL bytes... (see lastByte handling in atAllPut:)
-    bI := 1.
-    sz := self basicSize.
-    [bI <= sz] whileTrue:[
-        count := count + (self basicAt:bI) bitCount.
-        bI := bI + 1.
-    ].
-    ^ count
-
-"/    |i nI bI bits count|
-"/    i := bI := 1.
-"/    [
-"/        nI := i + 8.
-"/        nI <= tally
-"/    ] whileTrue:[
-"/        bits := self basicAt:bI.
-"/        count := count + bits bitCount.
-"/        bI := bI + 1.
-"/        i := nI
-"/    ].
-"/    [i <= tally] whileTrue:[
-"/        (self at:i) ifTrue:[ count := count + 1].
-"/        i := i + 1.
-"/    ].
-"/    ^ count
-
-    "
-     (BooleanArray new:100)
-        at:14 put:true; 
-        at:55 put:true; 
-        countOnes
-
-     (BooleanArray new:100)
-        at:14 put:true; 
-        at:55 put:true; 
-        occurrencesOf:true
-
-     (BooleanArray new:100)
-        at:14 put:true; 
-        at:55 put:true; 
-        occurrencesOf:false
-    "
-!
-
-indexOfNth:n occurrenceOf:what
-    "return the index of the nTh occurrence of a value, or 0 if there are not that many"
-
-    |sz byteIndex count countInByte|
-
-    n > self size ifTrue:[^ 0].
-
-    count := 0.
-
-    byteIndex := 1.
-    sz := self basicSize.
-    [byteIndex <= sz] whileTrue:[
-        countInByte := (self basicAt:byteIndex) bitCount.
-        what = self defaultElement ifTrue:[
-            countInByte := 8-countInByte.
-        ].
-        count := count + countInByte.
-        count >= n ifTrue:[
-            count := count - countInByte.
-            (byteIndex-1)*8+1 to:(byteIndex-1)*8+8 do:[:bitIndex |
-                (self at:bitIndex) = what ifTrue:[
-                    count := count + 1.
-                    count = n ifTrue:[
-                        ^ bitIndex.
-                    ]
-                ].
-            ].
-            ^ 0
-        ].
-        byteIndex := byteIndex + 1.
-    ].
-    ^ 0
-
-    "
-     (BooleanArray new:100)
-        at:1 put:true;
-        at:2 put:true;
-        at:4 put:true;
-        at:5 put:true;
-        at:6 put:true;
-        at:7 put:true;
-        at:8 put:true;
-        at:10 put:true;
-        indexOfNth:8 occurrenceOf:false
-    "
-!
-
-setTally:size
-    "set my tally - that is the actual number of bits in me
-     (usually a little less than the number of bits in my byte array)"
-
-    tally := size
-! !
-
-!BitArray methodsFor:'queries'!
-
-defaultElement
-    ^ 0
-!
-
-isValidElement:anObject
-    "return true, if I can hold this kind of object"
-
-    ^ anObject == 0 or:[anObject == 1]
-!
-
-size
-    "return the size of the receiver"
-
-    ^ tally
-! !
-
-
-!BitArray methodsFor:'visiting'!
-
-acceptVisitor:aVisitor with:aParameter
-    "dispatch for visitor pattern; send #visitBitArray:with: to aVisitor"
-
-    ^ aVisitor visitBitArray:self with:aParameter
-! !
-
-!BitArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/BooleanArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,228 +0,0 @@
-"{ Encoding: utf8 }"
-
-"
- COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-
- This is a demo example:
-
- THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
- SUCH DAMAGE.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-BitArray variableByteSubclass:#BooleanArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!BooleanArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-
- This is a demo example:
-
- THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
- SUCH DAMAGE.
-"
-!
-
-documentation
-"
-    This is a simple demo class only; currently not used in the system.
-
-    example for bulk boolean data (requires only 1/32th the memory
-    compared to an array of booleans).
-
-    This one stores 8 booleans per byte. Since instances store bits in multiples
-    of 8, we have to keep the real size of the collection in an extra instance
-    variable (tally).
-    It may be useful if huge boolean arrays are to be used.
-
-    Bits 1 to 8 of the BooleanArray are stored in bits 8 to 1 of the
-    corresponding byte, to allow easy mapping to ASN.1 BIT STRING encoding
-    in the BER.
-
-    [memory requirements:]
-        OBJ-HEADER + ((size + 7) // 8)
-
-    [see also:]
-        ByteArray WordArray Array
-
-    [author:]
-        Claus Gittinger
-"
-!
-
-examples
-"
-                                                                        [exBegin]
-    (BooleanArray new:7) inspect
-                                                                        [exEnd]
-                                                                        [exBegin]
-    (BooleanArray new:7) basicInspect
-                                                                        [exEnd]
-                                                                        [exBegin]
-    |flags|
-
-    flags := BooleanArray new:1000000.
-    (flags at:9999) printNL.
-    flags at:9999 put:true.
-    (flags at:9999) printNL.
-                                                                        [exEnd]
-"
-! !
-
-!BooleanArray methodsFor:'accessing'!
-
-at:index
-    "retrieve the boolean at index"
-
-    ^ (super at:index) == 1
-
-    "
-     (BooleanArray new:1000) at:555
-    "
-
-    "
-     |b|
-
-     b := BooleanArray new:1000.
-     b at:555 put:true.
-     b at:555   
-    "
-
-    "Modified: / 31.7.1997 / 18:37:25 / cg"
-    "Modified: / 23.5.1999 / 20:02:57 / stefan"
-!
-
-at:index put:aBoolean
-    "store the argument, aBoolean at index; return aBoolean (sigh)."
-
-    |v|
-
-    aBoolean == true ifTrue:[
-        v := 1.
-    ] ifFalse:[
-        aBoolean == false ifTrue:[
-            v := 0.
-        ] ifFalse:[
-            "/ not true or false
-            ^ self elementBoundsError:aBoolean
-        ]
-    ].
-    super at:index put:v.
-    ^ aBoolean
-
-    "
-     |b|
-
-     b := BooleanArray new:1000.
-     b at:555 put:true.
-     b at:555   
-    "
-!
-
-occurrencesOf:anElement
-    "count the occurrences of the argument, anElement in the receiver"
-
-    |nOnes|
-
-    nOnes := self countOnes.
-    anElement == true ifTrue:[
-        ^ nOnes
-    ].
-    anElement == false ifTrue:[
-        ^ tally - nOnes
-    ].
-    ^ 0
-
-    "
-     (BooleanArray new:10)
-        at:4 put:true;
-        at:6 put:true;
-        at:7 put:true;
-        occurrencesOf:true
-    "
-! !
-
-!BooleanArray methodsFor:'filling & replacing'!
-
-atAllPut:aBoolean
-    "replace all elements of the collection by the argument, aBoolean.
-     The argument, aBoolean must be true or false.
-     Notice: This operation modifies the receiver, NOT a copy;
-     therefore the change may affect all others referencing the receiver."
-
-    |v|
-
-    aBoolean == true ifTrue:[
-        v := 1
-    ] ifFalse:[
-        aBoolean == false ifTrue:[
-            v := 0
-        ] ifFalse:[
-            "/ booleanArrays can only hold true and false
-            ^ self elementBoundsError:aBoolean
-        ]
-    ].
-    super atAllPut:v
-! !
-
-!BooleanArray methodsFor:'queries'!
-
-defaultElement
-    ^ false
-!
-
-isValidElement:anObject
-    "return true, if I can hold this kind of object"
-
-    ^ anObject == true or:[anObject == false]
-! !
-
-!BooleanArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
-
--- a/CacheDictionary.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/CacheDictionary.st	Fri Nov 18 21:28:24 2016 +0000
@@ -38,11 +38,17 @@
 
 documentation
 "
-    a CacheDictionary is a Dictionary which will not grow - i.e. keep
-    only a limited number of elements.
+    a CacheDictionary is a Dictionary which will not grow beyond a given max. size
+    - i.e. keep only a limited number of elements.
     It can be used as a cache, for keeping recently used objects alive.
-    Must be created with an initial (=maximal) size. I.e. (CacheDictionary new:100)
+    Must be created with an initial (=maximal) size. 
+    I.e. (CacheDictionary new:100)
 
+    [see also:]
+        Dictionary
+        OrderedCollection
+        OrderedDictionary
+        
     [author:]
         Claus Gittinger
 "
--- a/CacheDictionaryWithFactory.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/CacheDictionaryWithFactory.st	Fri Nov 18 21:28:24 2016 +0000
@@ -38,18 +38,19 @@
 
 documentation
 "
-    like a Dictionary, but does not grow (i.e. only keeps size items),
-    and also keeps a factoryBlock to automatically compute missing elements.
+    like a Dictionary, but does not grow beyond a given max. size
+    (i.e. only keeps size items),
+    It can be used as a cache, for keeping recently used objects alive.
+    Must be created with an initial (=maximal) size. 
+    In addition to the normal CacheDictionary, 
+    this also keeps a factoryBlock to automatically compute missing elements.
 
     [author:]
         Claus Gittinger (cg@alan)
 
-    [instance variables:]
-
-    [class variables:]
-
     [see also:]
-
+        CacheDictionary
+        Dictionary
 "
 !
 
--- a/Cons.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Cons.st	Fri Nov 18 21:28:24 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 SequenceableCollection subclass:#Cons
 	instanceVariableNames:'car cdr'
 	classVariableNames:''
@@ -37,9 +39,6 @@
 documentation
 "
     A pair as in lisp.
-    Create with:
-        a !! b
-    or:
         Cons car:a cdr:b
 
     Conses are not heavily used by Smalltalk (actually: not at all).
@@ -150,20 +149,20 @@
 !
 
 readLispFrom:aStream
-    aStream skipSeparators.
-    aStream atEnd ifTrue:[^ nil].
+    [
+        aStream skipSeparators.
+        aStream atEnd ifTrue:[^ nil].
 
-    aStream peek ==$; ifTrue:[
-        "/ comment
+        aStream peek ==$; ifFalse:[
+            aStream peek ==$( ifTrue:[
+                ^ self readLispListFrom:aStream
+            ].
+            ^ self readLispAtomFrom:aStream
+        ].
+        "/ EOL comment
         aStream skipLine.
-        thisContext restart
-    ].
-
-    aStream peek ==$( ifTrue:[
-        ^ self readLispListFrom:aStream
-    ].
-    ^ self readLispAtomFrom:aStream
-
+    ] loop
+    
     "
      self readLispFrom:('(cons 1 2)' readStream).
     "
@@ -713,10 +712,10 @@
 !Cons class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/Cons.st,v 1.25 2014-06-25 17:19:00 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/Cons.st,v 1.25 2014-06-25 17:19:00 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/EpsonFX1PrinterStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/EpsonFX1PrinterStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -55,6 +55,7 @@
         It may need to be enhanced at some places (for example: provide more
         fonts/emphasis's; better international character translation etc.)
 
+    [Disclaimer:]    
         This class is not officially supported - take it or leave it.
 
     [author:]
--- a/FileURI.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/FileURI.st	Fri Nov 18 21:28:24 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 HierarchicalURI subclass:#FileURI
 	instanceVariableNames:''
 	classVariableNames:''
@@ -55,20 +57,23 @@
 asFilename
     "answer the receiver represented as filename"
 
-    ^ authority notNil ifTrue:[
+    ^ authority notEmptyOrNil ifTrue:[
         Filename remoteHost:authority rootComponents:pathSegments.
     ] ifFalse:[
-        "kludge"
-        (pathSegments first startsWith:$~) ifTrue:[
-            pathSegments first asFilename construct:(Filename rootComponents:(pathSegments copyFrom:2)).
+        isAbsolute ifTrue:[
+            Filename rootComponents:pathSegments.
         ] ifFalse:[
-            Filename rootComponents:pathSegments.
+            Filename fromComponents:pathSegments.
         ].
     ].
 
     "
-        (URI fromString:'file:~/bla') asFilename
-        (URI fromString:'file:~root/bla') asFilename 
+        (URI fromString:'file:///dir/file') asFilename
+        (URI fromString:'file:///C:dir/file') asFilename
+        (URI fromString:'file:///C:/dir/file') asFilename
+        (URI fromString:'file:///~/bla') asFilename
+        (URI fromString:'file:///~root/bla') asFilename 
+        (URI fromString:'file:////host/dir/file') asFilename 
     "
 ! !
 
@@ -77,29 +82,37 @@
 fromFilename:aFilename
     "create an URI based on an a filename"
 
-    |components|
+    |volume|
 
-    components := aFilename components.
+    pathSegments := aFilename components.
     aFilename isAbsolute ifTrue:[
-        (components size > 3 and:[(components at:2) size == 0]) ifTrue:[
+        (pathSegments notEmpty and:[pathSegments first startsWith:'\\']) ifTrue:[
             "this is a MS-Windows network path: \\host\path"
-            authority := components at:3.
-            pathSegments := components copyFrom:4.
+            isAbsolute := false. "there are already enogh / in the first pathComponent"
+            pathSegments at:1 put:(pathSegments first replaceAll:$\ with:$/).
         ] ifFalse:[
             "this is an absolute path"
             isAbsolute := true.
-            pathSegments := components copyFrom:2.
+            volume := aFilename volume.
+            volume notEmpty ifTrue:[
+                pathSegments at:1 put:volume.
+            ].
         ].
     ] ifFalse:[
         "this is a relative path"
         isAbsolute := false.
-        pathSegments := components.
     ]
 
     "
       self fromFilename:'/a/b/c'  asFilename   
       self fromFilename:'//a/b/c' asFilename  
       self fromFilename:'a/b/c'   asFilename    
+
+      self fromFilename:'\a\b\c'  asFilename   
+      self fromFilename:'~user\a\b\c'  asFilename   
+      self fromFilename:'C:\a\b\c'  asFilename   
+      self fromFilename:'\\a\b\c'  asFilename 
+      self fromFilename:'a\b\c'   asFilename    
     "
 ! !
 
@@ -352,10 +365,10 @@
 !FileURI class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/FileURI.st,v 1.18 2014-12-02 14:22:43 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/FileURI.st,v 1.18 2014-12-02 14:22:43 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/FilteringStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/FilteringStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1996 by Claus Gittinger
 	      All Rights Reserved
@@ -404,6 +402,10 @@
 
 !FilteringStream methodsFor:'misc'!
 
+clearEOF
+    ^ inputStream clearEOF
+!
+
 close
     "when I am closed, close my input - if any"
 
--- a/HPLjetIIPrinterStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/HPLjetIIPrinterStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libbasic2' }"
 
-"{ Package: 'stx:libbasic2' }"
+"{ NameSpace: Smalltalk }"
 
 PrinterStream subclass:#HPLjetIIPrinterStream
 	instanceVariableNames:''
@@ -51,6 +52,7 @@
         fonts/emphasis's, better international character translation,
         image printing etc.)
 
+    [Disclaimer:]    
         This class is not officially supported - take it or leave it.
 
     [author:]
@@ -152,7 +154,8 @@
 !HPLjetIIPrinterStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/HPLjetIIPrinterStream.st,v 1.18 2006-08-07 13:26:59 fm Exp $'
+    ^ '$Header$'
 ! !
 
+
 HPLjetIIPrinterStream initialize!
--- a/HierarchicalURI.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/HierarchicalURI.st	Fri Nov 18 21:28:24 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 URI subclass:#HierarchicalURI
 	instanceVariableNames:'authority isAbsolute isDirectory pathSegments query fragment'
 	classVariableNames:''
@@ -334,7 +336,6 @@
 !HierarchicalURI methodsFor:'initialization'!
 
 fromString:aString
-
     |i i1 separator|
 
     (aString startsWith:'//') ifTrue:[
@@ -346,7 +347,7 @@
             separator := aString at:i.
             authority := aString copyFrom:3 to:i-1.
         ].
-        (isAbsolute := (aString at:i) == $/).
+        isAbsolute := (aString at:i) == $/.
     ] ifFalse:[
         (isAbsolute := aString startsWith:$/) ifTrue:[
             i := 1.
@@ -478,8 +479,8 @@
      characters"
 
     super printOn:aStream.
-    authority notNil ifTrue: [
-        aStream nextPutAll:'//'.
+    aStream nextPutAll:'//'.
+    authority notNil ifTrue:[
         doEscape ifTrue:[
             self class escape:authority allow:'~$,;:@&=+' on:aStream
         ] ifFalse:[
@@ -598,5 +599,6 @@
 !HierarchicalURI class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/HierarchicalURI.st,v 1.15 2008-05-15 13:32:05 mb Exp $'
+    ^ '$Header$'
 ! !
+
--- a/IntegerArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,216 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-UnboxedIntegerArray variableLongSubclass:#IntegerArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!IntegerArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    IntegerArrays store integers in the range 0..16rFFFFFFFF.
-    In contrast to normal arrays (which store pointers to their elements),
-    integerArrays store the values in a dense & compact way. 
-    Since the representation fits the underlying C-language systems representation
-    of unsigned int32's, this is also useful to pass bulk data to c primitive code.
-
-    [memory requirements:]
-        OBJ-HEADER + (size * 4)
-
-    [see also:]
-        ByteArray BooleanArray FloatArray DoubleArray Array
-        SignedWordArray WordArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!IntegerArray class methodsFor:'queries'!
-
-elementByteSize
-    "for bit-like containers, return the number of bytes stored per element.
-     Here, 4 is returned"
-
-    ^ 4
-
-    "Created: / 15-09-2011 / 14:12:15 / cg"
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me"
-
-    ^ 16rFFFFFFFF
-!
-
-minVal
-    "the minimum value which can be stored in instances of me"
-
-    ^ 0
-! !
-
-!IntegerArray methodsFor:'accessing'!
-
-unsignedInt32At:index MSB:msb
-    "return the 4-bytes starting at index as an (unsigned) Integer.
-     The index is a smalltalk index (i.e. 1-based).
-     The value is retrieved MSB (high 8 bits at lower index) if msb is true;
-     LSB-first (i.e. low 8-bits at lower byte index) if its false.
-     Notice: 
-        the index is a byte index; thus, this allows for unaligned access to
-        words on any boundary.
-     Question: should it be retrieve signed values ? (see ByteArray>>signedWordAt:)"
-
-    |w|
-
-    (index bitAnd: 16r03) == 1 ifTrue:[
-        "/ aligned fetch
-        w := self at:(index // 4) + 1.
-        (msb ~~ UninterpretedBytes isBigEndian) ifTrue:[
-            w := w swapBytes
-        ].    
-        ^ w
-    ].
-    ^ super unsignedInt32At:index MSB:msb
-
-    "
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:1 MSB:false 
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:5 MSB:false
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:9 MSB:false
-
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:2 MSB:false
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:3 MSB:false
-     #(16r0201 16r0403 16r0605) asIntegerArray unsignedInt32At:4 MSB:false
-
-     #(16rFFEE 16r0403 16r0605) asIntegerArray unsignedInt32At:1 MSB:false
-     #(16rFFEE 16r0403 16r0605) asIntegerArray unsignedInt32At:1 MSB:true
-    "
-! !
-
-!IntegerArray methodsFor:'comparing'!
-
-< anIntegerArray
-    "Compare the receiver with the argument and return true if the
-     receiver is greater than the argument. Otherwise return false.
-
-     Redefined for speed (xpath handling)"
-
-%{  /* NOCONTEXT */
-
-    int len1, len2, min, i;
-    REGISTER OBJ s = anIntegerArray;
-    unsigned int *ip1, *ip2;
-    OBJ cls;
-    OBJ myCls;
-
-    if (__isNonNilObject(s)) {
-        cls = __qClass(s);
-        myCls = __qClass(self);
-
-        if ((cls == IntegerArray) || (cls == myCls)) {
-            ip2 = __integerArrayVal(s);
-            len2 = __integerArraySize(s);
-            /*
-             * care for instances of subclasses ...
-             */
-            if (cls != IntegerArray) {
-                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars)) / sizeof(__integerArrayVal(s));
-
-                ip2 += n;
-                len2 -= n;
-            }
-
-            ip1 = __integerArrayVal(self);
-            len1 = __integerArraySize(self);
-            /*
-             * care for instances of subclasses ...
-             */
-            if (myCls != IntegerArray) {
-                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(myCls)->c_ninstvars)) / sizeof(__integerArrayVal(s));
-
-                ip1 += n;
-                len1 -= n;
-            }
-
-            if (len1 <= len2)
-                min = len1;
-            else
-                min = len2;
-
-            for (i = 0; i < min; i++) {
-                if (ip1[i] < ip2[i]) {
-                    RETURN(true)
-                }
-                if (ip1[i] > ip2[i]) {
-                    RETURN(false)
-                }
-            }
-
-            if (len1 < len2) {
-                RETURN ( true );
-            }
-            RETURN ( false );
-        }
-    }
-%}.
-    ^ super < anIntegerArray
-
-
-    "
-        (IntegerArray newFrom:#[1 2 3 4 5]) < (IntegerArray newFrom:#[1 2 3 4 5])
-        (IntegerArray newFrom:#[1 2 3 4 5]) < (IntegerArray newFrom:#[1 2 3 4])
-        (IntegerArray newFrom:#[1 2 3 4]) < (IntegerArray newFrom:#[1 2 3 4 5])
-        (IntegerArray newFrom:#[1 2 3 4 5]) < (IntegerArray newFrom:#[1 2 3 4 6])
-        (IntegerArray newFrom:#[]) < (IntegerArray newFrom:#[1 2 3 4 6])
-    "
-! !
-
-!IntegerArray methodsFor:'converting'!
-
-asIntegerArray
-    "return a new IntegerArray with the collection's elements.
-     That's the receiver itself here"
-
-    ^ self.
-! !
-
-!IntegerArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/JISEncodedString.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/JISEncodedString.st	Fri Nov 18 21:28:24 2016 +0000
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libbasic2' }"
 
-"{ Package: 'stx:libbasic2' }"
+"{ NameSpace: Smalltalk }"
 
 TwoByteString variableWordSubclass:#JISEncodedString
 	instanceVariableNames:''
@@ -175,7 +176,7 @@
         char := aString at:idx.
         ((code := char codePoint) bitAnd:16rFF00) == 16r8E00 ifTrue:[
             cell := code bitAnd:16rFF.
-            (cell >= 16r21 and:[cell <= 16r5F]) ifTrue:[
+            (cell between:16r21 and:16r5F) ifTrue:[
                 newString isNil ifTrue:[
                     newString := JISEncodedString fromString:aString
                 ].
@@ -242,7 +243,8 @@
 !JISEncodedString class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/JISEncodedString.st,v 1.24 2004-03-15 14:10:57 cg Exp $'
+    ^ '$Header$'
 ! !
 
+
 JISEncodedString initialize!
--- a/KeywordInContextIndexBuilder.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/KeywordInContextIndexBuilder.st	Fri Nov 18 21:28:24 2016 +0000
@@ -11,8 +11,11 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#KeywordInContextIndexBuilder
-	instanceVariableNames:'keywordToLinesMapping excluded separatorAlgorithm'
+	instanceVariableNames:'keywordToLinesMapping excluded separatorAlgorithm
+		unquoteAlgorithm exclusionFilter matchSorter'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Collections-Support'
@@ -36,50 +39,88 @@
 
 documentation
 "
-    A support class for building a KWIC (Keyword in Context) index.
-    (for example, to build a KWIC index on html pages or class documentation).
+    A support class for building KWIC (Keyword in Context) or KWOC (Keyword out of Context) indexes.
+    (for example, to build such indexes on html pages or class documentation).
+    
     To generate a kwic, add each line together with a reference (or page number, or whatever),
     using addLine:reference:.
-    Then, when finished, enumerate the kwic.
+    Then, when finished, enumerate the kwic and print as kwic or kwoc.
+    
+    To ignore fill words (such as 'and', 'the', 'in', etc.), 
+    define those with the #excluded: messages.
+
+    The keyword handling is configurable by providing actions/lists for:
+        separatorAlgorithm      a block which separates lines into individual words
+                                gets a line; delivers a collection of words
+
+        excluded                a collection of words which are to be ignored
 
+        unquoteAlgorithm        a block to remove quotes around words. 
+                                gets word as argument, delivers unquoted word
+
+        keywordMappingAlgorithm 
+                                maps keywords; for example, can be used to map 'startsWith'
+                                to 'start', so they appear in the same section.
+                                Gets the word and the set-of-all-words as arguments,
+                                delivers the key into which the word's entries should be placed  
+                                
+        matchSorter             determines the order in which keywords are listed
+        
     [author:]
         Claus Gittinger (cg@alan)
 
-    [instance variables:]
-
-    [class variables:]
+    [examples:]
+        see examples method
 
     [see also:]
-
+        https://en.wikipedia.org/wiki/Key_Word_in_Context (english)
+        https://de.wikipedia.org/wiki/Permutiertes_Register (german)
+        
 "
 !
 
 examples
 "
+    building a kwic; print as kwic and kwoc
                                                                 [exBegin]
     |kwic|
 
     kwic := KeywordInContextIndexBuilder new.
-    kwic excluded:#('the' 'and' 'a' 'an').
+    kwic excluded:#('the' 'and' 'a' 'an' 'in').
 
     kwic addLine:'bla bla bla' reference:1.
-    kwic addLine:'one two three' reference:2.
-    kwic addLine:'a cat and a dog' reference:3.
-    kwic addLine:'the man in the middle' reference:4.
-    kwic addLine:'the man with the dog' reference:5.
+    kwic addLine:'foo, bar. baz' reference:2.
+    kwic addLine:'one two three' reference:3.
+    kwic addLine:'a cat and a dog' reference:4.
+    kwic addLine:'the man in the middle' reference:5.
+    kwic addLine:'the man with the dog' reference:6.
 
+    Transcript showCR:'Printed as KWIC:'.
     kwic 
         entriesDo:[:word :left :right :ref |
             Transcript 
                 show:((left contractTo:20) leftPaddedTo:20);
                 space;
-                show:((word contractTo:10) leftPaddedTo:10);
+                show:((word contractTo:10) leftPaddedTo:10) allBold;
                 space;
                 show:((right contractTo:20) leftPaddedTo:20);
                 space;
                 show:'['; show:ref; show:']';
                 cr    
         ].
+
+    Transcript cr.
+    Transcript showCR:'Printed as KWOC:'.
+    kwic 
+        entriesDo:[:word :left :right :ref :fullText :context |
+            Transcript 
+                show:((word contractTo:10) paddedTo:10) allBold;
+                space;
+                show:((context contractTo:60) paddedTo:60);
+                space;
+                show:'['; show:ref; show:']';
+                cr    
+        ].
                                                                 [exEnd]
 
 
@@ -127,7 +168,7 @@
 
   KWIC index over method comments:
                                                                 [exBegin]
-    |kwic|
+    |kwic v s c refs list|
 
     kwic := KeywordInContextIndexBuilder forMethodComments.
 
@@ -152,7 +193,7 @@
             ]
         ]
     ].
-    kwic
+    kwic.
                                                                 [exEnd]
 
   KWIC index over class comments:
@@ -222,9 +263,9 @@
                                         w nextPut:(frag last).
                                         keyWords add:(frag allButLast).
                                     ] ifFalse:[
-                                       ' frag := w contents.
-                                        w := '' writeStream.
-                                        keyWords add:frag. '.
+                                       "/ frag := w contents.
+                                       "/ w := '' writeStream.
+                                       "/ keyWords add:frag.
                                     ].
                                 ].
                             ].
@@ -255,52 +296,131 @@
 
 !KeywordInContextIndexBuilder methodsFor:'accessing'!
 
-excluded:something
-    excluded := something asSet.
+excluded:aListOfExcludedWords
+    "define words which are to be ignored.
+     Typically, this is a list of fillwords, such as 'and', 'the', 'in', etc."
+     
+    excluded := aListOfExcludedWords asSet.
+!
+
+exclusionFilter:aBlock
+    "define an additional filter to exclude more complicated patterns.
+     This is invoked after filtering by the exclusion list.
+     If defined, this should return true,if the word is to be excluded."
+     
+    exclusionFilter := aBlock.
 !
 
-separatorAlgorithm:something
-    separatorAlgorithm := something.
+matchSorter:aSortBlock
+    "if set, matches will be enumerated in that sort order."
+    
+    matchSorter := aSortBlock.
+!
+
+separatorAlgorithm:aBlock
+    "define the algorithm to split a given string into words.
+     The default is to split at punctuation and whitespace
+     (see #initialize)"
+     
+    separatorAlgorithm := aBlock.
+!
+
+unquoteAlgorithm:aBlock
+    "define the algorithm to unquote words.
+     The default is to unquote single and double quotes
+     (see #initialize)"
+     
+    unquoteAlgorithm := aBlock.
 ! !
 
 !KeywordInContextIndexBuilder methodsFor:'building'!
 
 addLine:aLine reference:opaqueReference
     "add a text line; the line is split at words and entered into the kwic.
-     the reference argument is stored as 'value' of the generated entries"
+     The reference argument is stored as 'value' of the generated entries.
+     It can be anything"
 
-    self addLine:aLine reference:opaqueReference ignoreCase:false
+    self addLine:aLine reference:opaqueReference ignoreCase:true
 !
 
 addLine:aLine reference:opaqueReference ignoreCase:ignoreCase
-    (separatorAlgorithm value:aLine) do:[:eachWord |
+    "add a line to the kwic.
+     The line is split up into words, and a reference to opaqueReference
+     is added for each word.
+     The reference argument is stored as 'value' of the generated entries;
+     it can be anything"
+     
+    (separatorAlgorithm value:aLine optionalArgument:keywordToLinesMapping) do:[:eachWord |
         |set word|
 
-        ignoreCase ifTrue:[
-            word := eachWord asLowercase.
-        ] ifFalse:[
-            word := eachWord asLowercase.
-        ].
-        (excluded includes:word) ifFalse:[
-            set := keywordToLinesMapping at:word ifAbsent:nil.
-            set isNil ifTrue:[
-                set := Set new.
-                keywordToLinesMapping at:word put:set
+        (excluded includes:eachWord) ifFalse:[
+            word := unquoteAlgorithm value:eachWord.
+            ignoreCase ifTrue:[
+                word := word asLowercase.
             ].
-            set add:(aLine -> opaqueReference).
+            (excluded includes:word) ifFalse:[
+                (exclusionFilter isNil or:[ (exclusionFilter value:word) not]) ifTrue:[
+                    set := keywordToLinesMapping at:word ifAbsentPut:[Set new].
+                    set add:(aLine -> opaqueReference).
+                ]
+            ]
         ]
     ].
+!
+
+remapKeywordsWith:keywordMappingAlgorithm 
+    "allows for an additional mapper to be applied (after the kwic has been constructed).
+     This can map multiple different words to the same keword.
+     It is given the word and the set of already known words as argument.
+     It may, for example figure out that a word with a long prefix is already in the
+     list and decide, that a new word should be brought into the same bucket.
+     For example, if 'starts' is already in the list, and 'startWith' is encountered."
+
+    |knownKeys|
+    
+    knownKeys := keywordToLinesMapping keys copy.
+    knownKeys do:[:kw |
+        |mappedWord oldSet newSet|
+
+        mappedWord := keywordMappingAlgorithm value:kw optionalArgument:knownKeys.
+        mappedWord ~= kw ifTrue:[
+            oldSet := keywordToLinesMapping at:kw ifAbsent:[nil].
+            oldSet notNil ifTrue:[
+                newSet := keywordToLinesMapping at:mappedWord ifAbsentPut:[Set new].
+                oldSet do:[:eachEntry |
+                    newSet add:eachEntry.
+                ].
+                keywordToLinesMapping removeKey:kw.
+            ]    
+        ]    
+    ].
 ! !
 
 !KeywordInContextIndexBuilder methodsFor:'enumerating'!
 
-entriesDo:aFourArgBlock
-    "evaluate the argument, aFourArgBlock for each triple of kwic-word, left-text, right text and reference"
+entriesDo:aFourToSixArgBlock
+    "evaluate the argument, for each entry.
+     If it is a 4-arg block, it is called with:
+        kwic-word, 
+        left-text, 
+        right text 
+        and reference
+     If it is a 5-arg block, the original text is passed as additional argument.
+     If it is a 6-arg block, the original text and the context are passed as additional argument.
+     (stupid, but done for backward compatibility)"
 
+    |fourArgBlock|
+
+    aFourToSixArgBlock numArgs == 4 ifTrue:[
+        fourArgBlock := aFourToSixArgBlock 
+    ].    
     keywordToLinesMapping keys asSortedCollection do:[:eachKey |
         |setOfMatches lcKey|
 
         setOfMatches := keywordToLinesMapping at:eachKey.
+        matchSorter notNil ifTrue:[
+            setOfMatches := setOfMatches asSortedCollection:matchSorter
+        ].    
         lcKey := eachKey asLowercase.
         setOfMatches do:[:eachAssoc |
             |text ref lines idx lIdx context left right word prevLine nextLine|
@@ -324,7 +444,11 @@
                 left := (context copyTo:lIdx - 1) withoutSeparators.
                 right := (context copyFrom:lIdx + lcKey size) withoutSeparators.
                 word := (context copyFrom:lIdx to:lIdx + lcKey size - 1) withoutSeparators.
-                aFourArgBlock value:word value:left value:right value:ref.
+                fourArgBlock notNil ifTrue:[
+                    fourArgBlock value:word value:left value:right value:ref.
+                ] ifFalse:[
+                    aFourToSixArgBlock value:word optionalArgument:left and:right and:ref and:text and:context
+                ].    
             ].
         ]
     ]
@@ -334,17 +458,19 @@
 
 initialize
     keywordToLinesMapping := Dictionary new.
-    excluded := Set new.
-    separatorAlgorithm := [:line | line asCollectionOfSubstringsSeparatedByAny:' .:,;-'].
+    self excluded:(Set new).
+    self exclusionFilter:nil.
+    self separatorAlgorithm:[:line | line asCollectionOfSubstringsSeparatedByAny:' .:,;-'].
+    self unquoteAlgorithm:[:word | (word unquote:$") unquote:$' ].
 ! !
 
 !KeywordInContextIndexBuilder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/KeywordInContextIndexBuilder.st,v 1.3 2014-02-25 07:19:54 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/KeywordInContextIndexBuilder.st,v 1.3 2014-02-25 07:19:54 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/LazyArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/LazyArray.st	Fri Nov 18 21:28:24 2016 +0000
@@ -20,7 +20,9 @@
 
 documentation
 "
-    An Array which computes its value lazily (on demand) and remembers those values.
+    An Array which computes its values lazily (on demand) and remembers them.
+    Useful if it is relatively expensive to compute an element, 
+    and it may be needed again later.
 
     [author:]
         Claus Gittinger (cg@alan)
--- a/LineNumberReadStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/LineNumberReadStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1996 by eXept Software AG
 	      All Rights Reserved
@@ -191,6 +189,14 @@
 
 !LineNumberReadStream methodsFor:'reading'!
 
+contents
+    ^ inputStream contents
+!
+
+contentsAsString
+    ^ inputStream contentsAsString
+!
+
 upToAll_positionBefore:aCollection
     "read until a subcollection consisting of the elements in aCollection is encountered.
      Return everything read excluding the elements in aCollection.
@@ -225,10 +231,10 @@
 !LineNumberReadStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/LineNumberReadStream.st,v 1.12 2015-04-22 18:07:41 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/LineNumberReadStream.st,v 1.12 2015-04-22 18:07:41 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/List.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/List.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1996 by eXept Software AG
               All Rights Reserved
@@ -54,6 +52,17 @@
     It has been mostly provided, for ST-80 compatibility,
     where it adds sorting capabilities.
 
+    [caveat:]
+        'List' is probably a bad name, which may confuse beginners.
+        I have nothing in common with LinkedLists.
+        Instances are just regular ordered collections, with the added benefit of
+        sending out information about changes.
+        Thus, they can be used as a model of textviews or selection list views,
+        which need to redraw whenever the contents of the list changes.
+        (and Lists not only send out change notifications when modified,
+         but also include information about the range of changed elements.
+         So the view can optimize its redraws)
+        
     [see also:]
         Array OrderedCollection
 
--- a/LongIntegerArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,97 +0,0 @@
-"
- COPYRIGHT (c) 1998 by Claus Gittinger / eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-UnboxedIntegerArray variableLongLongSubclass:#LongIntegerArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!LongIntegerArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1998 by Claus Gittinger / eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    LongIntegerArrays store 64bit unsigned integers in the range 
-    0..16rFFFFFFFFFFFFFFFF.
-    In contrast to normal arrays (which store pointers to their elements),
-    longIntegerArrays store the values in a dense & compact way. 
-    Since the representation fits the underlying C-language systems representation
-    of unsigned longlong's, this is also useful to pass bulk data to c primitive code.
-    (the system makes certain, that the first longlong is aligned as required)
-
-    [memory requirements:]
-        OBJ-HEADER + (size * 8)
-
-    [see also:]
-        ByteArray BooleanArray FloatArray DoubleArray Array
-        WordArray SignedWordArray IntegerArray SignedIntegerArray
-        SignedLongIntegerArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!LongIntegerArray class methodsFor:'queries'!
-
-elementByteSize
-    "for bit-like containers, return the number of bytes stored per element.
-     Here, 8 is returned"
-
-    ^ 8
-
-    "Created: / 15-09-2011 / 14:11:59 / cg"
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me.
-     For LongIntegerArrays, this is 18446744073709551615 eg. 16rFFFFFFFFFFFFFFFF 
-     (largest 64bit unsigned int)"
-
-    ^ 16rFFFFFFFFFFFFFFFF
-!
-
-minVal
-    "the minimum value which can be stored in instances of me.
-     For LongIntegerArrays, this is 0"
-
-    ^ 0
-! !
-
-!LongIntegerArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/Make.proto	Fri Nov 18 21:26:37 2016 +0000
+++ b/Make.proto	Fri Nov 18 21:28:24 2016 +0000
@@ -139,11 +139,10 @@
 $(OUTDIR)Bezier.$(O) Bezier.$(C) Bezier.$(H): Bezier.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BinaryTree.$(O) BinaryTree.$(C) BinaryTree.$(H): BinaryTree.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BinaryTreeNode.$(O) BinaryTreeNode.$(C) BinaryTreeNode.$(H): BinaryTreeNode.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)BitArray.$(O) BitArray.$(C) BitArray.$(H): BitArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)BoltLock.$(O) BoltLock.$(C) BoltLock.$(H): BoltLock.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CRC32Stream.$(O) CRC32Stream.$(C) CRC32Stream.$(H): CRC32Stream.st $(INCLUDE_TOP)/stx/libbasic/HashStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)CacheDictionary.$(O) CacheDictionary.$(C) CacheDictionary.$(H): CacheDictionary.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
-$(OUTDIR)CachedValue.$(O) CachedValue.$(C) CachedValue.$(H): CachedValue.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)CachedValue.$(O) CachedValue.$(C) CachedValue.$(H): CachedValue.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CharacterSet.$(O) CharacterSet.$(C) CharacterSet.$(H): CharacterSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Circle.$(O) Circle.$(C) Circle.$(H): Circle.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CollectingReadStream.$(O) CollectingReadStream.$(C) CollectingReadStream.$(H): CollectingReadStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
@@ -237,7 +236,6 @@
 $(OUTDIR)Trie.$(O) Trie.$(C) Trie.$(H): Trie.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
 $(OUTDIR)URI.$(O) URI.$(C) URI.$(H): URI.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)UUID.$(O) UUID.$(C) UUID.$(H): UUID.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/ByteArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnboxedIntegerArray.$(O) UnboxedIntegerArray.$(C) UnboxedIntegerArray.$(H): UnboxedIntegerArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)UndoSupport.$(O) UndoSupport.$(C) UndoSupport.$(H): UndoSupport.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)UnitConverter.$(O) UnitConverter.$(C) UnitConverter.$(H): UnitConverter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)UnixPTYStream.$(O) UnixPTYStream.$(C) UnixPTYStream.$(H): UnixPTYStream.st $(INCLUDE_TOP)/stx/libbasic/ExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/NonPositionableExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PipeStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
@@ -259,7 +257,6 @@
 $(OUTDIR)Base64Coder.$(O) Base64Coder.$(C) Base64Coder.$(H): Base64Coder.st $(INCLUDE_TOP)/stx/libbasic/AspectVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ObjectCoder.$(H) $(INCLUDE_TOP)/stx/libbasic/Visitor.$(H) $(INCLUDE_TOP)/stx/libbasic2/BaseNCoder.$(H) $(STCHDR)
 $(OUTDIR)BayesClassifier.$(O) BayesClassifier.$(C) BayesClassifier.$(H): BayesClassifier.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/TextClassifier.$(H) $(STCHDR)
 $(OUTDIR)Bezier2Segment.$(O) Bezier2Segment.$(C) Bezier2Segment.$(H): Bezier2Segment.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/LineSegment.$(H) $(STCHDR)
-$(OUTDIR)BooleanArray.$(O) BooleanArray.$(C) BooleanArray.$(H): BooleanArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic2/BitArray.$(H) $(STCHDR)
 $(OUTDIR)CacheDictionaryWithFactory.$(O) CacheDictionaryWithFactory.$(C) CacheDictionaryWithFactory.$(H): CacheDictionaryWithFactory.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic2/CacheDictionary.$(H) $(STCHDR)
 $(OUTDIR)DecNetSocketAddress.$(O) DecNetSocketAddress.$(C) DecNetSocketAddress.$(H): DecNetSocketAddress.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/SocketAddress.$(H) $(STCHDR)
 $(OUTDIR)EpsonFX1PrinterStream.$(O) EpsonFX1PrinterStream.$(C) EpsonFX1PrinterStream.$(H): EpsonFX1PrinterStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/PrinterStream.$(H) $(STCHDR)
@@ -270,23 +267,17 @@
 $(OUTDIR)HostAddressLookupError.$(O) HostAddressLookupError.$(C) HostAddressLookupError.$(H): HostAddressLookupError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic2/NameLookupError.$(H) $(STCHDR)
 $(OUTDIR)HostNameLookupError.$(O) HostNameLookupError.$(C) HostNameLookupError.$(H): HostNameLookupError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic2/NameLookupError.$(H) $(STCHDR)
 $(OUTDIR)IPSocketAddress.$(O) IPSocketAddress.$(C) IPSocketAddress.$(H): IPSocketAddress.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/SocketAddress.$(H) $(STCHDR)
-$(OUTDIR)IntegerArray.$(O) IntegerArray.$(C) IntegerArray.$(H): IntegerArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)LazyCons.$(O) LazyCons.$(C) LazyCons.$(H): LazyCons.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic2/Cons.$(H) $(STCHDR)
 $(OUTDIR)LineNumberReadStream.$(O) LineNumberReadStream.$(C) LineNumberReadStream.$(H): LineNumberReadStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/FilteringStream.$(H) $(STCHDR)
-$(OUTDIR)LongIntegerArray.$(O) LongIntegerArray.$(C) LongIntegerArray.$(H): LongIntegerArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)PostscriptPrinterStream.$(O) PostscriptPrinterStream.$(C) PostscriptPrinterStream.$(H): PostscriptPrinterStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/PrinterStream.$(H) $(STCHDR)
 $(OUTDIR)RandomGenerator.$(O) RandomGenerator.$(C) RandomGenerator.$(H): RandomGenerator.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/Random.$(H) $(STCHDR)
 $(OUTDIR)SharedQueue.$(O) SharedQueue.$(C) SharedQueue.$(H): SharedQueue.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/Queue.$(H) $(STCHDR)
-$(OUTDIR)SignedIntegerArray.$(O) SignedIntegerArray.$(C) SignedIntegerArray.$(H): SignedIntegerArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
-$(OUTDIR)SignedLongIntegerArray.$(O) SignedLongIntegerArray.$(C) SignedLongIntegerArray.$(H): SignedLongIntegerArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
-$(OUTDIR)SignedWordArray.$(O) SignedWordArray.$(C) SignedWordArray.$(H): SignedWordArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)TSMultiTree.$(O) TSMultiTree.$(C) TSMultiTree.$(H): TSMultiTree.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/TSTree.$(H) $(STCHDR)
 $(OUTDIR)TSMultiTreeNode.$(O) TSMultiTreeNode.$(C) TSMultiTreeNode.$(H): TSMultiTreeNode.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic2/TSTreeNode.$(H) $(STCHDR)
 $(OUTDIR)TimedPromise.$(O) TimedPromise.$(C) TimedPromise.$(H): TimedPromise.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/Promise.$(H) $(STCHDR)
 $(OUTDIR)UDSocketAddress.$(O) UDSocketAddress.$(C) UDSocketAddress.$(H): UDSocketAddress.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/SocketAddress.$(H) $(STCHDR)
 $(OUTDIR)Unicode32String.$(O) Unicode32String.$(C) Unicode32String.$(H): Unicode32String.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/FourByteString.$(H) $(STCHDR)
 $(OUTDIR)ValueDoubleLink.$(O) ValueDoubleLink.$(C) ValueDoubleLink.$(H): ValueDoubleLink.st $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/DoubleLink.$(H) $(STCHDR)
-$(OUTDIR)WordArray.$(O) WordArray.$(C) WordArray.$(H): WordArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic2/UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)ZipArchive.$(O) ZipArchive.$(C) ZipArchive.$(H): ZipArchive.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/ZipArchiveConstants.$(H) $(STCHDR)
 $(OUTDIR)ZipStream.$(O) ZipStream.$(C) ZipStream.$(H): ZipStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/CompressionStream.$(H) $(STCHDR)
 $(OUTDIR)FileURI.$(O) FileURI.$(C) FileURI.$(H): FileURI.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/HierarchicalURI.$(H) $(INCLUDE_TOP)/stx/libbasic2/URI.$(H) $(STCHDR)
--- a/Make.spec	Fri Nov 18 21:26:37 2016 +0000
+++ b/Make.spec	Fri Nov 18 21:28:24 2016 +0000
@@ -63,7 +63,6 @@
 	Bezier \
 	BinaryTree \
 	BinaryTreeNode \
-	BitArray \
 	BoltLock \
 	CRC32Stream \
 	CacheDictionary \
@@ -161,7 +160,6 @@
 	Trie \
 	URI \
 	UUID \
-	UnboxedIntegerArray \
 	UndoSupport \
 	UnitConverter \
 	UnixPTYStream \
@@ -183,7 +181,6 @@
 	Base64Coder \
 	BayesClassifier \
 	Bezier2Segment \
-	BooleanArray \
 	CacheDictionaryWithFactory \
 	DecNetSocketAddress \
 	EpsonFX1PrinterStream \
@@ -194,23 +191,17 @@
 	HostAddressLookupError \
 	HostNameLookupError \
 	IPSocketAddress \
-	IntegerArray \
 	LazyCons \
 	LineNumberReadStream \
-	LongIntegerArray \
 	PostscriptPrinterStream \
 	RandomGenerator \
 	SharedQueue \
-	SignedIntegerArray \
-	SignedLongIntegerArray \
-	SignedWordArray \
 	TSMultiTree \
 	TSMultiTreeNode \
 	TimedPromise \
 	UDSocketAddress \
 	Unicode32String \
 	ValueDoubleLink \
-	WordArray \
 	ZipArchive \
 	ZipStream \
 	FileURI \
@@ -236,7 +227,6 @@
     $(OUTDIR_SLASH)Bezier.$(O) \
     $(OUTDIR_SLASH)BinaryTree.$(O) \
     $(OUTDIR_SLASH)BinaryTreeNode.$(O) \
-    $(OUTDIR_SLASH)BitArray.$(O) \
     $(OUTDIR_SLASH)BoltLock.$(O) \
     $(OUTDIR_SLASH)CRC32Stream.$(O) \
     $(OUTDIR_SLASH)CacheDictionary.$(O) \
@@ -334,7 +324,6 @@
     $(OUTDIR_SLASH)Trie.$(O) \
     $(OUTDIR_SLASH)URI.$(O) \
     $(OUTDIR_SLASH)UUID.$(O) \
-    $(OUTDIR_SLASH)UnboxedIntegerArray.$(O) \
     $(OUTDIR_SLASH)UndoSupport.$(O) \
     $(OUTDIR_SLASH)UnitConverter.$(O) \
     $(OUTDIR_SLASH)UnixPTYStream.$(O) \
@@ -356,7 +345,6 @@
     $(OUTDIR_SLASH)Base64Coder.$(O) \
     $(OUTDIR_SLASH)BayesClassifier.$(O) \
     $(OUTDIR_SLASH)Bezier2Segment.$(O) \
-    $(OUTDIR_SLASH)BooleanArray.$(O) \
     $(OUTDIR_SLASH)CacheDictionaryWithFactory.$(O) \
     $(OUTDIR_SLASH)DecNetSocketAddress.$(O) \
     $(OUTDIR_SLASH)EpsonFX1PrinterStream.$(O) \
@@ -367,23 +355,17 @@
     $(OUTDIR_SLASH)HostAddressLookupError.$(O) \
     $(OUTDIR_SLASH)HostNameLookupError.$(O) \
     $(OUTDIR_SLASH)IPSocketAddress.$(O) \
-    $(OUTDIR_SLASH)IntegerArray.$(O) \
     $(OUTDIR_SLASH)LazyCons.$(O) \
     $(OUTDIR_SLASH)LineNumberReadStream.$(O) \
-    $(OUTDIR_SLASH)LongIntegerArray.$(O) \
     $(OUTDIR_SLASH)PostscriptPrinterStream.$(O) \
     $(OUTDIR_SLASH)RandomGenerator.$(O) \
     $(OUTDIR_SLASH)SharedQueue.$(O) \
-    $(OUTDIR_SLASH)SignedIntegerArray.$(O) \
-    $(OUTDIR_SLASH)SignedLongIntegerArray.$(O) \
-    $(OUTDIR_SLASH)SignedWordArray.$(O) \
     $(OUTDIR_SLASH)TSMultiTree.$(O) \
     $(OUTDIR_SLASH)TSMultiTreeNode.$(O) \
     $(OUTDIR_SLASH)TimedPromise.$(O) \
     $(OUTDIR_SLASH)UDSocketAddress.$(O) \
     $(OUTDIR_SLASH)Unicode32String.$(O) \
     $(OUTDIR_SLASH)ValueDoubleLink.$(O) \
-    $(OUTDIR_SLASH)WordArray.$(O) \
     $(OUTDIR_SLASH)ZipArchive.$(O) \
     $(OUTDIR_SLASH)ZipStream.$(O) \
     $(OUTDIR_SLASH)FileURI.$(O) \
--- a/NumberSet.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/NumberSet.st	Fri Nov 18 21:28:24 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 SequenceableCollection subclass:#NumberSet
 	instanceVariableNames:'intervals'
 	classVariableNames:''
@@ -36,26 +38,26 @@
 
 documentation
 "
-    NumberSets are Sets holding positive integers.
+    NumberSets are sets holding positive integers.
 
-    This class has been written especially to represent number-ranges from .newsrc-files,
+    This class has been written especially to represent number-ranges as found in .newsrc-files,
     and it supports reading/writing of that format (for example: '0-62,69,82,84,86,88,91').
     It is space optimized for sparse sets of numbers, containing a mix of single numbers
-    and chunks of sequential sub ranges. When adding elements, holes between 2 subranges
+    and chunks of sequential sub ranges. 
+    When adding elements, holes between 2 subranges
     are detected, and merged into single subranges.
     It may need some care to be used in other situations.
 
     The implementation uses an array of intervals or individual numbers.
 
-    Reading and writing is done in .newsrc-format.
-
-    written spring 92 by claus
+    Reading and writing is in .newsrc-format.
 
     [author:]
-        Claus Gittinger
+        Claus Gittinger (spring '92)
 
     [see also:]
         NewsHandler
+        Interval Set
 "
 ! !
 
@@ -557,6 +559,6 @@
 !NumberSet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/NumberSet.st,v 1.10 2013-06-29 11:32:33 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/PhoneticStringUtilities.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/PhoneticStringUtilities.st	Fri Nov 18 21:28:24 2016 +0000
@@ -281,7 +281,7 @@
     "return a soundex phonetic code or nil.
      Soundex (1918, 1922) returns similar codes for similar sounding words, making it a useful
      tool when searching for words where the correct spelling is unknown.
-     (read Knuth or search the web if you dont know what a soundex code is).
+     (read Knuth or search the web if you don't know what a soundex code is).
      Caveat: 'similar sounding words' means: 'similar sounding in english'."
 
     ^ (SoundexStringComparator new phoneticStringsFor:aString) first
@@ -882,7 +882,7 @@
     and also removing vokals first, then removing duplicate codes
     (whereas the soundex code does this in reverse order).
 
-    These variations are important, if you need the ame soundex codes to be generated.
+    These variations are important, if you need the miracode soundex codes to be generated.
 "
 ! !
 
@@ -1230,11 +1230,11 @@
 
     k := key copy.
      "2. Transcode initial strings:  MAC => MC   PF => F"
-    (k copyFrom:1 to:3) = 'MAC' ifTrue:[
-        k := 'MC' , (k copyFrom:4 to:k size)
+    (k startsWith:'MAC') ifTrue:[
+        k := 'MC' , (k copyFrom:4)
     ].
-    (k copyFrom:1 to:2) = 'PF' ifTrue:[
-        k := 'F' , (k copyFrom:3 to:k size)
+    (k startsWith:'PF') ifTrue:[
+        k := 'F' , (k copyFrom:3)
     ].
     ^ k
 !
@@ -2792,7 +2792,7 @@
         ].
         ((((currentIndex = self inputKey size) and: [(self keyAt: currentIndex - 1) isVowel])
                 or: [#('EWSKI' 'EWSKY' 'OWSKI' 'OWSKY') includes: (self inputKey copyFrom: ((currentIndex - 1) max: 1) to: (currentIndex + 3 min: self inputKey size))])
-                        or: [(self inputKey copyFrom: 1 to: 3) = 'SCH'])
+                        or: [self inputKey startsWith:'SCH'])
         ifTrue: [
                 self addPrimaryTranslation: '';
                 addSecondaryTranslation: 'F'.
--- a/PluggableSet.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/PluggableSet.st	Fri Nov 18 21:28:24 2016 +0000
@@ -178,9 +178,9 @@
         ].
 
         (probe ~~ DeletedEntry 
-         and:[compareFunction value:probe value:key]) ifTrue:[ "<<<< == is different from inherited"
+         and:[compareFunction value:probe value:key]) ifTrue:[ " <<<< == is different from inherited"
             ^ index
-         ].         
+        ].         
 
         index == length ifTrue:[
             index := 1
--- a/PostscriptPrinterStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/PostscriptPrinterStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -63,9 +63,10 @@
     PSGraphicsContext generates its own postscript - not caring for the margin/font settings
     here (these are only used if the printer-stream protocol is used (i.e. nextPut, cr etc.)
 
-    Notice, that these postscript classes are derived from public domain code; there is no warranty.
+    [Disclaimer:]    
+        Notice, that these postscript classes are derived from public domain code; 
+        there is no warranty.
 
-    
     [see also:]
         PSGraphicsContext 
         EpsonFX1PrinterStream HPLjetIIPrinterStream PrinterStream
--- a/PriorityQueue.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/PriorityQueue.st	Fri Nov 18 21:28:24 2016 +0000
@@ -16,21 +16,24 @@
     a priority queue is a collection with a given maximum size
     which only keeps the maxSize largest values.
     Only up to maxSize elements are stored at any time.
-    The internal organization is a heap; eg. elements are not kept
-    sorted internally.
+    The internal organization is a heap; 
+    eg. elements are not kept sorted internally.
 
-    When elements are added, a check is made, if the new element should
-    be kept or not.
+    When elements are added, a check is made, 
+    if the new element should be kept or not.
 
     Finally, when all elements have been added,
     get the elements in sorted order by repeated calls to removeFirst,
     which will remove and return the smallest element.
+
+    [author:]
+        Claus Gittinger
 "
 !
 
 examples
 "
-    find the 10 largest files in the stx source tree
+  find the 10 largest files in the stx source tree
                                                             [exBegin]
     |pq dir|
 
@@ -51,7 +54,7 @@
     ].
                                                             [exEnd]
 
-    generate 1 million random numbers and show the 10 largest
+  generate 1 million random numbers and show the 10 largest
                                                             [exBegin]
     |pq|
 
@@ -64,7 +67,7 @@
     ].
                                                             [exEnd]
 
-    a little test
+  a little test
                                                             [exBegin]
     |pq|
 
--- a/Queue.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Queue.st	Fri Nov 18 21:28:24 2016 +0000
@@ -49,7 +49,7 @@
     and another element is to be added. 
     Likewise, it will report an error if it is empty and an element is to be removed.
 
-    It is NOT safe when two processes access instances of Queue simultaneously,
+    It is NOT safe when two processes access the same queue-instance simultaneously,
     since accesses to the internals are not protected against process-switches.
     See SharedQueue for a class which IS safe w.r.t. processes and which blocks
     on write when full or on read when empty.
--- a/Random.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Random.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
 ======================================================================
 |
@@ -309,14 +311,13 @@
         nextPut:OperatingSystem getProcessId; 
         nextPut:(ObjectMemory addressOf:Object new); 
         nextPut:ObjectMemory oldSpaceUsed; 
-        nextPut:ObjectMemory newSpaceUsed. 
-    [
-        hash nextPut:OperatingSystem getCPUCycleCount. 
-    ] on:PrimitiveFailure do:[].
+        nextPut:ObjectMemory newSpaceUsed; 
+        nextPut:OperatingSystem getCPUCycleCount. 
 
     "/ any other cheap sources of entropy?
 
-    "/ I think there is no problem in that MD5 is not a secure hash algo here - the idea is to shuffle the bits around a bit
+    "/ I think there is no problem in that MD5 is not a secure hash algo here 
+    "/ - the idea is to shuffle the bits around a bit
     "/ (because the numbers above usually have many high bits in common)
     "/ and then condense the bits into a smaller number.
     "/ Any comment from a crypto guy here - I am willing to change this to some other hash, if that makes a problem
--- a/ReindexedCollection.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/ReindexedCollection.st	Fri Nov 18 21:28:24 2016 +0000
@@ -40,17 +40,26 @@
 "
     ReindexedCollection is a wrapper around a sequenceable collection that remaps the indices 
     with in linear algorithm.  
-    The elements in the ReindexedCollection are elements in the sequenceable collection at 
-    some start to some stop at some step.  
+    The elements in the ReindexedCollection are the elements of the original collection 
+    at 'some start' to 'some stop' (optionally 'by some step').  
 
     ReindexedCollection allows for efficient use of first/rest-like algorithms (i.e. aka Lisp)
     applied to Sequenceable collections, as they avoid element-copying.
 
+    For example,
+        coll1 := #(1 2 3 4 5 6 7 8 9 10).
+        coll2 := coll1 from:8.
+    gives us a collection in coll2, which 'contains' 3 elements, 8, 9, 10
+    with indices 1,2,3. 
+    I.e. a slice from the other array.
+
+    The reindexed collection is 'read-only'. I.e. it does not allow for elements to be changed.
+    
     See class side examples.
 
     [Instance Variables:]
-        sequence        <SequenceableCollection>        the sequence that will be reindexed.
-        interval        <Interval>      the object that describes indicies of interest in the sequence.
+        sequence        <SequenceableCollection>    the sequence that will be reindexed.
+        interval        <Interval>                  the object that describes indicies of interest in the sequence.
 
     [Origin:]
         Part of the Engineering Math Goodies package from Travis.
--- a/RunArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/RunArray.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  This class is not covered by or part of the ST/X licence.
 
@@ -364,7 +362,7 @@
             index >= runOffset ifTrue:[
                 index < nextIdx ifTrue:[
                     runIndex := idx.
-                    nextIdx := runOffset. "/ dont advance
+                    nextIdx := runOffset. "/ don't advance
                 ].
             ].
             runOffset := nextIdx.
--- a/SegmentedOrderedCollection.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/SegmentedOrderedCollection.st	Fri Nov 18 21:28:24 2016 +0000
@@ -16,9 +16,13 @@
     SegmentedOrderedCollections are intended as a replacement for huge OrderedCollections or Lists.
     They keep their elements in chunks (segments), allowing for fast 
     adding/removing at either end AND relatively fast add/remove inside the collection.
-    For huge collections, the performance is much better when adding/removing inner elements.
+    Compared to regular orderedColletions, there is not much of a difference if
+    elements are added at either end.
+    However, when adding/removing inner elements, the performance of SegementedOrderedCollections
+    is much better above a certain number of elements (actually quite big).
 
-    However, notice: when only removing at either end only, an OrderedCollection is faster.
+    However, notice again: 
+        when only removing at either end only, an OrderedCollection is faster.
 
     The break-even in performance depends on the number of elements and the usage pattern.
     Consider it with (say) > 10000 elements and many adds/removes from the inside.
--- a/SharedCollection.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/SharedCollection.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -43,10 +41,21 @@
     Instances of this class provide synchronized access (of multiple processes) 
     to a collection.
 
-    Notice: the message-forwarding is done by catching subclassResponsibility and
-    doesNotUnderstand errors.
+    Notice: 
+        the message-forwarding is done by catching subclassResponsibility and
+        doesNotUnderstand errors.
+
     For performance, and for more complex operation-atomicy, more messages might need
-    an explicit handling. See the implementation of #at: / #at:put: and #size for examples.
+    an explicit handling. 
+    See the implementation of #at: / #at:put: and #size for examples.
+
+    [auhor:]
+        Claus Gittinger
+
+    [see also:]
+        Semaphore RecursionLock
+        SharedQueue
+        #synchronized: method in Object.
 "
 !
 
--- a/SignedIntegerArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,94 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-UnboxedIntegerArray variableSignedLongSubclass:#SignedIntegerArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!SignedIntegerArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    SignedIntegerArrays store 32bit signed integers in the range -16r80000000..16r7FFFFFFF.
-    In contrast to normal arrays (which store pointers to their elements),
-    signedIntegerArrays store the values in a dense & compact way. 
-    Since the representation fits the underlying C-language systems representation
-    of signed int32's, this is also useful to pass bulk data to c primitive code.
-
-    [memory requirements:]
-        OBJ-HEADER + (size * 4)
-
-    [see also:]
-        ByteArray BooleanArray FloatArray DoubleArray Array
-        SignedWordArray WordArray IntegerArray LongIntegerArray
-        SignedLongIntegerArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!SignedIntegerArray class methodsFor:'queries'!
-
-elementByteSize
-    "for bit-like containers, return the number of bytes stored per element.
-     Here, 4 is returned"
-
-    ^ 4
-
-    "Created: / 15-09-2011 / 14:11:46 / cg"
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me.
-     For SignedIntegerArrays, this is 2147483647, eg. 16r7FFFFFFF (largest 32bit signed int)"
-
-    ^ 16r7FFFFFFF
-!
-
-minVal
-    "the minimum value which can be stored in instances of me.
-     For SignedIntegerArrays, this is -2147483648 eg. -16r80000000 (smallest 32bit signed int)"
-
-    ^ -16r80000000
-! !
-
-!SignedIntegerArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/SignedLongIntegerArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,98 +0,0 @@
-"
- COPYRIGHT (c) 1998 by Claus Gittinger / eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-UnboxedIntegerArray variableSignedLongLongSubclass:#SignedLongIntegerArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!SignedLongIntegerArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1998 by Claus Gittinger / eXept Software AG
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    SignedLongIntegerArrays store 64bit signed integers in the range 
-    -16r8000000000000000..16r7FFFFFFFFFFFFFFF.
-    In contrast to normal arrays (which store pointers to their elements),
-    signedLongIntegerArrays store the values in a dense & compact way. 
-    Since the representation fits the underlying C-language systems representation
-    of signed longlong's, this is also useful to pass bulk data to c primitive code.
-    (the system makes certain, that the first longlong is aligned as required)
-
-    [memory requirements:]
-        OBJ-HEADER + (size * 8)
-
-    [see also:]
-        ByteArray BooleanArray FloatArray DoubleArray Array
-        WordArray SignedWordArray IntegerArray SignedIntegerArray
-        LongIntegerArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!SignedLongIntegerArray class methodsFor:'queries'!
-
-elementByteSize
-    "for bit-like containers, return the number of bytes stored per element.
-     Here, 8 is returned"
-
-    ^ 8
-
-    "Created: / 15-09-2011 / 14:11:31 / cg"
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me.
-     For SignedLongIntegerArrays, this is 9223372036854775807 eg. 16r7FFFFFFFFFFFFFFF 
-     (largest 64bit signed int)"
-
-    ^ 16r7FFFFFFFFFFFFFFF
-!
-
-minVal
-    "the minimum value which can be stored in instances of me.
-     For SignedLongIntegerArrays, this is -9223372036854775808 eg. -16r8000000000000000 
-     (smallest 64bit signed int)"
-
-    ^ -16r8000000000000000
-! !
-
-!SignedLongIntegerArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/Socket.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Socket.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
 	      All Rights Reserved
@@ -321,7 +319,7 @@
         ] whileTrue.
         sock close.
 
-        'dont know enough of the ftp protocol to continue here ...'
+        'don't know enough of the ftp protocol to continue here ...'
                                                                         [exEnd]
 
 
@@ -2012,13 +2010,19 @@
 
 !Socket methodsFor:'closing'!
 
-finalize
-    self linger:0.      "/ discard buffered data
-    super finalize.
+abortAndClose
+    "immediately abort the connection:
+        discard buffered data and close the stream"
+
+    self linger:0.     
+    self close.         
 !
 
 shutDown
-    "shutDown and close the socket"
+    "shutDown (initiate a graceful close) 
+     and close (free the filedescriptor) the socket.
+     The close will return immediately and buffered data will be sent in the 
+     background, unless you set linger"
 
     self shutdown:2.
     self close
@@ -2036,8 +2040,11 @@
 shutDownOutput
     "shutDown the output side of the socket.
      Any write to the socket will signal end-of-file from now on.
-     An orderly realease (TCP FIN) will be initiated after the last buffered data
-     has been sent, so the other side will get a end-of-file condition eventually."
+     An orderly release (TCP FIN) will be initiated after the last buffered data
+     has been sent, so the other side will get a end-of-file condition eventually.
+     If you set linger > 0, the operation will wait until buffered data 
+     has been delivered to the peer.
+     Otherwise the operation returns immediately."
 
     self shutdown:1.
 ! !
@@ -2808,6 +2815,13 @@
     self primitiveFailed
 ! !
 
+!Socket methodsFor:'finalization'!
+
+finalize
+    self linger:0.      "/ do an abortive release - discard buffered data
+    self closeFile.     "/ does not wait due to abortive release.
+! !
+
 !Socket methodsFor:'initialization'!
 
 initialize
@@ -2816,73 +2830,6 @@
     eolMode := nil.
 ! !
 
-!Socket protectedMethodsFor:'low level'!
-
-closeFile
-    "low level close - may be redefined in subclasses
-     Don't send this message, send #close instead"
-
-    |fp error|
-
-    fp := handle.
-
-%{
-    int rslt;
-
-    if (fp == nil) {
-	error = @symbol(errorNotOpen);
-	goto out;
-    }
-
-    if (__INST(handleType) == @symbol(socketHandle)) {
-	SOCKET socket = SOCKET_FROM_FILE_OBJECT(fp);
-
-	if (@global(FileOpenTrace) == true) {
-	    console_fprintf(stderr, "close socket [ExternalStream] %"_lx_"\n", socket);
-	}
-
-	// whether the close() will be successful or not - the handle is invalid now!
-	__INST(handle) = nil;
-	do {
-#ifdef __win32__
-	    rslt = __STX_WSA_NOINT_CALL1("closesocket", closesocket, socket);
-#else
-	    rslt = close(socket);
-#endif
-	} while((rslt < 0) && (__threadErrno == EINTR));
-	if (rslt == 0) {
-	    RETURN(self);
-	}
-	error = __mkSmallInteger(__threadErrno);
-    }
-
-out:;
-%}.
-
-    error notNil ifTrue:[
-	error == #errorNotOpen ifTrue:[
-	    self errorNotOpen.
-	].
-	error isInteger ifTrue:[
-	    lastErrorNumber := error.
-	    self writeError:error.
-	    ^ self.
-	].
-	self primitiveFailed:error.
-	^ self.
-    ].
-
-    super closeFile.
-
-    "/ fallback for rel5
-
-    fp := handle.
-    fp notNil ifTrue:[
-	handle := nil.
-	self closeFile:fp
-    ]
-! !
-
 !Socket methodsFor:'low level'!
 
 getSocketAdress
@@ -2942,20 +2889,21 @@
     |serverSocketHandle addr domainClass newHandle|
 
     handle notNil ifTrue:[
-	^ self errorAlreadyOpen
+        ^ self errorAlreadyOpen.
+    ].
+    serverSocketHandle := aServerSocket fileHandle.
+    serverSocketHandle isNil ifTrue:[
+        "socket is not open"
+        ^ false
     ].
 
     domain := aServerSocket domain.
     socketType := aServerSocket type.
     handleType := aServerSocket handleType.
-    serverSocketHandle := aServerSocket fileHandle.
-    serverSocketHandle isNil ifTrue:[
-	^ self error:'invalid server socket'
-    ].
     "unix domain sockets do not return a valid peer name on accept"
     domainClass := self class socketAddressClassForDomain:domain.
     domainClass isNil ifTrue:[
-	^ self error:'invalid (unsupported) domain'.
+        ^ self error:'invalid (unsupported) domain'.
     ].
     addr := domainClass new.
     newHandle := OperatingSystem socketAccessor new.
@@ -2977,25 +2925,25 @@
 
 # if defined(O_NONBLOCK) && defined(SET_NDELAY)
     if (blocking == false) {
-	flags = fcntl(serverSocket, F_GETFL);
-	fcntl(serverSocket, F_SETFL, flags | O_NONBLOCK);
+        flags = fcntl(serverSocket, F_GETFL);
+        fcntl(serverSocket, F_SETFL, flags | O_NONBLOCK);
     }
 # endif
 
 # ifdef DO_WRAP_CALLS
     do {
-	__threadErrno = 0;
-	alen = sizeof(sa);
-	newSock = (SOCKET)STX_WSA_CALL3("accept", accept, serverSocket, &sa, &alen);
+        __threadErrno = 0;
+        alen = sizeof(sa);
+        newSock = (SOCKET)STX_WSA_CALL3("accept", accept, serverSocket, &sa, &alen);
     } while ((newSock < 0) && (__threadErrno == EINTR));
     if (newSock < 0) {
-	errno = __threadErrno;
+        errno = __threadErrno;
     }
 # else
     __BEGIN_INTERRUPTABLE__
     do {
-	alen = sizeof(sa);
-	newSock = accept(serverSocket, (struct sockaddr *) &sa, &alen);
+        alen = sizeof(sa);
+        newSock = accept(serverSocket, (struct sockaddr *) &sa, &alen);
     } while ((newSock < 0) && (errno == EINTR));
     __END_INTERRUPTABLE__
 # endif
@@ -3003,41 +2951,41 @@
 
 # if defined(O_NDELAY) && defined(SET_NDELAY)
     if (blocking == false) {
-	fcntl(serverSocket, F_SETFL, flags);
+        fcntl(serverSocket, F_SETFL, flags);
     }
 # endif
 
     if (newSock == -1) {
-	DBGPRINTF(("SOCKET: accept call failed errno=%d\n", errno));
-	__INST(lastErrorNumber) = __MKSMALLINT(errno);
-	RETURN (false);
+        DBGPRINTF(("SOCKET: accept call failed errno=%d\n", errno));
+        __INST(lastErrorNumber) = __MKSMALLINT(errno);
+        RETURN (false);
     }
 
     if (__isNonNilObject(addr)) {
-	OBJ oClass = __qClass(addr);
-	int nInstVars, nInstBytes, objSize;
-	char *addrP;
-
-	if (! __isBytes(addr) ) {
-	    DBGPRINTF(("SOCKET: bad addr\n"));
-	    closesocket(newSock);
-	    RETURN (false);
-	}
-
-	nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
-	nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
-	objSize = __qSize(addr) - nInstBytes;
-	addrP = (char *)__InstPtr(addr) + nInstBytes;
-	if (objSize < alen) {
-	    DBGPRINTF(("SOCKET: bad addr\n"));
-	    closesocket(newSock);
-	    RETURN (false);
-	}
-
-	/*
-	 * extract the partners address
-	 */
-	memcpy(addrP, (char *)&sa, alen);
+        OBJ oClass = __qClass(addr);
+        int nInstVars, nInstBytes, objSize;
+        char *addrP;
+
+        if (! __isBytes(addr) ) {
+            DBGPRINTF(("SOCKET: bad addr\n"));
+            closesocket(newSock);
+            RETURN (false);
+        }
+
+        nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
+        nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
+        objSize = __qSize(addr) - nInstBytes;
+        addrP = (char *)__InstPtr(addr) + nInstBytes;
+        if (objSize < alen) {
+            DBGPRINTF(("SOCKET: bad addr\n"));
+            closesocket(newSock);
+            RETURN (false);
+        }
+
+        /*
+         * extract the partners address
+         */
+        memcpy(addrP, (char *)&sa, alen);
     }
 
     /*
@@ -3055,19 +3003,19 @@
 # else // ! __win32__
     fp = fdopen(newSock, "r+");
     if (! fp) {
-	DBGPRINTF(("SOCKET: fdopen call failed\n"));
-	__INST(lastErrorNumber) = __MKSMALLINT(errno);
-	closesocket(newSock);
-	DBGFPRINTF((stderr, "SOCKET: close (fdopen failed) (%d)\n", newSock));
-	RETURN (false);
+        DBGPRINTF(("SOCKET: fdopen call failed\n"));
+        __INST(lastErrorNumber) = __MKSMALLINT(errno);
+        closesocket(newSock);
+        DBGFPRINTF((stderr, "SOCKET: close (fdopen failed) (%d)\n", newSock));
+        RETURN (false);
     }
 # endif // ! __win32__
 
     if ((@global(FileOpenTrace) == true) || __debugging__) {
 # ifdef __win32__
-	console_fprintf(stderr, "fdopen [Socket accept] -> fd: %d (H: %"_lx_")\n", _fd, (INT)newSock);
+        console_fprintf(stderr, "fdopen [Socket accept] -> fd: %d (H: %"_lx_")\n", _fd, (INT)newSock);
 # else
-	console_fprintf(stderr, "fdopen [Socket accept] -> %"_lx_" (fd: %d)\n", (INT)fp, newSock);
+        console_fprintf(stderr, "fdopen [Socket accept] -> %"_lx_" (fd: %d)\n", (INT)fp, newSock);
 # endif
     }
 
@@ -3835,16 +3783,16 @@
 linger:anIntegerOrNil
     "set the linger behavior on close:
       anIntegerOrNil == nil: close returns immediately, socket tries
-			     to send buffered data in background.
+                             to send buffered data in background.
       anIntegerOrNil == 0:   close returns immediately, bufferd data is discarded.
       anIntegerOrNil > 0:    close waits this many seconds for buffered data
-			     to be delivered, after this time buffered data is
-			     discarded and close returns"
+                             to be delivered, after this time buffered data is
+                             discarded and close returns with an error"
 
     ^ self
-	setSocketOption:#'SO_LINGER'
-	argument:anIntegerOrNil notNil
-	argument:anIntegerOrNil.
+        setSocketOption:#'SO_LINGER'
+        argument:anIntegerOrNil notNil
+        argument:anIntegerOrNil.
 !
 
 receiveBufferSize
@@ -4177,6 +4125,10 @@
         "a timeout occurred - no connection within timeout"
         ^ nil
     ].
+    self isOpen ifFalse:[
+        "socket has been closed while waiting"
+        ^ nil.
+    ].
     newSock := self class new.
     (newSock primAcceptOn:self blocking:false) ifFalse:[
         "should raise an error here"
--- a/SoundStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/SoundStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1706,22 +1706,22 @@
     ALport p;
 
     if ((port = __INST(alPort)) != nil) {
-	p = __ALportVal(port);
-	while (ALgetfilled(p) > 0) {
-	    sginap(1);
-	}
+        p = __ALportVal(port);
+        while (ALgetfilled(p) > 0) {
+            sginap(1);
+        }
     }
     RETURN(self);
 #endif /* IRIS_AUDIO */
 
 #if defined(DEV_AUDIO)
     if (__isSmallInteger(fd)) {
-	int f = __intVal(fd);
-	/* ... */
+        int f = __intVal(fd);
+        /* ... */
     }
 #endif /* DEV_AUDIO */
 %}.
-    "dont know how to wait on non-iris systems"
+    "don't know how to wait on non-iris systems"
     ^ self
 !
 
@@ -1843,7 +1843,7 @@
     "write count bytes from an object starting at index start.
      return the number of bytes written or nil on error.
      Redefined, since IRIS audio library cannot be used with stdio.
-     (at least I dont know). Use with ByteArrays only."
+     (at least I don't know). Use with ByteArrays only."
 
 %{
 #ifdef IRIS_AUDIO
@@ -1855,27 +1855,27 @@
     char *cp;
 
     if ((port = __INST(alPort)) != nil) {
-	if (__INST(mode) != @symbol(readonly)) {
-	    if (__bothSmallInteger(count, start)) {
-		cnt = __intVal(count);
-		offs = __intVal(start) - 1;
-		p = __ALportVal(port);
+        if (__INST(mode) != @symbol(readonly)) {
+            if (__bothSmallInteger(count, start)) {
+                cnt = __intVal(count);
+                offs = __intVal(start) - 1;
+                p = __ALportVal(port);
 
-		/*
-		 * compute number of samples
-		 */
-		objSize = _Size(anObject) - OHDR_SIZE;
-		if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
-		    cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
-		    if (__INST(bitsPerSample) == __MKSMALLINT(16))
-			nSamp = cnt / 2;
-		    else
-			nSamp = cnt;
-		    ALwritesamps(p, cp, cnt);
-		    RETURN ( count );
-		}
-	    }
-	}
+                /*
+                 * compute number of samples
+                 */
+                objSize = _Size(anObject) - OHDR_SIZE;
+                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
+                    cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
+                    if (__INST(bitsPerSample) == __MKSMALLINT(16))
+                        nSamp = cnt / 2;
+                    else
+                        nSamp = cnt;
+                    ALwritesamps(p, cp, cnt);
+                    RETURN ( count );
+                }
+            }
+        }
     }
   }
 #endif /* IRIS_AUDIO */
@@ -1898,15 +1898,15 @@
     int cnt, offs;
 
     if ((oDSBuffer = __INST(pDSBuffer)) != nil) {
-	t_pDSBuffer = __DSBufferVal(oDSBuffer);
+        t_pDSBuffer = __DSBufferVal(oDSBuffer);
     }
     if ((oDirectSound = __INST(pDirectSound)) != nil) {
-	t_pDirectSound = __DirectSoundVal(oDirectSound);
+        t_pDirectSound = __DirectSoundVal(oDirectSound);
     }
 
     if (!t_pDSBuffer || !t_pDirectSound) {
-	console_fprintf(stderr, "SoundStream not open!\n");
-	RETURN (0);
+        console_fprintf(stderr, "SoundStream not open!\n");
+        RETURN (0);
     }
     t_cbBufOffset = __intVal(__INST(bufferOffset));
     t_cbBufSize = __intVal(__INST(bufferSize));
@@ -1918,47 +1918,47 @@
     // Should be playing, right?
     hr = IDirectSoundBuffer_GetStatus(t_pDSBuffer, &status );
     if (!(status && DSBSTATUS_PLAYING)) {
-	console_fprintf(stderr, "Buffer not playing!\n");
-	RETURN (0);
+        console_fprintf(stderr, "Buffer not playing!\n");
+        RETURN (0);
     }
 
     // Sleep until we have enough room in buffer.
     hr = IDirectSoundBuffer_GetCurrentPosition(t_pDSBuffer, &playPos, &safePos );
     if( hr != DS_OK ) {
-	console_fprintf(stderr, "Cannot get position!\n");
-	RETURN (0);
+        console_fprintf(stderr, "Cannot get position!\n");
+        RETURN (0);
     }
     if( playPos < t_cbBufOffset ) playPos += t_cbBufSize;
 
     endWrite = t_cbBufOffset + (cnt * sizeof(short));
     while ( playPos < endWrite ) {
-	// Calculate number of milliseconds until we will have room, as
-	// time = distance * (milliseconds/second) / ((bytes/sample) * (samples/second)),
-	// rounded up.
-	millis = (DWORD) (1.0 + ((endWrite - playPos) * 1000.0) / ( sizeof(short) * __intVal(__INST(sampleRate))));
+        // Calculate number of milliseconds until we will have room, as
+        // time = distance * (milliseconds/second) / ((bytes/sample) * (samples/second)),
+        // rounded up.
+        millis = (DWORD) (1.0 + ((endWrite - playPos) * 1000.0) / ( sizeof(short) * __intVal(__INST(sampleRate))));
 
-	// Sleep for that long
-	Sleep( millis );
+        // Sleep for that long
+        Sleep( millis );
 
-	// Wake up, find out where we are now
-	hr = IDirectSoundBuffer_GetCurrentPosition(t_pDSBuffer, &playPos, &safePos );
-	if( hr != DS_OK ) {
-	    console_fprintf(stderr, "Cannot get position!\n");
-	    RETURN (0);
-	}
-	if( playPos < t_cbBufOffset ) playPos += t_cbBufSize; // unwrap offset
+        // Wake up, find out where we are now
+        hr = IDirectSoundBuffer_GetCurrentPosition(t_pDSBuffer, &playPos, &safePos );
+        if( hr != DS_OK ) {
+            console_fprintf(stderr, "Cannot get position!\n");
+            RETURN (0);
+        }
+        if( playPos < t_cbBufOffset ) playPos += t_cbBufSize; // unwrap offset
     }
 
     // Lock free space in the DS
     hr = IDirectSoundBuffer_Lock(t_pDSBuffer, t_cbBufOffset, cnt * sizeof(short), &lpbuf1, &dwsize1, &lpbuf2, &dwsize2, 0);
     if (hr == DS_OK) {
-	// Copy the buffer into the DS
-	CopyMemory(lpbuf1, buf, dwsize1);
-	if(NULL != lpbuf2) CopyMemory(lpbuf2, buf+dwsize1, dwsize2);
+        // Copy the buffer into the DS
+        CopyMemory(lpbuf1, buf, dwsize1);
+        if(NULL != lpbuf2) CopyMemory(lpbuf2, buf+dwsize1, dwsize2);
 
-	// Update our buffer offset and unlock sound buffer
-	t_cbBufOffset = (t_cbBufOffset + dwsize1 + dwsize2) % t_cbBufSize;
-	IDirectSoundBuffer_Unlock(t_pDSBuffer, lpbuf1, dwsize1, lpbuf2, dwsize2);
+        // Update our buffer offset and unlock sound buffer
+        t_cbBufOffset = (t_cbBufOffset + dwsize1 + dwsize2) % t_cbBufSize;
+        IDirectSoundBuffer_Unlock(t_pDSBuffer, lpbuf1, dwsize1, lpbuf2, dwsize2);
     }
     __INST(buffferOffset) = __MKSMALLINT(t_cbBufOffset);
 
@@ -1977,7 +1977,7 @@
     OBJ oWaveHandle;
 
     if ((oWaveHandle = __INST(waveHandle)) == nil) {
-	RETURN(0);
+        RETURN(0);
     }
     t_waveHandle = __WaveHandleVal(oWaveHandle);
 
@@ -1986,50 +1986,50 @@
     buf = (short *)__InstPtr(anObject) + OHDR_SIZE + offs;
 
     while (dataLen > 0) {
-	if (free_list == NULL && total_buffers < MAXBUF) {
-	    /* Expand available buffer space */
-	    bp = (struct buf *)malloc(sizeof(struct buf));
-	    total_buffers++;
-	} else {
-	    if (free_list == NULL) {
-		/* We must wait for a free buffer */
-		while (free_list == NULL) {
-		    WaitForSingleObject(free_buffer_event, INFINITE);
-		}
-	    }
-	    EnterCriticalSection(&free_list_lock);
-	    bp = free_list;
-	    free_list = free_list->next;
-	    --free_buffers;
-	    LeaveCriticalSection(&free_list_lock);
-	    r = waveOutUnprepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
-	    if (r != 0) {
-		console_printf("waveOutUnprepareHeader\n");
-		RETURN(self);
-	    }
-	}
-	len = min(dataLen, DATALEN);
-	bp->hdr.lpData = (char *)bp->data;
-	bp->hdr.dwBufferLength = len;
-	bp->hdr.dwBytesRecorded = len;
-	bp->hdr.dwUser = (INT)(bp);
-	bp->hdr.dwFlags = 0;
-	bp->hdr.dwLoops = 0;
-	r = waveOutPrepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
-	if (r != 0) {
-	    console_printf("waveOutPrepareHeader\n");
-	    RETURN(self);
-	}
-	for (i = 0; i < len; i++) {
-	    bp->data[i] = buf[i];
-	}
-	r = waveOutWrite(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
-	if (r != 0) {
-	    console_printf("waveOutWrite\n");
-	    RETURN(self);
-	}
-	buf += len;
-	dataLen -= len;
+        if (free_list == NULL && total_buffers < MAXBUF) {
+            /* Expand available buffer space */
+            bp = (struct buf *)malloc(sizeof(struct buf));
+            total_buffers++;
+        } else {
+            if (free_list == NULL) {
+                /* We must wait for a free buffer */
+                while (free_list == NULL) {
+                    WaitForSingleObject(free_buffer_event, INFINITE);
+                }
+            }
+            EnterCriticalSection(&free_list_lock);
+            bp = free_list;
+            free_list = free_list->next;
+            --free_buffers;
+            LeaveCriticalSection(&free_list_lock);
+            r = waveOutUnprepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
+            if (r != 0) {
+                console_printf("waveOutUnprepareHeader\n");
+                RETURN(self);
+            }
+        }
+        len = min(dataLen, DATALEN);
+        bp->hdr.lpData = (char *)bp->data;
+        bp->hdr.dwBufferLength = len;
+        bp->hdr.dwBytesRecorded = len;
+        bp->hdr.dwUser = (INT)(bp);
+        bp->hdr.dwFlags = 0;
+        bp->hdr.dwLoops = 0;
+        r = waveOutPrepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
+        if (r != 0) {
+            console_printf("waveOutPrepareHeader\n");
+            RETURN(self);
+        }
+        for (i = 0; i < len; i++) {
+            bp->data[i] = buf[i];
+        }
+        r = waveOutWrite(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
+        if (r != 0) {
+            console_printf("waveOutWrite\n");
+            RETURN(self);
+        }
+        buf += len;
+        dataLen -= len;
     }
     RETURN (count);
   }
@@ -2053,47 +2053,47 @@
     int fd;
 
     if ((fp = __INST(handle)) != nil) {
-	f = __FILEVal(fp);
-	if (__INST(mode) != @symbol(readonly)) {
-	    if (__bothSmallInteger(count, start)) {
-		cnt = __intVal(count);
-		offs = __intVal(start) - 1;
+        f = __FILEVal(fp);
+        if (__INST(mode) != @symbol(readonly)) {
+            if (__bothSmallInteger(count, start)) {
+                cnt = __intVal(count);
+                offs = __intVal(start) - 1;
 
-		objSize = _Size(anObject) - OHDR_SIZE;
-		if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
-		    do {
-			cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
+                objSize = _Size(anObject) - OHDR_SIZE;
+                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
+                    do {
+                        cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
 
-			n = cnt;
+                        n = cnt;
 /*                        if (n > 4096) n = 4096; */
 # ifdef LINUX
-			sigsetmask(~0);
+                        sigsetmask(~0);
 # endif
-			if (__INST(buffered) == true) {
-			    n = fwrite(cp, 1, n, f);
-			} else {
-			    fd = fileno(f);
-			    n = write(fd, cp, n);
-			}
+                        if (__INST(buffered) == true) {
+                            n = fwrite(cp, 1, n, f);
+                        } else {
+                            fd = fileno(f);
+                            n = write(fd, cp, n);
+                        }
 # ifdef LINUX
-			sigsetmask(0);
+                        sigsetmask(0);
 # endif
-			__BEGIN_INTERRUPTABLE__
-			__END_INTERRUPTABLE__
-			if (n > 0) {
-			    offs += n;
-			    cnt -= n;
-			} else {
-			    if (n < 0) {
-				console_fprintf(stderr, "write error: %d\n", __threadErrno);
-				RETURN (count);
-			    }
-			}
-		    } while (cnt);
-		}
-		RETURN (count);
-	    }
-	}
+                        __BEGIN_INTERRUPTABLE__
+                        __END_INTERRUPTABLE__
+                        if (n > 0) {
+                            offs += n;
+                            cnt -= n;
+                        } else {
+                            if (n < 0) {
+                                console_fprintf(stderr, "write error: %d\n", __threadErrno);
+                                RETURN (count);
+                            }
+                        }
+                    } while (cnt);
+                }
+                RETURN (count);
+            }
+        }
     }
 #endif /* DEV_AUDIO */
 
--- a/TSMultiTree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/TSMultiTree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -13,6 +13,8 @@
 
 documentation
 "
+    BTree and TSTree
+
     A bunch of collection classes that are useful for building large indices of things. 
     It's especially geared towards people using OODBs like GOODS, but can be used it in the image too: 
     the BTree class is great for when you need to select numeric keys by range, 
--- a/TSMultiTreeNode.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/TSMultiTreeNode.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 TSTreeNode subclass:#TSMultiTreeNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -115,7 +117,7 @@
     value isNil ifTrue:[ ^ #() ].
 
     value class == ValueArray 
-        ifTrue:[ value ]
+        ifTrue:[ ^ value ]
         ifFalse:[ ^ Array with: value ].
 
     "Created: / 26-04-2014 / 11:50:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -136,10 +138,10 @@
 !TSMultiTreeNode class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/TSMultiTreeNode.st,v 1.1 2014-04-26 11:13:46 vrany Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/TSMultiTreeNode.st,v 1.1 2014-04-26 11:13:46 vrany Exp $'
+    ^ '$Header$'
 ! !
 
--- a/TSTree.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/TSTree.st	Fri Nov 18 21:28:24 2016 +0000
@@ -13,6 +13,8 @@
 
 documentation
 "
+    BTree and TSTree
+
     A bunch of collection classes that are useful for building large indices of things. 
     It's especially geared towards people using OODBs like GOODS, but can be used it in the image too: 
     the BTree class is great for when you need to select numeric keys by range, 
--- a/TerminalSession.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/TerminalSession.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "{ Package: 'stx:libbasic2' }"
 
 "{ NameSpace: Smalltalk }"
@@ -644,7 +642,7 @@
     bufferSize := 1024.
     buffer := String new:bufferSize.
 
-    ExternalStream readErrorSignal handle:[:ex |
+    StreamError handle:[:ex |
         n := 0
     ] do:[
         |line|
--- a/Text.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Text.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1996 by Claus Gittinger
               All Rights Reserved
@@ -1629,6 +1627,13 @@
 
 !Text methodsFor:'queries'!
 
+bitsPerCharacter
+    "return the number of bits I (my underlying string) require for storage.
+     (i.e. is it a regular String or a TwoByteString)"
+
+    ^ string bitsPerCharacter.
+!
+
 emphasisAtPoint:aPoint on:aGCOrView
     "return the emphasis at a given point, or nil if there is none"
 
--- a/TreeSet.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/TreeSet.st	Fri Nov 18 21:28:24 2016 +0000
@@ -13,6 +13,8 @@
 
 documentation
 "
+    BTree and TSTree
+
     A bunch of collection classes that are useful for building large indices of things. 
     It's especially geared towards people using OODBs like GOODS, but can be used it in the image too: 
     the BTree class is great for when you need to select numeric keys by range, 
--- a/Trie.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/Trie.st	Fri Nov 18 21:28:24 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
+
 SequenceableCollection subclass:#Trie
 	instanceVariableNames:'value children'
 	classVariableNames:''
@@ -7,7 +9,7 @@
 	category:'Collections-Ordered'
 !
 
-Smalltalk::Dictionary subclass:#Dictionary
+Dictionary subclass:#RegularDictionary
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -294,7 +296,7 @@
     "Created: / 04-08-2012 / 10:48:45 / cg"
 ! !
 
-!Trie::Dictionary methodsFor:'accessing'!
+!Trie::RegularDictionary methodsFor:'accessing'!
 
 newAt:key put:value
     self at:key put:value.
@@ -468,7 +470,7 @@
     key = k1 ifTrue:[ v1 := value. ^ self ].
     key = k2 ifTrue:[ v2 := value. ^ self ].
     key = k3 ifTrue:[ v3 := value. ^ self ].
-    ^ Trie::Dictionary new
+    ^ Trie::RegularDictionary new
         at:k1 put:v1;
         at:k2 put:v2;
         at:k3 put:v3;
@@ -499,9 +501,10 @@
 !Trie class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/Trie.st,v 1.3 2012-11-13 13:05:13 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/Trie.st,v 1.3 2012-11-13 13:05:13 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/UnboxedIntegerArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,114 +0,0 @@
-"
- COPYRIGHT (c) 2003 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-AbstractNumberVector subclass:#UnboxedIntegerArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!UnboxedIntegerArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 2003 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    An abstract superclass for all unboxed integer classes.
-    In contrast to normal arrays (which store pointers to their elements),
-    unboxedIntegerArrays store the values in a dense & compact way. 
-    Since the representation fits corresponding underlying C-language representations,
-    these are also useful to pass bulk data to c primitive code.
-
-    [see also:]
-        ByteArray WordArray BooleanArray FloatArray DoubleArray Array
-        IntegerArray LongIntegerArray SignedLongIntegerArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!UnboxedIntegerArray class methodsFor:'queries'!
-
-isAbstract
-    "Return if this class is an abstract class.
-     True is returned for UnboxedIntegerArray here; false for subclasses.
-     Abstract subclasses must redefine this again."
-
-    ^ self == UnboxedIntegerArray
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me"
-    
-    ^ self subclassResponsibility.
-!
-
-minVal
-    "the minimum value which can be stored in instances of me"
-    
-    ^ self subclassResponsibility.
-! !
-
-!UnboxedIntegerArray methodsFor:'printing'!
-
-printOn:aStream base:radix showRadix:showRadix
-    "append a printed representation to aStream in the given number base."
-
-    (self class == WordArray or:[self class == LongIntegerArray]) 
-    ifTrue:[    "/ care for subclasses
-        aStream nextPutAll:'#('.
-        self 
-            do:[:word | word printOn:aStream base:radix showRadix:showRadix]
-            separatedBy:[aStream space].
-        aStream nextPut:$).
-        ^ self
-    ].
-    ^ self printOn:aStream
-! !
-
-!UnboxedIntegerArray methodsFor:'queries'!
-
-defaultElement
-    ^ 0
-!
-
-isValidElement:anObject
-    "return true, if I can hold this kind of object"
-
-    ^ anObject isInteger
-    and:[ (anObject >= self class minVal)
-    and:[ (anObject <= self class maxVal) ]]
-! !
-
-!UnboxedIntegerArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
-
--- a/WordArray.st	Fri Nov 18 21:26:37 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,138 +0,0 @@
-"
- COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic2' }"
-
-"{ NameSpace: Smalltalk }"
-
-UnboxedIntegerArray variableWordSubclass:#WordArray
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Arrayed'
-!
-
-!WordArray class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    WordArrays store integers in the range 0..16rFFFF.
-    In contrast to normal arrays (which store pointers to their elements),
-    wordArrays store the values in a dense & compact way. 
-    Since the representation fits the underlying C-language systems representation
-    of unsigned int16's, this is also useful to pass bulk data to c primitive code.
-
-    WordArrays can be used to hold bulk integer data in a more compact way.
-        For example:
-            Array new:100000 withAll:1
-        requires 400k of object memory;
-
-        in contrast,
-            WordArray new:100000 withAll:1
-        only requires half of it.
-
-    [memory requirements:]
-        OBJ-HEADER + (size * 2)
-
-    [see also:]
-        ByteArray BooleanArray FloatArray DoubleArray Array
-        SignedWordArray
-
-    [author:]
-        Claus Gittinger
-"
-! !
-
-!WordArray class methodsFor:'queries'!
-
-elementByteSize
-    "for bit-like containers, return the number of bytes stored per element.
-     Here, 2 is returned"
-
-    ^ 2
-
-    "Created: / 15-09-2011 / 14:10:54 / cg"
-!
-
-maxVal
-    "the maximum value which can be stored in instances of me.
-     For WordArrays, this is 16rFFFF (largest 16bit unsigned int)"
-
-    ^ 16rFFFF
-!
-
-minVal
-    "the minimum value which can be stored in instances of me.
-     For WordArrays, this is 0"
-
-    ^ 0
-! !
-
-!WordArray methodsFor:'accessing'!
-
-unsignedInt16At:index MSB:msb
-    "return the 2-bytes starting at index as an (unsigned) Integer.
-     The index is a smalltalk index (i.e. 1-based).
-     The value is retrieved MSB (high 8 bits at lower index) if msb is true;
-     LSB-first (i.e. low 8-bits at lower byte index) if its false.
-     Notice: 
-        the index is a byte index; thus, this allows for unaligned access to
-        words on any boundary"
-
-    |w|
-    
-    index odd ifTrue:[
-        "/ aligned fetch
-        w := self at:(index // 2) + 1.
-        (msb ~~ UninterpretedBytes isBigEndian) ifTrue:[
-            w := w swapBytes
-        ].    
-        ^ w
-    ].
-    ^ super unsignedInt16At:index MSB:msb
-
-    "
-     #(16r0201 16r0403 16r0605) asWordArray wordAt:1 MSB:false
-     #(16r0201 16r0403 16r0605) asWordArray wordAt:3 MSB:false
-     #(16r0201 16r0403 16r0605) asWordArray wordAt:5 MSB:false
-
-     #(16r0201 16r0403 16r0605) asWordArray wordAt:2 MSB:false
-     #(16r0201 16r0403 16r0605) asWordArray wordAt:4 MSB:false
-
-     #(16rFFEE 16r0403 16r0605) asWordArray wordAt:1 MSB:false
-     #(16rFFEE 16r0403 16r0605) asWordArray wordAt:1 MSB:true
-    "
-! !
-
-!WordArray class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-!
-
-version_CVS
-    ^ '$Header$'
-! !
-
--- a/ZipArchive.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/ZipArchive.st	Fri Nov 18 21:28:24 2016 +0000
@@ -16,8 +16,9 @@
 Object subclass:#ZipArchive
 	instanceVariableNames:'file mode archiveName firstEntry lastEntry centralDirectory
 		startOfArchive endOfArchive zipMembersByName appendTrailingSlash'
-	classVariableNames:'Lobby RecentlyUsedZipArchives FlushBlock ZipFileFormatErrorSignal
-		UnsupportedZipFileFormatErrorSignal DefaultAppendTrailingSlash'
+	classVariableNames:'RecentlyUsedZipArchives FlushBlock ZipFileFormatErrorSignal
+		UnsupportedZipFileFormatErrorSignal DefaultAppendTrailingSlash
+		ZipFileCachingTime'
 	poolDictionaries:'ZipArchiveConstants'
 	category:'System-Support-FileFormats'
 !
@@ -2969,6 +2970,14 @@
     DefaultAppendTrailingSlash := aBoolean
 
     "Created: / 19-11-2012 / 11:53:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+zipFileCachingTime:seconds
+    "by default, zip files are cached for some time, 
+     in case they are reconsulted soon.
+     The defualt time is 60s, but can be changed by this setter"
+     
+    ZipFileCachingTime := seconds
 ! !
 
 !ZipArchive class methodsFor:'class initialization'!
@@ -2984,10 +2993,6 @@
         UnsupportedZipFileFormatErrorSignal notifierString:'unsupported zip file format'.
     ].
 
-    Lobby isNil ifTrue:[
-        Lobby := Registry new.
-    ].
-
     DefaultAppendTrailingSlash := true.
 
     "
@@ -3019,7 +3024,7 @@
     FlushBlock isNil ifTrue:[
         FlushBlock := [RecentlyUsedZipArchives := nil. FlushBlock := nil].
     ].
-    Processor addTimedBlock:FlushBlock for:Processor timeoutHandlerProcess afterSeconds:60.
+    Processor addTimedBlock:FlushBlock for:Processor timeoutHandlerProcess afterSeconds:(ZipFileCachingTime ? 60).
 
     "
      self installFlushBlock
@@ -3253,33 +3258,22 @@
     ZipFileFormatErrorSignal raiseErrorString:anErrorString.
 ! !
 
-!ZipArchive methodsFor:'finalization'!
-
-finalizationLobby
-    "answer the registry used for finalization."
-    ^ Lobby
-!
-
-finalize
-    "some Stream has been collected - close the file if not already done"
-    self closeFile
-! !
-
 !ZipArchive methodsFor:'open & close'!
 
 close
-     self closeFile
+    file notNil ifTrue:[
+        self flush.
+        file close.
+        file := archiveName := centralDirectory := zipMembersByName := nil.
+        firstEntry := lastEntry := nil.
+    ].
 !
 
 flush
     "finish the zip archive, but do not close the underlying stream"
 
-    file notNil ifTrue:[
-        Lobby unregister:self.
-        mode == #write ifTrue: [
-            self addCentralZipDirectory
-        ].
-        file := nil.
+    (file notNil and:[mode == #write]) ifTrue: [
+        self addCentralZipDirectory
     ]
 !
 
@@ -3297,7 +3291,7 @@
     ].
 
     file notNil ifTrue: [
-        self closeFile.
+        self close.
     ].
 
     archiveName := filename name.
@@ -3323,7 +3317,7 @@
                 mode := #write.
             ].
         ] ensure:[
-            mustCloseFile ifTrue:[self closeFile].
+            mustCloseFile ifTrue:[self close].
         ].
     ] ifFalse:[
         zipMembersByName := Dictionary new.
@@ -3346,7 +3340,7 @@
 
     file notNil ifTrue: [
         file ~~ aPositionableStream ifTrue: [
-            self closeFile.
+            self close.
         ].
     ].
 
@@ -3380,7 +3374,7 @@
     "initialize the archive to write to aPositionableStream"
 
     file notNil ifTrue: [
-        self closeFile.
+        self close.
     ].
 
     mode := #write.
@@ -3397,15 +3391,12 @@
 !ZipArchive methodsFor:'private'!
 
 closeFile
-    "finish the zip archive and close the stream"
-
-    |savedFile|
-
-    file notNil ifTrue:[
-        savedFile := file.
-        self flush.
-        savedFile close.
-    ]
+    <resource: #obsolete>
+    "backward compatibility"
+
+    self obsoleteMethodWarning:'use #close'.
+
+    self close.
 !
 
 dataStartOf:zipEntry
@@ -3474,7 +3465,6 @@
             file := fn writeStream
         ].
         file binary.
-        Lobby register:self.
     ].
 
     "Modified: / 31-08-2010 / 12:40:41 / sr"
@@ -3746,7 +3736,7 @@
         "ignore duplicate entries for backward compatibility.
          Argh: expecco once added wrong duplicates to the end of ets files.
                The first entry is valid."
-        Logger info: 'Duplicate entry in ZIP (ignored): %1' with: zmemb fileName.
+        Logger warning:'duplicate entry in ZIP file ignored: %1' with:zmemb fileName.
     ] ifFalse:[
         zipMembersByName at:zmemb fileName put:zmemb.
     ].
@@ -3792,7 +3782,7 @@
     [
         isValidArchive := self checkZipArchive.
     ] ensure:[
-        self closeFile.
+        self close.
     ].
     ^ isValidArchive
 !
@@ -4000,7 +3990,6 @@
     ^ false.
 ! !
 
-
 !ZipArchive methodsFor:'reading'!
 
 extract:fileName
@@ -4110,7 +4099,6 @@
     "Created: / 21-11-2010 / 11:51:41 / cg"
 ! !
 
-
 !ZipArchive methodsFor:'reading - stream'!
 
 extract:fileName intoStream: aWriteStream
@@ -4136,7 +4124,7 @@
                     compressionMethod == COMPRESSION_DEFLATED ifTrue:[
                         myZipStream isNil ifTrue: [
                             file binary.
-                            myZipStream := ZipStream readOpenAsZipStreamOn: file.
+                            myZipStream := ZipStream readOpenAsZipStreamOn:file suppressHeaderAndChecksum:true.
                         ].
                         myZipStream next:nextBlockSize into:buffer startingAt:1.
                     ] ifFalse:[compressionMethod == COMPRESSION_STORED ifTrue:[
@@ -4273,7 +4261,6 @@
     theZipFileName := self validZipFileNameFrom:aFileName. 
 
     zipEntry fileName: theZipFileName.
-    zipEntry fileNameLength: theZipFileName size.
     zipEntry uncompressedSize: 0.
 
     isDirectory ifTrue: [
@@ -4308,7 +4295,7 @@
                 crc32 := ZipStream crc32BytesIn: buffer from:1 to:nextBlockSize crc:crc32.
                 theCompressMethod == COMPRESSION_DEFLATED ifTrue: [
                     myZipStream isNil ifTrue: [
-                        myZipStream := ZipStream writeOpenAsZipStreamOn:file.
+                        myZipStream := ZipStream writeOpenAsZipStreamOn:file suppressHeaderAndChecksum:true.
                     ].
                     myZipStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
                 ] ifFalse: [theCompressMethod == COMPRESSION_STORED ifTrue: [
@@ -4326,7 +4313,7 @@
 
     zipEntry compressedSize:(file position) - startDataPosition.
 
-    "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
+    "/ crc32 is always required (not as written in docu to be zero in case of uncompressed mode)
     zipEntry crc32:crc32.
     zipEntry uncompressedSize: unCompressedDataSize.
 
@@ -4373,26 +4360,23 @@
 basicAddFile:aFileName withContents:data compressMethod:theCompressMethodArg asDirectory:isDirectory 
     "do not create directories (isDirectory = true) - they are not compatible between operating systems"
     
-    | zipEntry  theCompressedData theZipFileName  theCompressMethod |
+    | zipEntry theCompressedData theZipFileName theCompressMethod  compressedDataOffset|
 
     (file isNil or:[ mode ~~ #write ]) ifTrue:[
         ^ self error:'ZipArchive not open for writing ...'.
     ].
     theCompressMethod := theCompressMethodArg.
-    ((theCompressMethod == COMPRESSION_DEFLATED) 
-        or:[ theCompressMethod == COMPRESSION_STORED ]) 
-            ifFalse:[
-                UnsupportedZipFileFormatErrorSignal 
-                    raiseRequestErrorString:'unsupported compressMethod'.
-                
-                "/ if proceeded, write as uncompressed
-                
-                theCompressMethod := COMPRESSION_STORED
-            ].
+    ((theCompressMethod ~~ COMPRESSION_DEFLATED) 
+      and:[theCompressMethod ~~ COMPRESSION_STORED]) ifTrue:[
+        UnsupportedZipFileFormatErrorSignal 
+            raiseRequestErrorString:'unsupported compressMethod'.
+        "/ if proceeded, write as uncompressed
+        theCompressMethod := COMPRESSION_STORED
+    ].
+
     zipEntry := ZipMember new default.
     theZipFileName := self validZipFileNameFrom:aFileName.
     zipEntry fileName:theZipFileName.
-    zipEntry fileNameLength:theZipFileName size.
 
     (self appendTrailingSlash and:[isDirectory]) ifTrue:[
         theZipFileName last == $/ ifFalse:[
@@ -4414,32 +4398,27 @@
     zipEntry setModificationTimeAndDateToNow.
 
     data notEmptyOrNil ifTrue:[
-        "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
-        zipEntry crc32:(ZipStream crc32BytesIn:data).
+        "/ crc32 is always required (not as written in docu to be zero in case of uncompressed mode)
+        zipEntry crc32:(ZipStream crc32BytesIn:data from:1 to:data size crc:0).
     ].
     (isDirectory not and:[ theCompressMethod == COMPRESSION_DEFLATED ]) ifTrue:[
-        | tmpCompressedData  tmpCompressedDataSize |
-
-        tmpCompressedData := ByteArray new:(data size + 16).
-        tmpCompressedDataSize := ZipStream compress:data into:tmpCompressedData.
-        zipEntry compressedSize:(tmpCompressedDataSize - 6).
-        theCompressedData := tmpCompressedData copyFrom:3.
-    ] ifFalse:[
-        theCompressMethod == COMPRESSION_STORED ifTrue:[
-            zipEntry compressedSize:zipEntry uncompressedSize.
-            theCompressedData := data.
-        ] ifFalse:[
-            self error
-            "/ cannot happen
-        ].
+        |tmpCompressedDataSize|
+
+        theCompressedData := ByteArray new:(data size + 16).
+        tmpCompressedDataSize := ZipStream compress:data into:theCompressedData.
+        zipEntry compressedSize:tmpCompressedDataSize - 6.
+        compressedDataOffset := 3.
+    ] ifFalse:["theCompressMethod == COMPRESSION_STORED"
+        zipEntry compressedSize:zipEntry uncompressedSize.
+        theCompressedData := data.
+        compressedDataOffset := 1.
     ].
     
     "/ ensure that the file position is at the end
-    
     file setToEnd.
     zipEntry writeTo:file.
     theCompressedData notNil ifTrue:[
-        file nextPutBytes:zipEntry compressedSize from:theCompressedData.
+        file nextPutBytes:zipEntry compressedSize from:theCompressedData startingAt:compressedDataOffset.
     ].
     self addMember:zipEntry.
 
@@ -4470,7 +4449,7 @@
     theCompressMethod := theCompressMethodArg.
 
     ((theCompressMethod == COMPRESSION_DEFLATED) 
-    or:[ theCompressMethod == COMPRESSION_STORED ]) ifFalse:[
+     or:[theCompressMethod == COMPRESSION_STORED]) ifFalse:[
         UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
         "/ if proceeded, write as uncompressed
         theCompressMethod := COMPRESSION_STORED
@@ -4480,7 +4459,6 @@
     theZipFileName := self validZipFileNameFrom:nameOfFileInArchive. 
 
     zipEntry fileName: theZipFileName.
-    zipEntry fileNameLength: theZipFileName size.
     zipEntry uncompressedSize: 0.
 
     zipEntry compressionMethod: theCompressMethod.
@@ -4807,6 +4785,9 @@
 !
 
 fileNameLength
+    fileNameLength isNil ifTrue:[
+        ^ fileName size.
+    ].
     ^ fileNameLength
 !
 
@@ -4916,14 +4897,13 @@
     crc32 := 0.
     compressedSize := 0.
     uncompressedSize := 0.
-    fileNameLength := 0.
     extraFieldLength := 0.
     fileCommentLength := 0.
     diskNumberStart := 0.
     internalFileAttributes := 0.
     externalFileAttributes := 0.
     relativeLocalHeaderOffset := 0.
-    fileName := nil.
+    fileName := fileNameLength := nil.
     extraField := nil.
     fileComment := nil.
     dataStart := 0.
@@ -5023,7 +5003,7 @@
         nextPutInt32LSB:crc32;
         nextPutInt32LSB:compressedSize;
         nextPutInt32LSB:uncompressedSize;
-        nextPutInt16LSB:fileNameLength;
+        nextPutInt16LSB:self fileNameLength;
         nextPutInt16LSB:extraFieldLength;
         nextPutAll:fileName.
 
@@ -5053,7 +5033,7 @@
     readPosition := 0.
 
     zipEntry compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-        compressingStream := ZipStream readOpenAsZipStreamOn:zipFileStream.
+        compressingStream := ZipStream readOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
     ] ifFalse:[
         compressingStream := zipFileStream.
         compressingStream text.
@@ -5142,7 +5122,7 @@
 
     zipEntry compressedSize:(zipFileStream position) - startDataPosition.
 
-    "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
+    "/ crc32 is always reqired (not as written in docu to be zero in case of uncompressed mode)
     zipEntry crc32:crc32.
     zipEntry uncompressedSize:uncompressedDataSize.
 
@@ -5162,7 +5142,7 @@
     uncompressedDataSize := 0.
 
     zipEntry compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-        compressingStream := ZipStream writeOpenAsZipStreamOn:zipFileStream.
+        compressingStream := ZipStream writeOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
     ] ifFalse:[
         compressingStream := zipFileStream.
     ].
--- a/ZipStream.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/ZipStream.st	Fri Nov 18 21:28:24 2016 +0000
@@ -237,64 +237,52 @@
 
 flatBytesIn:bytesIn from:start to:stop into:bytesOut doCompress:doCompress
     "compress or uncompress the bytesIn buffer into the bytesOut buffer; returns
-     the un/compressed size; on error an exception is raised
-    "
-    |errorNr size|
-
-     size := stop - start + 1.
+     the un/compressed size; on error an exception is raised"
 
-     (    (start between:1 and:stop)
-      and:[size > 0
-      and:[bytesIn  size >= stop
-      and:[bytesOut size >  0]]]
-     ) ifFalse:[
+    |errorNr|
+
+    ((start between:1 and:stop) and:[stop <= bytesIn size]) ifFalse:[
         ^ self error:'invalid argument size'
     ].
 
 %{
-    char *  __bytesIn  = 0;
-    uLong   __countIn  = 0;
-    char *  __bytesOut = 0;
-    uLong   __countOut = 0;
-
-    if( (__isSmallInteger(start)) && (__isSmallInteger(stop)) && (__isSmallInteger(size)) )
-    {
-        __countIn = __intVal( size );
+    if (__bothSmallInteger(start, stop)) {
+        uLong __start = __intVal(start);
+        uLong __stop = __intVal(stop);
+        uLong __countIn = __stop - __start + 1;
+        char *__bytesIn;
+        char *__bytesOut;
+        uLong __countOut;
 
         if (__isBytes(bytesIn)) {
-            __bytesIn = __ByteArrayInstPtr(bytesIn)->ba_element;
-        } else {
-            if (__isStringLike(bytesIn)) {
-                __bytesIn = __stringVal( bytesIn );
-            }
+            __bytesIn = __byteArrayVal(bytesIn);
+        } else if (__isStringLike(bytesIn)) {
+            __bytesIn = __stringVal(bytesIn);
         }
 
         if (__isBytes(bytesOut)) {
-            __bytesOut = __ByteArrayInstPtr(bytesOut)->ba_element;
-            __countOut = __byteArraySize( bytesOut );
-        } else {
-            if (__isString(bytesOut)) {
-                __bytesOut = __stringVal( bytesOut );
-                __countOut = __stringSize( bytesOut );
-            }
+            __bytesOut = __byteArrayVal(bytesOut);
+            __countOut = __byteArraySize(bytesOut);
+        } else if (__isString(bytesOut)) {
+            __bytesOut = __stringVal(bytesOut);
+            __countOut = __stringSize(bytesOut);
         }
-    }
+
+        if (__bytesOut && __bytesIn && __countOut > 0) {
+            int __result;
 
-    if( __bytesOut && __bytesIn )
-    {
-        int __result = Z_OK;
+            __bytesIn += __intVal(start) - 1;
 
-        __bytesIn += (__intVal( start)) - 1;
+            __result = (doCompress == true)
+                    ? compress  ((Byte *) __bytesOut, &__countOut, (Byte *) __bytesIn, __countIn)
+                    : uncompress((Byte *) __bytesOut, &__countOut, (Byte *) __bytesIn, __countIn);
 
-        if( doCompress == true )
-            __result   = compress  ( (Byte *) __bytesOut, & __countOut, (Byte *) __bytesIn, __countIn );
-        else
-            __result   = uncompress( (Byte *) __bytesOut, & __countOut, (Byte *) __bytesIn, __countIn );
+            if (__result == Z_OK) {
+                RETURN(__MKSMALLINT(__countOut));
+            }
 
-        if( __result == Z_OK )
-            { RETURN(__MKSMALLINT(__countOut)); }
-
-        errorNr = __MKSMALLINT( __result );
+            errorNr = __MKSMALLINT(__result);
+        }
     }
 %}.
 
@@ -318,24 +306,27 @@
 !ZipStream class methodsFor:'ZipInterface compatibility - crc'!
 
 crc32Add:aCharacterOrByte crc:crc
-    "Update a running crc waCharacterOrByte
+    "Update a running crc with aCharacterOrByte
      and return the updated crc "
-%{
-    if( (__isInteger(crc)))     {
-	char __byte;
-	uLong  __crc;
+%{ /* NOCONTEXT */
+    if (__isInteger(crc)) {
+        int __int;
+        char __byte;
+        uLong  __crc;
 
-	if (__isCharacter(aCharacterOrByte)) {
-	    __byte = __smallIntegerVal(__characterVal(aCharacterOrByte));
-	} else if (__isSmallInteger(aCharacterOrByte)) {
-	    __byte = __intVal(aCharacterOrByte);
-	} else{
-	    goto err;
-	}
+        if (__isCharacter(aCharacterOrByte)) {
+            __int = __smallIntegerVal(__characterVal(aCharacterOrByte));
+        } else if (__isSmallInteger(aCharacterOrByte)) {
+            __int = __smallIntegerVal(aCharacterOrByte);
+        } else{
+            goto err;
+        }
+        if (__int < 0 || __int > 255) goto err;
+        __byte = __int;
 
-	__crc  = __unsignedLongIntVal( crc );
-	__crc = crc32(__crc, (Byte *) &__byte, 1 );
-	RETURN( __MKUINT(__crc) );
+        __crc  = __unsignedLongIntVal( crc );
+        __crc = crc32(__crc, (Byte *) &__byte, 1 );
+        RETURN( __MKUINT(__crc) );
     }
 err:;
 %}.
@@ -343,52 +334,17 @@
     ^ self error:'invalid argument'
 !
 
-crc32BytesIn:bytesIn
-    "compute crc with the bytes buf[1.. bytesIn size]
-     and return the crc
-    "
-    ^ self crc32BytesIn:bytesIn from:1
-!
-
-crc32BytesIn:bytesIn crc:aCrc
-    "Update a running crc with the bytes buf[1.. bytesIn size]
-     and return the updated
-    "
-    ^ self crc32BytesIn:bytesIn from:1 crc:aCrc
-!
-
-crc32BytesIn:bytesIn from:start
-    "compute crc with the bytes buf[start.. bytesIn size]
-     and return the crc
-    "
-    ^ self crc32BytesIn:bytesIn from:start to:(bytesIn size)
-!
-
-crc32BytesIn:bytesIn from:start crc:aCrc
-    "Update a running crc with the bytes buf[start.. bytesIn size]
-     and return the updated
-    "
-    ^ self crc32BytesIn:bytesIn from:start to:(bytesIn size) crc:aCrc
-!
-
-crc32BytesIn:bytesIn from:start to:stop
-    "compute crc with the bytes buf[start.. stop]
-     and return the crc
-    "
-    ^ self crc32BytesIn:bytesIn from:start to:stop crc:0
-!
-
 crc32BytesIn:bytesIn from:start to:stop crc:crc
     "Update a running crc with the bytes buf[start.. stop]
      and return the updated crc"
 
-%{
-    if (__isInteger(crc) && __isSmallInteger(start) && __isSmallInteger(stop)) {
+%{ /* NOCONTEXT */
+    if (__isInteger(crc) && __bothSmallInteger(start, stop)) {
         char * __bytes  = 0;
         unsigned int __size;
         uLong  __crc  = __unsignedLongIntVal( crc );
-        uInt   __start = __intVal( start );
-        uInt   __stop = __intVal( stop );
+        int   __start = __intVal( start );
+        int   __stop = __intVal( stop );
 
         if (__isBytes(bytesIn)) {
             __bytes = __byteArrayVal(bytesIn);
@@ -400,12 +356,9 @@
             goto err;
         }
 
-
-        if (__start < 1 || __start > __size) goto err;
-        if (__stop < 1 || __stop > __size) goto err;
+        if (__start < 1 || __start > __stop || __stop > __size) goto err;
 
         __size = __stop - __start + 1;
-
         __bytes += __start - 1;
         __crc = crc32(__crc, (Byte *) __bytes, __size );
 
--- a/abbrev.stc	Fri Nov 18 21:26:37 2016 +0000
+++ b/abbrev.stc	Fri Nov 18 21:28:24 2016 +0000
@@ -13,7 +13,6 @@
 Bezier Bezier stx:libbasic2 'Graphics-Geometry-Objects' 0
 BinaryTree BinaryTree stx:libbasic2 'Collections-Ordered-Trees' 0
 BinaryTreeNode BinaryTreeNode stx:libbasic2 'Collections-Ordered-Trees' 0
-BitArray BitArray stx:libbasic2 'Collections-Arrayed' 0
 BoltLock BoltLock stx:libbasic2 'Kernel-Processes' 0
 CRC32Stream CRC32Stream stx:libbasic2 'System-Crypt-Hashing' 0
 CacheDictionary CacheDictionary stx:libbasic2 'Collections-Unordered' 0
@@ -111,7 +110,6 @@
 Trie Trie stx:libbasic2 'Collections-Ordered' 0
 URI URI stx:libbasic2 'Net-Resources' 0
 UUID UUID stx:libbasic2 'Net-Communication-Support' 0
-UnboxedIntegerArray UnboxedIntegerArray stx:libbasic2 'Collections-Arrayed' 0
 UndoSupport UndoSupport stx:libbasic2 'Views-Text' 0
 UnitConverter UnitConverter stx:libbasic2 'Magnitude-General' 0
 UnixPTYStream UnixPTYStream stx:libbasic2 'OS-Unix' 0
@@ -133,7 +131,6 @@
 Base64Coder Base64Coder stx:libbasic2 'System-Storage' 0
 BayesClassifier BayesClassifier stx:libbasic2 'Collections-Text-Support' 0
 Bezier2Segment Bezier2Segment stx:libbasic2 'Graphics-Geometry-Objects' 0
-BooleanArray BooleanArray stx:libbasic2 'Collections-Arrayed' 0
 CacheDictionaryWithFactory CacheDictionaryWithFactory stx:libbasic2 'Collections-Unordered' 0
 DecNetSocketAddress DecNetSocketAddress stx:libbasic2 'OS-Sockets' 0
 EpsonFX1PrinterStream EpsonFX1PrinterStream stx:libbasic2 'Interface-Printing' 8
@@ -144,23 +141,17 @@
 HostAddressLookupError HostAddressLookupError stx:libbasic2 'Kernel-Exceptions-Errors' 1
 HostNameLookupError HostNameLookupError stx:libbasic2 'Kernel-Exceptions-Errors' 1
 IPSocketAddress IPSocketAddress stx:libbasic2 'OS-Sockets' 2
-IntegerArray IntegerArray stx:libbasic2 'Collections-Arrayed' 0
 LazyCons LazyCons stx:libbasic2 'Collections-Linked' 0
 LineNumberReadStream LineNumberReadStream stx:libbasic2 'Streams-Misc' 0
-LongIntegerArray LongIntegerArray stx:libbasic2 'Collections-Arrayed' 0
 PostscriptPrinterStream PostscriptPrinterStream stx:libbasic2 'Interface-Printing' 8
 RandomGenerator RandomGenerator stx:libbasic2 'Magnitude-Numbers' 0
 SharedQueue SharedQueue stx:libbasic2 'Kernel-Processes' 0
-SignedIntegerArray SignedIntegerArray stx:libbasic2 'Collections-Arrayed' 0
-SignedLongIntegerArray SignedLongIntegerArray stx:libbasic2 'Collections-Arrayed' 0
-SignedWordArray SignedWordArray stx:libbasic2 'Collections-Arrayed' 0
 TSMultiTree TSMultiTree stx:libbasic2 'Collections-Ordered-Trees' 0
 TSMultiTreeNode TSMultiTreeNode stx:libbasic2 'Collections-Ordered-Trees-Private' 0
 TimedPromise TimedPromise stx:libbasic2 'Kernel-Processes' 0
 UDSocketAddress UDSocketAddress stx:libbasic2 'OS-Sockets' 0
 Unicode32String Unicode32String stx:libbasic2 'Collections-Text' 0
 ValueDoubleLink ValueDoubleLink stx:libbasic2 'Collections-Support' 0
-WordArray WordArray stx:libbasic2 'Collections-Arrayed' 0
 ZipArchive ZipArchive stx:libbasic2 'System-Support-FileFormats' 0
 ZipStream ZipStream stx:libbasic2 'System-Compress' 0
 FileURI FileURI stx:libbasic2 'Net-Resources' 0
--- a/bc.mak	Fri Nov 18 21:26:37 2016 +0000
+++ b/bc.mak	Fri Nov 18 21:28:24 2016 +0000
@@ -99,11 +99,10 @@
 $(OUTDIR)Bezier.$(O) Bezier.$(C) Bezier.$(H): Bezier.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BinaryTree.$(O) BinaryTree.$(C) BinaryTree.$(H): BinaryTree.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BinaryTreeNode.$(O) BinaryTreeNode.$(C) BinaryTreeNode.$(H): BinaryTreeNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)BitArray.$(O) BitArray.$(C) BitArray.$(H): BitArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)BoltLock.$(O) BoltLock.$(C) BoltLock.$(H): BoltLock.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CRC32Stream.$(O) CRC32Stream.$(C) CRC32Stream.$(H): CRC32Stream.st $(INCLUDE_TOP)\stx\libbasic\HashStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)CacheDictionary.$(O) CacheDictionary.$(C) CacheDictionary.$(H): CacheDictionary.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
-$(OUTDIR)CachedValue.$(O) CachedValue.$(C) CachedValue.$(H): CachedValue.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)CachedValue.$(O) CachedValue.$(C) CachedValue.$(H): CachedValue.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CharacterSet.$(O) CharacterSet.$(C) CharacterSet.$(H): CharacterSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Circle.$(O) Circle.$(C) Circle.$(H): Circle.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CollectingReadStream.$(O) CollectingReadStream.$(C) CollectingReadStream.$(H): CollectingReadStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
@@ -197,7 +196,6 @@
 $(OUTDIR)Trie.$(O) Trie.$(C) Trie.$(H): Trie.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
 $(OUTDIR)URI.$(O) URI.$(C) URI.$(H): URI.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)UUID.$(O) UUID.$(C) UUID.$(H): UUID.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\ByteArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnboxedIntegerArray.$(O) UnboxedIntegerArray.$(C) UnboxedIntegerArray.$(H): UnboxedIntegerArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)UndoSupport.$(O) UndoSupport.$(C) UndoSupport.$(H): UndoSupport.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)UnitConverter.$(O) UnitConverter.$(C) UnitConverter.$(H): UnitConverter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)UnixPTYStream.$(O) UnixPTYStream.$(C) UnixPTYStream.$(H): UnixPTYStream.st $(INCLUDE_TOP)\stx\libbasic\ExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\NonPositionableExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PipeStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
@@ -219,7 +217,6 @@
 $(OUTDIR)Base64Coder.$(O) Base64Coder.$(C) Base64Coder.$(H): Base64Coder.st $(INCLUDE_TOP)\stx\libbasic\AspectVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ObjectCoder.$(H) $(INCLUDE_TOP)\stx\libbasic\Visitor.$(H) $(INCLUDE_TOP)\stx\libbasic2\BaseNCoder.$(H) $(STCHDR)
 $(OUTDIR)BayesClassifier.$(O) BayesClassifier.$(C) BayesClassifier.$(H): BayesClassifier.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\TextClassifier.$(H) $(STCHDR)
 $(OUTDIR)Bezier2Segment.$(O) Bezier2Segment.$(C) Bezier2Segment.$(H): Bezier2Segment.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\LineSegment.$(H) $(STCHDR)
-$(OUTDIR)BooleanArray.$(O) BooleanArray.$(C) BooleanArray.$(H): BooleanArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic2\BitArray.$(H) $(STCHDR)
 $(OUTDIR)CacheDictionaryWithFactory.$(O) CacheDictionaryWithFactory.$(C) CacheDictionaryWithFactory.$(H): CacheDictionaryWithFactory.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic2\CacheDictionary.$(H) $(STCHDR)
 $(OUTDIR)DecNetSocketAddress.$(O) DecNetSocketAddress.$(C) DecNetSocketAddress.$(H): DecNetSocketAddress.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\SocketAddress.$(H) $(STCHDR)
 $(OUTDIR)EpsonFX1PrinterStream.$(O) EpsonFX1PrinterStream.$(C) EpsonFX1PrinterStream.$(H): EpsonFX1PrinterStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\PrinterStream.$(H) $(STCHDR)
@@ -230,23 +227,17 @@
 $(OUTDIR)HostAddressLookupError.$(O) HostAddressLookupError.$(C) HostAddressLookupError.$(H): HostAddressLookupError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic2\NameLookupError.$(H) $(STCHDR)
 $(OUTDIR)HostNameLookupError.$(O) HostNameLookupError.$(C) HostNameLookupError.$(H): HostNameLookupError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic2\NameLookupError.$(H) $(STCHDR)
 $(OUTDIR)IPSocketAddress.$(O) IPSocketAddress.$(C) IPSocketAddress.$(H): IPSocketAddress.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\SocketAddress.$(H) $(STCHDR)
-$(OUTDIR)IntegerArray.$(O) IntegerArray.$(C) IntegerArray.$(H): IntegerArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)LazyCons.$(O) LazyCons.$(C) LazyCons.$(H): LazyCons.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic2\Cons.$(H) $(STCHDR)
 $(OUTDIR)LineNumberReadStream.$(O) LineNumberReadStream.$(C) LineNumberReadStream.$(H): LineNumberReadStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\FilteringStream.$(H) $(STCHDR)
-$(OUTDIR)LongIntegerArray.$(O) LongIntegerArray.$(C) LongIntegerArray.$(H): LongIntegerArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)PostscriptPrinterStream.$(O) PostscriptPrinterStream.$(C) PostscriptPrinterStream.$(H): PostscriptPrinterStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\PrinterStream.$(H) $(STCHDR)
 $(OUTDIR)RandomGenerator.$(O) RandomGenerator.$(C) RandomGenerator.$(H): RandomGenerator.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\Random.$(H) $(STCHDR)
 $(OUTDIR)SharedQueue.$(O) SharedQueue.$(C) SharedQueue.$(H): SharedQueue.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\Queue.$(H) $(STCHDR)
-$(OUTDIR)SignedIntegerArray.$(O) SignedIntegerArray.$(C) SignedIntegerArray.$(H): SignedIntegerArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
-$(OUTDIR)SignedLongIntegerArray.$(O) SignedLongIntegerArray.$(C) SignedLongIntegerArray.$(H): SignedLongIntegerArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
-$(OUTDIR)SignedWordArray.$(O) SignedWordArray.$(C) SignedWordArray.$(H): SignedWordArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)TSMultiTree.$(O) TSMultiTree.$(C) TSMultiTree.$(H): TSMultiTree.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\TSTree.$(H) $(STCHDR)
 $(OUTDIR)TSMultiTreeNode.$(O) TSMultiTreeNode.$(C) TSMultiTreeNode.$(H): TSMultiTreeNode.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic2\TSTreeNode.$(H) $(STCHDR)
 $(OUTDIR)TimedPromise.$(O) TimedPromise.$(C) TimedPromise.$(H): TimedPromise.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\Promise.$(H) $(STCHDR)
 $(OUTDIR)UDSocketAddress.$(O) UDSocketAddress.$(C) UDSocketAddress.$(H): UDSocketAddress.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\SocketAddress.$(H) $(STCHDR)
 $(OUTDIR)Unicode32String.$(O) Unicode32String.$(C) Unicode32String.$(H): Unicode32String.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\FourByteString.$(H) $(STCHDR)
 $(OUTDIR)ValueDoubleLink.$(O) ValueDoubleLink.$(C) ValueDoubleLink.$(H): ValueDoubleLink.st $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\DoubleLink.$(H) $(STCHDR)
-$(OUTDIR)WordArray.$(O) WordArray.$(C) WordArray.$(H): WordArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic2\UnboxedIntegerArray.$(H) $(STCHDR)
 $(OUTDIR)ZipArchive.$(O) ZipArchive.$(C) ZipArchive.$(H): ZipArchive.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\ZipArchiveConstants.$(H) $(STCHDR)
 $(OUTDIR)ZipStream.$(O) ZipStream.$(C) ZipStream.$(H): ZipStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\CompressionStream.$(H) $(STCHDR)
 $(OUTDIR)FileURI.$(O) FileURI.$(C) FileURI.$(H): FileURI.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\HierarchicalURI.$(H) $(INCLUDE_TOP)\stx\libbasic2\URI.$(H) $(STCHDR)
--- a/extensions.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/extensions.st	Fri Nov 18 21:28:24 2016 +0000
@@ -73,11 +73,11 @@
     "return a soundex phonetic code or nil.
      Soundex returns similar codes for similar sounding words, making it a useful
      tool when searching for words where the correct spelling is unknown.
-     (read Knuth or search the web if you dont know what a soundex code is).
+     (read Knuth or search the web if you don't know what a soundex code is).
 
      Caveat: 'similar sounding words' means: 'similar sounding in ENGLISH'
-	     Please have a look at the other phonetic comparison operators found
-	     in PhoneticStringUtilities."
+             Please have a look at the other phonetic comparison operators found
+             in PhoneticStringUtilities."
 
     ^ PhoneticStringUtilities soundexCodeOf:self
 
@@ -1002,12 +1002,15 @@
 
 retractInterestIn:aspect for:someOne
     "remove the interest of someOne in the receiver changing aspect
-     (as installed with #expressInterestIn:for:sendBack:)."
+     (as installed with #expressInterestIn:for:sendBack:).
+     Answer the retracted interests."
 
     "/ for now, remove the interestConverter.
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
-    self retractInterestsForWhich:[:i | (i aspect == aspect) and:[i destination == someOne]]
+    ^ self retractInterestsForWhich:[:i | 
+            (i aspect == aspect) and:[i destination == someOne]
+        ]
 
     "
      |p b|
@@ -1071,24 +1074,26 @@
 
 retractInterests
     "remove all interests in the receiver changing aspect
-     (as installed with #expressInterestIn:for:sendBack:)."
+     (as installed with #expressInterestIn:for:sendBack:).
+     Answer the retraced interests."
 
     "/ for now, remove the interestConverter.
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
-    self retractInterestsForWhich:[:i | true ]
+    ^ self retractInterestsForWhich:[:i | true ]
 ! !
 
 !Object methodsFor:'dependents-interests'!
 
 retractInterestsFor:someOne
     "remove the interest of someOne in the receiver
-     (as installed with #onChangeSend:to:)."
+     (as installed with #onChangeSend:to:).
+     Answer the retracted interests."
 
     "/ for now, remove the interestConverter.
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
-    self retractInterestsForWhich:[:i | i destination == someOne ]
+    ^ self retractInterestsForWhich:[:i | i destination == someOne ]
 
     "
      |p b|
@@ -1131,7 +1136,8 @@
 
 retractInterestsForWhich:aBlock
     "remove all interests in the receiver changing aspect
-     (as installed with #expressInterestIn:for:sendBack:)."
+     (as installed with #expressInterestIn:for:sendBack:).
+     Answer the retracted interests."
 
     "/ for now, remove the interestConverter.
     "/ In the future, a more intelligent DependencyCollection class is planned for
@@ -1140,29 +1146,32 @@
 
     deps := self interests.
     deps size ~~ 0 ifTrue:[
-	"/ cannot removeDependent within the loop - the interests collection rehashes
-	coll := OrderedCollection new.
-	deps do:[:dep |
-	    dep isInterestConverter ifTrue:[
-		(aBlock value:dep) ifTrue:[coll add:dep].
-	    ]
-	].
-	coll do:[:dep |
-	    self removeInterest:dep.
-	].
+        "/ cannot removeDependent within the loop - the interests collection rehashes
+        coll := IdentitySet new.
+        deps do:[:dep |
+            dep isInterestConverter ifTrue:[
+                (aBlock value:dep) ifTrue:[coll add:dep].
+            ]
+        ].
+        coll do:[:dep |
+            self removeInterest:dep.
+        ].
+        ^ coll.
     ].
+    ^ #()
 ! !
 
 !Object methodsFor:'dependents-interests'!
 
 retractInterestsIn:aspect
     "remove all interests in the receiver changing aspect
-     (as installed with #expressInterestIn:for:sendBack:)."
+     (as installed with #expressInterestIn:for:sendBack:).
+     Answer the retracted interests."
 
     "/ for now, remove the interestConverter.
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
-    self retractInterestsForWhich:[:i | i aspect == aspect ]
+    ^ self retractInterestsForWhich:[:i | i aspect == aspect ]
 ! !
 
 !Object methodsFor:'Compatibility-Dolphin'!
--- a/libInit.cc	Fri Nov 18 21:26:37 2016 +0000
+++ b/libInit.cc	Fri Nov 18 21:28:24 2016 +0000
@@ -28,7 +28,6 @@
 extern void _Bezier_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BinaryTree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BinaryTreeNode_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _BitArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BoltLock_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CRC32Stream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CacheDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -126,7 +125,6 @@
 extern void _Trie_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _URI_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UUID_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _UnboxedIntegerArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UndoSupport_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UnitConverter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UnixPTYStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -148,7 +146,6 @@
 extern void _Base64Coder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BayesClassifier_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Bezier2Segment_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _BooleanArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CacheDictionaryWithFactory_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DecNetSocketAddress_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _EpsonFX1PrinterStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -159,23 +156,17 @@
 extern void _HostAddressLookupError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HostNameLookupError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _IPSocketAddress_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _IntegerArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LazyCons_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LineNumberReadStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _LongIntegerArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PostscriptPrinterStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _RandomGenerator_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SharedQueue_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SignedIntegerArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SignedLongIntegerArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SignedWordArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TSMultiTree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TSMultiTreeNode_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TimedPromise_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UDSocketAddress_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Unicode32String_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ValueDoubleLink_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _WordArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ZipArchive_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ZipStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FileURI_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -210,7 +201,6 @@
     _Bezier_Init(pass,__pRT__,snd);
     _BinaryTree_Init(pass,__pRT__,snd);
     _BinaryTreeNode_Init(pass,__pRT__,snd);
-    _BitArray_Init(pass,__pRT__,snd);
     _BoltLock_Init(pass,__pRT__,snd);
     _CRC32Stream_Init(pass,__pRT__,snd);
     _CacheDictionary_Init(pass,__pRT__,snd);
@@ -308,7 +298,6 @@
     _Trie_Init(pass,__pRT__,snd);
     _URI_Init(pass,__pRT__,snd);
     _UUID_Init(pass,__pRT__,snd);
-    _UnboxedIntegerArray_Init(pass,__pRT__,snd);
     _UndoSupport_Init(pass,__pRT__,snd);
     _UnitConverter_Init(pass,__pRT__,snd);
     _UnixPTYStream_Init(pass,__pRT__,snd);
@@ -330,7 +319,6 @@
     _Base64Coder_Init(pass,__pRT__,snd);
     _BayesClassifier_Init(pass,__pRT__,snd);
     _Bezier2Segment_Init(pass,__pRT__,snd);
-    _BooleanArray_Init(pass,__pRT__,snd);
     _CacheDictionaryWithFactory_Init(pass,__pRT__,snd);
     _DecNetSocketAddress_Init(pass,__pRT__,snd);
     _EpsonFX1PrinterStream_Init(pass,__pRT__,snd);
@@ -341,23 +329,17 @@
     _HostAddressLookupError_Init(pass,__pRT__,snd);
     _HostNameLookupError_Init(pass,__pRT__,snd);
     _IPSocketAddress_Init(pass,__pRT__,snd);
-    _IntegerArray_Init(pass,__pRT__,snd);
     _LazyCons_Init(pass,__pRT__,snd);
     _LineNumberReadStream_Init(pass,__pRT__,snd);
-    _LongIntegerArray_Init(pass,__pRT__,snd);
     _PostscriptPrinterStream_Init(pass,__pRT__,snd);
     _RandomGenerator_Init(pass,__pRT__,snd);
     _SharedQueue_Init(pass,__pRT__,snd);
-    _SignedIntegerArray_Init(pass,__pRT__,snd);
-    _SignedLongIntegerArray_Init(pass,__pRT__,snd);
-    _SignedWordArray_Init(pass,__pRT__,snd);
     _TSMultiTree_Init(pass,__pRT__,snd);
     _TSMultiTreeNode_Init(pass,__pRT__,snd);
     _TimedPromise_Init(pass,__pRT__,snd);
     _UDSocketAddress_Init(pass,__pRT__,snd);
     _Unicode32String_Init(pass,__pRT__,snd);
     _ValueDoubleLink_Init(pass,__pRT__,snd);
-    _WordArray_Init(pass,__pRT__,snd);
     _ZipArchive_Init(pass,__pRT__,snd);
     _ZipStream_Init(pass,__pRT__,snd);
     _FileURI_Init(pass,__pRT__,snd);
--- a/stx_libbasic2.st	Fri Nov 18 21:26:37 2016 +0000
+++ b/stx_libbasic2.st	Fri Nov 18 21:28:24 2016 +0000
@@ -71,22 +71,24 @@
      are extended by myself.
      They are mandatory, because we need these packages as a prerequisite for loading and compiling.
      This method is generated automatically,
-     by searching along the inheritance chain of all of my classes."
+     by searching along the inheritance chain of all of my classes.
+     Please take a look at the #referencedPreRequisites method as well."
 
     ^ #(
-	#'stx:libbasic'    "AbstractNumberVector - superclass of HalfFloatArray"
+        #'stx:libbasic'    "AbstractNumberVector - superclass of HalfFloatArray"
     )
 !
 
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for compiling or loading,
+     These packages are NOT needed as a prerequisite for compiling or loading,
      however, a class from it may be referenced during execution and having it
      unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
      includes explicit checks for the package being present.
      This method is generated automatically,
-     by searching all classes (and their packages) which are referenced by my classes."
+     by searching all classes (and their packages) which are referenced by my classes.
+     Please also take a look at the #mandatoryPreRequisites method"
 
     ^ #(
     )
@@ -213,7 +215,6 @@
         Bezier
         BinaryTree
         BinaryTreeNode
-        BitArray
         BoltLock
         CRC32Stream
         CacheDictionary
@@ -311,7 +312,6 @@
         Trie
         URI
         UUID
-        UnboxedIntegerArray
         UndoSupport
         UnitConverter
         UnixPTYStream
@@ -333,7 +333,6 @@
         Base64Coder
         BayesClassifier
         Bezier2Segment
-        BooleanArray
         CacheDictionaryWithFactory
         DecNetSocketAddress
         EpsonFX1PrinterStream
@@ -344,23 +343,17 @@
         HostAddressLookupError
         HostNameLookupError
         IPSocketAddress
-        IntegerArray
         LazyCons
         LineNumberReadStream
-        LongIntegerArray
         PostscriptPrinterStream
         RandomGenerator
         SharedQueue
-        SignedIntegerArray
-        SignedLongIntegerArray
-        SignedWordArray
         TSMultiTree
         TSMultiTreeNode
         TimedPromise
         UDSocketAddress
         Unicode32String
         ValueDoubleLink
-        WordArray
         ZipArchive
         ZipStream
         FileURI
@@ -380,49 +373,49 @@
      if it has extensions."
 
     ^ #(
-	CharacterArray asKoelnerPhoneticCode
-	CharacterArray asSoundexCode
-	CharacterArray printf:
-	CharacterArray printf:on:
-	CharacterArray printfWith:
-	CharacterArray printfWith:with:
-	CharacterArray printfWith:with:with:
-	CharacterArray printfWith:with:with:with:
-	CharacterArray #'printf_formatArgCount'
-	CharacterArray #'printf_printArgFrom:to:withData:'
-	CharacterArray #'printf_printOn:withData:'
-	CharacterArray scanf:
-	CharacterArray #'scanf_scanArgFrom:to:format:'
-	CharacterArray sscanf:
-	Float absDecimalPrintOn:digits:
-	Float absPrintOn:digits:
-	Float absScientificPrintOn:digits:
-	Object addInterest:
-	Object asDoubleLink
-	Object expressInterestIn:for:sendBack:
-	Object interests
-	Object interestsFor:
-	Object onChangeEvaluate:
-	Object onChangeSend:to:
-	Object removeActionsForEvent:
-	Object removeActionsWithReceiver:
-	Object removeAllActionsWithReceiver:
-	Object removeInterest:
-	Object retractInterestIn:for:
-	Object retractInterests
-	Object retractInterestsFor:
-	Object retractInterestsForWhich:
-	Object retractInterestsIn:
-	Object trigger:
-	Object trigger:with:
-	Object triggerEvent:
-	Object triggerEvent:with:
-	Object triggerEvent:withArguments:
-	Object when:send:to:
-	Object when:send:to:with:
-	Object when:sendTo:
-	Stream collecting:
-	Stream selecting:
+        CharacterArray asKoelnerPhoneticCode
+        CharacterArray asSoundexCode
+        CharacterArray printf:
+        CharacterArray printf:on:
+        CharacterArray printfWith:
+        CharacterArray printfWith:with:
+        CharacterArray printfWith:with:with:
+        CharacterArray printfWith:with:with:with:
+        CharacterArray #'printf_formatArgCount'
+        CharacterArray #'printf_printArgFrom:to:withData:'
+        CharacterArray #'printf_printOn:withData:'
+        CharacterArray scanf:
+        CharacterArray #'scanf_scanArgFrom:to:format:'
+        CharacterArray sscanf:
+        Float absDecimalPrintOn:digits:
+        Float absPrintOn:digits:
+        Float absScientificPrintOn:digits:
+        Object addInterest:
+        Object asDoubleLink
+        Object expressInterestIn:for:sendBack:
+        Object interests
+        Object interestsFor:
+        Object onChangeEvaluate:
+        Object onChangeSend:to:
+        Object removeActionsForEvent:
+        Object removeActionsWithReceiver:
+        Object removeAllActionsWithReceiver:
+        Object removeInterest:
+        Object retractInterestIn:for:
+        Object retractInterests
+        Object retractInterestsFor:
+        Object retractInterestsForWhich:
+        Object retractInterestsIn:
+        Object trigger:
+        Object trigger:with:
+        Object triggerEvent:
+        Object triggerEvent:with:
+        Object triggerEvent:withArguments:
+        Object when:send:to:
+        Object when:send:to:with:
+        Object when:sendTo:
+        Stream collecting:
+        Stream selecting:
     )
 ! !
 
--- a/stx_libbasic2WINrc.rc	Fri Nov 18 21:26:37 2016 +0000
+++ b/stx_libbasic2WINrc.rc	Fri Nov 18 21:28:24 2016 +0000
@@ -3,7 +3,7 @@
 // automagically generated from the projectDefinition: stx_libbasic2.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     7,1,1,144
+  FILEVERSION     7,1,1,146
   PRODUCTVERSION  7,1,0,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
@@ -20,12 +20,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Additional Basic Classes (LIB)\0"
-      VALUE "FileVersion", "7.1.1.144\0"
+      VALUE "FileVersion", "7.1.1.146\0"
       VALUE "InternalName", "stx:libbasic2\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 2012\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "7.1.0.0\0"
-      VALUE "ProductDate", "Wed, 07 Sep 2016 13:41:55 GMT\0"
+      VALUE "ProductDate", "Fri, 14 Oct 2016 15:56:21 GMT\0"
     END
 
   END