Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 14 Jun 2016 08:57:11 +0100
branchjv
changeset 3967 875620210043
parent 3882 a013a37e2c3d (current diff)
parent 3966 d086178fcab2 (diff)
child 3969 adab0e032049
Merge
CompressionStreamTest.st
Make.proto
Make.spec
WinAPIFunction.st
bc.mak
libInit.cc
stx_libbasic2.st
--- a/.hgtags	Mon Jun 06 06:56:04 2016 +0200
+++ b/.hgtags	Tue Jun 14 08:57:11 2016 +0100
@@ -41,6 +41,8 @@
 7c0313875ccb013fc3b286d59e101e7153f9fdf3 expecco_2_7_5a
 7e02ad6db29edd8e180c79f65f20d42fb5b02dfa expecco_2_9_0
 7e02ad6db29edd8e180c79f65f20d42fb5b02dfa expecco_2_9_0_a
+7e02ad6db29edd8e180c79f65f20d42fb5b02dfa expecco_2_9_0_win75_lx36
+7e02ad6db29edd8e180c79f65f20d42fb5b02dfa expecco_2_9_1
 86122f38fc096357a5ab4acb1043548951777670 expecco_1_7_0rc8
 87b46aa9c1f8b80df869f1c0ceddcea809d96690 expecco_2_8_0
 87b46aa9c1f8b80df869f1c0ceddcea809d96690 expecco_2_8_0a
--- a/AppletalkSocketAddress.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/AppletalkSocketAddress.st	Tue Jun 14 08:57:11 2016 +0100
@@ -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 }"
 
 SocketAddress variableByteSubclass:#AppletalkSocketAddress
 	instanceVariableNames:''
@@ -83,7 +83,7 @@
 
 !AppletalkSocketAddress class methodsFor:'queries'!
 
-domainSymbol
+domain
 
     ^ #'AF_APPLETALK'
 !
@@ -157,5 +157,6 @@
 !AppletalkSocketAddress class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/AppletalkSocketAddress.st,v 1.10 2003-10-17 16:42:59 penk Exp $'
+    ^ '$Header$'
 ! !
+
--- a/BZip2Stream.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/BZip2Stream.st	Tue Jun 14 08:57:11 2016 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -28,8 +28,92 @@
  */
 
 #include <stdio.h>
+
+#ifdef WIN32
+// sigh - bzlib.h includes windows.h, which does not like ST/X definitions
+# undef Process
+# undef Processor
+# undef Context
+# undef Array
+# undef Date
+# undef Method
+# undef Delay
+# undef Character
+# undef String
+# undef Time
+# undef Signal
+# undef Set
+# undef Message
+# undef Rectangle
+# undef Block
+# undef Object
+# undef Point
+# undef INT
+# undef UINT
+# define NO_STDIO
+# if defined(__i386__) || defined(__x86__)
+#  define _X86_
+# endif
+#endif
+
 #include "bzlib.h"
 
+#ifdef WIN32
+# define INT  STX_INT
+# define UINT STX_UINT
+# ifdef STX_Process
+#  define Process STX_Process
+# endif
+# ifdef STX_Processor
+#  define Processor STX_Processor
+# endif
+# ifdef STX_Context
+#  define Context STX_Context
+# endif
+# ifdef STX_Array
+#  define Array STX_Array
+# endif
+# ifdef STX_Date
+#  define Date STX_Date
+# endif
+# ifdef STX_Method
+#  define Method STX_Method
+# endif
+# ifdef STX_Delay
+#  define Delay STX_Delay
+# endif
+# ifdef STX_Character
+#  define Character STX_Character
+# endif
+# ifdef STX_String
+#  define String STX_String
+# endif
+# ifdef STX_Time
+#  define Time STX_Time
+# endif
+# ifdef STX_Signal
+#  define Signal STX_Signal
+# endif
+# ifdef STX_Set
+#  define Set STX_Set
+# endif
+# ifdef STX_Message
+#  define Message STX_Message
+# endif
+# ifdef STX_Rectangle
+#  define Rectangle STX_Rectangle
+# endif
+# ifdef STX_Block
+#  define Block STX_Block
+# endif
+# ifdef STX_Object
+#  define Object STX_Object
+# endif
+# ifdef STX_Point
+#  define Point STXPoint
+# endif
+#endif
+
 typedef enum {
 	  e_opmode_unspecified          /* processing done */
 	, e_opmode_deflate              /* running deflate */
@@ -53,7 +137,7 @@
 copyright
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -100,52 +184,52 @@
 
     if( _zstreamObj != nil )
     {
-        int          _errorNo, _action;
-        unsigned int _bfsize;
-        zstream_s *  _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+	int          _errorNo, _action;
+	unsigned int _bfsize;
+	zstream_s *  _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
 
-        if( _zstream->op_mode != e_opmode_deflate )
-            RETURN( nil );
+	if( _zstream->op_mode != e_opmode_deflate )
+	    RETURN( nil );
 
-        _bfsize = _zstream->out_total;
+	_bfsize = _zstream->out_total;
 
-        if( _zstream->stream.state == NULL )
-        {
-            _zstream->op_mode = e_opmode_unspecified;
-            RETURN( nil );
-        }
-        _action = (__INST(hitEOF) == true) ? BZ_FINISH : BZ_RUN;        
+	if( _zstream->stream.state == NULL )
+	{
+	    _zstream->op_mode = e_opmode_unspecified;
+	    RETURN( nil );
+	}
+	_action = (__INST(hitEOF) == true) ? BZ_FINISH : BZ_RUN;
 
-        _zstream->stream.avail_out = _bfsize;
-        _zstream->stream.next_out  = _zstream->out_ref;
-        
-        _errorNo = BZ2_bzCompress( & _zstream->stream, _action );
+	_zstream->stream.avail_out = _bfsize;
+	_zstream->stream.next_out  = _zstream->out_ref;
+
+	_errorNo = BZ2_bzCompress( & _zstream->stream, _action );
 
-        if( _errorNo == BZ_STREAM_END )
-        {
-            _zstream->stream.avail_in = 0;
-            _zstream->stream.next_in  = NULL;
-            _errorNo = BZ2_bzCompressEnd( & _zstream->stream );
-        }
+	if( _errorNo == BZ_STREAM_END )
+	{
+	    _zstream->stream.avail_in = 0;
+	    _zstream->stream.next_in  = NULL;
+	    _errorNo = BZ2_bzCompressEnd( & _zstream->stream );
+	}
 
-        if(   (_errorNo == BZ_OK)
-           || (_errorNo == BZ_RUN_OK)
-           || (_errorNo == BZ_FINISH_OK)
-          )
-        {
-            if(   (_zstream->stream.avail_out != _bfsize)
-               || (_zstream->stream.avail_in  != 0)
-              )
-              RETURN( true );
+	if(   (_errorNo == BZ_OK)
+	   || (_errorNo == BZ_RUN_OK)
+	   || (_errorNo == BZ_FINISH_OK)
+	  )
+	{
+	    if(   (_zstream->stream.avail_out != _bfsize)
+	       || (_zstream->stream.avail_in  != 0)
+	      )
+	      RETURN( true );
 
-            RETURN( false );
-        }
-        errorNo = __MKSMALLINT( _errorNo );
+	    RETURN( false );
+	}
+	errorNo = __MKSMALLINT( _errorNo );
     }
 %}.
     errorNo ifNil:[
-        zstream ifNil:[self errorNotOpen].
-        self invalidArgument.
+	zstream ifNil:[self errorNotOpen].
+	self invalidArgument.
     ].
     self zerror:errorNo.
 !
@@ -163,23 +247,23 @@
 
     if( (_zstreamObj != nil) && __bothSmallInteger(blockSize100k, workFactor) )
     {
-        int         _errorNo;
-        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+	int         _errorNo;
+	zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
 
-        _zstream->op_mode = e_opmode_deflate;
+	_zstream->op_mode = e_opmode_deflate;
 
-        _errorNo = BZ2_bzCompressInit( & _zstream->stream
-                                     , __intVal( blockSize100k ), 0, __intVal( workFactor ) );
+	_errorNo = BZ2_bzCompressInit( & _zstream->stream
+				     , __intVal( blockSize100k ), 0, __intVal( workFactor ) );
 
-        if( _errorNo == BZ_OK )
-            RETURN( self );
+	if( _errorNo == BZ_OK )
+	    RETURN( self );
 
-        errorNo = __MKSMALLINT( _errorNo );
+	errorNo = __MKSMALLINT( _errorNo );
     }
 %}.
     errorNo ifNil:[
-        zstream ifNil:[ self errorNotOpen ].
-        self invalidArgument.
+	zstream ifNil:[ self errorNotOpen ].
+	self invalidArgument.
     ].
     self zerror:errorNo.
 !
@@ -330,20 +414,20 @@
 
     if( (_zstreamObj != nil) && __isSmallInteger(count) )
     {
-        int         _count;
-        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+	int         _count;
+	zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
 
-        if( (_count = __intVal( count )) > 0 )
-        {
-            char * _in_ref = _zstream->in_ref;
+	if( (_count = __intVal( count )) > 0 )
+	{
+	    char * _in_ref = _zstream->in_ref;
 
-            _zstream->stream.avail_in = _count;
-            _zstream->stream.next_in  = _in_ref;
-        } else {
-            _zstream->stream.avail_in = 0;
-            _zstream->stream.next_in  = NULL;
-        }
-        RETURN( self );
+	    _zstream->stream.avail_in = _count;
+	    _zstream->stream.next_in  = _in_ref;
+	} else {
+	    _zstream->stream.avail_in = 0;
+	    _zstream->stream.next_in  = NULL;
+	}
+	RETURN( self );
     }
 %}.
     zstream ifNil:[ self errorNotOpen ].
@@ -353,5 +437,5 @@
 !BZip2Stream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/BZip2Stream.st,v 1.11 2007-01-18 15:16:27 stefan Exp $'
+    ^ '$Header$'
 ! !
--- a/CompressionStreamTest.st	Mon Jun 06 06:56:04 2016 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,482 +0,0 @@
-"
- COPYRIGHT (c) 2002 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' }"
-
-TestCase subclass:#CompressionStreamTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'System-Compress'
-!
-
-!CompressionStreamTest class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 2002 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
-"
-    extracted testCases from CompressionStream
-"
-! !
-
-!CompressionStreamTest class methodsFor:'tests'!
-
-compress
-    "
-     self compress
-    "
-   |fileContents in zip out|
-
-   fileContents := 'symbols.stc' asFilename contentsOfEntireFile.
-
-   in  := fileContents readStream.
-   out := FileStream newFileNamed:'YYY.gz'.
-   out ifNil:[ ^ self ].
-   [ 
-      zip := ZipStream writeOpenOn:out.
-
-     [in atEnd] whileFalse:[ |buf|
-        buf := in nextAvailable:512.
-        buf do:[:n|
-            zip nextPut:n
-        ]
-     ].
-   ] ensure:[
-        zip notNil ifTrue:[ zip close ].
-        out isOpen ifTrue: [ out close ].
-   ].
-!
-
-compress:fn
-    "
-     self compress
-    "
-   |fileContents in zip out|
-
-   fileContents := fn asFilename contentsOfEntireFile.
-
-   in  := fileContents readStream.
-   out := FileStream newFileNamed:'YYY.gz'.
-   out ifNil:[ ^ self ].
-   [ 
-      zip := ZipStream writeOpenOn:out.
-
-     [in atEnd] whileFalse:[ |buf|
-        buf := in nextAvailable:512.
-        buf do:[:n|
-            zip nextPut:n
-        ]
-     ].
-   ] ensure:[
-        zip notNil ifTrue:[ zip close ].
-        out close.
-   ].
-!
-
-testUncompress
-    "
-     self testUncompress #(521755 686495 false)  #(521755 686495 false)
-    "
-    |stream zipStream contents contentsOfOriginal|
-
-    [
-        stream    := 'YYY.gz' asFilename readStream.
-        zipStream := ZipStream readOpenOn:stream.
-        contents  := zipStream contents.
-    ] ensure:[
-        zipStream notNil ifTrue:[zipStream close].
-        stream    notNil ifTrue:[stream close].
-    ]. 
-    stream := 'symbols.stc' asFilename readStream.
-    contentsOfOriginal := stream contentsOfEntireFile.
-    stream close.
-    ^ Array with: contents size
-            with: contentsOfOriginal size
-            with: contents = contentsOfOriginal.
-!
-
-testUncompress: fn
-    "
-     (self testUncompress: 'symbols.stc') inspect
-    "
-    |stream zipStream contents contentsOfOriginal|
-
-    self compress: fn.
-    [
-        stream    := 'YYY.gz' asFilename readStream.
-        zipStream := ZipStream readOpenOn:stream.
-        contents  := zipStream contents.
-    ] ensure:[
-        zipStream notNil ifTrue:[zipStream close].
-        stream    notNil ifTrue:[stream close].
-    ]. 
-    stream := fn asFilename readStream.
-    contentsOfOriginal := stream contentsOfEntireFile.
-    stream close.
-    ^ Array with: contents size
-            with: contentsOfOriginal size
-            with: contents = contentsOfOriginal.
-!
-
-uncompress
-    "
-     self uncompress
-    "
-    |stream zipStream contents|
-
-    [
-        stream    := 'YYY.gz' asFilename readStream.
-        zipStream := ZipStream readOpenOn:stream.
-        contents  := zipStream contents.
-    ] ensure:[
-        zipStream notNil ifTrue:[zipStream close].
-        (stream   notNil and: [stream isOpen]) ifTrue:[stream close].
-    ].        
-    ^ contents
-! !
-
-!CompressionStreamTest class methodsFor:'ttt'!
-
-compress:fn toFileNamed:aName
-    "
-    self compress:'symbols.stc' toFileNamed:'YYY'.
-    "
-    |sourceFile in zip out zipFile|
-
-    sourceFile := fn asFilename.
-    sourceFile exists ifFalse:[self error].
-
-    zipFile := aName asFilename.
-    zipFile := zipFile withSuffix:'gz'.
-    zipFile exists ifTrue:[ zipFile remove ].
-
-    in  := sourceFile readStream.
-    out := FileStream newFileNamed:zipFile.
-
-    [ 
-        in  := sourceFile readStream.
-        in binary.
-        out := FileStream newFileNamed:zipFile.
-        out binary.
-        zip := ZipStream writeOpenOn:out.
-        zip binary.
-
-        [in atEnd] whileFalse:[ |buf|
-            buf := in nextAvailable:512.
-            buf do:[:n|
-                zip nextPut:n
-            ]
-        ].
-    ] ensure:[
-        zip notNil ifTrue:[ zip close ].
-        in  notNil ifTrue:[ in  close ].
-        out notNil ifTrue:[ out close ].
-
-    ].
-    ^ zipFile
-!
-
-test
-"
-self test
-"
-    |zipFile srcFile oldContents newContents s|
-
-    srcFile := 'symbols.stc' asFilename.
-    zipFile := 'YYY'.
-
-    self compress:srcFile toFileNamed:zipFile.
-    newContents := self uncompressFileNamed:zipFile.
-    oldContents := srcFile binaryContentsOfEntireFile asString.
-    newContents := newContents asString.
-
-    oldContents keysAndValuesDo:[:i :v|
-        s := newContents at:i ifAbsent:nil.
-        v = s ifFalse:[
-            Transcript showCR:'#ERROR#'.
-self halt.
-            ^ self
-        ].
-        Transcript show:v.
-    ].
-    self halt.
-!
-
-uncompressFileNamed:aName
-    "
-    self uncompressFileNamed:'YYY'
-    "
-    |stream zipFile zipStream outStream c|
-
-    zipFile := aName asFilename.
-    zipFile := zipFile withSuffix:'gz'.
-
-    zipFile exists ifFalse:[ self error ].
-
-    [
-        stream    := zipFile readStream.
-        stream binary.
-
-        zipStream := ZipStream readOpenOn:stream.
-        zipStream binary.
-
-        outStream := #[] writeStream.
-
-        [ (c := zipStream next) notNil ] whileTrue:[
-            outStream nextPut:c
-        ].
-    ] ensure:[
-        zipStream notNil ifTrue:[zipStream close].
-        stream    notNil ifTrue:[stream close].
-    ]. 
-    ^ outStream contents
-! !
-
-!CompressionStreamTest methodsFor:'helpers'!
-
-doTest01:compressionStreamClass
-    "
-     ZipStream test
-     self test01_ZipStream
-    "
-   |original compressed contents in out zip|
-
-   original := 'smalltalk.rc' asFilename contentsOfEntireFile.
-
-   in := original readStream.
-
-   [ |b|
-        out := WriteStream on:(ByteArray new:10).
-        zip := compressionStreamClass writeOpenOn:out.
-
-        [in atEnd] whileFalse:[
-            zip nextPut:in next
-        ]
-   ] ensure:[ zip notNil ifTrue:[ zip close ] ].
-
-   compressed := out contents.
-   [ |b|
-        zip := compressionStreamClass readOpenOn:(compressed readStream).
-        out := String writeStream.
-
-        [ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
-
-   ] ensure:[
-        zip notNil ifTrue:[ zip close ].
-        contents := out contents.
-
-        Transcript showCR:(contents   size).
-        Transcript showCR:(compressed size).
-   ].
-
-   original = contents ifFalse:[
-        self error:'contents differs'.
-        ^ self
-   ].
-   Transcript showCR:'OK'.
-! !
-
-!CompressionStreamTest methodsFor:'tests'!
-
-test01_ZipStream
-    "
-     ZipStream test
-     self test01_ZipStream
-    "
-   self doTest01:ZipStream
-!
-
-test02_ZipStream
-    "
-     ZipStream testFile
-    "
-   |fileContents in zip out gzipCmd|
-
-   fileContents := 'smalltalk.rc' asFilename contentsOfEntireFile.
-
-   in  := fileContents readStream.
-   out := FileStream newFileNamed:'YYY.gz'.
-   out ifNil:[ ^ self ].
-
-   [ 
-      zip := ZipStream writeOpenOn:out.
-
-     [in atEnd] whileFalse:[ |buf|
-        buf := in nextAvailable:512.
-        buf do:[:n|
-            zip nextPut:n
-        ]
-     ].
-   ] ensure:[
-        zip notNil ifTrue:[ zip close ].
-        out close.
-   ].
-   gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
-
-   Transcript showCR:gzipCmd.
-   gzipCmd printCR.
-!
-
-test03_ZipStream_testUnixAgainstClass
-    "
-     CompressionStream doTestUnixAgainstClass
-    "
-   |stream time file zipCont cmdCont|
-
-   file := '/boot/vmlinuz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   time := Time millisecondsToRun:[ |zipStream|
-        zipStream := stream := zipCont := nil.
-        [
-            stream    := file readStream.
-            zipStream := BZip2Stream readOpenOn:stream.
-            zipCont   := zipStream contents.
-        ] ensure:[
-            zipStream notNil ifTrue:[zipStream close].
-            stream    notNil ifTrue:[stream close].
-        ].
-   ].
-   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
-
-   time := Time millisecondsToRun:[ |command|
-        cmdCont := stream := nil.
-        [
-            command := 'gunzip < ' , file pathName.
-            stream  := PipeStream readingFrom:command.
-            cmdCont := stream contentsOfEntireFile.
-
-        ] ensure:[
-            stream notNil ifTrue:[stream close].
-        ]
-   ].
-   Transcript showCR:('UNIX  Time : %1  Size: %2' bindWith:time with:(cmdCont size)).
-
-   cmdCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
-                    ifFalse:[ self error:'contents differs' ].
-!
-
-test04_ZipStream_NextN
-    "
-        CompressionStream doTestNextN
-    "
-   |stream time file zipCont nxtCont|
-
-   file := '/boot/vmlinuz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   time := Time millisecondsToRun:[ |zipStream|
-        zipStream := stream := zipCont := nil.
-        [
-            stream    := file readStream.
-            zipStream := BZip2Stream readOpenOn:stream.
-            zipCont   := zipStream contents.
-        ] ensure:[
-            zipStream notNil ifTrue:[zipStream close].
-            stream    notNil ifTrue:[stream close].
-        ].
-   ].
-   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
-
-   time := Time millisecondsToRun:[ |zipStream wstream|
-        zipStream := stream := nxtCont := nil.
-        [
-            stream    := file readStream.
-            wstream   := String writeStream.
-            zipStream := BZip2Stream readOpenOn:stream.
-
-            [zipStream atEnd] whileFalse:[
-                wstream nextPutAll:(zipStream next:117)
-            ].
-            nxtCont := wstream contents.
-        ] ensure:[
-            zipStream notNil ifTrue:[zipStream close].
-            stream    notNil ifTrue:[stream close].
-        ].
-   ].
-   Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
-
-   nxtCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
-                    ifFalse:[ self error:'contents differs' ].
-!
-
-test04_ZipStream_SkipN
-"
-    CompressionStream doTestSkipN
-"
-   |stream time file skpCont nxtCont skip|
-
-   file := '/boot/vmlinuz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   skip := 6885379.
-
-   time := Time millisecondsToRun:[ |zipStream wstream|
-        zipStream := stream := nxtCont := nil.
-        [
-            stream    := file readStream.
-            wstream   := String writeStream.
-            zipStream := BZip2Stream readOpenOn:stream.
-            skip timesRepeat:[ zipStream next ].
-
-            [zipStream atEnd] whileFalse:[
-                wstream nextPutAll:(zipStream next:117)
-            ].
-            nxtCont := wstream contents.
-        ] ensure:[
-            zipStream notNil ifTrue:[zipStream close].
-            stream    notNil ifTrue:[stream close].
-        ].
-   ].
-
-   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
-
-   time := Time millisecondsToRun:[ |zipStream wstream|
-        zipStream := stream := skpCont := nil.
-        [
-            stream    := file readStream.
-            wstream   := '' writeStream.
-            zipStream := BZip2Stream readOpenOn:stream.
-            zipStream skip:skip.
-            [zipStream atEnd] whileFalse:[
-                wstream nextPutAll:(zipStream next:117)
-            ].
-            skpCont := wstream contents.
-        ] ensure:[
-            zipStream notNil ifTrue:[zipStream close].
-            stream    notNil ifTrue:[stream close].
-        ].
-   ].
-   Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(skpCont size)).
-
-   nxtCont = skpCont ifTrue:[ Transcript showCR:'OK' ]
-                    ifFalse:[ self error:'contents differs' ].
-! !
-
-!CompressionStreamTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStreamTest.st,v 1.4 2014-05-19 14:40:40 stefan Exp $'
-! !
-
--- a/DecNetSocketAddress.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/DecNetSocketAddress.st	Tue Jun 14 08:57:11 2016 +0100
@@ -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 }"
 
 SocketAddress variableByteSubclass:#DecNetSocketAddress
 	instanceVariableNames:''
@@ -54,7 +55,7 @@
 
 !DecNetSocketAddress class methodsFor:'queries'!
 
-domainSymbol
+domain
 
     ^ #'AF_DECnet'
 !
@@ -70,5 +71,6 @@
 !DecNetSocketAddress class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/DecNetSocketAddress.st,v 1.3 2003-07-09 15:31:37 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/DoubleLink.st	Tue Jun 14 08:57:11 2016 +0100
@@ -0,0 +1,82 @@
+"
+ COPYRIGHT (c) 2016 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 }"
+
+Link subclass:#DoubleLink
+	instanceVariableNames:'previousLink'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Collections-Support'
+!
+
+!DoubleLink class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2016 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
+"
+    this class provides the basic functionality for DoubleLink-nodes.
+    DoubleLinks are abstract in that they do not provide a place for storing 
+    something, just the link-chains. So concrete linkedList elements
+    must subclass from me and add their value slots.
+    
+    For more usability look at ValueDoubleLink or other subclasses.
+
+    [author:]
+        Claus Gittinger
+"
+! !
+
+!DoubleLink methodsFor:'accessing'!
+
+previousLink
+    "return the previous link"
+    
+    ^ previousLink
+!
+
+previousLink:aLInk
+    "set the previous link"
+
+    previousLink := aLInk.
+! !
+
+!DoubleLink methodsFor:'converting'!
+
+asDoubleLink
+    ^ self
+! !
+
+!DoubleLink class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/DoubleLinkedList.st	Tue Jun 14 08:57:11 2016 +0100
@@ -0,0 +1,486 @@
+"
+ COPYRIGHT (c) 2016 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 }"
+
+LinkedList subclass:#DoubleLinkedList
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Collections-Linked'
+!
+
+!DoubleLinkedList class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2016 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.
+"
+!
+
+examples
+"
+                                                                        [exBegin]
+    |l|
+
+    l := DoubleLinkedList new.
+    l addLast:'one'.
+    l addLast:'two'.
+    l addLast:'three'.
+    l addLast:'four'.
+    l inspect
+                                                                        [exEnd]
+
+
+                                                                        [exBegin]
+    |l|
+
+    l := LinkedList new.
+    l addLast:(ValueDoubleLink new value:'one').
+    l addLast:(ValueDoubleLink new value:'two').
+    l addLast:(ValueDoubleLink new value:'three').
+    l addLast:(ValueDoubleLink new value:'four').
+    (l at:3) value inspect.        'slow operation for large lists'.
+                                                                        [exEnd]
+
+
+                                                                        [exBegin]
+    |l link|
+
+    l := LinkedList new.
+    l addLast:(ValueDoubleLink new value:'one').
+    l addLast:(ValueDoubleLink new value:'two').
+    l addLast:(ValueDoubleLink new value:'three').
+    l addLast:(ValueDoubleLink new value:'four').
+    link := l removeFirst.
+    l addLast:link.
+    l inspect.
+                                                                        [exEnd]
+"
+! !
+
+!DoubleLinkedList methodsFor:'adding & removing'!
+
+add:aLinkOrAnyOtherObject
+    "adds aLink to the end of the sequence. Returns aLink"
+
+    |newLink|
+
+    newLink := aLinkOrAnyOtherObject asDoubleLink.
+
+    newLink nextLink:nil.
+    newLink previousLink:lastLink.
+    lastLink isNil ifTrue:[
+        firstLink := newLink
+    ] ifFalse: [
+        lastLink nextLink:newLink
+    ].
+    lastLink := newLink.
+    numberOfNodes := numberOfNodes + 1.
+    ^ newLink
+
+    "
+     |l e1 e2|
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e2 := l add:'two'.
+     self assert:(l firstLink == e1).
+     self assert:(l lastLink == e2).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink isNil).
+     self assert:(e1 previousLink isNil).
+     self assert:(e2 previousLink == e1).
+    "
+!
+
+add:aLinkOrAnyOtherObject after:aLinkOrValue
+    |linkToAddAfter newLink this nextLink|
+
+    aLinkOrValue asDoubleLink == aLinkOrValue ifTrue:[
+        linkToAddAfter := aLinkOrValue
+    ] ifFalse:[
+        this := firstLink.
+        [this notNil and:[this value ~~ aLinkOrAnyOtherObject]] whileTrue:[
+            this := this nextLink
+        ].
+        this isNil ifTrue:[
+            ^ self addLast:aLinkOrAnyOtherObject
+        ].
+        linkToAddAfter := this.
+    ].
+    newLink := aLinkOrAnyOtherObject asDoubleLink.
+
+    newLink nextLink:(nextLink := linkToAddAfter nextLink).
+    newLink previousLink:linkToAddAfter.
+    linkToAddAfter nextLink:newLink.
+    nextLink isNil ifTrue:[
+        lastLink := newLink
+    ] ifFalse:[
+        nextLink previousLink:newLink.
+    ].
+    numberOfNodes := numberOfNodes + 1.
+    ^ newLink
+
+    "
+     |l e1 e2 e3 e2_5 e4|
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e2 := l add:'two'.
+     e3 := l add:'three'.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     e2_5 := l add:'twoPointFife' after:e2.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e2_5).
+     self assert:(e2_5 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2_5).
+     self assert:(e2_5 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     e4 := l add:'four' after:e3.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e2_5).
+     self assert:(e2_5 nextLink == e3).
+     self assert:(e3 nextLink == e4).
+     self assert:(e4 nextLink isNil).
+
+     self assert:(l lastLink == e4).
+     self assert:(e4 previousLink == e3).
+     self assert:(e3 previousLink == e2_5).
+     self assert:(e2_5 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+    "
+!
+
+addFirst:aLinkOrAnyOtherObject
+    "adds aLink to the beginning of the sequence. Returns aLink"
+
+    |newLink|
+
+    newLink := aLinkOrAnyOtherObject asDoubleLink.
+
+    newLink nextLink:firstLink.
+    firstLink isNil ifTrue:[
+        lastLink := newLink
+    ] ifFalse: [
+        firstLink previousLink:newLink
+    ].
+    firstLink := newLink.
+    numberOfNodes := numberOfNodes + 1.
+    ^ newLink
+
+    "
+     |l e1 e0|
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e0 := l addFirst:'zero'.
+     self assert:(l firstLink == e0).
+     self assert:(l lastLink == e1).
+     self assert:(e0 nextLink == e1).
+     self assert:(e1 nextLink isNil).
+     self assert:(e0 previousLink isNil).
+     self assert:(e1 previousLink == e0).
+    "
+!
+
+remove:aLinkOrValue ifAbsent:exceptionBlock
+    "remove the argument, aLinkOrValue from the sequence and return it;
+     if absent, evaluate the exceptionBlock."
+
+    |linkToRemove this nextLink previousLink|
+
+    aLinkOrValue asDoubleLink == aLinkOrValue ifTrue:[
+        linkToRemove := aLinkOrValue
+    ] ifFalse:[
+        this := firstLink.
+        [this notNil and:[this value ~= aLinkOrValue]] whileTrue:[
+            this := this nextLink
+        ].
+        this isNil ifTrue:[
+            ^ exceptionBlock value
+        ].
+        linkToRemove := this.
+    ].
+
+    nextLink := linkToRemove nextLink.
+    previousLink := linkToRemove previousLink.
+    nextLink notNil ifTrue:[
+        nextLink previousLink:previousLink.
+    ] ifFalse:[
+        lastLink := previousLink
+    ].
+    previousLink notNil ifTrue:[
+        previousLink nextLink:nextLink.
+    ] ifFalse:[
+        firstLink := nextLink
+    ].
+    numberOfNodes := numberOfNodes - 1.
+    ^ linkToRemove
+
+    "
+     |l e1 e2 e3 e2_5 e4|
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e2 := l add:'two'.
+     e3 := l add:'three'.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l remove:'two'.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l remove:'one'.
+     self assert:(l firstLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink isNil).
+
+     l remove:'three'.
+     self assert:(l size == 0).
+    "
+!
+
+removeFirst
+    "remove and return the first node from the sequence"
+
+    |link|
+
+    firstLink isNil ifTrue:[
+        ^ self emptyCollectionError
+    ].
+    link := firstLink.
+    firstLink := firstLink nextLink.
+    firstLink isNil ifTrue:[
+        lastLink := nil
+    ] ifFalse:[ 
+        firstLink previousLink:nil.
+    ].        
+    link nextLink:nil.
+    link previousLink:nil.
+    numberOfNodes := numberOfNodes - 1.
+    ^ link
+
+    "
+     |l v1 v2 v3 e1 e2 e3 e2_5 e4|
+
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e2 := l add:'two'.
+     e3 := l add:'three'.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeFirst.
+     self assert:(l firstLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink isNil).
+
+     l removeFirst.
+     self assert:(l firstLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink isNil).
+
+     l removeFirst.
+     self assert:(l size == 0).
+    "
+!
+
+removeIdentical:aLinkOrValue ifAbsent:exceptionBlock
+    "remove the argument, aLinkOrValue from the sequence and return it;
+     if absent, evaluate the exceptionBlock."
+
+    |linkToRemove this nextLink previousLink|
+
+    aLinkOrValue asDoubleLink == aLinkOrValue ifTrue:[
+        linkToRemove := aLinkOrValue
+    ] ifFalse:[
+        this := firstLink.
+        [this notNil and:[this value ~~ aLinkOrValue]] whileTrue:[
+            this := this nextLink
+        ].
+        this isNil ifTrue:[
+            ^ exceptionBlock value
+        ].
+        linkToRemove := this.
+    ].
+
+    nextLink := linkToRemove nextLink.
+    previousLink := linkToRemove previousLink.
+    nextLink notNil ifTrue:[
+        nextLink previousLink:previousLink.
+    ] ifFalse:[
+        lastLink := previousLink
+    ].
+    previousLink notNil ifTrue:[
+        previousLink nextLink:nextLink.
+    ] ifFalse:[
+        firstLink := nextLink
+    ].
+    numberOfNodes := numberOfNodes - 1.
+    ^ linkToRemove
+
+    "
+     |l v1 v2 v3 e1 e2 e3 e2_5 e4|
+     l := DoubleLinkedList new.
+     e1 := l add:(v1 := 'one').
+     e2 := l add:(v2 := 'two').
+     e3 := l add:(v3 := 'three').
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeIdentical:v2.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeIdentical:v1.
+     self assert:(l firstLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink isNil).
+
+     l removeIdentical:v3.
+     self assert:(l size == 0).
+    "
+!
+
+removeLast
+    "remove and return the last node from the sequence"
+
+    |link|
+
+    lastLink isNil ifTrue:[
+        ^ self emptyCollectionError
+    ].
+    link := lastLink.
+    lastLink := lastLink previousLink.
+    lastLink isNil ifTrue:[
+        firstLink := nil
+    ] ifFalse:[ 
+        lastLink nextLink:nil.
+    ].        
+    link nextLink:nil.
+    link previousLink:nil.
+    numberOfNodes := numberOfNodes - 1.
+    ^ link
+
+    "
+     |l v1 v2 v3 e1 e2 e3 e2_5 e4|
+
+     l := DoubleLinkedList new.
+     e1 := l add:'one'.
+     e2 := l add:'two'.
+     e3 := l add:'three'.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink == e3).
+     self assert:(e3 nextLink isNil).
+
+     self assert:(l lastLink == e3).
+     self assert:(e3 previousLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeLast.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink == e2).
+     self assert:(e2 nextLink isNil).
+
+     self assert:(l lastLink == e2).
+     self assert:(e2 previousLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeLast.
+     self assert:(l firstLink == e1).
+     self assert:(e1 nextLink isNil).
+
+     self assert:(l lastLink == e1).
+     self assert:(e1 previousLink isNil).
+
+     l removeLast.
+     self assert:(l size == 0).
+    "
+! !
+
+!DoubleLinkedList class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+
--- a/HTMLPrinterStream.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/HTMLPrinterStream.st	Tue Jun 14 08:57:11 2016 +0100
@@ -126,6 +126,10 @@
 
 initialize
     super initialize.
+    
+    HTML::TreeBuilder isNil ifTrue:[
+        Smalltalk loadPackage:#'stx:goodies/webServer/htmlTree'
+    ].    
     bold := italic := false.
     htmlBuilder := HTML::TreeBuilder new.
     htmlBuilder body.
--- a/Make.proto	Mon Jun 06 06:56:04 2016 +0200
+++ b/Make.proto	Tue Jun 14 08:57:11 2016 +0100
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES=-I$(ZLIB_DIR) -I$(INCLUDE_TOP)/stx/libbasic
+LOCALINCLUDES=-I$(ZLIB_DIR) -I$(BZ2LIB_DIR) -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
@@ -127,10 +127,13 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)AVLTree.$(O) AVLTree.$(C) AVLTree.$(H): AVLTree.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)AbstractBackgroundJob.$(O) AbstractBackgroundJob.$(C) AbstractBackgroundJob.$(H): AbstractBackgroundJob.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ActiveObject.$(O) ActiveObject.$(C) ActiveObject.$(H): ActiveObject.st $(INCLUDE_TOP)/stx/libbasic/Lookup.$(H) $(INCLUDE_TOP)/stx/libbasic/Message.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ActorStream.$(O) ActorStream.$(C) ActorStream.$(H): ActorStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)Archiver.$(O) Archiver.$(C) Archiver.$(H): Archiver.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)AutoResizingOrderedCollection.$(O) AutoResizingOrderedCollection.$(C) AutoResizingOrderedCollection.$(H): AutoResizingOrderedCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)BIG5EncodedString.$(O) BIG5EncodedString.$(C) BIG5EncodedString.$(H): BIG5EncodedString.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/TwoByteString.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)BTree.$(O) BTree.$(C) BTree.$(H): BTree.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BaseNCoder.$(O) BaseNCoder.$(C) BaseNCoder.$(H): BaseNCoder.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) $(STCHDR)
 $(OUTDIR)Bezier.$(O) Bezier.$(C) Bezier.$(H): Bezier.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -144,45 +147,72 @@
 $(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)
+$(OUTDIR)CollectingSharedQueueStream.$(O) CollectingSharedQueueStream.$(C) CollectingSharedQueueStream.$(H): CollectingSharedQueueStream.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)CompressionStream.$(O) CompressionStream.$(C) CompressionStream.$(H): CompressionStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
+$(OUTDIR)Cons.$(O) Cons.$(C) Cons.$(H): Cons.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)ConsStream.$(O) ConsStream.$(C) ConsStream.$(H): ConsStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)Curve.$(O) Curve.$(C) Curve.$(H): Curve.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)DirectoryContents.$(O) DirectoryContents.$(C) DirectoryContents.$(H): DirectoryContents.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)DoubleLink.$(O) DoubleLink.$(C) DoubleLink.$(H): DoubleLink.st $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)EllipticalArc.$(O) EllipticalArc.$(C) EllipticalArc.$(H): EllipticalArc.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ExternalLong.$(O) ExternalLong.$(C) ExternalLong.$(H): ExternalLong.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)FileSorter.$(O) FileSorter.$(C) FileSorter.$(H): FileSorter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)FileText.$(O) FileText.$(C) FileText.$(H): FileText.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/StringCollection.$(H) $(STCHDR)
 $(OUTDIR)FilteringStream.$(O) FilteringStream.$(C) FilteringStream.$(H): FilteringStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)FourByteString.$(O) FourByteString.$(C) FourByteString.$(H): FourByteString.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) $(STCHDR)
 $(OUTDIR)Future.$(O) Future.$(C) Future.$(H): Future.st $(INCLUDE_TOP)/stx/libbasic/ProtoObject.$(H) $(STCHDR)
+$(OUTDIR)GBEncodedString.$(O) GBEncodedString.$(C) GBEncodedString.$(H): GBEncodedString.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/TwoByteString.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)GeometricSeries.$(O) GeometricSeries.$(C) GeometricSeries.$(H): GeometricSeries.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadOnlySequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)HTMLUtilities.$(O) HTMLUtilities.$(C) HTMLUtilities.$(H): HTMLUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HalfFloatArray.$(O) HalfFloatArray.$(C) HalfFloatArray.$(H): HalfFloatArray.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)HandlerCollection.$(O) HandlerCollection.$(C) HandlerCollection.$(H): HandlerCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)Heap.$(O) Heap.$(C) Heap.$(H): Heap.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)IdentityBag.$(O) IdentityBag.$(C) IdentityBag.$(H): IdentityBag.st $(INCLUDE_TOP)/stx/libbasic/Bag.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IncrementNotification.$(O) IncrementNotification.$(C) IncrementNotification.$(H): IncrementNotification.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)InterestConverterWithParameters.$(O) InterestConverterWithParameters.$(C) InterestConverterWithParameters.$(H): InterestConverterWithParameters.st $(INCLUDE_TOP)/stx/libbasic/InterestConverter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)InternalPipeStream.$(O) InternalPipeStream.$(C) InternalPipeStream.$(H): InternalPipeStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)Iterator.$(O) Iterator.$(C) Iterator.$(H): Iterator.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JISEncodedString.$(O) JISEncodedString.$(C) JISEncodedString.$(H): JISEncodedString.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/TwoByteString.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)KSCEncodedString.$(O) KSCEncodedString.$(C) KSCEncodedString.$(H): KSCEncodedString.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/TwoByteString.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)KeywordInContextIndexBuilder.$(O) KeywordInContextIndexBuilder.$(C) KeywordInContextIndexBuilder.$(H): KeywordInContextIndexBuilder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Lazy.$(O) Lazy.$(C) Lazy.$(H): Lazy.st $(INCLUDE_TOP)/stx/libbasic/ProtoObject.$(H) $(STCHDR)
 $(OUTDIR)LazyArray.$(O) LazyArray.$(C) LazyArray.$(H): LazyArray.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)LazyValue.$(O) LazyValue.$(C) LazyValue.$(H): LazyValue.st $(INCLUDE_TOP)/stx/libbasic/ProtoObject.$(H) $(STCHDR)
 $(OUTDIR)LineSegment.$(O) LineSegment.$(C) LineSegment.$(H): LineSegment.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)List.$(O) List.$(C) List.$(H): List.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)LoggingStream.$(O) LoggingStream.$(C) LoggingStream.$(H): LoggingStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
+$(OUTDIR)MacPlistBinaryDecoder.$(O) MacPlistBinaryDecoder.$(C) MacPlistBinaryDecoder.$(H): MacPlistBinaryDecoder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MappedCollection.$(O) MappedCollection.$(C) MappedCollection.$(H): MappedCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MessageChannel.$(O) MessageChannel.$(C) MessageChannel.$(H): MessageChannel.st $(INCLUDE_TOP)/stx/libbasic/Message.$(H) $(INCLUDE_TOP)/stx/libbasic/MessageSend.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Monitor.$(O) Monitor.$(C) Monitor.$(H): Monitor.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MultiReadStream.$(O) MultiReadStream.$(C) MultiReadStream.$(H): MultiReadStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)NameLookupError.$(O) NameLookupError.$(C) NameLookupError.$(H): NameLookupError.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) $(STCHDR)
+$(OUTDIR)NumberSet.$(O) NumberSet.$(C) NumberSet.$(H): NumberSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)OperationQueue.$(O) OperationQueue.$(C) OperationQueue.$(H): OperationQueue.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PhoneticStringUtilities.$(O) PhoneticStringUtilities.$(C) PhoneticStringUtilities.$(H): PhoneticStringUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PluggableDictionary.$(O) PluggableDictionary.$(C) PluggableDictionary.$(H): PluggableDictionary.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)PluggableSet.$(O) PluggableSet.$(C) PluggableSet.$(H): PluggableSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
 $(OUTDIR)Polygon.$(O) Polygon.$(C) Polygon.$(H): Polygon.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PowerSet.$(O) PowerSet.$(C) PowerSet.$(H): PowerSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PrinterStream.$(O) PrinterStream.$(C) PrinterStream.$(H): PrinterStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)PrintfScanf.$(O) PrintfScanf.$(C) PrintfScanf.$(H): PrintfScanf.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PriorityQueue.$(O) PriorityQueue.$(C) PriorityQueue.$(H): PriorityQueue.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Promise.$(O) Promise.$(C) Promise.$(H): Promise.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Queue.$(O) Queue.$(C) Queue.$(H): Queue.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Random.$(O) Random.$(C) Random.$(H): Random.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
+$(OUTDIR)RandomBlumBlumShub.$(O) RandomBlumBlumShub.$(C) RandomBlumBlumShub.$(H): RandomBlumBlumShub.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)RandomKISS.$(O) RandomKISS.$(C) RandomKISS.$(H): RandomKISS.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)RandomKISS2.$(O) RandomKISS2.$(C) RandomKISS2.$(H): RandomKISS2.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)RandomMT19937.$(O) RandomMT19937.$(C) RandomMT19937.$(H): RandomMT19937.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)RandomParkMiller.$(O) RandomParkMiller.$(C) RandomParkMiller.$(H): RandomParkMiller.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)RandomRDRand.$(O) RandomRDRand.$(C) RandomRDRand.$(H): RandomRDRand.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)RandomTT800.$(O) RandomTT800.$(C) RandomTT800.$(H): RandomTT800.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ReindexedCollection.$(O) ReindexedCollection.$(C) ReindexedCollection.$(H): ReindexedCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)RunArray.$(O) RunArray.$(C) RunArray.$(H): RunArray.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)SegmentedOrderedCollection.$(O) SegmentedOrderedCollection.$(C) SegmentedOrderedCollection.$(H): SegmentedOrderedCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)SelectingReadStream.$(O) SelectingReadStream.$(C) SelectingReadStream.$(H): SelectingReadStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)SequenceWithSentinel.$(O) SequenceWithSentinel.$(C) SequenceWithSentinel.$(H): SequenceWithSentinel.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)SequenceableCollectionSorter.$(O) SequenceableCollectionSorter.$(C) SequenceableCollectionSorter.$(H): SequenceableCollectionSorter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SerialPort.$(O) SerialPort.$(C) SerialPort.$(H): SerialPort.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/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)SharedCollection.$(O) SharedCollection.$(C) SharedCollection.$(H): SharedCollection.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Singleton.$(O) Singleton.$(C) Singleton.$(H): Singleton.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -201,35 +231,47 @@
 $(OUTDIR)TSTreeNode.$(O) TSTreeNode.$(C) TSTreeNode.$(H): TSTreeNode.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TerminalSession.$(O) TerminalSession.$(C) TerminalSession.$(H): TerminalSession.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Text.$(O) Text.$(C) Text.$(H): Text.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) $(STCHDR)
+$(OUTDIR)TextClassifier.$(O) TextClassifier.$(C) TextClassifier.$(H): TextClassifier.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TextStream.$(O) TextStream.$(C) TextStream.$(H): TextStream.st $(INCLUDE_TOP)/stx/libbasic/CharacterWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)TreeSet.$(O) TreeSet.$(C) TreeSet.$(H): TreeSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(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)
+$(OUTDIR)ValueLink.$(O) ValueLink.$(C) ValueLink.$(H): ValueLink.st $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)VirtualArray.$(O) VirtualArray.$(C) VirtualArray.$(H): VirtualArray.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)ZipArchiveConstants.$(O) ZipArchiveConstants.$(C) ZipArchiveConstants.$(H): ZipArchiveConstants.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(STCHDR)
 $(OUTDIR)stx_libbasic2.$(O) stx_libbasic2.$(C) stx_libbasic2.$(H): stx_libbasic2.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
 $(OUTDIR)AATree.$(O) AATree.$(C) AATree.$(H): AATree.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/BinaryTree.$(H) $(STCHDR)
 $(OUTDIR)AATreeNode.$(O) AATreeNode.$(C) AATreeNode.$(H): AATreeNode.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/BinaryTreeNode.$(H) $(STCHDR)
+$(OUTDIR)AppletalkSocketAddress.$(O) AppletalkSocketAddress.$(C) AppletalkSocketAddress.$(H): AppletalkSocketAddress.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)Arrow.$(O) Arrow.$(C) Arrow.$(H): Arrow.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/LineSegment.$(H) $(STCHDR)
 $(OUTDIR)ArrowedSpline.$(O) ArrowedSpline.$(C) ArrowedSpline.$(H): ArrowedSpline.st $(INCLUDE_TOP)/stx/libbasic/Geometric.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/Spline.$(H) $(STCHDR)
 $(OUTDIR)AutoResizingOrderedCollectionWithDefault.$(O) AutoResizingOrderedCollectionWithDefault.$(C) AutoResizingOrderedCollectionWithDefault.$(H): AutoResizingOrderedCollectionWithDefault.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic2/AutoResizingOrderedCollection.$(H) $(STCHDR)
+$(OUTDIR)BZip2Stream.$(O) BZip2Stream.$(C) BZip2Stream.$(H): BZip2Stream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/CompressionStream.$(H) $(STCHDR)
 $(OUTDIR)BackgroundJob.$(O) BackgroundJob.$(C) BackgroundJob.$(H): BackgroundJob.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)BackgroundPeriodicalJob.$(O) BackgroundPeriodicalJob.$(C) BackgroundPeriodicalJob.$(H): BackgroundPeriodicalJob.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)BackgroundQueueProcessingJob.$(O) BackgroundQueueProcessingJob.$(C) BackgroundQueueProcessingJob.$(H): BackgroundQueueProcessingJob.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)Base32Coder.$(O) Base32Coder.$(C) Base32Coder.$(H): Base32Coder.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)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)
 $(OUTDIR)FilteringLineStream.$(O) FilteringLineStream.$(C) FilteringLineStream.$(H): FilteringLineStream.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)HPLjetIIPrinterStream.$(O) HPLjetIIPrinterStream.$(C) HPLjetIIPrinterStream.$(H): HPLjetIIPrinterStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/PrinterStream.$(H) $(STCHDR)
+$(OUTDIR)HTMLPrinterStream.$(O) HTMLPrinterStream.$(C) HTMLPrinterStream.$(H): HTMLPrinterStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic2/PrinterStream.$(H) $(STCHDR)
 $(OUTDIR)HierarchicalURI.$(O) HierarchicalURI.$(C) HierarchicalURI.$(H): HierarchicalURI.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic2/URI.$(H) $(STCHDR)
 $(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)
@@ -243,6 +285,7 @@
 $(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)
--- a/Make.spec	Mon Jun 06 06:56:04 2016 +0200
+++ b/Make.spec	Tue Jun 14 08:57:11 2016 +0100
@@ -51,10 +51,13 @@
 STCWARNINGS=-warnNonStandard -warnUnused
 
 COMMON_CLASSES= \
+	AVLTree \
 	AbstractBackgroundJob \
+	ActiveObject \
 	ActorStream \
 	Archiver \
 	AutoResizingOrderedCollection \
+	BIG5EncodedString \
 	BTree \
 	BaseNCoder \
 	Bezier \
@@ -68,45 +71,72 @@
 	CharacterSet \
 	Circle \
 	CollectingReadStream \
+	CollectingSharedQueueStream \
 	CompressionStream \
+	Cons \
+	ConsStream \
 	Curve \
 	DirectoryContents \
+	DoubleLink \
 	EllipticalArc \
 	ExternalLong \
 	FileSorter \
+	FileText \
 	FilteringStream \
 	FourByteString \
 	Future \
+	GBEncodedString \
+	GeometricSeries \
 	HTMLUtilities \
 	HalfFloatArray \
+	HandlerCollection \
 	Heap \
 	IdentityBag \
 	IncrementNotification \
 	InterestConverterWithParameters \
+	InternalPipeStream \
 	Iterator \
 	JISEncodedString \
+	KSCEncodedString \
+	KeywordInContextIndexBuilder \
 	Lazy \
 	LazyArray \
+	LazyValue \
 	LineSegment \
 	List \
+	LoggingStream \
+	MacPlistBinaryDecoder \
 	MappedCollection \
+	MessageChannel \
 	Monitor \
 	MultiReadStream \
 	NameLookupError \
+	NumberSet \
 	OperationQueue \
 	PhoneticStringUtilities \
+	PluggableDictionary \
+	PluggableSet \
 	Polygon \
+	PowerSet \
 	PrinterStream \
 	PrintfScanf \
+	PriorityQueue \
 	Promise \
 	Queue \
 	Random \
+	RandomBlumBlumShub \
+	RandomKISS \
+	RandomKISS2 \
+	RandomMT19937 \
+	RandomParkMiller \
+	RandomRDRand \
 	RandomTT800 \
 	ReindexedCollection \
 	RunArray \
 	SegmentedOrderedCollection \
 	SelectingReadStream \
 	SequenceWithSentinel \
+	SequenceableCollectionSorter \
 	SerialPort \
 	SharedCollection \
 	Singleton \
@@ -125,35 +155,47 @@
 	TSTreeNode \
 	TerminalSession \
 	Text \
+	TextClassifier \
 	TextStream \
 	TreeSet \
+	Trie \
 	URI \
 	UUID \
 	UnboxedIntegerArray \
 	UndoSupport \
 	UnitConverter \
+	UnixPTYStream \
+	ValueLink \
 	VirtualArray \
 	ZipArchiveConstants \
 	stx_libbasic2 \
 	AATree \
 	AATreeNode \
+	AppletalkSocketAddress \
 	Arrow \
 	ArrowedSpline \
 	AutoResizingOrderedCollectionWithDefault \
+	BZip2Stream \
 	BackgroundJob \
 	BackgroundPeriodicalJob \
 	BackgroundQueueProcessingJob \
 	Base32Coder \
 	Base64Coder \
+	BayesClassifier \
 	Bezier2Segment \
 	BooleanArray \
 	CacheDictionaryWithFactory \
+	DecNetSocketAddress \
+	EpsonFX1PrinterStream \
 	FilteringLineStream \
+	HPLjetIIPrinterStream \
+	HTMLPrinterStream \
 	HierarchicalURI \
 	HostAddressLookupError \
 	HostNameLookupError \
 	IPSocketAddress \
 	IntegerArray \
+	LazyCons \
 	LineNumberReadStream \
 	LongIntegerArray \
 	PostscriptPrinterStream \
@@ -167,6 +209,7 @@
 	TimedPromise \
 	UDSocketAddress \
 	Unicode32String \
+	ValueDoubleLink \
 	WordArray \
 	ZipArchive \
 	ZipStream \
@@ -180,10 +223,13 @@
 
 
 COMMON_OBJS= \
+    $(OUTDIR_SLASH)AVLTree.$(O) \
     $(OUTDIR_SLASH)AbstractBackgroundJob.$(O) \
+    $(OUTDIR_SLASH)ActiveObject.$(O) \
     $(OUTDIR_SLASH)ActorStream.$(O) \
     $(OUTDIR_SLASH)Archiver.$(O) \
     $(OUTDIR_SLASH)AutoResizingOrderedCollection.$(O) \
+    $(OUTDIR_SLASH)BIG5EncodedString.$(O) \
     $(OUTDIR_SLASH)BTree.$(O) \
     $(OUTDIR_SLASH)BaseNCoder.$(O) \
     $(OUTDIR_SLASH)Bezier.$(O) \
@@ -197,45 +243,72 @@
     $(OUTDIR_SLASH)CharacterSet.$(O) \
     $(OUTDIR_SLASH)Circle.$(O) \
     $(OUTDIR_SLASH)CollectingReadStream.$(O) \
+    $(OUTDIR_SLASH)CollectingSharedQueueStream.$(O) \
     $(OUTDIR_SLASH)CompressionStream.$(O) \
+    $(OUTDIR_SLASH)Cons.$(O) \
+    $(OUTDIR_SLASH)ConsStream.$(O) \
     $(OUTDIR_SLASH)Curve.$(O) \
     $(OUTDIR_SLASH)DirectoryContents.$(O) \
+    $(OUTDIR_SLASH)DoubleLink.$(O) \
     $(OUTDIR_SLASH)EllipticalArc.$(O) \
     $(OUTDIR_SLASH)ExternalLong.$(O) \
     $(OUTDIR_SLASH)FileSorter.$(O) \
+    $(OUTDIR_SLASH)FileText.$(O) \
     $(OUTDIR_SLASH)FilteringStream.$(O) \
     $(OUTDIR_SLASH)FourByteString.$(O) \
     $(OUTDIR_SLASH)Future.$(O) \
+    $(OUTDIR_SLASH)GBEncodedString.$(O) \
+    $(OUTDIR_SLASH)GeometricSeries.$(O) \
     $(OUTDIR_SLASH)HTMLUtilities.$(O) \
     $(OUTDIR_SLASH)HalfFloatArray.$(O) \
+    $(OUTDIR_SLASH)HandlerCollection.$(O) \
     $(OUTDIR_SLASH)Heap.$(O) \
     $(OUTDIR_SLASH)IdentityBag.$(O) \
     $(OUTDIR_SLASH)IncrementNotification.$(O) \
     $(OUTDIR_SLASH)InterestConverterWithParameters.$(O) \
+    $(OUTDIR_SLASH)InternalPipeStream.$(O) \
     $(OUTDIR_SLASH)Iterator.$(O) \
     $(OUTDIR_SLASH)JISEncodedString.$(O) \
+    $(OUTDIR_SLASH)KSCEncodedString.$(O) \
+    $(OUTDIR_SLASH)KeywordInContextIndexBuilder.$(O) \
     $(OUTDIR_SLASH)Lazy.$(O) \
     $(OUTDIR_SLASH)LazyArray.$(O) \
+    $(OUTDIR_SLASH)LazyValue.$(O) \
     $(OUTDIR_SLASH)LineSegment.$(O) \
     $(OUTDIR_SLASH)List.$(O) \
+    $(OUTDIR_SLASH)LoggingStream.$(O) \
+    $(OUTDIR_SLASH)MacPlistBinaryDecoder.$(O) \
     $(OUTDIR_SLASH)MappedCollection.$(O) \
+    $(OUTDIR_SLASH)MessageChannel.$(O) \
     $(OUTDIR_SLASH)Monitor.$(O) \
     $(OUTDIR_SLASH)MultiReadStream.$(O) \
     $(OUTDIR_SLASH)NameLookupError.$(O) \
+    $(OUTDIR_SLASH)NumberSet.$(O) \
     $(OUTDIR_SLASH)OperationQueue.$(O) \
     $(OUTDIR_SLASH)PhoneticStringUtilities.$(O) \
+    $(OUTDIR_SLASH)PluggableDictionary.$(O) \
+    $(OUTDIR_SLASH)PluggableSet.$(O) \
     $(OUTDIR_SLASH)Polygon.$(O) \
+    $(OUTDIR_SLASH)PowerSet.$(O) \
     $(OUTDIR_SLASH)PrinterStream.$(O) \
     $(OUTDIR_SLASH)PrintfScanf.$(O) \
+    $(OUTDIR_SLASH)PriorityQueue.$(O) \
     $(OUTDIR_SLASH)Promise.$(O) \
     $(OUTDIR_SLASH)Queue.$(O) \
     $(OUTDIR_SLASH)Random.$(O) \
+    $(OUTDIR_SLASH)RandomBlumBlumShub.$(O) \
+    $(OUTDIR_SLASH)RandomKISS.$(O) \
+    $(OUTDIR_SLASH)RandomKISS2.$(O) \
+    $(OUTDIR_SLASH)RandomMT19937.$(O) \
+    $(OUTDIR_SLASH)RandomParkMiller.$(O) \
+    $(OUTDIR_SLASH)RandomRDRand.$(O) \
     $(OUTDIR_SLASH)RandomTT800.$(O) \
     $(OUTDIR_SLASH)ReindexedCollection.$(O) \
     $(OUTDIR_SLASH)RunArray.$(O) \
     $(OUTDIR_SLASH)SegmentedOrderedCollection.$(O) \
     $(OUTDIR_SLASH)SelectingReadStream.$(O) \
     $(OUTDIR_SLASH)SequenceWithSentinel.$(O) \
+    $(OUTDIR_SLASH)SequenceableCollectionSorter.$(O) \
     $(OUTDIR_SLASH)SerialPort.$(O) \
     $(OUTDIR_SLASH)SharedCollection.$(O) \
     $(OUTDIR_SLASH)Singleton.$(O) \
@@ -254,35 +327,47 @@
     $(OUTDIR_SLASH)TSTreeNode.$(O) \
     $(OUTDIR_SLASH)TerminalSession.$(O) \
     $(OUTDIR_SLASH)Text.$(O) \
+    $(OUTDIR_SLASH)TextClassifier.$(O) \
     $(OUTDIR_SLASH)TextStream.$(O) \
     $(OUTDIR_SLASH)TreeSet.$(O) \
+    $(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) \
+    $(OUTDIR_SLASH)ValueLink.$(O) \
     $(OUTDIR_SLASH)VirtualArray.$(O) \
     $(OUTDIR_SLASH)ZipArchiveConstants.$(O) \
     $(OUTDIR_SLASH)stx_libbasic2.$(O) \
     $(OUTDIR_SLASH)AATree.$(O) \
     $(OUTDIR_SLASH)AATreeNode.$(O) \
+    $(OUTDIR_SLASH)AppletalkSocketAddress.$(O) \
     $(OUTDIR_SLASH)Arrow.$(O) \
     $(OUTDIR_SLASH)ArrowedSpline.$(O) \
     $(OUTDIR_SLASH)AutoResizingOrderedCollectionWithDefault.$(O) \
+    $(OUTDIR_SLASH)BZip2Stream.$(O) \
     $(OUTDIR_SLASH)BackgroundJob.$(O) \
     $(OUTDIR_SLASH)BackgroundPeriodicalJob.$(O) \
     $(OUTDIR_SLASH)BackgroundQueueProcessingJob.$(O) \
     $(OUTDIR_SLASH)Base32Coder.$(O) \
     $(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) \
     $(OUTDIR_SLASH)FilteringLineStream.$(O) \
+    $(OUTDIR_SLASH)HPLjetIIPrinterStream.$(O) \
+    $(OUTDIR_SLASH)HTMLPrinterStream.$(O) \
     $(OUTDIR_SLASH)HierarchicalURI.$(O) \
     $(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) \
@@ -296,6 +381,7 @@
     $(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) \
--- a/UnixPTYStream.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/UnixPTYStream.st	Tue Jun 14 08:57:11 2016 +0100
@@ -9,7 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libbasic2' }"
 
+"{ NameSpace: Smalltalk }"
 
 PipeStream subclass:#UnixPTYStream
 	instanceVariableNames:''
@@ -188,16 +190,16 @@
      shellPath shellArgs mbx mbxName
      env shell args|
 
-    filePointer notNil ifTrue:[
+    handle notNil ifTrue:[
         "the pipe was already open ...
          this should (can) not happen."
         ^ self errorOpen
     ].
-
+        
     lastErrorNumber := nil.
     exitStatus := nil.
     exitSema := Semaphore new name:'pty exitSema'.
-
+    
     OperatingSystem isVMSlike ifTrue:[
         mbx := OperatingSystem createMailBox.
         mbx isNil ifTrue:[
@@ -256,16 +258,16 @@
                   ].
                ].
 
-    (osType ~~ #vms) ifTrue:[
+    (OperatingSystem isVMSlike) ifFalse:[
         OperatingSystem closeFd:slaveFd.
     ].
 
     pid notNil ifTrue:[
-        (osType == #win32) ifTrue:[
+        (OperatingSystem isMSWINDOWSlike) ifTrue:[
             self setFileDescriptor:masterFd mode:mode.
             "/ self setFileHandle:masterFd mode:mode
         ] ifFalse:[
-            (osType == #vms) ifTrue:[
+            (OperatingSystem isVMSlike) ifTrue:[
                 "/
                 "/ reopen the mailbox as a file ...
                 "/
@@ -279,7 +281,7 @@
         ]
     ] ifFalse:[
         lastErrorNumber := OperatingSystem currentErrorNumber.
-        osType == #vms ifTrue:[
+        OperatingSystem isVMSlike ifTrue:[
             OperatingSystem destroyMailBox:mbx
         ] ifFalse:[
             OperatingSystem closeFd:masterFd.
@@ -339,5 +341,6 @@
 !UnixPTYStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/UnixPTYStream.st,v 1.6 2003-02-27 14:50:38 stefan Exp $'
+    ^ '$Header$'
 ! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/ValueDoubleLink.st	Tue Jun 14 08:57:11 2016 +0100
@@ -0,0 +1,90 @@
+"{ Encoding: utf8 }"
+
+"
+ COPYRIGHT (c) 2016 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 }"
+
+DoubleLink subclass:#ValueDoubleLink
+	instanceVariableNames:'value'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Collections-Support'
+!
+
+!ValueDoubleLink class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2016 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
+"
+    this class provides DoubleLinks which can hold a value.
+    Instances are typically used as elements in a doubleLinkedList.
+
+    [see also:]
+        LinkedList DoubleLinkedList ValueLink Link
+        Collection OrderedCollection
+
+    [author:]
+        Claus Gittinger
+"
+! !
+
+!ValueDoubleLink class methodsFor:'instance creation'!
+
+value: aValue
+    "return a new instance with a value of aValue."
+
+    ^self basicNew value:aValue
+
+    "Created: 9.5.1996 / 16:12:19 / cg"
+! !
+
+!ValueDoubleLink methodsFor:'accessing'!
+
+value
+    ^ value
+!
+
+value:something
+    value := something.
+! !
+
+!ValueDoubleLink methodsFor:'printing'!
+
+printOn:aStream
+    aStream show:'%1(%2)' with:(self class name) with:self value.
+! !
+
+!ValueDoubleLink class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+
--- a/ValueLink.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/ValueLink.st	Tue Jun 14 08:57:11 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
 	      All Rights Reserved
@@ -9,6 +11,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libbasic2' }"
+
+"{ NameSpace: Smalltalk }"
 
 Link subclass:#ValueLink
 	instanceVariableNames:'value'
@@ -71,8 +76,15 @@
     value := anObject
 ! !
 
+!ValueLink methodsFor:'printing'!
+
+printOn:aStream
+    aStream show:'%1(%2)' with:(self class name) with:self value.
+! !
+
 !ValueLink class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ValueLink.st,v 1.13 1996-05-09 14:12:38 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/WinAPIFunction.st	Mon Jun 06 06:56:04 2016 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,259 +0,0 @@
-"
- COPYRIGHT (c) 1998 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.
-"
-
-
-ExternalFunction subclass:#WinAPIFunction
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'OS-Windows'
-!
-
-!WinAPIFunction primitiveDefinitions!
-%{
-typedef WINAPI INT  (*WINAPI_INTFUNC)();
-%}
-
-! !
-
-!WinAPIFunction class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1998 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
-"
-    WIN32 only:
-
-    Experimental class representing external (non-Smalltalk) WINAPI functions.
-    These will provide the same functionality and protocol as
-    regular externalFunctions, but use a different calling convention.
-
-    Warning: under construction.
-
-    [author:]
-        Claus Gittinger
-
-    [see also:]
-        ExternalAddress ExternalBytes
-"
-
-
-! !
-
-!WinAPIFunction methodsFor:'function calling'!
-
-call
-    "call the underlying C function, passing no argument.
-     The return value is interpreted as an integer 
-     (and must be converted to an externalBytes object,
-      if it is a pointer to something).
-
-     DANGER alert: This is an unprotected low-level entry.
-     Not for normal application usage.
-    "
-%{
-    WINAPI_INTFUNC func;
-    INT retVal;
-
-    func = (WINAPI_INTFUNC) __INST(code_);
-    if (func) {
-        retVal = (*func)();
-        RETURN (__MKINT(retVal));
-    }
-%}.
-    self primitiveFailed
-
-    "Created: / 18.6.1998 / 18:01:28 / cg"
-    "Modified: / 18.6.1998 / 18:04:48 / cg"
-!
-
-callWith:arg
-    "call the underlying C function, passing a single argument.
-     The argument arg is converted to a corresponding C data type,
-     as defined in the convertST_to_C() function.
-     The return value is interpreted as an integer 
-     (and must be converted to an externalBytes object,
-      if it is a pointer to something).
-
-     DANGER alert: This is an unprotected low-level entry.
-     Not for normal application usage.
-    "
-%{
-    WINAPI_INTFUNC func;
-    INT retVal;
-
-    func = (WINAPI_INTFUNC) __INST(code_);
-    if (func) {
-        retVal = (*func)(convertST_to_C(arg));
-        RETURN (__MKINT(retVal));
-    }
-%}.
-    self primitiveFailed
-
-    "Created: / 18.6.1998 / 18:04:30 / cg"
-    "Modified: / 18.6.1998 / 18:04:53 / cg"
-!
-
-callWith:arg1 with:arg2
-    "call the underlying C function, passing two args.
-     The arguments are converted to a corresponding C data type,
-     as defined in the convertST_to_C() function.
-     The return value is interpreted as an integer 
-     (and must be converted to an externalBytes object,
-      if it is a pointer to something).
-
-     DANGER alert: This is an unprotected low-level entry.
-     Not for normal application usage.
-    "
-%{
-    WINAPI_INTFUNC func;
-    INT retVal;
-
-    func = (WINAPI_INTFUNC) __INST(code_);
-    if (func) {
-        retVal = (*func)(convertST_to_C(arg1), convertST_to_C(arg2));
-        RETURN (__MKINT(retVal));
-    }
-%}.
-    self primitiveFailed
-
-    "Created: / 18.6.1998 / 18:05:07 / cg"
-!
-
-callWith:arg1 with:arg2 with:arg3
-    "call the underlying C function, passing three args.
-     The arguments are converted to a corresponding C data type,
-     as defined in the convertST_to_C() function.
-     The return value is interpreted as an integer 
-     (and must be converted to an externalBytes object,
-      if it is a pointer to something).
-
-     DANGER alert: This is an unprotected low-level entry.
-     Not for normal application usage.
-    "
-%{
-    WINAPI_INTFUNC func;
-    INT retVal;
-
-    func = (WINAPI_INTFUNC) __INST(code_);
-    if (func) {
-        retVal = (*func)(convertST_to_C(arg1), convertST_to_C(arg2), convertST_to_C(arg3));
-        RETURN (__MKINT(retVal));
-    }
-%}.
-    self primitiveFailed
-
-    "Created: / 18.6.1998 / 18:05:18 / cg"
-!
-
-callWithArguments:argArray
-    "call the underlying C function, passing up to 10 arguments.
-     The arguments are converted to a corresponding C data type,
-     as defined in the convertST_to_C() function.
-     The return value is interpreted as an integer 
-     (and must be converted to an externalBytes object,
-      if it is a pointer to something).
-
-     DANGER alert: This is an unprotected low-level entry.
-     Not for normal application usage.
-    "
-%{
-    WINAPI_INTFUNC func;
-#   define NUMARGS 10
-    INT args[NUMARGS];
-    INT retVal;
-    OBJ *ap;
-    INT convertST_to_C();
-
-    func = (WINAPI_INTFUNC) __INST(code_);
-    if (func && __isArrayLike(argArray)) {
-        int n = __arraySize(argArray);
-        int i;
-
-        if (n <= 10) {
-            ap = __ArrayInstPtr(argArray)->a_element;
-            for (i=0; i<NUMARGS; i++) {
-                args[i] = convertST_to_C(*ap++);
-            }
-        }
-        switch (n) {
-            case 0:
-                retVal = (*func)();
-                break;
-            case 1:
-                retVal = (*func)(args[0]);
-                break;
-            case 2:
-                retVal = (*func)(args[0], args[1]);
-                break;
-            case 3:
-                retVal = (*func)(args[0], args[1], args[2]);
-                break;
-            case 4:
-                retVal = (*func)(args[0], args[1], args[2], args[3]);
-                break;
-            case 5:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4]);
-                break;
-            case 6:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4], args[5]);
-                break;
-            case 7:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4], args[5], args[6]);
-                break;
-            case 8:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4], args[5], args[6], args[7]);
-                break;
-            case 9:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4], args[5], args[6], args[7],
-                                 args[8]);
-                break;
-            case 10:
-                retVal = (*func)(args[0], args[1], args[2], args[3],
-                                 args[4], args[5], args[6], args[7],
-                                 args[8], args[9]);
-                break;
-            default:
-                goto err;
-        }
-        RETURN (__MKINT(retVal));
-    }
-  err: ;
-%}.
-    self primitiveFailed
-
-    "Created: / 18.6.1998 / 18:05:46 / cg"
-! !
-
-!WinAPIFunction class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/libbasic2/WinAPIFunction.st,v 1.3 2005-07-13 14:22:19 cg Exp $'
-! !
--- a/abbrev.stc	Mon Jun 06 06:56:04 2016 +0200
+++ b/abbrev.stc	Tue Jun 14 08:57:11 2016 +0100
@@ -1,10 +1,13 @@
 # automagically generated by the project definition
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
+AVLTree AVLTree stx:libbasic2 'Collections-Ordered-Trees' 0
 AbstractBackgroundJob AbstractBackgroundJob stx:libbasic2 'System-Support' 0
+ActiveObject ActiveObject stx:libbasic2 'Kernel-Processes' 0
 ActorStream ActorStream stx:libbasic2 'Streams' 0
 Archiver Archiver stx:libbasic2 'System-Support-FileFormats' 0
 AutoResizingOrderedCollection AutoResizingOrderedCollection stx:libbasic2 'Collections-Sequenceable' 0
+BIG5EncodedString BIG5EncodedString stx:libbasic2 'Collections-Text' 0
 BTree BTree stx:libbasic2 'Collections-Ordered-Trees' 0
 BaseNCoder BaseNCoder stx:libbasic2 'System-Storage' 0
 Bezier Bezier stx:libbasic2 'Graphics-Geometry-Objects' 0
@@ -18,45 +21,73 @@
 CharacterSet CharacterSet stx:libbasic2 'Collections-Unordered' 0
 Circle Circle stx:libbasic2 'Graphics-Geometry-Objects' 0
 CollectingReadStream CollectingReadStream stx:libbasic2 'Streams-Misc' 0
+CollectingSharedQueueStream CollectingSharedQueueStream stx:libbasic2 'Streams' 0
 CompressionStream CompressionStream stx:libbasic2 'System-Compress' 0
+Cons Cons stx:libbasic2 'Collections-Linked' 0
+ConsStream ConsStream stx:libbasic2 'Collections-Linked' 0
 Curve Curve stx:libbasic2 'Graphics-Geometry-Objects' 0
 DirectoryContents DirectoryContents stx:libbasic2 'System-Support' 0
+DoubleLink DoubleLink stx:libbasic2 'Collections-Support' 0
+DoubleLinkedList DoubleLinkedList stx:libbasic2 'Collections-Linked' 0
 EllipticalArc EllipticalArc stx:libbasic2 'Graphics-Geometry-Objects' 0
 ExternalLong ExternalLong stx:libbasic2 'System-Support' 0
 FileSorter FileSorter stx:libbasic2 'Interface-Tools-File' 0
+FileText FileText stx:libbasic2 'Collections-Text' 0
 FilteringStream FilteringStream stx:libbasic2 'Streams-Misc' 0
 FourByteString FourByteString stx:libbasic2 'Collections-Text' 0
 Future Future stx:libbasic2 'Kernel-Processes' 0
+GBEncodedString GBEncodedString stx:libbasic2 'Collections-Text' 0
+GeometricSeries GeometricSeries stx:libbasic2 'Collections-Sequenceable' 0
 HTMLUtilities HTMLUtilities stx:libbasic2 'Net-Communication-Support' 0
 HalfFloatArray HalfFloatArray stx:libbasic2 'Collections-Arrayed' 0
+HandlerCollection HandlerCollection stx:libbasic2 'Kernel-Exceptions' 0
 Heap Heap stx:libbasic2 'Collections-Sequenceable' 0
 IdentityBag IdentityBag stx:libbasic2 'Collections-Unordered' 0
 IncrementNotification IncrementNotification stx:libbasic2 'Kernel-Exceptions-Notifications' 1
 InterestConverterWithParameters InterestConverterWithParameters stx:libbasic2 'Interface-Support-Models' 0
+InternalPipeStream InternalPipeStream stx:libbasic2 'Streams' 0
 Iterator Iterator stx:libbasic2 'Collections-Sequenceable' 0
 JISEncodedString JISEncodedString stx:libbasic2 'Collections-Text' 0
+KSCEncodedString KSCEncodedString stx:libbasic2 'Collections-Text' 0
+KeywordInContextIndexBuilder KeywordInContextIndexBuilder stx:libbasic2 'Collections-Support' 0
 Lazy Lazy stx:libbasic2 'Kernel-Processes' 0
 LazyArray LazyArray stx:libbasic2 'Collections-Arrayed' 0
+LazyValue LazyValue stx:libbasic2 'Kernel-Processes' 0
 LineSegment LineSegment stx:libbasic2 'Graphics-Geometry-Objects' 0
 List List stx:libbasic2 'Collections-Sequenceable' 0
+LoggingStream LoggingStream stx:libbasic2 'Streams-Misc' 0
+MacPlistBinaryDecoder MacPlistBinaryDecoder stx:libbasic2 'System-Support-FileFormats' 0
 MappedCollection MappedCollection stx:libbasic2 'Collections-Sequenceable' 0
+MessageChannel MessageChannel stx:libbasic2 'Kernel-Methods' 0
 Monitor Monitor stx:libbasic2 'Kernel-Processes' 0
 MultiReadStream MultiReadStream stx:libbasic2 'Streams-Misc' 0
 NameLookupError NameLookupError stx:libbasic2 'OS-Sockets' 1
+NumberSet NumberSet stx:libbasic2 'Collections-Ordered' 0
 OperationQueue OperationQueue stx:libbasic2 'Kernel-Processes' 0
 PhoneticStringUtilities PhoneticStringUtilities stx:libbasic2 'Collections-Text-Support' 0
+PluggableDictionary PluggableDictionary stx:libbasic2 'Collections-Unordered' 0
+PluggableSet PluggableSet stx:libbasic2 'Collections-Unordered' 0
 Polygon Polygon stx:libbasic2 'Graphics-Geometry-Objects' 0
+PowerSet PowerSet stx:libbasic2 'Collections-Unordered' 0
 PrinterStream PrinterStream stx:libbasic2 'Interface-Printing' 8
 PrintfScanf PrintfScanf stx:libbasic2 'System-Support' 0
+PriorityQueue PriorityQueue stx:libbasic2 'Collections-Ordered' 0
 Promise Promise stx:libbasic2 'Kernel-Processes' 0
 Queue Queue stx:libbasic2 'Collections-Ordered' 0
 Random Random stx:libbasic2 'Magnitude-Numbers' 0
+RandomBlumBlumShub RandomBlumBlumShub stx:libbasic2 'Magnitude-Numbers' 0
+RandomKISS RandomKISS stx:libbasic2 'Magnitude-Numbers' 0
+RandomKISS2 RandomKISS2 stx:libbasic2 'Magnitude-Numbers' 0
+RandomMT19937 RandomMT19937 stx:libbasic2 'Magnitude-Numbers' 0
+RandomParkMiller RandomParkMiller stx:libbasic2 'Magnitude-Numbers' 0
+RandomRDRand RandomRDRand stx:libbasic2 'Magnitude-Numbers' 0
 RandomTT800 RandomTT800 stx:libbasic2 'Magnitude-Numbers' 0
 ReindexedCollection ReindexedCollection stx:libbasic2 'Collections-Sequenceable' 0
 RunArray RunArray stx:libbasic2 'Collections-Sequenceable' 0
 SegmentedOrderedCollection SegmentedOrderedCollection stx:libbasic2 'Collections-Sequenceable' 0
 SelectingReadStream SelectingReadStream stx:libbasic2 'Streams-Misc' 0
 SequenceWithSentinel SequenceWithSentinel stx:libbasic2 'Collections-Sequenceable' 0
+SequenceableCollectionSorter SequenceableCollectionSorter stx:libbasic2 'Collections-Support' 0
 SerialPort SerialPort stx:libbasic2 'Streams-External' 0
 SharedCollection SharedCollection stx:libbasic2 'Collections-Support' 0
 Singleton Singleton stx:libbasic2 'System-Support' 1
@@ -75,35 +106,47 @@
 TSTreeNode TSTreeNode stx:libbasic2 'Collections-Ordered-Trees-Private' 0
 TerminalSession TerminalSession stx:libbasic2 'Views-TerminalViews' 0
 Text Text stx:libbasic2 'Collections-Text' 0
+TextClassifier TextClassifier stx:libbasic2 'Collections-Text-Support' 0
 TextStream TextStream stx:libbasic2 'Streams' 0
 TreeSet TreeSet stx:libbasic2 'Collections-Ordered-Trees' 0
+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
+ValueLink ValueLink stx:libbasic2 'Collections-Support' 0
 VirtualArray VirtualArray stx:libbasic2 'Collections-Arrayed' 0
 ZipArchiveConstants ZipArchiveConstants stx:libbasic2 'System-Support-FileFormats' 0
 stx_libbasic2 stx_libbasic2 stx:libbasic2 '* Projects & Packages *' 3
 AATree AATree stx:libbasic2 'Collections-Ordered-Trees' 0
 AATreeNode AATreeNode stx:libbasic2 'Collections-Ordered-Trees' 0
+AppletalkSocketAddress AppletalkSocketAddress stx:libbasic2 'OS-Sockets' 0
 Arrow Arrow stx:libbasic2 'Graphics-Geometry-Objects' 0
 ArrowedSpline ArrowedSpline stx:libbasic2 'Graphics-Geometry-Objects' 0
 AutoResizingOrderedCollectionWithDefault AutoResizingOrderedCollectionWithDefault stx:libbasic2 'Collections-Sequenceable' 0
+BZip2Stream BZip2Stream stx:libbasic2 'System-Compress' 0
 BackgroundJob BackgroundJob stx:libbasic2 'System-Support' 0
 BackgroundPeriodicalJob BackgroundPeriodicalJob stx:libbasic2 'System-Support' 0
 BackgroundQueueProcessingJob BackgroundQueueProcessingJob stx:libbasic2 'System-Support' 0
 Base32Coder Base32Coder stx:libbasic2 'System-Storage' 0
 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
 FilteringLineStream FilteringLineStream stx:libbasic2 'Streams-Misc' 0
+HPLjetIIPrinterStream HPLjetIIPrinterStream stx:libbasic2 'Interface-Printing' 8
+HTMLPrinterStream HTMLPrinterStream stx:libbasic2 'Interface-Printing' 8
 HierarchicalURI HierarchicalURI stx:libbasic2 'Net-Resources' 0
 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
@@ -117,6 +160,7 @@
 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
@@ -125,45 +169,3 @@
 HttpURI HttpURI stx:libbasic2 'Net-Resources' 0
 IPv6SocketAddress IPv6SocketAddress stx:libbasic2 'OS-Sockets' 2
 SftpURI SftpURI stx:libbasic2 'Net-Resources' 0
-AVLTree AVLTree stx:libbasic2 'Collections-Ordered-Trees' 0
-ActiveObject ActiveObject stx:libbasic2 'Kernel-Processes' 0
-AppletalkSocketAddress AppletalkSocketAddress stx:libbasic2 'OS-Sockets' 0
-BIG5EncodedString BIG5EncodedString stx:libbasic2 'Collections-Text' 0
-BZip2Stream BZip2Stream stx:libbasic2 'System-Compress' 0
-BayesClassifier BayesClassifier stx:libbasic2 'Collections-Text-Support' 0
-CollectingSharedQueueStream CollectingSharedQueueStream stx:libbasic2 'Streams' 0
-CompressionStreamTest CompressionStreamTest stx:libbasic2 'System-Compress' 1
-Cons Cons stx:libbasic2 'Collections-Linked' 0
-ConsStream ConsStream stx:libbasic2 'Collections-Linked' 0
-DecNetSocketAddress DecNetSocketAddress stx:libbasic2 'OS-Sockets' 0
-EpsonFX1PrinterStream EpsonFX1PrinterStream stx:libbasic2 'Interface-Printing' 8
-FileText FileText stx:libbasic2 'Collections-Text' 0
-GBEncodedString GBEncodedString stx:libbasic2 'Collections-Text' 0
-GeometricSeries GeometricSeries stx:libbasic2 'Collections-Sequenceable' 0
-HPLjetIIPrinterStream HPLjetIIPrinterStream stx:libbasic2 'Interface-Printing' 8
-HandlerCollection HandlerCollection stx:libbasic2 'Kernel-Exceptions' 0
-InternalPipeStream InternalPipeStream stx:libbasic2 'Streams' 0
-KSCEncodedString KSCEncodedString stx:libbasic2 'Collections-Text' 0
-KeywordInContextIndexBuilder KeywordInContextIndexBuilder stx:libbasic2 'Collections-Support' 0
-LazyCons LazyCons stx:libbasic2 'Collections-Linked' 0
-LazyValue LazyValue stx:libbasic2 'Kernel-Processes' 0
-LoggingStream LoggingStream stx:libbasic2 'Streams-Misc' 0
-MacPlistBinaryDecoder MacPlistBinaryDecoder stx:libbasic2 'System-Support-FileFormats' 0
-MessageChannel MessageChannel stx:libbasic2 'Kernel-Methods' 0
-NumberSet NumberSet stx:libbasic2 'Collections-Ordered' 0
-PluggableDictionary PluggableDictionary stx:libbasic2 'Collections-Unordered' 0
-PluggableSet PluggableSet stx:libbasic2 'Collections-Unordered' 0
-PowerSet PowerSet stx:libbasic2 'Collections-Unordered' 0
-PriorityQueue PriorityQueue stx:libbasic2 'Collections-Ordered' 0
-RandomBlumBlumShub RandomBlumBlumShub stx:libbasic2 'Magnitude-Numbers' 0
-RandomKISS RandomKISS stx:libbasic2 'Magnitude-Numbers' 0
-RandomKISS2 RandomKISS2 stx:libbasic2 'Magnitude-Numbers' 0
-RandomMT19937 RandomMT19937 stx:libbasic2 'Magnitude-Numbers' 0
-RandomParkMiller RandomParkMiller stx:libbasic2 'Magnitude-Numbers' 0
-RandomRDRand RandomRDRand stx:libbasic2 'Magnitude-Numbers' 0
-SequenceableCollectionSorter SequenceableCollectionSorter stx:libbasic2 'Collections-Support' 0
-TextClassifier TextClassifier stx:libbasic2 'Collections-Text-Support' 0
-Trie Trie stx:libbasic2 'Collections-Ordered' 0
-UnixPTYStream UnixPTYStream stx:libbasic2 'OS-Unix' 0
-ValueLink ValueLink stx:libbasic2 'Collections-Support' 0
-WinAPIFunction WinAPIFunction stx:libbasic2 'OS-Windows' 0
--- a/bc.mak	Mon Jun 06 06:56:04 2016 +0200
+++ b/bc.mak	Tue Jun 14 08:57:11 2016 +0100
@@ -43,15 +43,15 @@
 !endif
 
 
-LOCALINCLUDES=-I$(ZLIB_DIR) -I$(INCLUDE_TOP)\stx\libbasic
+LOCALINCLUDES=-I$(ZLIB_DIR) -I$(BZ2LIB_DIR) -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) $(COMMONSYMBOLS) -varPrefix=$(LIBNAME)
-LOCALLIBS=$(ZLIB_DIR)\$(ZLIB) $(WINSOCK_LIB)
+LOCALLIBS=$(ZLIB_DIR)\$(ZLIB) $(BZ2LIB) $(WINSOCK_LIB)
 
 OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
 
-ALL:: $(ZLIB) classLibRule
+ALL:: $(ZLIB) $(BZ2LIB) classLibRule
 
 classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
 
@@ -71,7 +71,7 @@
 
 $(BZ2LIB):
 	cd $(BZ2LIB_DIR)
-	$(MAKE) $(MAKE_BZ2LIB_ARG) bz2.lib
+	$(MAKE_BAT) 
 	cd ..\..\libbasic2
 
 
@@ -82,14 +82,17 @@
 	$(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
         
 clean::
-	del *.$(CSUFFIX)
+	-del *.$(CSUFFIX)
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)AVLTree.$(O) AVLTree.$(C) AVLTree.$(H): AVLTree.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)AbstractBackgroundJob.$(O) AbstractBackgroundJob.$(C) AbstractBackgroundJob.$(H): AbstractBackgroundJob.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ActiveObject.$(O) ActiveObject.$(C) ActiveObject.$(H): ActiveObject.st $(INCLUDE_TOP)\stx\libbasic\Lookup.$(H) $(INCLUDE_TOP)\stx\libbasic\Message.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ActorStream.$(O) ActorStream.$(C) ActorStream.$(H): ActorStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)Archiver.$(O) Archiver.$(C) Archiver.$(H): Archiver.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)AutoResizingOrderedCollection.$(O) AutoResizingOrderedCollection.$(C) AutoResizingOrderedCollection.$(H): AutoResizingOrderedCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)BIG5EncodedString.$(O) BIG5EncodedString.$(C) BIG5EncodedString.$(H): BIG5EncodedString.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\TwoByteString.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)BTree.$(O) BTree.$(C) BTree.$(H): BTree.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BaseNCoder.$(O) BaseNCoder.$(C) BaseNCoder.$(H): BaseNCoder.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) $(STCHDR)
 $(OUTDIR)Bezier.$(O) Bezier.$(C) Bezier.$(H): Bezier.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -103,45 +106,72 @@
 $(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)
+$(OUTDIR)CollectingSharedQueueStream.$(O) CollectingSharedQueueStream.$(C) CollectingSharedQueueStream.$(H): CollectingSharedQueueStream.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)CompressionStream.$(O) CompressionStream.$(C) CompressionStream.$(H): CompressionStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
+$(OUTDIR)Cons.$(O) Cons.$(C) Cons.$(H): Cons.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)ConsStream.$(O) ConsStream.$(C) ConsStream.$(H): ConsStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)Curve.$(O) Curve.$(C) Curve.$(H): Curve.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)DirectoryContents.$(O) DirectoryContents.$(C) DirectoryContents.$(H): DirectoryContents.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)DoubleLink.$(O) DoubleLink.$(C) DoubleLink.$(H): DoubleLink.st $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)EllipticalArc.$(O) EllipticalArc.$(C) EllipticalArc.$(H): EllipticalArc.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ExternalLong.$(O) ExternalLong.$(C) ExternalLong.$(H): ExternalLong.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)FileSorter.$(O) FileSorter.$(C) FileSorter.$(H): FileSorter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)FileText.$(O) FileText.$(C) FileText.$(H): FileText.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\StringCollection.$(H) $(STCHDR)
 $(OUTDIR)FilteringStream.$(O) FilteringStream.$(C) FilteringStream.$(H): FilteringStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)FourByteString.$(O) FourByteString.$(C) FourByteString.$(H): FourByteString.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) $(STCHDR)
 $(OUTDIR)Future.$(O) Future.$(C) Future.$(H): Future.st $(INCLUDE_TOP)\stx\libbasic\ProtoObject.$(H) $(STCHDR)
+$(OUTDIR)GBEncodedString.$(O) GBEncodedString.$(C) GBEncodedString.$(H): GBEncodedString.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\TwoByteString.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)GeometricSeries.$(O) GeometricSeries.$(C) GeometricSeries.$(H): GeometricSeries.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadOnlySequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)HTMLUtilities.$(O) HTMLUtilities.$(C) HTMLUtilities.$(H): HTMLUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HalfFloatArray.$(O) HalfFloatArray.$(C) HalfFloatArray.$(H): HalfFloatArray.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)HandlerCollection.$(O) HandlerCollection.$(C) HandlerCollection.$(H): HandlerCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)Heap.$(O) Heap.$(C) Heap.$(H): Heap.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)IdentityBag.$(O) IdentityBag.$(C) IdentityBag.$(H): IdentityBag.st $(INCLUDE_TOP)\stx\libbasic\Bag.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IncrementNotification.$(O) IncrementNotification.$(C) IncrementNotification.$(H): IncrementNotification.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)InterestConverterWithParameters.$(O) InterestConverterWithParameters.$(C) InterestConverterWithParameters.$(H): InterestConverterWithParameters.st $(INCLUDE_TOP)\stx\libbasic\InterestConverter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)InternalPipeStream.$(O) InternalPipeStream.$(C) InternalPipeStream.$(H): InternalPipeStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)Iterator.$(O) Iterator.$(C) Iterator.$(H): Iterator.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JISEncodedString.$(O) JISEncodedString.$(C) JISEncodedString.$(H): JISEncodedString.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\TwoByteString.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)KSCEncodedString.$(O) KSCEncodedString.$(C) KSCEncodedString.$(H): KSCEncodedString.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\TwoByteString.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)KeywordInContextIndexBuilder.$(O) KeywordInContextIndexBuilder.$(C) KeywordInContextIndexBuilder.$(H): KeywordInContextIndexBuilder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Lazy.$(O) Lazy.$(C) Lazy.$(H): Lazy.st $(INCLUDE_TOP)\stx\libbasic\ProtoObject.$(H) $(STCHDR)
 $(OUTDIR)LazyArray.$(O) LazyArray.$(C) LazyArray.$(H): LazyArray.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)LazyValue.$(O) LazyValue.$(C) LazyValue.$(H): LazyValue.st $(INCLUDE_TOP)\stx\libbasic\ProtoObject.$(H) $(STCHDR)
 $(OUTDIR)LineSegment.$(O) LineSegment.$(C) LineSegment.$(H): LineSegment.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)List.$(O) List.$(C) List.$(H): List.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)LoggingStream.$(O) LoggingStream.$(C) LoggingStream.$(H): LoggingStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
+$(OUTDIR)MacPlistBinaryDecoder.$(O) MacPlistBinaryDecoder.$(C) MacPlistBinaryDecoder.$(H): MacPlistBinaryDecoder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MappedCollection.$(O) MappedCollection.$(C) MappedCollection.$(H): MappedCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MessageChannel.$(O) MessageChannel.$(C) MessageChannel.$(H): MessageChannel.st $(INCLUDE_TOP)\stx\libbasic\Message.$(H) $(INCLUDE_TOP)\stx\libbasic\MessageSend.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Monitor.$(O) Monitor.$(C) Monitor.$(H): Monitor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MultiReadStream.$(O) MultiReadStream.$(C) MultiReadStream.$(H): MultiReadStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)NameLookupError.$(O) NameLookupError.$(C) NameLookupError.$(H): NameLookupError.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) $(STCHDR)
+$(OUTDIR)NumberSet.$(O) NumberSet.$(C) NumberSet.$(H): NumberSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)OperationQueue.$(O) OperationQueue.$(C) OperationQueue.$(H): OperationQueue.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PhoneticStringUtilities.$(O) PhoneticStringUtilities.$(C) PhoneticStringUtilities.$(H): PhoneticStringUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PluggableDictionary.$(O) PluggableDictionary.$(C) PluggableDictionary.$(H): PluggableDictionary.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)PluggableSet.$(O) PluggableSet.$(C) PluggableSet.$(H): PluggableSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
 $(OUTDIR)Polygon.$(O) Polygon.$(C) Polygon.$(H): Polygon.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PowerSet.$(O) PowerSet.$(C) PowerSet.$(H): PowerSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PrinterStream.$(O) PrinterStream.$(C) PrinterStream.$(H): PrinterStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)PrintfScanf.$(O) PrintfScanf.$(C) PrintfScanf.$(H): PrintfScanf.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PriorityQueue.$(O) PriorityQueue.$(C) PriorityQueue.$(H): PriorityQueue.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Promise.$(O) Promise.$(C) Promise.$(H): Promise.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Queue.$(O) Queue.$(C) Queue.$(H): Queue.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Random.$(O) Random.$(C) Random.$(H): Random.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
+$(OUTDIR)RandomBlumBlumShub.$(O) RandomBlumBlumShub.$(C) RandomBlumBlumShub.$(H): RandomBlumBlumShub.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)RandomKISS.$(O) RandomKISS.$(C) RandomKISS.$(H): RandomKISS.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)RandomKISS2.$(O) RandomKISS2.$(C) RandomKISS2.$(H): RandomKISS2.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)RandomMT19937.$(O) RandomMT19937.$(C) RandomMT19937.$(H): RandomMT19937.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)RandomParkMiller.$(O) RandomParkMiller.$(C) RandomParkMiller.$(H): RandomParkMiller.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)RandomRDRand.$(O) RandomRDRand.$(C) RandomRDRand.$(H): RandomRDRand.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)RandomTT800.$(O) RandomTT800.$(C) RandomTT800.$(H): RandomTT800.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ReindexedCollection.$(O) ReindexedCollection.$(C) ReindexedCollection.$(H): ReindexedCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)RunArray.$(O) RunArray.$(C) RunArray.$(H): RunArray.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)SegmentedOrderedCollection.$(O) SegmentedOrderedCollection.$(C) SegmentedOrderedCollection.$(H): SegmentedOrderedCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)SelectingReadStream.$(O) SelectingReadStream.$(C) SelectingReadStream.$(H): SelectingReadStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)SequenceWithSentinel.$(O) SequenceWithSentinel.$(C) SequenceWithSentinel.$(H): SequenceWithSentinel.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)SequenceableCollectionSorter.$(O) SequenceableCollectionSorter.$(C) SequenceableCollectionSorter.$(H): SequenceableCollectionSorter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SerialPort.$(O) SerialPort.$(C) SerialPort.$(H): SerialPort.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\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)SharedCollection.$(O) SharedCollection.$(C) SharedCollection.$(H): SharedCollection.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Singleton.$(O) Singleton.$(C) Singleton.$(H): Singleton.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -160,35 +190,47 @@
 $(OUTDIR)TSTreeNode.$(O) TSTreeNode.$(C) TSTreeNode.$(H): TSTreeNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TerminalSession.$(O) TerminalSession.$(C) TerminalSession.$(H): TerminalSession.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Text.$(O) Text.$(C) Text.$(H): Text.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) $(STCHDR)
+$(OUTDIR)TextClassifier.$(O) TextClassifier.$(C) TextClassifier.$(H): TextClassifier.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TextStream.$(O) TextStream.$(C) TextStream.$(H): TextStream.st $(INCLUDE_TOP)\stx\libbasic\CharacterWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)TreeSet.$(O) TreeSet.$(C) TreeSet.$(H): TreeSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(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)
+$(OUTDIR)ValueLink.$(O) ValueLink.$(C) ValueLink.$(H): ValueLink.st $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)VirtualArray.$(O) VirtualArray.$(C) VirtualArray.$(H): VirtualArray.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)ZipArchiveConstants.$(O) ZipArchiveConstants.$(C) ZipArchiveConstants.$(H): ZipArchiveConstants.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SharedPool.$(H) $(STCHDR)
 $(OUTDIR)stx_libbasic2.$(O) stx_libbasic2.$(C) stx_libbasic2.$(H): stx_libbasic2.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
 $(OUTDIR)AATree.$(O) AATree.$(C) AATree.$(H): AATree.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\BinaryTree.$(H) $(STCHDR)
 $(OUTDIR)AATreeNode.$(O) AATreeNode.$(C) AATreeNode.$(H): AATreeNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\BinaryTreeNode.$(H) $(STCHDR)
+$(OUTDIR)AppletalkSocketAddress.$(O) AppletalkSocketAddress.$(C) AppletalkSocketAddress.$(H): AppletalkSocketAddress.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)Arrow.$(O) Arrow.$(C) Arrow.$(H): Arrow.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\LineSegment.$(H) $(STCHDR)
 $(OUTDIR)ArrowedSpline.$(O) ArrowedSpline.$(C) ArrowedSpline.$(H): ArrowedSpline.st $(INCLUDE_TOP)\stx\libbasic\Geometric.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\Spline.$(H) $(STCHDR)
 $(OUTDIR)AutoResizingOrderedCollectionWithDefault.$(O) AutoResizingOrderedCollectionWithDefault.$(C) AutoResizingOrderedCollectionWithDefault.$(H): AutoResizingOrderedCollectionWithDefault.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic2\AutoResizingOrderedCollection.$(H) $(STCHDR)
+$(OUTDIR)BZip2Stream.$(O) BZip2Stream.$(C) BZip2Stream.$(H): BZip2Stream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\CompressionStream.$(H) $(STCHDR)
 $(OUTDIR)BackgroundJob.$(O) BackgroundJob.$(C) BackgroundJob.$(H): BackgroundJob.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)BackgroundPeriodicalJob.$(O) BackgroundPeriodicalJob.$(C) BackgroundPeriodicalJob.$(H): BackgroundPeriodicalJob.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)BackgroundQueueProcessingJob.$(O) BackgroundQueueProcessingJob.$(C) BackgroundQueueProcessingJob.$(H): BackgroundQueueProcessingJob.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\AbstractBackgroundJob.$(H) $(STCHDR)
 $(OUTDIR)Base32Coder.$(O) Base32Coder.$(C) Base32Coder.$(H): Base32Coder.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)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)
 $(OUTDIR)FilteringLineStream.$(O) FilteringLineStream.$(C) FilteringLineStream.$(H): FilteringLineStream.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)HPLjetIIPrinterStream.$(O) HPLjetIIPrinterStream.$(C) HPLjetIIPrinterStream.$(H): HPLjetIIPrinterStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\PrinterStream.$(H) $(STCHDR)
+$(OUTDIR)HTMLPrinterStream.$(O) HTMLPrinterStream.$(C) HTMLPrinterStream.$(H): HTMLPrinterStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic2\PrinterStream.$(H) $(STCHDR)
 $(OUTDIR)HierarchicalURI.$(O) HierarchicalURI.$(C) HierarchicalURI.$(H): HierarchicalURI.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic2\URI.$(H) $(STCHDR)
 $(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)
@@ -202,6 +244,7 @@
 $(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)
--- a/bmake.bat	Mon Jun 06 06:56:04 2016 +0200
+++ b/bmake.bat	Tue Jun 14 08:57:11 2016 +0100
@@ -8,3 +8,5 @@
 make.exe -N -f bc.mak  %DEFINES% %*
 
 
+
+
--- a/extensions.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/extensions.st	Tue Jun 14 08:57:11 2016 +0100
@@ -752,6 +752,15 @@
     "Created: 14.10.1996 / 22:27:34 / stefan"
 ! !
 
+!Object methodsFor:'converting'!
+
+asDoubleLink
+    "return a valueDoubleLink for the receiver.
+     Used to make sure the receiver can be added to a double linked list"
+
+    ^ ValueDoubleLink value:self
+! !
+
 !Object methodsFor:'dependents-interests'!
 
 expressInterestIn:aspect for:anObject sendBack:aSelector
--- a/libInit.cc	Mon Jun 06 06:56:04 2016 +0200
+++ b/libInit.cc	Tue Jun 14 08:57:11 2016 +0100
@@ -16,10 +16,13 @@
 DLL_EXPORT void _libstx_libbasic2_InitDefinition() INIT_TEXT_SECTION;
 #endif
 
+extern void _AVLTree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AbstractBackgroundJob_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ActiveObject_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ActorStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Archiver_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AutoResizingOrderedCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BIG5EncodedString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BTree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BaseNCoder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Bezier_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -33,45 +36,72 @@
 extern void _CharacterSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Circle_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CollectingReadStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CollectingSharedQueueStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CompressionStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _Cons_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ConsStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Curve_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DirectoryContents_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DoubleLink_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _EllipticalArc_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ExternalLong_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FileSorter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _FileText_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FilteringStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FourByteString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Future_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _GBEncodedString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _GeometricSeries_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HTMLUtilities_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HalfFloatArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HandlerCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Heap_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _IdentityBag_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _IncrementNotification_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InterestConverterWithParameters_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _InternalPipeStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Iterator_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _JISEncodedString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _KSCEncodedString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _KeywordInContextIndexBuilder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Lazy_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LazyArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _LazyValue_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LineSegment_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _List_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _LoggingStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MacPlistBinaryDecoder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _MappedCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MessageChannel_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Monitor_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _MultiReadStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NameLookupError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _NumberSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _OperationQueue_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PhoneticStringUtilities_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _PluggableDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _PluggableSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Polygon_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _PowerSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PrinterStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PrintfScanf_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _PriorityQueue_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Promise_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Queue_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Random_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomBlumBlumShub_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomKISS_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomKISS2_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomMT19937_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomParkMiller_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RandomRDRand_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _RandomTT800_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ReindexedCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _RunArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SegmentedOrderedCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SelectingReadStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SequenceWithSentinel_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SequenceableCollectionSorter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SerialPort_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SharedCollection_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Singleton_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -90,35 +120,47 @@
 extern void _TSTreeNode_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TerminalSession_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Text_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _TextClassifier_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TextStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TreeSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+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);
+extern void _ValueLink_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _VirtualArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ZipArchiveConstants_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _stx_137libbasic2_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AATree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AATreeNode_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _AppletalkSocketAddress_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Arrow_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ArrowedSpline_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AutoResizingOrderedCollectionWithDefault_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BZip2Stream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BackgroundJob_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BackgroundPeriodicalJob_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BackgroundQueueProcessingJob_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Base32Coder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 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);
 extern void _FilteringLineStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HPLjetIIPrinterStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HTMLPrinterStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HierarchicalURI_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 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);
@@ -132,6 +174,7 @@
 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);
@@ -153,10 +196,13 @@
 void _libstx_libbasic2_Init(int pass, struct __vmData__ *__pRT__, OBJ snd)
 {
   __BEGIN_PACKAGE2__("libstx_libbasic2", _libstx_libbasic2_Init, "stx:libbasic2");
+    _AVLTree_Init(pass,__pRT__,snd);
     _AbstractBackgroundJob_Init(pass,__pRT__,snd);
+    _ActiveObject_Init(pass,__pRT__,snd);
     _ActorStream_Init(pass,__pRT__,snd);
     _Archiver_Init(pass,__pRT__,snd);
     _AutoResizingOrderedCollection_Init(pass,__pRT__,snd);
+    _BIG5EncodedString_Init(pass,__pRT__,snd);
     _BTree_Init(pass,__pRT__,snd);
     _BaseNCoder_Init(pass,__pRT__,snd);
     _Bezier_Init(pass,__pRT__,snd);
@@ -170,45 +216,72 @@
     _CharacterSet_Init(pass,__pRT__,snd);
     _Circle_Init(pass,__pRT__,snd);
     _CollectingReadStream_Init(pass,__pRT__,snd);
+    _CollectingSharedQueueStream_Init(pass,__pRT__,snd);
     _CompressionStream_Init(pass,__pRT__,snd);
+    _Cons_Init(pass,__pRT__,snd);
+    _ConsStream_Init(pass,__pRT__,snd);
     _Curve_Init(pass,__pRT__,snd);
     _DirectoryContents_Init(pass,__pRT__,snd);
+    _DoubleLink_Init(pass,__pRT__,snd);
     _EllipticalArc_Init(pass,__pRT__,snd);
     _ExternalLong_Init(pass,__pRT__,snd);
     _FileSorter_Init(pass,__pRT__,snd);
+    _FileText_Init(pass,__pRT__,snd);
     _FilteringStream_Init(pass,__pRT__,snd);
     _FourByteString_Init(pass,__pRT__,snd);
     _Future_Init(pass,__pRT__,snd);
+    _GBEncodedString_Init(pass,__pRT__,snd);
+    _GeometricSeries_Init(pass,__pRT__,snd);
     _HTMLUtilities_Init(pass,__pRT__,snd);
     _HalfFloatArray_Init(pass,__pRT__,snd);
+    _HandlerCollection_Init(pass,__pRT__,snd);
     _Heap_Init(pass,__pRT__,snd);
     _IdentityBag_Init(pass,__pRT__,snd);
     _IncrementNotification_Init(pass,__pRT__,snd);
     _InterestConverterWithParameters_Init(pass,__pRT__,snd);
+    _InternalPipeStream_Init(pass,__pRT__,snd);
     _Iterator_Init(pass,__pRT__,snd);
     _JISEncodedString_Init(pass,__pRT__,snd);
+    _KSCEncodedString_Init(pass,__pRT__,snd);
+    _KeywordInContextIndexBuilder_Init(pass,__pRT__,snd);
     _Lazy_Init(pass,__pRT__,snd);
     _LazyArray_Init(pass,__pRT__,snd);
+    _LazyValue_Init(pass,__pRT__,snd);
     _LineSegment_Init(pass,__pRT__,snd);
     _List_Init(pass,__pRT__,snd);
+    _LoggingStream_Init(pass,__pRT__,snd);
+    _MacPlistBinaryDecoder_Init(pass,__pRT__,snd);
     _MappedCollection_Init(pass,__pRT__,snd);
+    _MessageChannel_Init(pass,__pRT__,snd);
     _Monitor_Init(pass,__pRT__,snd);
     _MultiReadStream_Init(pass,__pRT__,snd);
     _NameLookupError_Init(pass,__pRT__,snd);
+    _NumberSet_Init(pass,__pRT__,snd);
     _OperationQueue_Init(pass,__pRT__,snd);
     _PhoneticStringUtilities_Init(pass,__pRT__,snd);
+    _PluggableDictionary_Init(pass,__pRT__,snd);
+    _PluggableSet_Init(pass,__pRT__,snd);
     _Polygon_Init(pass,__pRT__,snd);
+    _PowerSet_Init(pass,__pRT__,snd);
     _PrinterStream_Init(pass,__pRT__,snd);
     _PrintfScanf_Init(pass,__pRT__,snd);
+    _PriorityQueue_Init(pass,__pRT__,snd);
     _Promise_Init(pass,__pRT__,snd);
     _Queue_Init(pass,__pRT__,snd);
     _Random_Init(pass,__pRT__,snd);
+    _RandomBlumBlumShub_Init(pass,__pRT__,snd);
+    _RandomKISS_Init(pass,__pRT__,snd);
+    _RandomKISS2_Init(pass,__pRT__,snd);
+    _RandomMT19937_Init(pass,__pRT__,snd);
+    _RandomParkMiller_Init(pass,__pRT__,snd);
+    _RandomRDRand_Init(pass,__pRT__,snd);
     _RandomTT800_Init(pass,__pRT__,snd);
     _ReindexedCollection_Init(pass,__pRT__,snd);
     _RunArray_Init(pass,__pRT__,snd);
     _SegmentedOrderedCollection_Init(pass,__pRT__,snd);
     _SelectingReadStream_Init(pass,__pRT__,snd);
     _SequenceWithSentinel_Init(pass,__pRT__,snd);
+    _SequenceableCollectionSorter_Init(pass,__pRT__,snd);
     _SerialPort_Init(pass,__pRT__,snd);
     _SharedCollection_Init(pass,__pRT__,snd);
     _Singleton_Init(pass,__pRT__,snd);
@@ -227,35 +300,47 @@
     _TSTreeNode_Init(pass,__pRT__,snd);
     _TerminalSession_Init(pass,__pRT__,snd);
     _Text_Init(pass,__pRT__,snd);
+    _TextClassifier_Init(pass,__pRT__,snd);
     _TextStream_Init(pass,__pRT__,snd);
     _TreeSet_Init(pass,__pRT__,snd);
+    _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);
+    _ValueLink_Init(pass,__pRT__,snd);
     _VirtualArray_Init(pass,__pRT__,snd);
     _ZipArchiveConstants_Init(pass,__pRT__,snd);
     _stx_137libbasic2_Init(pass,__pRT__,snd);
     _AATree_Init(pass,__pRT__,snd);
     _AATreeNode_Init(pass,__pRT__,snd);
+    _AppletalkSocketAddress_Init(pass,__pRT__,snd);
     _Arrow_Init(pass,__pRT__,snd);
     _ArrowedSpline_Init(pass,__pRT__,snd);
     _AutoResizingOrderedCollectionWithDefault_Init(pass,__pRT__,snd);
+    _BZip2Stream_Init(pass,__pRT__,snd);
     _BackgroundJob_Init(pass,__pRT__,snd);
     _BackgroundPeriodicalJob_Init(pass,__pRT__,snd);
     _BackgroundQueueProcessingJob_Init(pass,__pRT__,snd);
     _Base32Coder_Init(pass,__pRT__,snd);
     _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);
     _FilteringLineStream_Init(pass,__pRT__,snd);
+    _HPLjetIIPrinterStream_Init(pass,__pRT__,snd);
+    _HTMLPrinterStream_Init(pass,__pRT__,snd);
     _HierarchicalURI_Init(pass,__pRT__,snd);
     _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);
@@ -269,6 +354,7 @@
     _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);
--- a/libbasic2.rc	Mon Jun 06 06:56:04 2016 +0200
+++ b/libbasic2.rc	Tue Jun 14 08:57:11 2016 +0100
@@ -3,8 +3,8 @@
 // automagically generated from the projectDefinition: stx_libbasic2.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     6,2,1,131
-  PRODUCTVERSION  6,2,5,0
+  FILEVERSION     7,1,1,143
+  PRODUCTVERSION  7,1,0,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -20,12 +20,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Additional Basic Classes (LIB)\0"
-      VALUE "FileVersion", "6.2.1.131\0"
+      VALUE "FileVersion", "7.1.1.143\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", "6.2.5.0\0"
-      VALUE "ProductDate", "Mon, 11 Apr 2016 16:01:05 GMT\0"
+      VALUE "ProductVersion", "7.1.0.0\0"
+      VALUE "ProductDate", "Mon, 13 Jun 2016 14:16:16 GMT\0"
     END
 
   END
--- a/mingwmake.bat	Mon Jun 06 06:56:04 2016 +0200
+++ b/mingwmake.bat	Tue Jun 14 08:57:11 2016 +0100
@@ -11,3 +11,5 @@
 make.exe -N -f bc.mak %DEFINES% %USEMINGW_ARG% %*
 
 
+
+
--- a/stx_libbasic2.st	Mon Jun 06 06:56:04 2016 +0200
+++ b/stx_libbasic2.st	Tue Jun 14 08:57:11 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
 	      All Rights Reserved
@@ -41,12 +43,12 @@
     Package documentation:
 
     This library contains additional basic (nonGUI) classes.
-    
+
     These are less fundamental as in libbasic and not required by many stand alone applications.
     Beside additional container classes, this includes URL support, Zip support,
     PTY, serial line, sockets and IP addresses, and other less frequently needed things.
 
-    Most real world applications will include this, but it is possible to create 
+    Most real world applications will include this, but it is possible to create
     small standAlone apps which do not need it.
 "
 ! !
@@ -55,12 +57,13 @@
 
 excludedFromPreRequisites
     ^ #(
-        #'exept:libcrypt'    "Rc4Cipher - referenced by RandomGenerator class>>new "
-        #'stx:goodies/communication'    "FTPClient - referenced by FtpURI>>writeStreamDo:create:atomic: "
-        #'stx:libtool'    "FileBrowser - referenced by Archiver::ArchiverOutputParser>>parseLine:forItemClass: "
-        #'stx:libview2'    "MIMETypes - referenced by Archiver::ArchiverOutputParser>>parseLine:forItemClass: "
-        #'stx:libwidg'    "DialogBox - referenced by Archiver::CompressedFile>>compressFile:to: "
-        #'stx:libhtml'    "HTMLParser - referenced by HTMLUtilities class>>plainTextOfHTML: "
+	#'exept:libcrypt'    "Rc4Cipher - referenced by RandomGenerator class>>new "
+	#'stx:goodies/communication'    "FTPClient - referenced by FtpURI>>writeStreamDo:create:atomic: "
+	#'stx:libtool'    "FileBrowser - referenced by Archiver::ArchiverOutputParser>>parseLine:forItemClass: "
+	#'stx:libview2'    "MIMETypes - referenced by Archiver::ArchiverOutputParser>>parseLine:forItemClass: "
+	#'stx:libwidg'    "DialogBox - referenced by Archiver::CompressedFile>>compressFile:to: "
+	#'stx:libhtml'    "HTMLParser - referenced by HTMLUtilities class>>plainTextOfHTML: "
+	#'stx:goodies/webServer/htmlTree'    "HTML::TreeBuilder - referenced by HTMLPrinterStream>>initialize"
     )
 !
 
@@ -73,7 +76,7 @@
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "AbstractNumberVector - superclass of HalfFloatArray"
+	#'stx:libbasic'    "AbstractNumberVector - superclass of HalfFloatArray"
     )
 !
 
@@ -129,8 +132,7 @@
 !
 
 additionalLinkLibraries_bc_dot_mak
-"/    ^ '$(ZLIB) $(BZ2LIB)'
-    ^ '$(ZLIB_DIR)\$(ZLIB) $(WINSOCK_LIB)'
+    ^ '$(ZLIB_DIR)\$(ZLIB) $(BZ2LIB) $(WINSOCK_LIB)'
 
     "Modified: / 12-05-2015 / 19:00:25 / jv"
 !
@@ -148,7 +150,7 @@
 
 $(BZ2LIB):
         cd $(BZ2LIB_DIR)
-        $(MAKE) $(MAKE_BZ2LIB_ARG) bz2.lib
+        $(MAKE_BAT) 
         cd ..\..\libbasic2
 '
 
@@ -166,8 +168,7 @@
 !
 
 additionalTargets_bc_dot_mak
-"/    ^ '$(BZ2LIB) $(ZLIB)'      bz2lib doesn't work for now
-    ^ '$(ZLIB)'
+    ^ '$(ZLIB) $(BZ2LIB)'
 !
 
 additionalTargets_make_dot_proto
@@ -177,7 +178,7 @@
 !
 
 localIncludes
-    ^ '-I$(ZLIB_DIR)'
+    ^ '-I$(ZLIB_DIR) -I$(BZ2LIB_DIR)'
 
     "Created: / 06-09-2006 / 18:18:15 / cg"
 !
@@ -202,10 +203,13 @@
 
     ^ #(
         "<className> or (<className> attributes...) in load order"
+        AVLTree
         AbstractBackgroundJob
+        ActiveObject
         ActorStream
         Archiver
         AutoResizingOrderedCollection
+        BIG5EncodedString
         BTree
         BaseNCoder
         Bezier
@@ -219,45 +223,73 @@
         CharacterSet
         Circle
         CollectingReadStream
+        CollectingSharedQueueStream
         CompressionStream
+        Cons
+        ConsStream
         Curve
         DirectoryContents
+        DoubleLink
+        (DoubleLinkedList autoload)
         EllipticalArc
         ExternalLong
         FileSorter
+        FileText
         FilteringStream
         FourByteString
         Future
+        GBEncodedString
+        GeometricSeries
         HTMLUtilities
         HalfFloatArray
+        HandlerCollection
         Heap
         IdentityBag
         IncrementNotification
         InterestConverterWithParameters
+        InternalPipeStream
         Iterator
         JISEncodedString
+        KSCEncodedString
+        KeywordInContextIndexBuilder
         Lazy
         LazyArray
+        LazyValue
         LineSegment
         List
+        LoggingStream
+        MacPlistBinaryDecoder
         MappedCollection
+        MessageChannel
         Monitor
         MultiReadStream
         NameLookupError
+        NumberSet
         OperationQueue
         PhoneticStringUtilities
+        PluggableDictionary
+        PluggableSet
         Polygon
+        PowerSet
         PrinterStream
         PrintfScanf
+        PriorityQueue
         Promise
         Queue
         Random
+        RandomBlumBlumShub
+        RandomKISS
+        RandomKISS2
+        RandomMT19937
+        RandomParkMiller
+        RandomRDRand
         RandomTT800
         ReindexedCollection
         RunArray
         SegmentedOrderedCollection
         SelectingReadStream
         SequenceWithSentinel
+        SequenceableCollectionSorter
         SerialPort
         SharedCollection
         Singleton
@@ -276,36 +308,47 @@
         TSTreeNode
         TerminalSession
         Text
+        TextClassifier
         TextStream
         TreeSet
+        Trie
         URI
         UUID
         UnboxedIntegerArray
         UndoSupport
         UnitConverter
+        UnixPTYStream
+        ValueLink
         VirtualArray
         ZipArchiveConstants
         #'stx_libbasic2'
         AATree
         AATreeNode
+        AppletalkSocketAddress
         Arrow
         ArrowedSpline
         AutoResizingOrderedCollectionWithDefault
+        BZip2Stream
         BackgroundJob
         BackgroundPeriodicalJob
         BackgroundQueueProcessingJob
         Base32Coder
         Base64Coder
+        BayesClassifier
         Bezier2Segment
         BooleanArray
         CacheDictionaryWithFactory
+        DecNetSocketAddress
+        EpsonFX1PrinterStream
         FilteringLineStream
-        (HTMLPrinterStream autoload)
+        HPLjetIIPrinterStream
+        HTMLPrinterStream
         HierarchicalURI
         HostAddressLookupError
         HostNameLookupError
         IPSocketAddress
         IntegerArray
+        LazyCons
         LineNumberReadStream
         LongIntegerArray
         PostscriptPrinterStream
@@ -319,6 +362,7 @@
         TimedPromise
         UDSocketAddress
         Unicode32String
+        ValueDoubleLink
         WordArray
         ZipArchive
         ZipStream
@@ -327,98 +371,59 @@
         HttpURI
         IPv6SocketAddress
         SftpURI
-        (AVLTree autoload)
-        (ActiveObject autoload)
-        (AppletalkSocketAddress autoload)
-        (BIG5EncodedString autoload)
-        (BZip2Stream autoload)
-        (BayesClassifier autoload)
-        (CollectingSharedQueueStream autoload)
-        (CompressionStreamTest autoload)
-        (Cons autoload)
-        (ConsStream autoload)
-        (DecNetSocketAddress autoload)
-        (EpsonFX1PrinterStream autoload)
-        (FileText autoload)
-        (GBEncodedString autoload)
-        (GeometricSeries autoload)
-        (HPLjetIIPrinterStream autoload)
-        (HandlerCollection autoload)
-        (InternalPipeStream autoload)
-        (KSCEncodedString autoload)
-        (KeywordInContextIndexBuilder autoload)
-        (LazyCons autoload)
-        (LazyValue autoload)
-        (LoggingStream autoload)
-        (MacPlistBinaryDecoder autoload)
-        (MessageChannel autoload)
-        (NumberSet autoload)
-        (PluggableDictionary autoload)
-        (PluggableSet autoload)
-        (PowerSet autoload)
-        (PriorityQueue autoload)
-        (RandomBlumBlumShub autoload)
-        (RandomKISS autoload)
-        (RandomKISS2 autoload)
-        (RandomMT19937 autoload)
-        (RandomParkMiller autoload)
-        (RandomRDRand autoload)
-        (SequenceableCollectionSorter autoload)
-        (TextClassifier autoload)
-        (Trie autoload)
-        (UnixPTYStream autoload)
-        (ValueLink autoload)
-        (WinAPIFunction autoload)
     )
 !
 
 extensionMethodNames
-    "list class/selector pairs of extensions.
-     A correponding method with real names must be present in my concrete subclasses"
+    "lists the extension methods which are to be included in the project.
+     Entries are 2-element array literals, consisting of class-name and selector.
+     A correponding method with real names must be present in my concrete subclasses
+     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 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/vcmake.bat	Mon Jun 06 06:56:04 2016 +0200
+++ b/vcmake.bat	Tue Jun 14 08:57:11 2016 +0100
@@ -15,3 +15,4 @@
 
 
 
+
--- a/vms.mak	Mon Jun 06 06:56:04 2016 +0200
+++ b/vms.mak	Tue Jun 14 08:57:11 2016 +0100
@@ -1,8 +1,8 @@
 #
-# DO NOT EDIT 
+# DO NOT EDIT
 # automatically generated from Make.proto
 #
-# $Header: /cvs/stx/stx/libbasic2/vms.mak,v 1.4 1999-09-18 14:04:54 cg Exp $
+# $Header$
 #
 TOP=..
 LIBNAME=libbasic2
@@ -58,68 +58,67 @@
 
 
 # BEGINMAKEDEPEND
-$(OUTDIR)ActorStream.$(O) ActorStream.$(H): ActorStream.st $(STCHDR)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Arrow.$(O) Arrow.$(H): Arrow.st $(STCHDR) 
-$(OUTDIR)ArrowedSpline.$(O) ArrowedSpline.$(H): ArrowedSpline.st $(STCHDR) 
-$(OUTDIR)BIG5EncodedString.$(O) BIG5EncodedString.$(H): BIG5EncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Bezier.$(O) Bezier.$(H): Bezier.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Bezier2Segment.$(O) Bezier2Segment.$(H): Bezier2Segment.st $(STCHDR) 
-$(OUTDIR)BitArray.$(O) BitArray.$(H): BitArray.st $(STCHDR) 
-$(OUTDIR)BooleanArray.$(O) BooleanArray.$(H): BooleanArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)CacheDictionary.$(O) CacheDictionary.$(H): CacheDictionary.st $(STCHDR)  ../include/Dictionary.$(H)  ../include/Set.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)CachingRegistry.$(O) CachingRegistry.$(H): CachingRegistry.st $(STCHDR)  ../include/Registry.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Circle.$(O) Circle.$(H): Circle.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)CollectingSharedQueueStream.$(O) CollectingSharedQueueStream.$(H): CollectingSharedQueueStream.st $(STCHDR)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Curve.$(O) Curve.$(H): Curve.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)DirectoryContents.$(O) DirectoryContents.$(H): DirectoryContents.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)EllipticalArc.$(O) EllipticalArc.$(H): EllipticalArc.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)EpsonFX1PrinterStream.$(O) EpsonFX1PrinterStream.$(H): EpsonFX1PrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)ExternalLong.$(O) ExternalLong.$(H): ExternalLong.st $(STCHDR)  ../include/ExternalBytes.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)FileText.$(O) FileText.$(H): FileText.st $(STCHDR)  ../include/StringCollection.$(H)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)GBEncodedString.$(O) GBEncodedString.$(H): GBEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)HPLjetIIPrinterStream.$(O) HPLjetIIPrinterStream.$(H): HPLjetIIPrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)HandlerCollection.$(O) HandlerCollection.$(H): HandlerCollection.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)IPSocketAddress.$(O) IPSocketAddress.$(H): IPSocketAddress.st $(STCHDR) 
-$(OUTDIR)IntegerArray.$(O) IntegerArray.$(H): IntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)JISEncodedString.$(O) JISEncodedString.$(H): JISEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)KSCEncodedString.$(O) KSCEncodedString.$(H): KSCEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)KeyedCollection.$(O) KeyedCollection.$(H): KeyedCollection.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)LineSegment.$(O) LineSegment.$(H): LineSegment.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)List.$(O) List.$(H): List.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)LongIntegerArray.$(O) LongIntegerArray.$(H): LongIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)MappedCollection.$(O) MappedCollection.$(H): MappedCollection.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)MessageChannel.$(O) MessageChannel.$(H): MessageChannel.st $(STCHDR)  ../include/MessageSend.$(H)  ../include/Message.$(H)  ../include/Object.$(H) 
-$(OUTDIR)MessageSend.$(O) MessageSend.$(H): MessageSend.st $(STCHDR)  ../include/Message.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Monitor.$(O) Monitor.$(H): Monitor.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)Polygon.$(O) Polygon.$(H): Polygon.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)PostscriptPrinterStream.$(O) PostscriptPrinterStream.$(H): PostscriptPrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)PrinterStream.$(O) PrinterStream.$(H): PrinterStream.st $(STCHDR)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Promise.$(O) Promise.$(H): Promise.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)Queue.$(O) Queue.$(H): Queue.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Random.$(O) Random.$(H): Random.st $(STCHDR)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)RecursionLock.$(O) RecursionLock.$(H): RecursionLock.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)RunArray.$(O) RunArray.$(H): RunArray.st $(STCHDR)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SequenceableCollectionSorter.$(O) SequenceableCollectionSorter.$(H): SequenceableCollectionSorter.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)SharedQueue.$(O) SharedQueue.$(H): SharedQueue.st $(STCHDR)  ../include/Queue.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SignedIntegerArray.$(O) SignedIntegerArray.$(H): SignedIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SignedLongIntegerArray.$(O) SignedLongIntegerArray.$(H): SignedLongIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SignedWordArray.$(O) SignedWordArray.$(H): SignedWordArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SocketAddress.$(O) SocketAddress.$(H): SocketAddress.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)Socket.$(O) Socket.$(H): Socket.st $(STCHDR)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)SoundStream.$(O) SoundStream.$(H): SoundStream.st $(STCHDR)  ../include/FileStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Spline.$(O) Spline.$(H): Spline.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H) 
-$(OUTDIR)StringCollection.$(O) StringCollection.$(H): StringCollection.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)Text.$(O) Text.$(H): Text.st $(STCHDR)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)TextStream.$(O) TextStream.$(H): TextStream.st $(STCHDR)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)TwoByteString.$(O) TwoByteString.$(H): TwoByteString.st $(STCHDR)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)UDSocketAddress.$(O) UDSocketAddress.$(H): UDSocketAddress.st $(STCHDR) 
-$(OUTDIR)UnicodeString.$(O) UnicodeString.$(H): UnicodeString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)UnitConverter.$(O) UnitConverter.$(H): UnitConverter.st $(STCHDR)  ../include/Object.$(H) 
-$(OUTDIR)UnixPTYStream.$(O) UnixPTYStream.$(H): UnixPTYStream.st $(STCHDR)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
-$(OUTDIR)ValueLink.$(O) ValueLink.$(H): ValueLink.st $(STCHDR)  ../include/Link.$(H)  ../include/Object.$(H) 
-$(OUTDIR)VariableArray.$(O) VariableArray.$(H): VariableArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)VariableString.$(O) VariableString.$(H): VariableString.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)WinAPIFunction.$(O) WinAPIFunction.$(H): WinAPIFunction.st $(STCHDR)  ../include/ExternalFunction.$(H)  ../include/ExecutableFunction.$(H)  ../include/Object.$(H) 
-$(OUTDIR)WordArray.$(O) WordArray.$(H): WordArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H) 
-$(OUTDIR)ZipArchive.$(O) ZipArchive.$(H): ZipArchive.st $(STCHDR)  ../include/Object.$(H) 
+$(OUTDIR)ActorStream.$(O) ActorStream.$(H): ActorStream.st $(STCHDR)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)Arrow.$(O) Arrow.$(H): Arrow.st $(STCHDR)
+$(OUTDIR)ArrowedSpline.$(O) ArrowedSpline.$(H): ArrowedSpline.st $(STCHDR)
+$(OUTDIR)BIG5EncodedString.$(O) BIG5EncodedString.$(H): BIG5EncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)Bezier.$(O) Bezier.$(H): Bezier.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)Bezier2Segment.$(O) Bezier2Segment.$(H): Bezier2Segment.st $(STCHDR)
+$(OUTDIR)BitArray.$(O) BitArray.$(H): BitArray.st $(STCHDR)
+$(OUTDIR)BooleanArray.$(O) BooleanArray.$(H): BooleanArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)CacheDictionary.$(O) CacheDictionary.$(H): CacheDictionary.st $(STCHDR)  ../include/Dictionary.$(H)  ../include/Set.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)CachingRegistry.$(O) CachingRegistry.$(H): CachingRegistry.st $(STCHDR)  ../include/Registry.$(H)  ../include/Object.$(H)
+$(OUTDIR)Circle.$(O) Circle.$(H): Circle.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)CollectingSharedQueueStream.$(O) CollectingSharedQueueStream.$(H): CollectingSharedQueueStream.st $(STCHDR)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)Curve.$(O) Curve.$(H): Curve.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)DirectoryContents.$(O) DirectoryContents.$(H): DirectoryContents.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)EllipticalArc.$(O) EllipticalArc.$(H): EllipticalArc.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)EpsonFX1PrinterStream.$(O) EpsonFX1PrinterStream.$(H): EpsonFX1PrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)ExternalLong.$(O) ExternalLong.$(H): ExternalLong.st $(STCHDR)  ../include/ExternalBytes.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)FileText.$(O) FileText.$(H): FileText.st $(STCHDR)  ../include/StringCollection.$(H)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)GBEncodedString.$(O) GBEncodedString.$(H): GBEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)HPLjetIIPrinterStream.$(O) HPLjetIIPrinterStream.$(H): HPLjetIIPrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)HandlerCollection.$(O) HandlerCollection.$(H): HandlerCollection.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)IPSocketAddress.$(O) IPSocketAddress.$(H): IPSocketAddress.st $(STCHDR)
+$(OUTDIR)IntegerArray.$(O) IntegerArray.$(H): IntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)JISEncodedString.$(O) JISEncodedString.$(H): JISEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)KSCEncodedString.$(O) KSCEncodedString.$(H): KSCEncodedString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)KeyedCollection.$(O) KeyedCollection.$(H): KeyedCollection.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)LineSegment.$(O) LineSegment.$(H): LineSegment.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)List.$(O) List.$(H): List.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)LongIntegerArray.$(O) LongIntegerArray.$(H): LongIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)MappedCollection.$(O) MappedCollection.$(H): MappedCollection.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)MessageChannel.$(O) MessageChannel.$(H): MessageChannel.st $(STCHDR)  ../include/MessageSend.$(H)  ../include/Message.$(H)  ../include/Object.$(H)
+$(OUTDIR)MessageSend.$(O) MessageSend.$(H): MessageSend.st $(STCHDR)  ../include/Message.$(H)  ../include/Object.$(H)
+$(OUTDIR)Monitor.$(O) Monitor.$(H): Monitor.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)Polygon.$(O) Polygon.$(H): Polygon.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)PostscriptPrinterStream.$(O) PostscriptPrinterStream.$(H): PostscriptPrinterStream.st $(STCHDR)  ../include/PrinterStream.$(H)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)PrinterStream.$(O) PrinterStream.$(H): PrinterStream.st $(STCHDR)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)Promise.$(O) Promise.$(H): Promise.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)Queue.$(O) Queue.$(H): Queue.st $(STCHDR)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)Random.$(O) Random.$(H): Random.st $(STCHDR)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)RecursionLock.$(O) RecursionLock.$(H): RecursionLock.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)RunArray.$(O) RunArray.$(H): RunArray.st $(STCHDR)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)SequenceableCollectionSorter.$(O) SequenceableCollectionSorter.$(H): SequenceableCollectionSorter.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)SharedQueue.$(O) SharedQueue.$(H): SharedQueue.st $(STCHDR)  ../include/Queue.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)SignedIntegerArray.$(O) SignedIntegerArray.$(H): SignedIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)SignedLongIntegerArray.$(O) SignedLongIntegerArray.$(H): SignedLongIntegerArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)SignedWordArray.$(O) SignedWordArray.$(H): SignedWordArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)SocketAddress.$(O) SocketAddress.$(H): SocketAddress.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)Socket.$(O) Socket.$(H): Socket.st $(STCHDR)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)SoundStream.$(O) SoundStream.$(H): SoundStream.st $(STCHDR)  ../include/FileStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)Spline.$(O) Spline.$(H): Spline.st $(STCHDR)  ../include/Geometric.$(H)  ../include/Object.$(H)
+$(OUTDIR)StringCollection.$(O) StringCollection.$(H): StringCollection.st $(STCHDR)  ../include/OrderedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)Text.$(O) Text.$(H): Text.st $(STCHDR)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)TextStream.$(O) TextStream.$(H): TextStream.st $(STCHDR)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)TwoByteString.$(O) TwoByteString.$(H): TwoByteString.st $(STCHDR)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)UDSocketAddress.$(O) UDSocketAddress.$(H): UDSocketAddress.st $(STCHDR)
+$(OUTDIR)UnicodeString.$(O) UnicodeString.$(H): UnicodeString.st $(STCHDR)  ../include/TwoByteString.$(H)  ../include/CharacterArray.$(H)  ../include/ByteArray.$(H)  ../include/UninterpretedBytes.$(H)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)UnitConverter.$(O) UnitConverter.$(H): UnitConverter.st $(STCHDR)  ../include/Object.$(H)
+$(OUTDIR)UnixPTYStream.$(O) UnixPTYStream.$(H): UnixPTYStream.st $(STCHDR)  ../include/PipeStream.$(H)  ../include/NonPositionableExternalStream.$(H)  ../include/ExternalStream.$(H)  ../include/ReadWriteStream.$(H)  ../include/WriteStream.$(H)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H)
+$(OUTDIR)ValueLink.$(O) ValueLink.$(H): ValueLink.st $(STCHDR)  ../include/Link.$(H)  ../include/Object.$(H)
+$(OUTDIR)VariableArray.$(O) VariableArray.$(H): VariableArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)VariableString.$(O) VariableString.$(H): VariableString.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)WordArray.$(O) WordArray.$(H): WordArray.st $(STCHDR)  ../include/ArrayedCollection.$(H)  ../include/SequenceableCollection.$(H)  ../include/Collection.$(H)  ../include/Object.$(H)
+$(OUTDIR)ZipArchive.$(O) ZipArchive.$(H): ZipArchive.st $(STCHDR)  ../include/Object.$(H)
 # ENDMAKEDEPEND