bcopy -> memcpy
authorClaus Gittinger <cg@exept.de>
Mon, 19 Jun 2017 09:58:01 +0200
changeset 4414 42edc97b2323
parent 4413 e3ee8be3627f
child 4415 2b984cf54494
bcopy -> memcpy
Socket.st
ZipArchive.st
--- a/Socket.st	Mon Jun 19 09:57:38 2017 +0200
+++ b/Socket.st	Mon Jun 19 09:58:01 2017 +0200
@@ -247,422 +247,422 @@
     which are meant to be compatible to ST-80's UnixSocketAccessor interface.
 
     TODO: cleanup historic leftovers,
-          change to raise more signals on errors.
+	  change to raise more signals on errors.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
 examples
 "
     example (get help info from an nntp server):
-                                                                        [exBegin]
-        |sock|
-
-        sock := Socket newTCPclientToHost:'smtp.exept.de' port:'smtp'.
-        sock isNil ifTrue:[
-            self warn:'no smtp daemon is running'.
-            ^ self
-        ].
-        Transcript showCR:sock nextLine.
-
-        sock nextPutAll:'HELO STX socket test'; cr.
-        Transcript showCR:sock nextLine.
-        sock close
-                                                                        [exEnd]
+									[exBegin]
+	|sock|
+
+	sock := Socket newTCPclientToHost:'smtp.exept.de' port:'smtp'.
+	sock isNil ifTrue:[
+	    self warn:'no smtp daemon is running'.
+	    ^ self
+	].
+	Transcript showCR:sock nextLine.
+
+	sock nextPutAll:'HELO STX socket test'; cr.
+	Transcript showCR:sock nextLine.
+	sock close
+									[exEnd]
 
 
     example (connect to finger daemon, get users entry):
-                                                                        [exBegin]
-        |sock entry|
-
-        sock := Socket newTCPclientToHost:'localhost' port:'finger'.
-        sock isNil ifTrue:[
-            self warn:'no finger daemon is running'.
-            ^ self
-        ].
-        sock useCRLF:true.
-        sock buffered:false.
-        sock isNil ifTrue:[
-            Transcript showCR:'cannot connect to local finger daemon'
-        ] ifFalse:[
-            sock nextPutAll:(OperatingSystem getLoginName).
-            sock cr.
-
-            entry := sock nextLine.
-            Transcript showCR:entry.
-
-            sock close
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|sock entry|
+
+	sock := Socket newTCPclientToHost:'localhost' port:'finger'.
+	sock isNil ifTrue:[
+	    self warn:'no finger daemon is running'.
+	    ^ self
+	].
+	sock useCRLF:true.
+	sock buffered:false.
+	sock isNil ifTrue:[
+	    Transcript showCR:'cannot connect to local finger daemon'
+	] ifFalse:[
+	    sock nextPutAll:(OperatingSystem getLoginName).
+	    sock cr.
+
+	    entry := sock nextLine.
+	    Transcript showCR:entry.
+
+	    sock close
+	]
+									[exEnd]
 
     example (connect to an ftp server):
-                                                                        [exBegin]
-        |sock|
-
-        sock := Socket newTCPclientToHost:'www.exept.de' port:'ftp'.
-
-        sock buffered:false.
-        Transcript showCR:sock nextLine.
-        sock nextPutAll:('USER ' , 'anonymous'); cr.
-        Transcript showCR:sock nextLine.
-        sock nextPutAll:('PASS ' , 'fooBar'); cr.
-        Transcript showCR:sock nextLine.
-        sock nextPutAll:'HELP'; cr.
-        [
-            |line|
-            line := sock nextLine.
-            Transcript showCR:line.
-            (line at:4) = $-
-        ] whileTrue.
-        sock close.
-
-        'don't know enough of the ftp protocol to continue here ...'
-                                                                        [exEnd]
+									[exBegin]
+	|sock|
+
+	sock := Socket newTCPclientToHost:'www.exept.de' port:'ftp'.
+
+	sock buffered:false.
+	Transcript showCR:sock nextLine.
+	sock nextPutAll:('USER ' , 'anonymous'); cr.
+	Transcript showCR:sock nextLine.
+	sock nextPutAll:('PASS ' , 'fooBar'); cr.
+	Transcript showCR:sock nextLine.
+	sock nextPutAll:'HELP'; cr.
+	[
+	    |line|
+	    line := sock nextLine.
+	    Transcript showCR:line.
+	    (line at:4) = $-
+	] whileTrue.
+	sock close.
+
+	'don't know enough of the ftp protocol to continue here ...'
+									[exEnd]
 
 
     example (connect to an snmp server [UDP]):
     Note: this is not a real connection, only the destination address is
-          being fixed.
-                                                                        [exBegin]
-        |sock port|
-
-        sock := Socket newUDP.
-        port := Socket portOfService:'snmp'.
-        sock connectTo:'localhost' port:port.
-        sock buffered:false.
-        Transcript showCR:'got it'.
-        sock close.
-                                                                        [exEnd]
+	  being fixed.
+									[exBegin]
+	|sock port|
+
+	sock := Socket newUDP.
+	port := Socket portOfService:'snmp'.
+	sock connectTo:'localhost' port:port.
+	sock buffered:false.
+	Transcript showCR:'got it'.
+	sock close.
+									[exEnd]
 
 
     example (await connection from a client and read some data):
-                                                                        [exBegin]
-        |connectSock sock|
-
-        connectSock := Socket newTCPserverAtPort:9998.
-        connectSock isNil ifTrue:[
-            Transcript showCR:'socket setup failed.'.
-        ] ifFalse:[
-            Transcript showCR:'listen ..'.
-            (connectSock listenFor:5) ifFalse:[
-                Transcript showCR:'listen failed.'.
-            ] ifTrue:[
-                Transcript showCR:'wait'.
-                connectSock readWait.
-                Transcript showCR:'accept'.
-                sock := connectSock accept.
-                sock isNil ifTrue:[
-                    Transcript showCR:'accept failed.'.
-                ] ifFalse:[
-                    sock buffered:false.
-                    Transcript showCR:'server: got it'.
-                    'can now do transfer via sock'.
-                    Transcript showCR:'read'.
-                    Transcript showCR:('got: ' , sock nextLine).
-
-                    Transcript showCR:'close'.
-                    sock close
-                ].
-                connectSock close.
-            ]
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|connectSock sock|
+
+	connectSock := Socket newTCPserverAtPort:9998.
+	connectSock isNil ifTrue:[
+	    Transcript showCR:'socket setup failed.'.
+	] ifFalse:[
+	    Transcript showCR:'listen ..'.
+	    (connectSock listenFor:5) ifFalse:[
+		Transcript showCR:'listen failed.'.
+	    ] ifTrue:[
+		Transcript showCR:'wait'.
+		connectSock readWait.
+		Transcript showCR:'accept'.
+		sock := connectSock accept.
+		sock isNil ifTrue:[
+		    Transcript showCR:'accept failed.'.
+		] ifFalse:[
+		    sock buffered:false.
+		    Transcript showCR:'server: got it'.
+		    'can now do transfer via sock'.
+		    Transcript showCR:'read'.
+		    Transcript showCR:('got: ' , sock nextLine).
+
+		    Transcript showCR:'close'.
+		    sock close
+		].
+		connectSock close.
+	    ]
+	]
+									[exEnd]
 
 
     example (connect to above server and send some data):
-                                                                        [exBegin]
-        |sock|
-
-        sock := Socket newTCPclientToHost:'localhost' port:9998.
-        sock isNil ifTrue:[
-            Transcript showCR:'nope'
-        ] ifFalse:[
-            sock buffered:false.
-            Transcript showCR:'client: got it'.
-            'can now do transfer via sock'.
-            Transcript showCR:'sending <hello>'.
-            sock nextPutLine:'hello'.
-            sock close
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|sock|
+
+	sock := Socket newTCPclientToHost:'localhost' port:9998.
+	sock isNil ifTrue:[
+	    Transcript showCR:'nope'
+	] ifFalse:[
+	    sock buffered:false.
+	    Transcript showCR:'client: got it'.
+	    'can now do transfer via sock'.
+	    Transcript showCR:'sending <hello>'.
+	    sock nextPutLine:'hello'.
+	    sock close
+	]
+									[exEnd]
 
     example: UNIX domain socket (await connection from a client and read some data):
 
-        |connectSock sock|
-
-        '/tmp/ud_socket' asFilename remove.
-        connectSock := Socket newUNIXserverAt:'/tmp/ud_socket'.
-        connectSock isNil ifTrue:[
-            Transcript showCR:'socket setup failed.'.
-        ] ifFalse:[
-            Transcript showCR:'listen ..'.
-            (connectSock listenFor:5) ifFalse:[
-                Transcript showCR:'listen failed.'.
-            ] ifTrue:[
-                Transcript showCR:'wait'.
-                connectSock buffered:false.
-                connectSock readWait.
-                Transcript showCR:'accept'.
-                sock := connectSock accept.
-                sock isNil ifTrue:[
-                    Transcript showCR:'accept failed.'.
-                ] ifFalse:[
-                    sock buffered:false.
-                    Transcript showCR:'server: got it'.
-                    'can now do transfer via sock'.
-                    Transcript showCR:'read'.
-                    Transcript showCR:('got: ' , sock nextLine).
-
-                    Transcript showCR:'close'.
-                    sock close
-                ].
-                connectSock close.
-            ]
-        ]
+	|connectSock sock|
+
+	'/tmp/ud_socket' asFilename remove.
+	connectSock := Socket newUNIXserverAt:'/tmp/ud_socket'.
+	connectSock isNil ifTrue:[
+	    Transcript showCR:'socket setup failed.'.
+	] ifFalse:[
+	    Transcript showCR:'listen ..'.
+	    (connectSock listenFor:5) ifFalse:[
+		Transcript showCR:'listen failed.'.
+	    ] ifTrue:[
+		Transcript showCR:'wait'.
+		connectSock buffered:false.
+		connectSock readWait.
+		Transcript showCR:'accept'.
+		sock := connectSock accept.
+		sock isNil ifTrue:[
+		    Transcript showCR:'accept failed.'.
+		] ifFalse:[
+		    sock buffered:false.
+		    Transcript showCR:'server: got it'.
+		    'can now do transfer via sock'.
+		    Transcript showCR:'read'.
+		    Transcript showCR:('got: ' , sock nextLine).
+
+		    Transcript showCR:'close'.
+		    sock close
+		].
+		connectSock close.
+	    ]
+	]
 
 
     example (connect to above server and send some data;
-             Notice, this fails, if above server code is executed in the same ST/X image
-                     (at least on LINUX), since the OS does not correctly handle
-                     a connect from within an interrupted accept system call
-                     On SGI's SVR4, this works ok
-                                                                        [exBegin]
-        |sock|
-
-        sock := Socket newUNIXclientTo:'/tmp/ud_socket'.
-        sock isNil ifTrue:[
-            Transcript showCR:'nope'
-        ] ifFalse:[
-            sock buffered:false.
-            Transcript showCR:'client: got it'.
-            'can now do transfer via sock'.
-            Transcript showCR:'sending <hello>'.
-            sock nextPutLine:'hello'.
-            sock close
-        ]
-                                                                        [exEnd]
+	     Notice, this fails, if above server code is executed in the same ST/X image
+		     (at least on LINUX), since the OS does not correctly handle
+		     a connect from within an interrupted accept system call
+		     On SGI's SVR4, this works ok
+									[exBegin]
+	|sock|
+
+	sock := Socket newUNIXclientTo:'/tmp/ud_socket'.
+	sock isNil ifTrue:[
+	    Transcript showCR:'nope'
+	] ifFalse:[
+	    sock buffered:false.
+	    Transcript showCR:'client: got it'.
+	    'can now do transfer via sock'.
+	    Transcript showCR:'sending <hello>'.
+	    sock nextPutLine:'hello'.
+	    sock close
+	]
+									[exEnd]
 
 
     example (UDP await packet from a client and read some data):
-                                                                        [exBegin]
-        |udpSock sock addr n dataBuffer|
-
-        udpSock := Socket newUDPserverAtPort:9999.
-        udpSock isNil ifTrue:[
-            Transcript showCR:'socket setup failed.'.
-        ] ifFalse:[
-            Transcript showCR:'wait'.
-            udpSock readWait.
-
-            addr := IPSocketAddress new.
-            dataBuffer := ByteArray new:1000.
-            n := udpSock receiveFrom:addr buffer:dataBuffer start:1 for:dataBuffer size.
-            n > 0 ifTrue:[
-                Transcript showCR:('got: ' , n printString , 'bytes  from ' , addr printString).
-                Transcript showCR:('data: ' , (dataBuffer copyTo:n) printString).
-            ] ifFalse:[
-                Transcript showCR:'read failed'.
-            ].
-
-            Transcript showCR:'close'.
-            udpSock close
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|udpSock sock addr n dataBuffer|
+
+	udpSock := Socket newUDPserverAtPort:9999.
+	udpSock isNil ifTrue:[
+	    Transcript showCR:'socket setup failed.'.
+	] ifFalse:[
+	    Transcript showCR:'wait'.
+	    udpSock readWait.
+
+	    addr := IPSocketAddress new.
+	    dataBuffer := ByteArray new:1000.
+	    n := udpSock receiveFrom:addr buffer:dataBuffer start:1 for:dataBuffer size.
+	    n > 0 ifTrue:[
+		Transcript showCR:('got: ' , n printString , 'bytes  from ' , addr printString).
+		Transcript showCR:('data: ' , (dataBuffer copyTo:n) printString).
+	    ] ifFalse:[
+		Transcript showCR:'read failed'.
+	    ].
+
+	    Transcript showCR:'close'.
+	    udpSock close
+	]
+									[exEnd]
     example (connect to above UDP server and send some data;
-                                                                        [exBegin]
-        |sock|
-
-        sock := Socket newUDP.
-        sock isNil ifTrue:[
-            Transcript showCR:'nope'
-        ] ifFalse:[
-            sock sendTo:(IPSocketAddress new hostName:'localhost' port:9999) buffer:'hello world'.
-            sock close
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|sock|
+
+	sock := Socket newUDP.
+	sock isNil ifTrue:[
+	    Transcript showCR:'nope'
+	] ifFalse:[
+	    sock sendTo:(IPSocketAddress new hostName:'localhost' port:9999) buffer:'hello world'.
+	    sock close
+	]
+									[exEnd]
 
     example: pingWalk (try to ping hosts on the local network)
     Note: it dosen't use ICMP ping, but tries to reache the echo service,
-          which is disabled on most OS.
-                                                                        [exBegin]
-        |myAddress list top hosts walkProcess port|
-
-        myAddress := OperatingSystem getNetworkAddresses
-                        keysAndValuesSelect:[:eachIFName :eachAddress|
-                            eachAddress isLocal not
-                            and:[eachIFName = 'wlan0']
-                        ].
-        myAddress := myAddress first hostAddress.
-
-        port := Socket portOfService:'echo'.
-        port isNil ifTrue:[
-            self error:'dont know echo port'.
-            ^ self
-        ].
-
-        top := StandardSystemView new.
-        top label:'PING net walk'.
-
-        list := ScrollableView for:ListView in:top.
-        list origin:0.0@0.0 corner:1.0@1.0.
-
-        top openAndWait.
-
-        walkProcess := [
-            |l low hi direction tryHostID dottedName hostName conn addr|
-
-            l := SortedCollection new.
-
-            ' only works with type C-net
-              the code below could simply do 1 to:254 do:[:hostID }
-              but, to probe likely hosts earlier, the probing is done
-              ping-pong like around my ip-address (assuming, that other machines
-              have numbers around my own)'.
-
-            low := hi := (myAddress at:4).
-            direction := 1.
-
-            [low > 0 or:[hi < 255]] whileTrue:[
-                direction > 0 ifTrue:[
-                    hi := hi + 1.
-                    tryHostID := hi.
-                    direction := -1.
-                ] ifFalse:[
-                    low := low - 1.
-                    tryHostID := low.
-                    direction := 1.
-                ].
-                (tryHostID between:1 and:254) ifTrue:[
-                    dottedName := (myAddress at:1) printString
-                                  , '.' , (myAddress at:2) printString
-                                  , '.' , (myAddress at:3) printString
-                                  , '.' , tryHostID printString.
-
-                    top label:'PING net walk - trying ' , dottedName.
-
-                    top windowGroup withCursor:Cursor wait do:[
-                        conn := Socket newTCPclientToHost:dottedName port:port withTimeout:1000.
-                        conn notNil ifTrue:[
-                            addr := Socket ipAddressOfHost:dottedName.
-                            hostName := Socket hostWithIpAddress:addr.
-                            hostName isNil ifTrue:[
-                                hostName :='?'
-                            ].
-                            l add:(dottedName paddedTo:15 with:Character space)
-                                   , ' '
-                                   , (hostName paddedTo:15 with:Character space)
-                                   , ' up & reachable'.
-                            list list:l.
-                            conn close.
-                        ]
-                    ].
-                ].
-            ].
-            top label:'PING reachable hosts'.
-        ] forkAt:(Processor userBackgroundPriority).
-        walkProcess name:'ping net walker'.
-                                                                        [exEnd]
-
-
-        This example creates a simple UDP server that accepts
-        single packets from anybody and broadcasts them to all
-        clients that have connected so far.
-
-                                                                        [exBegin]
-        | socket address buffer msgSize clients |
-        clients := Set new.
-        address := IPSocketAddress new.
-        buffer := String new: 1024.
-
-        socket := self newUDPserverAtPort: 6666.
-
-        Transcript showCR: 'server starting'.
-
-        [
-            [true] whileTrue: [
-                (socket readWaitWithTimeoutMs: 200) ifFalse: [
-                    msgSize := socket
-                            receiveFrom: address
-                            buffer: buffer
-                            start: 1
-                            for: buffer size.
-
-                    clients add: address copy.
-                    clients do: [ :clientAddress |
-                            socket
-                                    sendTo: clientAddress
-                                    buffer: buffer
-                                    start: 1
-                                    for: msgSize]]
-            ]
-        ] ensure:[
-            Transcript showCR: 'server shutting down'.
-            socket close
-        ]
-                                                                        [exEnd]
+	  which is disabled on most OS.
+									[exBegin]
+	|myAddress list top hosts walkProcess port|
+
+	myAddress := OperatingSystem getNetworkAddresses
+			keysAndValuesSelect:[:eachIFName :eachAddress|
+			    eachAddress isLocal not
+			    and:[eachIFName = 'wlan0']
+			].
+	myAddress := myAddress first hostAddress.
+
+	port := Socket portOfService:'echo'.
+	port isNil ifTrue:[
+	    self error:'dont know echo port'.
+	    ^ self
+	].
+
+	top := StandardSystemView new.
+	top label:'PING net walk'.
+
+	list := ScrollableView for:ListView in:top.
+	list origin:0.0@0.0 corner:1.0@1.0.
+
+	top openAndWait.
+
+	walkProcess := [
+	    |l low hi direction tryHostID dottedName hostName conn addr|
+
+	    l := SortedCollection new.
+
+	    ' only works with type C-net
+	      the code below could simply do 1 to:254 do:[:hostID }
+	      but, to probe likely hosts earlier, the probing is done
+	      ping-pong like around my ip-address (assuming, that other machines
+	      have numbers around my own)'.
+
+	    low := hi := (myAddress at:4).
+	    direction := 1.
+
+	    [low > 0 or:[hi < 255]] whileTrue:[
+		direction > 0 ifTrue:[
+		    hi := hi + 1.
+		    tryHostID := hi.
+		    direction := -1.
+		] ifFalse:[
+		    low := low - 1.
+		    tryHostID := low.
+		    direction := 1.
+		].
+		(tryHostID between:1 and:254) ifTrue:[
+		    dottedName := (myAddress at:1) printString
+				  , '.' , (myAddress at:2) printString
+				  , '.' , (myAddress at:3) printString
+				  , '.' , tryHostID printString.
+
+		    top label:'PING net walk - trying ' , dottedName.
+
+		    top windowGroup withCursor:Cursor wait do:[
+			conn := Socket newTCPclientToHost:dottedName port:port withTimeout:1000.
+			conn notNil ifTrue:[
+			    addr := Socket ipAddressOfHost:dottedName.
+			    hostName := Socket hostWithIpAddress:addr.
+			    hostName isNil ifTrue:[
+				hostName :='?'
+			    ].
+			    l add:(dottedName paddedTo:15 with:Character space)
+				   , ' '
+				   , (hostName paddedTo:15 with:Character space)
+				   , ' up & reachable'.
+			    list list:l.
+			    conn close.
+			]
+		    ].
+		].
+	    ].
+	    top label:'PING reachable hosts'.
+	] forkAt:(Processor userBackgroundPriority).
+	walkProcess name:'ping net walker'.
+									[exEnd]
+
+
+	This example creates a simple UDP server that accepts
+	single packets from anybody and broadcasts them to all
+	clients that have connected so far.
+
+									[exBegin]
+	| socket address buffer msgSize clients |
+	clients := Set new.
+	address := IPSocketAddress new.
+	buffer := String new: 1024.
+
+	socket := self newUDPserverAtPort: 6666.
+
+	Transcript showCR: 'server starting'.
+
+	[
+	    [true] whileTrue: [
+		(socket readWaitWithTimeoutMs: 200) ifFalse: [
+		    msgSize := socket
+			    receiveFrom: address
+			    buffer: buffer
+			    start: 1
+			    for: buffer size.
+
+		    clients add: address copy.
+		    clients do: [ :clientAddress |
+			    socket
+				    sendTo: clientAddress
+				    buffer: buffer
+				    start: 1
+				    for: msgSize]]
+	    ]
+	] ensure:[
+	    Transcript showCR: 'server shutting down'.
+	    socket close
+	]
+									[exEnd]
 
    send a datagram to above server:
-                                                                        [exBegin]
-
-        | socket address buffer host msg |
-
-        host := Dialog
-                request: 'What is the name of the server''s host?'
-                initialAnswer: 'localhost'.
-
-        socket := self newUDP.
-
-        address := IPSocketAddress hostName: host port: 6666.
-
-        buffer := ByteArray new: 1000.
-        [
-            [(msg := Dialog request: 'Say something') isEmpty] whileFalse:[
-                | replySize stream |
-
-                socket writeWait.
-                stream := buffer writeStream.
-                stream nextPutAll: msg.
-                socket sendTo:address buffer:buffer start:1 for:stream position.
-                socket readWait.
-
-                replySize := socket receiveFrom:address buffer:buffer.
-                replySize > 0 ifTrue: [
-                    Transcript cr; nextPutAll: 'Server acknowledged: '.
-                    Transcript show: ((buffer copyFrom: 1 to: replySize) asString)
-                ]
-            ]
-        ] ensure: [socket close].
-        Transcript cr
-                                                                        [exEnd]
+									[exBegin]
+
+	| socket address buffer host msg |
+
+	host := Dialog
+		request: 'What is the name of the server''s host?'
+		initialAnswer: 'localhost'.
+
+	socket := self newUDP.
+
+	address := IPSocketAddress hostName: host port: 6666.
+
+	buffer := ByteArray new: 1000.
+	[
+	    [(msg := Dialog request: 'Say something') isEmpty] whileFalse:[
+		| replySize stream |
+
+		socket writeWait.
+		stream := buffer writeStream.
+		stream nextPutAll: msg.
+		socket sendTo:address buffer:buffer start:1 for:stream position.
+		socket readWait.
+
+		replySize := socket receiveFrom:address buffer:buffer.
+		replySize > 0 ifTrue: [
+		    Transcript cr; nextPutAll: 'Server acknowledged: '.
+		    Transcript show: ((buffer copyFrom: 1 to: replySize) asString)
+		]
+	    ]
+	] ensure: [socket close].
+	Transcript cr
+									[exEnd]
 
 
    loopBack:
-                                                                        [exBegin]
-
-        |readerTask readingSocket writingSocket|
-
-        readingSocket := self newTCPserverAtPort:9999.
-        readerTask :=
-            [
-                |connection|
-
-                readingSocket listenFor:1.
-                connection := readingSocket accept.
-                readingSocket close.
-                [connection atEnd] whileFalse:[
-                    Transcript showCR:(connection nextLine).
-                ].
-                connection close.
-            ] fork.
-
-        Delay waitForSeconds:1.
-        writingSocket := self newTCPclientToHost:'localhost' port:9999.
-        writingSocket nextPutLine:'Hello'.
-        writingSocket nextPutLine:'World'.
-        writingSocket close.
-                                                                        [exEnd]
+									[exBegin]
+
+	|readerTask readingSocket writingSocket|
+
+	readingSocket := self newTCPserverAtPort:9999.
+	readerTask :=
+	    [
+		|connection|
+
+		readingSocket listenFor:1.
+		connection := readingSocket accept.
+		readingSocket close.
+		[connection atEnd] whileFalse:[
+		    Transcript showCR:(connection nextLine).
+		].
+		connection close.
+	    ] fork.
+
+	Delay waitForSeconds:1.
+	writingSocket := self newTCPclientToHost:'localhost' port:9999.
+	writingSocket nextPutLine:'Hello'.
+	writingSocket nextPutLine:'World'.
+	writingSocket close.
+									[exEnd]
 "
 ! !
 
@@ -816,10 +816,10 @@
      See also: #newTCPclientToHost:port:withTimeout:"
 
     ^ self
-        newTCPclientToHost:hostNameOrAddress
-        port:aPortOrServiceName
-        domain:self defaultIpDomainForConnect
-        withTimeout:nil
+	newTCPclientToHost:hostNameOrAddress
+	port:aPortOrServiceName
+	domain:self defaultIpDomainForConnect
+	withTimeout:nil
 
     "
       Socket newTCPclientToHost:'www.exept.de' port:'https'
@@ -840,32 +840,32 @@
     |socket addressList lastDomainSymbol|
 
     hostNameOrAddress isString ifFalse:[
-        ^ self newTCPclientToAddress:hostNameOrAddress port:aPortOrServiceName withTimeout:millis.
+	^ self newTCPclientToAddress:hostNameOrAddress port:aPortOrServiceName withTimeout:millis.
     ].
 
     addressList := SocketAddress
-                        allForHostName:hostNameOrAddress
-                        serviceName:aPortOrServiceName
-                        domain:aDomainSymbolOrNil
-                        type:#stream.
+			allForHostName:hostNameOrAddress
+			serviceName:aPortOrServiceName
+			domain:aDomainSymbolOrNil
+			type:#stream.
 
     addressList do:[:eachAddress|
-        |domainSymbol|
-
-        domainSymbol := eachAddress domain.
-        domainSymbol ~~ lastDomainSymbol ifTrue:[
-            socket notNil ifTrue:[
-                socket close.
-            ].
-            socket := self new domain:domainSymbol type:#stream.
-            lastDomainSymbol := domainSymbol.
-        ].
-        (socket connectTo:eachAddress withTimeout:millis) ifTrue:[
-            ^ socket.
-        ].
+	|domainSymbol|
+
+	domainSymbol := eachAddress domain.
+	domainSymbol ~~ lastDomainSymbol ifTrue:[
+	    socket notNil ifTrue:[
+		socket close.
+	    ].
+	    socket := self new domain:domainSymbol type:#stream.
+	    lastDomainSymbol := domainSymbol.
+	].
+	(socket connectTo:eachAddress withTimeout:millis) ifTrue:[
+	    ^ socket.
+	].
     ].
     socket notNil ifTrue:[
-        socket close.
+	socket close.
     ].
     ^ nil.
 
@@ -888,10 +888,10 @@
      and return nil."
 
     ^ self
-        newTCPclientToHost:hostNameOrAddress
-        port:aPortOrServiceName
-        domain:self defaultIpDomainForConnect
-        withTimeout:millis
+	newTCPclientToHost:hostNameOrAddress
+	port:aPortOrServiceName
+	domain:self defaultIpDomainForConnect
+	withTimeout:millis
 !
 
 newTCPserverAtAnonymousPort
@@ -1121,9 +1121,9 @@
 
 defaultIpDomainForConnect
     "answer the domain used to look up host names for connect:
-        #AF_INET    use only IPv4
-        #AF_INET6   use only IPv6
-        nil         use both IPv4 and IPv6"
+	#AF_INET    use only IPv4
+	#AF_INET6   use only IPv6
+	nil         use both IPv4 and IPv6"
 
     ^ nil
 ! !
@@ -1218,12 +1218,12 @@
      WARNING: untested code - I have no appletalk to test this."
 
     NameLookupError
-        handle:[:ex |
-            ^ nil
-        ]
-        do:[
-            ^ (AppletalkSocketAddress hostAddress:addrByteArray) hostName
-        ]
+	handle:[:ex |
+	    ^ nil
+	]
+	do:[
+	    ^ (AppletalkSocketAddress hostAddress:addrByteArray) hostName
+	]
 
     "
      Socket appletalkAddressOfHost:'yourAppleHere'
@@ -1242,12 +1242,12 @@
      This is the reverse operation to #ipAddressOfHost:."
 
     NameLookupError
-        handle:[:ex |
-            ^ nil
-        ]
-        do:[
-            ^ (IPSocketAddress hostAddress:addrByteArray) hostName
-        ]
+	handle:[:ex |
+	    ^ nil
+	]
+	do:[
+	    ^ (IPSocketAddress hostAddress:addrByteArray) hostName
+	]
 
     "
      Socket ipAddressOfHost:'clam'
@@ -1272,12 +1272,12 @@
      This is the reverse operation to #ipV6AddressOfHost:."
 
     NameLookupError
-        handle:[:ex |
-            ^ nil
-        ]
-        do:[
-            ^ (IPv6SocketAddress hostAddress:addrByteArray) hostName
-        ]
+	handle:[:ex |
+	    ^ nil
+	]
+	do:[
+	    ^ (IPv6SocketAddress hostAddress:addrByteArray) hostName
+	]
 
     "
      Socket ipV6AddressOfHost:'clam'
@@ -1789,17 +1789,17 @@
     |ok error socketAddress|
 
     handle isNil ifTrue:[
-        ^ self errorNotOpen
+	^ self errorNotOpen
     ].
     socketAddress := aSocketAddress.
     socketAddress isNil ifTrue:[
-        "ok, get a all zero socket address, so it is for anyHost
-         and the port will be assigned"
-        socketAddress := self socketAddressClass new.
+	"ok, get a all zero socket address, so it is for anyHost
+	 and the port will be assigned"
+	socketAddress := self socketAddressClass new.
     ].
     domain == #'AF_INET6' ifTrue:[
-        "accept also IPv4 connections on IPv6 sockets (this is off by default for windows"
-        self setSocketOption:#'IPV6_V6ONLY' argument:false argument:nil.
+	"accept also IPv4 connections on IPv6 sockets (this is off by default for windows"
+	self setSocketOption:#'IPV6_V6ONLY' argument:false argument:nil.
     ].
     ok := false.
 
@@ -1813,52 +1813,52 @@
     int sockAddrOffs;
 
     if (fp == nil) {
-        goto getOutOfHere;
+	goto getOutOfHere;
     }
 
     if (! __isBytes(socketAddress)) {
-        error = __mkSmallInteger(-1);
-        goto getOutOfHere;
+	error = __mkSmallInteger(-1);
+	goto getOutOfHere;
     }
     /* get the socket-address */
     if (__isNonNilObject(socketAddress)){
-        int nIndex;
-        OBJ cls = __qClass(socketAddress);
-
-        sockAddrOffs = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-        nIndex = __qSize(socketAddress) - OHDR_SIZE;
-        sockaddr_size = nIndex - sockAddrOffs;
-        if (sockaddr_size > sizeof(sa)) {
-            error=__mkSmallInteger(-2);
-            goto getOutOfHere;
-        }
-        memcpy(&sa, __byteArrayVal(socketAddress) + sockAddrOffs, sockaddr_size);
+	int nIndex;
+	OBJ cls = __qClass(socketAddress);
+
+	sockAddrOffs = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	nIndex = __qSize(socketAddress) - OHDR_SIZE;
+	sockaddr_size = nIndex - sockAddrOffs;
+	if (sockaddr_size > sizeof(sa)) {
+	    error=__mkSmallInteger(-2);
+	    goto getOutOfHere;
+	}
+	memcpy(&sa, __byteArrayVal(socketAddress) + sockAddrOffs, sockaddr_size);
     }
 
     sock = SOCKET_FROM_FILE_OBJECT(fp);
 
 # ifdef SO_REUSEADDR
     if (reuse == true) {
-        int on = 1;
-        if (setsockopt(sock, SOL_SOCKET, SO_REUSEADDR, (char *) &on, sizeof (on)) < 0) {
-            DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR failed\n"));
-        }
+	int on = 1;
+	if (setsockopt(sock, SOL_SOCKET, SO_REUSEADDR, (char *) &on, sizeof (on)) < 0) {
+	    DBGPRINTF(("SOCKET: setsockopt - SO_REUSEADDR failed\n"));
+	}
     }
 # endif /* SO_REUSEADDR */
 
 # ifdef BIND_BLOCKS
 #  ifdef DO_WRAP_CALLS
     do {
-        __threadErrno = 0;
-        ret = STX_WSA_NOINT_CALL3("bind", bind, sock, &sa, sockaddr_size);
+	__threadErrno = 0;
+	ret = STX_WSA_NOINT_CALL3("bind", bind, sock, &sa, sockaddr_size);
     } while ((ret < 0) && (__threadErrno == EINTR));
     if (ret < 0) {
-        errno = __threadErrno;
+	errno = __threadErrno;
     }
 #  else
     __BEGIN_INTERRUPTABLE__
     do {
-        ret = bind(sock, (struct sockaddr *)&sa, sockaddr_size);
+	ret = bind(sock, (struct sockaddr *)&sa, sockaddr_size);
     } while ((ret < 0) && (errno == EINTR));
     __END_INTERRUPTABLE__
 #  endif
@@ -1868,68 +1868,68 @@
 # endif
     if (ret < 0) {
 # ifdef __win32__
-        if (errno == 0) {
-            errno = WSAGetLastError();
-        }
+	if (errno == 0) {
+	    errno = WSAGetLastError();
+	}
 # endif
-        DBGPRINTF(("SOCKET: bind failed errno=%d\n", errno));
-        error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
-        goto getOutOfHere;
+	DBGPRINTF(("SOCKET: bind failed errno=%d\n", errno));
+	error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
+	goto getOutOfHere;
     } else {
-        ok = true;
+	ok = true;
     }
 #endif /* NO_SOCKET */
 
 getOutOfHere: ;
 %}.
     ok ifFalse:[
-        |errorHolder errorString|
-
-        error isInteger ifTrue:[
-            errorHolder := OperatingSystem errorHolderForNumber:error.
-            errorString := errorHolder errorString.
-        ] ifFalse:[
-            errorString := error.
-        ].
-        OpenError newException
-            errorString:('cannot bind socket to address: %1 (%2)'
-                            bindWith:socketAddress
-                            with:errorString);
-            errorCode:error;
-            osErrorHolder:errorHolder;
-            parameter:self;
-            raiseRequest.
-        "maybe someone catches the error and binds to some other port..."
-        ^ true.
+	|errorHolder errorString|
+
+	error isInteger ifTrue:[
+	    errorHolder := OperatingSystem errorHolderForNumber:error.
+	    errorString := errorHolder errorString.
+	] ifFalse:[
+	    errorString := error.
+	].
+	OpenError newException
+	    errorString:('cannot bind socket to address: %1 (%2)'
+			    bindWith:socketAddress
+			    with:errorString);
+	    errorCode:error;
+	    osErrorHolder:errorHolder;
+	    parameter:self;
+	    raiseRequest.
+	"maybe someone catches the error and binds to some other port..."
+	^ true.
     ].
 
     port := socketAddress port.
     port == 0 ifTrue:[
-        "this is a bind to a random port, now we can get the real port"
-        port := self getFullSocketAddress port.
+	"this is a bind to a random port, now we can get the real port"
+	port := self getFullSocketAddress port.
     ].
     ^ true
 
     "
      (Socket domain:#'AF_INET' type:#stream)
-        bindTo:(IPSocketAddress anyHost port:445) reuseAddress:false;
-        yourself.
+	bindTo:(IPSocketAddress anyHost port:445) reuseAddress:false;
+	yourself.
 
      (Socket domain:#'AF_INET' type:#stream)
-        bindTo:139 reuseAddress:false;
-        yourself.
+	bindTo:139 reuseAddress:false;
+	yourself.
 
      (Socket domain:#'AF_INET6' type:#stream)
-        bindTo:nil reuseAddress:false;
-        yourself.
+	bindTo:nil reuseAddress:false;
+	yourself.
 
      (Socket domain:#'AF_INET' type:#stream)
-        bindTo:(IPSocketAddress localHost port:2122) reuseAddress:false;
-        yourself.
+	bindTo:(IPSocketAddress localHost port:2122) reuseAddress:false;
+	yourself.
 
      (Socket domain:#'AF_UNIX' type:#stream)
-        bindTo:nil reuseAddress:false;
-        yourself.
+	bindTo:nil reuseAddress:false;
+	yourself.
     "
 !
 
@@ -1996,16 +1996,16 @@
 
 abortAndClose
     "immediately abort the connection:
-        discard buffered data and close the stream"
-
-    self linger:0.     
-    self close.         
+	discard buffered data and close the stream"
+
+    self linger:0.
+    self close.
 !
 
 shutDown
-    "shutDown (initiate a graceful close) 
+    "shutDown (initiate a graceful close)
      and close (free the filedescriptor) the socket.
-     The close will return immediately and buffered data will be sent in the 
+     The close will return immediately and buffered data will be sent in the
      background, unless you set linger"
 
     self shutdown:2.
@@ -2026,7 +2026,7 @@
      Any write to the socket will signal end-of-file from now on.
      An orderly release (TCP FIN) will be initiated after the last buffered data
      has been sent, so the other side will get a end-of-file condition eventually.
-     If you set linger > 0, the operation will wait until buffered data 
+     If you set linger > 0, the operation will wait until buffered data
      has been delivered to the peer.
      Otherwise the operation returns immediately."
 
@@ -2065,26 +2065,26 @@
     |domainClass socketAddress|
 
     (hostOrPathNameOrSocketAddr isSocketAddress) ifTrue:[
-        socketAddress := hostOrPathNameOrSocketAddr.
-        portNrOrNameOrNil notNil ifTrue:[
-            socketAddress port:portNrOrNameOrNil.
-        ].
+	socketAddress := hostOrPathNameOrSocketAddr.
+	portNrOrNameOrNil notNil ifTrue:[
+	    socketAddress port:portNrOrNameOrNil.
+	].
     ] ifFalse:[
-        "backward compatibility: support for byteArray and string arg"
-        domainClass := self class socketAddressClassForDomain:domain.
-        domainClass isNil ifTrue:[
-            ^ self error:'invalid (unsupported) domain'.
-        ].
-
-        hostOrPathNameOrSocketAddr isString ifTrue:[
-            socketAddress := domainClass hostName:hostOrPathNameOrSocketAddr serviceName:portNrOrNameOrNil type:#SOCK_STREAM.
-            peerName := hostOrPathNameOrSocketAddr.
-        ] ifFalse:[
-            hostOrPathNameOrSocketAddr isByteCollection ifFalse:[
-                ^ self error:'connectTo: bad host (socketAddress) argument'
-            ].
-            socketAddress := domainClass hostAddress:hostOrPathNameOrSocketAddr port:portNrOrNameOrNil.
-        ].
+	"backward compatibility: support for byteArray and string arg"
+	domainClass := self class socketAddressClassForDomain:domain.
+	domainClass isNil ifTrue:[
+	    ^ self error:'invalid (unsupported) domain'.
+	].
+
+	hostOrPathNameOrSocketAddr isString ifTrue:[
+	    socketAddress := domainClass hostName:hostOrPathNameOrSocketAddr serviceName:portNrOrNameOrNil type:#SOCK_STREAM.
+	    peerName := hostOrPathNameOrSocketAddr.
+	] ifFalse:[
+	    hostOrPathNameOrSocketAddr isByteCollection ifFalse:[
+		^ self error:'connectTo: bad host (socketAddress) argument'
+	    ].
+	    socketAddress := domainClass hostAddress:hostOrPathNameOrSocketAddr port:portNrOrNameOrNil.
+	].
     ].
 
     ^ self connectTo:socketAddress withTimeout:timeout.
@@ -2112,7 +2112,7 @@
     |isAsync err|
 
     handle isNil ifTrue:[
-        ^ self errorNotOpen
+	^ self errorNotOpen
     ].
     isAsync := false.
 
@@ -2133,25 +2133,25 @@
     int sockaddr_size;
 
     if (!__isNonNilObject(aSocketAddress) || !__isBytes(aSocketAddress)) {
-        DBGPRINTF(("SOCKET: invalid socketAddress\n"));
-        err = @symbol(argumentError);
-        goto out;
+	DBGPRINTF(("SOCKET: invalid socketAddress\n"));
+	err = @symbol(argumentError);
+	goto out;
     }
 
     {
-        int sockAddrOffs = 0;
-        int nIndex =__byteArraySize(aSocketAddress);
-        OBJ cls = __qClass(aSocketAddress);
-
-        //if (cls != @global(ByteArray))
-        //    sockAddrOffs = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-        sockaddr_size = nIndex - sockAddrOffs;
-        if (sockaddr_size > sizeof(sa)) {
-            DBGPRINTF(("SOCKET: invalid (short) socketAddress\n"));
-            err = @symbol(argumentError);
-            goto out;
-        }
-        memcpy(&sa, __byteArrayVal(aSocketAddress) + sockAddrOffs, sockaddr_size);
+	int sockAddrOffs = 0;
+	int nIndex =__byteArraySize(aSocketAddress);
+	OBJ cls = __qClass(aSocketAddress);
+
+	//if (cls != @global(ByteArray))
+	//    sockAddrOffs = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	sockaddr_size = nIndex - sockAddrOffs;
+	if (sockaddr_size > sizeof(sa)) {
+	    DBGPRINTF(("SOCKET: invalid (short) socketAddress\n"));
+	    err = @symbol(argumentError);
+	    goto out;
+	}
+	memcpy(&sa, __byteArrayVal(aSocketAddress) + sockAddrOffs, sockaddr_size);
     }
 
     sock = SOCKET_FROM_FILE_OBJECT(fp);
@@ -2178,18 +2178,18 @@
 
 
     do {
-        DBGFPRINTF((stderr, "SOCKET: (sock=%d) connect...\n", sock));
-        ret = STX_WSA_NOINT_CALL3("connect", connect, sock, &sa, (INT)sockaddr_size);
-        DBGFPRINTF((stderr, "SOCKET: connect(%d) -> %"_ld_" (%d)\n", sock, (INT)ret, __threadErrno));
+	DBGFPRINTF((stderr, "SOCKET: (sock=%d) connect...\n", sock));
+	ret = STX_WSA_NOINT_CALL3("connect", connect, sock, &sa, (INT)sockaddr_size);
+	DBGFPRINTF((stderr, "SOCKET: connect(%d) -> %"_ld_" (%d)\n", sock, (INT)ret, __threadErrno));
     } while ((ret < 0) && (__threadErrno == EINTR));
 
     if (ret < 0) {
-        int optLen = sizeof(errno);
-        errno = __threadErrno;
+	int optLen = sizeof(errno);
+	errno = __threadErrno;
 #if 0
-        if (getsockopt(sock, SOL_SOCKET, SO_ERROR, &errno, &optLen) == SOCKET_ERROR) {
-            DBGFPRINTF((stderr, "SOCKET: getsockopt(SO_ERROR) failed: %d\n", WSAGetLastError()));
-        }
+	if (getsockopt(sock, SOL_SOCKET, SO_ERROR, &errno, &optLen) == SOCKET_ERROR) {
+	    DBGFPRINTF((stderr, "SOCKET: getsockopt(SO_ERROR) failed: %d\n", WSAGetLastError()));
+	}
 #endif // 0
     }
 
@@ -2200,16 +2200,16 @@
     __BEGIN_INTERRUPTABLE__
 #  endif
     do {
-        ret = connect(sock, (struct sockaddr *)&sa, sockaddr_size);
+	ret = connect(sock, (struct sockaddr *)&sa, sockaddr_size);
     } while ((ret < 0)
 #  ifdef __win32__
-             && (errno = WSAGetLastError())
+	     && (errno = WSAGetLastError())
 #  endif
-             && ((errno == EINTR)
+	     && ((errno == EINTR)
 #  ifdef EAGAIN
-                 || (errno == EAGAIN)
+		 || (errno == EAGAIN)
 #  endif
-                ));
+		));
 #  if !defined(__win32__) && !defined(O_NONBLOCK)
     __END_INTERRUPTABLE__
 #  endif
@@ -2222,47 +2222,47 @@
 
     if (ret < 0) {
 # if defined(EINPROGRESS) || defined(EALREADY)
-        if (0
+	if (0
 #  ifdef __win32__
-            || (errno == WSAEWOULDBLOCK)
+	    || (errno == WSAEWOULDBLOCK)
 #  endif
 #  ifdef EINPROGRESS
-            || (errno == EINPROGRESS)
+	    || (errno == EINPROGRESS)
 #  endif
 #  ifdef EALREADY
-            || (errno == EALREADY)
+	    || (errno == EALREADY)
 #  endif
-        ) {
-            /*
-             * This was a nonblocking operation that will take some time.
-             * Do a select on read to get informed when the operation is ready.
-             */
-            DBGFPRINTF((stderr, "SOCKET: isAsync is true\n"));
-            isAsync = true;
-        } else
+	) {
+	    /*
+	     * This was a nonblocking operation that will take some time.
+	     * Do a select on read to get informed when the operation is ready.
+	     */
+	    DBGFPRINTF((stderr, "SOCKET: isAsync is true\n"));
+	    isAsync = true;
+	} else
 # endif /* EINPROGRESS or EALREADY */
-        {
-            DBGFPRINTF((stderr, "SOCKET: connect failed ret=%"_ld_" errno=%d __threadErrno=%d\n",
-                        (INT)ret, errno, __threadErrno ));
+	{
+	    DBGFPRINTF((stderr, "SOCKET: connect failed ret=%"_ld_" errno=%d __threadErrno=%d\n",
+			(INT)ret, errno, __threadErrno ));
 # ifdef DUMP_ADDRESS
-            {
-                unsigned char *cp = (unsigned char *)(&sa);
-                int i;
-
-                console_printf("address data:\n");
-                for (i=0; i<sockaddr_size; i++) {
-                    console_printf(" %02x\n", *cp++);
-                }
-            }
+	    {
+		unsigned char *cp = (unsigned char *)(&sa);
+		int i;
+
+		console_printf("address data:\n");
+		for (i=0; i<sockaddr_size; i++) {
+		    console_printf(" %02x\n", *cp++);
+		}
+	    }
 # endif
-            err = __MKSMALLINT(errno);
-        }
+	    err = __MKSMALLINT(errno);
+	}
     }
 
 # ifdef __win32__
     {
-        int off = 0;
-        ioctlsocket(sock, FIONBIO, &off);
+	int off = 0;
+	ioctlsocket(sock, FIONBIO, &off);
     }
 # elif defined(O_NONBLOCK) // Linux / Unix
     fcntl(sock, F_SETFL, oldFlags);
@@ -2275,34 +2275,34 @@
 %}.
 
     err notNil ifTrue:[
-        err isSymbol ifTrue:[
-            self primitiveFailed:err.
-        ].
-        lastErrorNumber := err.
-        ^ false.
-        "/ Once we will raise an exception instead of returning false (and have to change some code above):
+	err isSymbol ifTrue:[
+	    self primitiveFailed:err.
+	].
+	lastErrorNumber := err.
+	^ false.
+	"/ Once we will raise an exception instead of returning false (and have to change some code above):
 "/        (OperatingSystem errorHolderForNumber:err) reportError.
     ].
     isAsync ifTrue:[
-        (self writeExceptionWaitWithTimeoutMs:timeout) ifTrue:[
-            "/ a timeout occurred
-            "/ should I cancel the connect?
-            lastErrorNumber := OperatingSystem errorNumberFor:#ETIMEDOUT.
-            ^ false.
-        ].
-        err := self getSocketError.
-        err ~~ 0 ifTrue:[
-            lastErrorNumber := err.
-            ^ false.
-        ].
+	(self writeExceptionWaitWithTimeoutMs:timeout) ifTrue:[
+	    "/ a timeout occurred
+	    "/ should I cancel the connect?
+	    lastErrorNumber := OperatingSystem errorNumberFor:#ETIMEDOUT.
+	    ^ false.
+	].
+	err := self getSocketError.
+	err ~~ 0 ifTrue:[
+	    lastErrorNumber := err.
+	    ^ false.
+	].
     ].
 
 
     peer := aSocketAddress.
     port isNil ifTrue:[
-        "socket has not been explicitly bound,
-         after connect it has been bound implicitly - fetch the port"
-        port := self getFullSocketAddress port.
+	"socket has not been explicitly bound,
+	 after connect it has been bound implicitly - fetch the port"
+	port := self getFullSocketAddress port.
     ].
     ^ true
 
@@ -2370,7 +2370,7 @@
 
 	if (allocatedBuffer) {
 	    if (n > 0) {
-		bcopy(allocatedBuffer, (char *)__InstPtr(aDataBuffer) + offs, n);
+		memcpy((char *)__InstPtr(aDataBuffer) + offs, allocatedBuffer, n);
 	    }
 	    free(allocatedBuffer);
 	}
@@ -2436,17 +2436,17 @@
 
     domainClass := self class socketAddressClassForDomain:domain.
     domainClass isNil ifTrue:[
-        ^ self error:'invalid (unsupported) domain'.
+	^ self error:'invalid (unsupported) domain'.
     ].
     anAddressBuffer isSocketAddress ifTrue:[
-        anAddressBuffer class == domainClass ifFalse:[
-            ^ self error:'addressBuffer class mismatch (domain)'.
-        ].
-        addr := anAddressBuffer.
+	anAddressBuffer class == domainClass ifFalse:[
+	    ^ self error:'addressBuffer class mismatch (domain)'.
+	].
+	addr := anAddressBuffer.
     ] ifFalse:[
-        anAddressBuffer notNil ifTrue:[
-            addr := domainClass new.
-        ].
+	anAddressBuffer notNil ifTrue:[
+	    addr := domainClass new.
+	].
     ].
 
 %{
@@ -2454,103 +2454,103 @@
     OBJ fp = __INST(handle);
 
     if (fp != nil) {
-        SOCKET sock;
-        size_t objSize;
-        union sockaddr_u sa;
-        socklen_t alen = 0;
-        INT n, offs;
-        int _flags = __longIntVal(flags);
-        char *extPtr;
-        unsigned char *allocatedBuffer = NULL, *buffer = NULL;
-
-        sock = SOCKET_FROM_FILE_OBJECT(fp);
-
-        if (! setupBufferParameters(aDataBuffer, startIndex, &extPtr, &offs, &objSize)) goto bad;
-        if (__isSmallInteger(nBytes)) {
-            if (__intVal(nBytes) < objSize) {
-                objSize = __intVal(nBytes);
-            }
-        }
+	SOCKET sock;
+	size_t objSize;
+	union sockaddr_u sa;
+	socklen_t alen = 0;
+	INT n, offs;
+	int _flags = __longIntVal(flags);
+	char *extPtr;
+	unsigned char *allocatedBuffer = NULL, *buffer = NULL;
+
+	sock = SOCKET_FROM_FILE_OBJECT(fp);
+
+	if (! setupBufferParameters(aDataBuffer, startIndex, &extPtr, &offs, &objSize)) goto bad;
+	if (__isSmallInteger(nBytes)) {
+	    if (__intVal(nBytes) < objSize) {
+		objSize = __intVal(nBytes);
+	    }
+	}
 # ifdef DO_WRAP_CALLS
-        if (extPtr) {
-            buffer = extPtr + offs;
-        } else {
-            allocatedBuffer = buffer = (char *)malloc(objSize);
-        }
-
-        do {
-            __threadErrno = 0;
-            alen = sizeof(sa);
-            n = (INT)STX_WSA_NOINT_CALL6("recvfrom", recvfrom, sock, buffer, objSize, _flags, (struct sockaddr *)&sa, &alen);
-        } while ((n < 0) && (__threadErrno == EINTR));
-        if (n < 0) {
-            errno = __threadErrno;
-        }
-
-        if (allocatedBuffer) {
-            if (n > 0) {
-                memcpy((char *)__InstPtr(aDataBuffer) + offs, allocatedBuffer, n);
-            }
-            free(allocatedBuffer);
-        }
+	if (extPtr) {
+	    buffer = extPtr + offs;
+	} else {
+	    allocatedBuffer = buffer = (char *)malloc(objSize);
+	}
+
+	do {
+	    __threadErrno = 0;
+	    alen = sizeof(sa);
+	    n = (INT)STX_WSA_NOINT_CALL6("recvfrom", recvfrom, sock, buffer, objSize, _flags, (struct sockaddr *)&sa, &alen);
+	} while ((n < 0) && (__threadErrno == EINTR));
+	if (n < 0) {
+	    errno = __threadErrno;
+	}
+
+	if (allocatedBuffer) {
+	    if (n > 0) {
+		memcpy((char *)__InstPtr(aDataBuffer) + offs, allocatedBuffer, n);
+	    }
+	    free(allocatedBuffer);
+	}
 # else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            alen = sizeof(sa);
-            if (extPtr) {
-                n = recvfrom(sock, extPtr + offs, objSize, _flags, (struct sockaddr *) &sa, &alen);
-            } else {
-                n = recvfrom(sock, (char *)__InstPtr(aDataBuffer) + offs, objSize, _flags, (struct sockaddr *) &sa, &alen);
-            }
-        } while ((n < 0) && (errno == EINTR));
-        __END_INTERRUPTABLE__
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    alen = sizeof(sa);
+	    if (extPtr) {
+		n = recvfrom(sock, extPtr + offs, objSize, _flags, (struct sockaddr *) &sa, &alen);
+	    } else {
+		n = recvfrom(sock, (char *)__InstPtr(aDataBuffer) + offs, objSize, _flags, (struct sockaddr *) &sa, &alen);
+	    }
+	} while ((n < 0) && (errno == EINTR));
+	__END_INTERRUPTABLE__
 # endif
 
-        if (n >= 0) {
-            if (__isNonNilObject(addr)) {
-                char *addrPtr;
-                OBJ oClass;
-                int nInstVars, nInstBytes, objSize;
-
-                oClass = __qClass(addr);
-                if (! __isBytes(addr) )
-                    goto bad;
-                nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
-                nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
-                objSize = __qSize(addr) - nInstBytes;
-                addrPtr = (char *)__InstPtr(addr) + nInstBytes;
-                if (objSize < alen)
-                    goto bad;
-
-                /*
-                 * extract the datagrams address
-                 */
-                memcpy(addrPtr, (char *)&sa, alen);
-                addrLen = __MKSMALLINT(alen);
-            }
-        }
-        if (n < 0) {
-            error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
-        }
-        nReceived = __MKSMALLINT(n);
+	if (n >= 0) {
+	    if (__isNonNilObject(addr)) {
+		char *addrPtr;
+		OBJ oClass;
+		int nInstVars, nInstBytes, objSize;
+
+		oClass = __qClass(addr);
+		if (! __isBytes(addr) )
+		    goto bad;
+		nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
+		nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
+		objSize = __qSize(addr) - nInstBytes;
+		addrPtr = (char *)__InstPtr(addr) + nInstBytes;
+		if (objSize < alen)
+		    goto bad;
+
+		/*
+		 * extract the datagrams address
+		 */
+		memcpy(addrPtr, (char *)&sa, alen);
+		addrLen = __MKSMALLINT(alen);
+	    }
+	}
+	if (n < 0) {
+	    error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
+	}
+	nReceived = __MKSMALLINT(n);
     }
 #endif
 bad: ;
 %}.
     error notNil ifTrue:[
-        ^ self readError:error.
+	^ self readError:error.
     ].
 
     nReceived notNil ifTrue:[
-        addrLen notNil ifTrue:[
-            (addr == anAddressBuffer) ifFalse:[
-                self obsoleteFeatureWarning:'please use a socketAddress argument'.
-
-                "can be a ByteArray for backward compatibility"
-                anAddressBuffer replaceFrom:1 to:addrLen with:(addr hostAddress).
-            ].
-        ].
-        ^ nReceived
+	addrLen notNil ifTrue:[
+	    (addr == anAddressBuffer) ifFalse:[
+		self obsoleteFeatureWarning:'please use a socketAddress argument'.
+
+		"can be a ByteArray for backward compatibility"
+		anAddressBuffer replaceFrom:1 to:addrLen with:(addr hostAddress).
+	    ].
+	].
+	^ nReceived
     ].
     "
      arrive here if you try to receive into an invalid buffer
@@ -2603,7 +2603,7 @@
 	    buffer = extPtr + offs;
 	} else {
 	    allocatedBuffer = buffer = (char *)malloc(objSize);
-	    bcopy((char *)__InstPtr(aDataBuffer) + offs, allocatedBuffer, objSize);
+	    memcpy(allocatedBuffer, (char *)__InstPtr(aDataBuffer) + offs, objSize);
 	}
 
 	do {
@@ -2687,16 +2687,16 @@
     |domainClass addr error|
 
     anAddressBuffer isSocketAddress ifTrue:[
-        addr := anAddressBuffer.
+	addr := anAddressBuffer.
     ] ifFalse:[
-        anAddressBuffer isByteArray ifFalse:[
-            ^ self error:'bad socketAddress argument'
-        ].
-        domainClass := self class socketAddressClassForDomain:domain.
-        domainClass isNil ifTrue:[
-            ^ self error:'invalid (unsupported) domain'.
-        ].
-        addr := domainClass hostAddress:anAddressBuffer.
+	anAddressBuffer isByteArray ifFalse:[
+	    ^ self error:'bad socketAddress argument'
+	].
+	domainClass := self class socketAddressClassForDomain:domain.
+	domainClass isNil ifTrue:[
+	    ^ self error:'invalid (unsupported) domain'.
+	].
+	addr := domainClass hostAddress:anAddressBuffer.
     ].
 %{
 #ifndef NO_SOCKET
@@ -2705,90 +2705,90 @@
     if ((fp != nil)
      && __isSmallInteger(startIndex)
      && __isSmallInteger(nBytes)) {
-        SOCKET sock;
-        INT objSize;
-        struct sockaddr *sockaddr_ptr;
-        union sockaddr_u sa;
-        socklen_t sockaddr_size, alen = 0;
-        INT sockAddrOffs;
-        INT n, offs;
-        char *extPtr;
-        int _flags = __longIntVal(flags);
-        unsigned long norder;
-        unsigned char *buffer;
-        unsigned char *allocatedBuffer = NULL;
-
-        sock = SOCKET_FROM_FILE_OBJECT(fp);
-
-        if (! __isBytes(addr)) {
-            sockaddr_size = 0;
-            sockaddr_ptr = (struct sockaddr *)0;
-        } else {
-            int nIndex;
-            OBJ cls;
-
-            sockAddrOffs = 0;
-            if ((cls = __qClass(addr)) != @global(ByteArray))
-                sockAddrOffs += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-            nIndex = __qSize(addr) - OHDR_SIZE;
-            sockaddr_size = nIndex - sockAddrOffs;
-            if (sockaddr_size > sizeof(sa)) {
-                console_fprintf(stderr, "Socket [warning]: bad socketAddr\n");
-                goto bad;
-            }
-            memcpy(&sa, (__byteArrayVal(addr) + sockAddrOffs), sockaddr_size);
-            sockaddr_ptr = (struct sockaddr *)(&sa);
-        }
-
-        if (! setupBufferParameters(aDataBuffer, startIndex, &extPtr, &offs, &objSize)) goto bad;
-        if (__isSmallInteger(nBytes)) {
-            if (__intVal(nBytes) < objSize) {
-                objSize = __intVal(nBytes);
-            }
-        }
+	SOCKET sock;
+	INT objSize;
+	struct sockaddr *sockaddr_ptr;
+	union sockaddr_u sa;
+	socklen_t sockaddr_size, alen = 0;
+	INT sockAddrOffs;
+	INT n, offs;
+	char *extPtr;
+	int _flags = __longIntVal(flags);
+	unsigned long norder;
+	unsigned char *buffer;
+	unsigned char *allocatedBuffer = NULL;
+
+	sock = SOCKET_FROM_FILE_OBJECT(fp);
+
+	if (! __isBytes(addr)) {
+	    sockaddr_size = 0;
+	    sockaddr_ptr = (struct sockaddr *)0;
+	} else {
+	    int nIndex;
+	    OBJ cls;
+
+	    sockAddrOffs = 0;
+	    if ((cls = __qClass(addr)) != @global(ByteArray))
+		sockAddrOffs += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	    nIndex = __qSize(addr) - OHDR_SIZE;
+	    sockaddr_size = nIndex - sockAddrOffs;
+	    if (sockaddr_size > sizeof(sa)) {
+		console_fprintf(stderr, "Socket [warning]: bad socketAddr\n");
+		goto bad;
+	    }
+	    memcpy(&sa, (__byteArrayVal(addr) + sockAddrOffs), sockaddr_size);
+	    sockaddr_ptr = (struct sockaddr *)(&sa);
+	}
+
+	if (! setupBufferParameters(aDataBuffer, startIndex, &extPtr, &offs, &objSize)) goto bad;
+	if (__isSmallInteger(nBytes)) {
+	    if (__intVal(nBytes) < objSize) {
+		objSize = __intVal(nBytes);
+	    }
+	}
 
 #ifdef DO_WRAP_CALLS
-        if (extPtr) {
-            buffer = extPtr + offs;
-        } else {
-            allocatedBuffer = buffer = (char *)malloc(objSize);
-            bcopy((char *)__InstPtr(aDataBuffer) + offs, allocatedBuffer, objSize);
-        }
-
-        do {
-            __threadErrno = 0;
-            n = (INT)STX_WSA_NOINT_CALL6("sendto", sendto, sock, buffer, objSize, _flags, sockaddr_ptr, sockaddr_size);
-        } while ((n < 0) && (__threadErrno == EINTR));
-        if (n < 0) {
-            errno = __threadErrno;
-        }
-
-        if (allocatedBuffer) {
-            free(allocatedBuffer);
-        }
+	if (extPtr) {
+	    buffer = extPtr + offs;
+	} else {
+	    allocatedBuffer = buffer = (char *)malloc(objSize);
+	    memcpy(allocatedBuffer, (char *)__InstPtr(aDataBuffer) + offs, objSize);
+	}
+
+	do {
+	    __threadErrno = 0;
+	    n = (INT)STX_WSA_NOINT_CALL6("sendto", sendto, sock, buffer, objSize, _flags, sockaddr_ptr, sockaddr_size);
+	} while ((n < 0) && (__threadErrno == EINTR));
+	if (n < 0) {
+	    errno = __threadErrno;
+	}
+
+	if (allocatedBuffer) {
+	    free(allocatedBuffer);
+	}
 #else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            if (extPtr) {
-                n = sendto(sock, extPtr + offs, objSize, _flags, sockaddr_ptr, sockaddr_size);
-            } else {
-                n = sendto(sock, (char *)__InstPtr(aDataBuffer) + offs, objSize, _flags, sockaddr_ptr, sockaddr_size);
-            }
-        } while ((n < 0) && (errno == EINTR));
-        __END_INTERRUPTABLE__
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    if (extPtr) {
+		n = sendto(sock, extPtr + offs, objSize, _flags, sockaddr_ptr, sockaddr_size);
+	    } else {
+		n = sendto(sock, (char *)__InstPtr(aDataBuffer) + offs, objSize, _flags, sockaddr_ptr, sockaddr_size);
+	    }
+	} while ((n < 0) && (errno == EINTR));
+	__END_INTERRUPTABLE__
 #endif
 
-        if (n < 0) {
-            error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
-        } else {
-            RETURN (__MKSMALLINT(n));
-        }
+	if (n < 0) {
+	    error = __INST(lastErrorNumber) = __MKSMALLINT(errno);
+	} else {
+	    RETURN (__MKSMALLINT(n));
+	}
     }
 #endif
 bad: ;
 %}.
     error notNil ifTrue:[
-        self writeError:error.
+	self writeError:error.
     ].
 
     "
@@ -2874,12 +2874,12 @@
     |serverSocketHandle addr domainClass newHandle|
 
     handle notNil ifTrue:[
-        ^ self errorAlreadyOpen.
+	^ self errorAlreadyOpen.
     ].
     serverSocketHandle := aServerSocket fileHandle.
     serverSocketHandle isNil ifTrue:[
-        "socket is not open"
-        ^ false
+	"socket is not open"
+	^ false
     ].
 
     domain := aServerSocket domain.
@@ -2888,7 +2888,7 @@
     "unix domain sockets do not return a valid peer name on accept"
     domainClass := self class socketAddressClassForDomain:domain.
     domainClass isNil ifTrue:[
-        ^ self error:'invalid (unsupported) domain'.
+	^ self error:'invalid (unsupported) domain'.
     ].
     addr := domainClass new.
     newHandle := OperatingSystem socketAccessor new.
@@ -2910,25 +2910,25 @@
 
 # if defined(O_NONBLOCK) && defined(SET_NDELAY)
     if (blocking == false) {
-        flags = fcntl(serverSocket, F_GETFL);
-        fcntl(serverSocket, F_SETFL, flags | O_NONBLOCK);
+	flags = fcntl(serverSocket, F_GETFL);
+	fcntl(serverSocket, F_SETFL, flags | O_NONBLOCK);
     }
 # endif
 
 # ifdef DO_WRAP_CALLS
     do {
-        __threadErrno = 0;
-        alen = sizeof(sa);
-        newSock = (SOCKET)STX_WSA_CALL3("accept", accept, serverSocket, &sa, &alen);
+	__threadErrno = 0;
+	alen = sizeof(sa);
+	newSock = (SOCKET)STX_WSA_CALL3("accept", accept, serverSocket, &sa, &alen);
     } while ((newSock < 0) && (__threadErrno == EINTR));
     if (newSock < 0) {
-        errno = __threadErrno;
+	errno = __threadErrno;
     }
 # else
     __BEGIN_INTERRUPTABLE__
     do {
-        alen = sizeof(sa);
-        newSock = accept(serverSocket, (struct sockaddr *) &sa, &alen);
+	alen = sizeof(sa);
+	newSock = accept(serverSocket, (struct sockaddr *) &sa, &alen);
     } while ((newSock < 0) && (errno == EINTR));
     __END_INTERRUPTABLE__
 # endif
@@ -2936,41 +2936,41 @@
 
 # if defined(O_NDELAY) && defined(SET_NDELAY)
     if (blocking == false) {
-        fcntl(serverSocket, F_SETFL, flags);
+	fcntl(serverSocket, F_SETFL, flags);
     }
 # endif
 
     if (newSock == -1) {
-        DBGPRINTF(("SOCKET: accept call failed errno=%d\n", errno));
-        __INST(lastErrorNumber) = __MKSMALLINT(errno);
-        RETURN (false);
+	DBGPRINTF(("SOCKET: accept call failed errno=%d\n", errno));
+	__INST(lastErrorNumber) = __MKSMALLINT(errno);
+	RETURN (false);
     }
 
     if (__isNonNilObject(addr)) {
-        OBJ oClass = __qClass(addr);
-        int nInstVars, nInstBytes, objSize;
-        char *addrP;
-
-        if (! __isBytes(addr) ) {
-            DBGPRINTF(("SOCKET: bad addr\n"));
-            closesocket(newSock);
-            RETURN (false);
-        }
-
-        nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
-        nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
-        objSize = __qSize(addr) - nInstBytes;
-        addrP = (char *)__InstPtr(addr) + nInstBytes;
-        if (objSize < alen) {
-            DBGPRINTF(("SOCKET: bad addr\n"));
-            closesocket(newSock);
-            RETURN (false);
-        }
-
-        /*
-         * extract the partners address
-         */
-        memcpy(addrP, (char *)&sa, alen);
+	OBJ oClass = __qClass(addr);
+	int nInstVars, nInstBytes, objSize;
+	char *addrP;
+
+	if (! __isBytes(addr) ) {
+	    DBGPRINTF(("SOCKET: bad addr\n"));
+	    closesocket(newSock);
+	    RETURN (false);
+	}
+
+	nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
+	nInstBytes = OHDR_SIZE + (nInstVars * sizeof(OBJ));
+	objSize = __qSize(addr) - nInstBytes;
+	addrP = (char *)__InstPtr(addr) + nInstBytes;
+	if (objSize < alen) {
+	    DBGPRINTF(("SOCKET: bad addr\n"));
+	    closesocket(newSock);
+	    RETURN (false);
+	}
+
+	/*
+	 * extract the partners address
+	 */
+	memcpy(addrP, (char *)&sa, alen);
     }
 
     /*
@@ -2988,19 +2988,19 @@
 # else // ! __win32__
     fp = fdopen(newSock, "r+");
     if (! fp) {
-        DBGPRINTF(("SOCKET: fdopen call failed\n"));
-        __INST(lastErrorNumber) = __MKSMALLINT(errno);
-        closesocket(newSock);
-        DBGFPRINTF((stderr, "SOCKET: close (fdopen failed) (%d)\n", newSock));
-        RETURN (false);
+	DBGPRINTF(("SOCKET: fdopen call failed\n"));
+	__INST(lastErrorNumber) = __MKSMALLINT(errno);
+	closesocket(newSock);
+	DBGFPRINTF((stderr, "SOCKET: close (fdopen failed) (%d)\n", newSock));
+	RETURN (false);
     }
 # endif // ! __win32__
 
     if ((@global(FileOpenTrace) == true) || __debugging__) {
 # ifdef __win32__
-        console_fprintf(stderr, "fdopen [Socket accept] -> fd: %d (H: %"_lx_")\n", _fd, (INT)newSock);
+	console_fprintf(stderr, "fdopen [Socket accept] -> fd: %d (H: %"_lx_")\n", _fd, (INT)newSock);
 # else
-        console_fprintf(stderr, "fdopen [Socket accept] -> %"_lx_" (fd: %d)\n", (INT)fp, newSock);
+	console_fprintf(stderr, "fdopen [Socket accept] -> %"_lx_" (fd: %d)\n", (INT)fp, newSock);
 # endif
     }
 
@@ -3531,7 +3531,7 @@
      partners host after an accept."
 
     peerName isNil ifTrue:[
-        peerName := self class peerNameFromDomain:domain peer:peer.
+	peerName := self class peerNameFromDomain:domain peer:peer.
     ].
     ^ peerName
 !
@@ -3575,7 +3575,7 @@
 
     domainClass := self class socketAddressClassForDomain:domain.
     domainClass isNil ifTrue:[
-        ^ self error:'invalid (unsupported) domain'.
+	^ self error:'invalid (unsupported) domain'.
     ].
     ^ domainClass.
 !
@@ -3606,7 +3606,7 @@
     |domainName domainCode typeCode error newHandle|
 
     handle notNil ifTrue:[
-        ^ self errorAlreadyOpen
+	^ self errorAlreadyOpen
     ].
     domainName := SocketAddress domainCodeFromName:domainArg.
     domainCode := OperatingSystem domainCodeOf:domainName.
@@ -3628,19 +3628,19 @@
 # endif
 
     if (! __isSmallInteger(domainCode)) {
-        error = @symbol(badArgument1);
-        goto out;
+	error = @symbol(badArgument1);
+	goto out;
     }
     if (! __isSmallInteger(typeCode)) {
-        error = @symbol(badArgument2);
-        goto out;
+	error = @symbol(badArgument2);
+	goto out;
     }
     if (protocolNumber != nil) {
-        if (!__isSmallInteger(protocolNumber)) {
-            error = @symbol(badArgument3);
-            goto out;
-        }
-        proto = __intVal(protocolNumber);
+	if (!__isSmallInteger(protocolNumber)) {
+	    error = @symbol(badArgument3);
+	    goto out;
+	}
+	proto = __intVal(protocolNumber);
     }
 
     /*
@@ -3652,91 +3652,91 @@
 # ifdef __win32__
     sock = WSASocket(dom, typ, proto, 0, 0, noInheritFlag);
     if (sock == INVALID_SOCKET && noInheritFlag) {
-        // tried to open socket with WSA_FLAG_NO_HANDLE_INHERIT
-        // This fails on older windows versions, e.g. Windows XP
-        sock = WSASocket(dom, typ, proto, 0, 0, 0);
-        if (sock != INVALID_SOCKET) {
-            // no error without WSA_FLAG_NO_HANDLE_INHERIT,
-            // never use this flag again!
-            noInheritFlag = 0;
-        }
+	// tried to open socket with WSA_FLAG_NO_HANDLE_INHERIT
+	// This fails on older windows versions, e.g. Windows XP
+	sock = WSASocket(dom, typ, proto, 0, 0, 0);
+	if (sock != INVALID_SOCKET) {
+	    // no error without WSA_FLAG_NO_HANDLE_INHERIT,
+	    // never use this flag again!
+	    noInheritFlag = 0;
+	}
     }
     if (sock == INVALID_SOCKET) {
-        errno = WSAGetLastError();
+	errno = WSAGetLastError();
 
 # else  // !__win32__
 
     sock = socket(dom, typ, proto);
 # if defined(EPROTONOSUPPORT) /* for SGI */
     if ((sock < 0) && (proto != 0) && (errno == EPROTONOSUPPORT)) {
-        DBGPRINTF(("SOCKET: retry with UNSPEC protocol\n"));
-        proto = 0;
-        sock = socket(dom, typ, 0);
+	DBGPRINTF(("SOCKET: retry with UNSPEC protocol\n"));
+	proto = 0;
+	sock = socket(dom, typ, 0);
     }
 # endif
     if (sock < 0) {
 # endif // !__win32__
 
-        DBGPRINTF(("SOCKET: socket(dom=%d typ=%d proto=%d) call failed errno=%d\n", dom, typ, proto, errno));
-        error = __MKSMALLINT(errno);
+	DBGPRINTF(("SOCKET: socket(dom=%d typ=%d proto=%d) call failed errno=%d\n", dom, typ, proto, errno));
+	error = __MKSMALLINT(errno);
     } else {
 # if defined(SET_LINGER_WHEN_CREATING_SOCKET) && defined(SO_LINGER)
-        {
-            struct linger l;
-
-            l.l_onoff = 1;
-            l.l_linger = 30;
-            setsockopt(sock, SOL_SOCKET, SO_LINGER, &l, sizeof(l));
-        }
+	{
+	    struct linger l;
+
+	    l.l_onoff = 1;
+	    l.l_linger = 30;
+	    setsockopt(sock, SOL_SOCKET, SO_LINGER, &l, sizeof(l));
+	}
 # endif
 # ifdef __win32__
-        /*
-         * make it blocking
-         */
-        {
-            unsigned long zero = 0;
-            ioctlsocket(sock, FIONBIO, &zero);
-        }
-        {
+	/*
+	 * make it blocking
+	 */
+	{
+	    unsigned long zero = 0;
+	    ioctlsocket(sock, FIONBIO, &zero);
+	}
+	{
 #  if 0 && (defined( __BORLANDC__ ) || defined( __MINGW__ ))
-            /*
-             * make it a FILE *
-             */
-            __stxWrapApiEnterCritical();
-            _fd = _open_osfhandle((long)sock, 0);
-            __stxWrapApiLeaveCritical();
+	    /*
+	     * make it a FILE *
+	     */
+	    __stxWrapApiEnterCritical();
+	    _fd = _open_osfhandle((long)sock, 0);
+	    __stxWrapApiLeaveCritical();
 #  else
-            _fd = (int)sock;
+	    _fd = (int)sock;
 #  endif
-            DBGPRINTF(("SOCKET: sock=%d fd=%d\n", sock, _fd));
-        }
+	    DBGPRINTF(("SOCKET: sock=%d fd=%d\n", sock, _fd));
+	}
 # else  // !__win32__
-        fp = fdopen(sock, "r+");
-        if (! fp) {
-            DBGPRINTF(("SOCKET: fdopen call failed\n"));
-            error = __MKSMALLINT(errno);
-            __BEGIN_INTERRUPTABLE__
-            closesocket(sock);
-            DBGFPRINTF((stderr, "SOCKET: fdopen failed (%d)\n", sock));
-            __END_INTERRUPTABLE__
-            goto out;
-        }
+	fp = fdopen(sock, "r+");
+	if (! fp) {
+	    DBGPRINTF(("SOCKET: fdopen call failed\n"));
+	    error = __MKSMALLINT(errno);
+	    __BEGIN_INTERRUPTABLE__
+	    closesocket(sock);
+	    DBGFPRINTF((stderr, "SOCKET: fdopen failed (%d)\n", sock));
+	    __END_INTERRUPTABLE__
+	    goto out;
+	}
 # endif // !__win32__
 
-        if (@global(FileOpenTrace) == true) {
+	if (@global(FileOpenTrace) == true) {
 # ifdef __win32__
-            console_fprintf(stderr, "fdopen [Socket create] -> fd: %d (H: %"_lx_")\n", (INT)_fd, (INT)sock);
+	    console_fprintf(stderr, "fdopen [Socket create] -> fd: %d (H: %"_lx_")\n", (INT)_fd, (INT)sock);
 # else
-            console_fprintf(stderr, "fdopen [Socket] -> %"_lx_" (fd: %d)\n", (INT)fp, sock);
+	    console_fprintf(stderr, "fdopen [Socket] -> %"_lx_" (fd: %d)\n", (INT)fp, sock);
 # endif
-        }
+	}
 
 # ifdef __win32__
-        __externalAddressVal(newHandle) = _fd;
-        __INST(handleType) = @symbol(socketHandle);
+	__externalAddressVal(newHandle) = _fd;
+	__INST(handleType) = @symbol(socketHandle);
 # else
-        __externalAddressVal(newHandle) = fp;
-        __INST(handleType) = @symbol(socketFilePointer);
+	__externalAddressVal(newHandle) = fp;
+	__INST(handleType) = @symbol(socketFilePointer);
 # endif
     }
 #endif
@@ -3745,15 +3745,15 @@
 
     "all ok?"
     handleType notNil ifTrue:[
-        handle := newHandle.
-        domain := domainArg.
-        socketType := typeArg.
-        self registerForFinalization.
-        ^ self.
+	handle := newHandle.
+	domain := domainArg.
+	socketType := typeArg.
+	self registerForFinalization.
+	^ self.
     ].
     error isInteger ifTrue:[
-        lastErrorNumber := error.
-        ^ self openError:error.
+	lastErrorNumber := error.
+	^ self openError:error.
     ].
     ^ self primitiveFailed:error.
 
@@ -3769,16 +3769,16 @@
 linger:anIntegerOrNil
     "set the linger behavior on close:
       anIntegerOrNil == nil: close returns immediately, socket tries
-                             to send buffered data in background.
+			     to send buffered data in background.
       anIntegerOrNil == 0:   close returns immediately, bufferd data is discarded.
       anIntegerOrNil > 0:    close waits this many seconds for buffered data
-                             to be delivered, after this time buffered data is
-                             discarded and close returns with an error"
+			     to be delivered, after this time buffered data is
+			     discarded and close returns with an error"
 
     ^ self
-        setSocketOption:#'SO_LINGER'
-        argument:anIntegerOrNil notNil
-        argument:anIntegerOrNil.
+	setSocketOption:#'SO_LINGER'
+	argument:anIntegerOrNil notNil
+	argument:anIntegerOrNil.
 !
 
 receiveBufferSize
@@ -4057,41 +4057,41 @@
 
     "first, a quick check if data is already available"
     self canReadWithoutBlocking ifTrue:[
-        ^ self accept.
+	^ self accept.
     ].
     otherConnections do:[:aConnection |
-        aConnection canReadWithoutBlocking ifTrue:[
-            ^ aConnection
-        ]
+	aConnection canReadWithoutBlocking ifTrue:[
+	    ^ aConnection
+	]
     ].
 
     "check again - prevent incoming interrupts from disturbing our setup"
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        sema := Semaphore new name:'multiReadWait'.
-        otherConnections do:[:aConnection |
-            Processor signal:sema onInput:(aConnection fileDescriptor).
-        ].
-        Processor signal:sema onInput:(self fileDescriptor).
-        timeoutSeconds notNil ifTrue:[
-            Processor signal:sema afterSeconds:timeoutSeconds
-        ].
-        Processor activeProcess state:#ioWait.
-        sema wait.
+	sema := Semaphore new name:'multiReadWait'.
+	otherConnections do:[:aConnection |
+	    Processor signal:sema onInput:(aConnection fileDescriptor).
+	].
+	Processor signal:sema onInput:(self fileDescriptor).
+	timeoutSeconds notNil ifTrue:[
+	    Processor signal:sema afterSeconds:timeoutSeconds
+	].
+	Processor activeProcess state:#ioWait.
+	sema wait.
     ] ifCurtailed:[
-        sema notNil ifTrue:[Processor disableSemaphore:sema].
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	sema notNil ifTrue:[Processor disableSemaphore:sema].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
     "see who it was ..."
     self canReadWithoutBlocking ifTrue:[
-        ^ self accept.
+	^ self accept.
     ].
     otherConnections do:[:aConnection |
-        aConnection canReadWithoutBlocking ifTrue:[
-            ^ aConnection
-        ]
+	aConnection canReadWithoutBlocking ifTrue:[
+	    ^ aConnection
+	]
     ].
 
     "none - a timeout"
@@ -4109,17 +4109,17 @@
     |newSock|
 
     (self readWaitWithTimeout:timeoutSecondsOrNil) ifTrue:[
-        "a timeout occurred - no connection within timeout"
-        ^ nil
+	"a timeout occurred - no connection within timeout"
+	^ nil
     ].
     self isOpen ifFalse:[
-        "socket has been closed while waiting"
-        ^ nil.
+	"socket has been closed while waiting"
+	^ nil.
     ].
     newSock := self class new.
     (newSock primAcceptOn:self blocking:false) ifFalse:[
-        "should raise an error here"
-        ^ nil
+	"should raise an error here"
+	^ nil
     ].
     ^ newSock
 ! !
@@ -4133,4 +4133,3 @@
 version_CVS
     ^ '$Header$'
 ! !
-
--- a/ZipArchive.st	Mon Jun 19 09:57:38 2017 +0200
+++ b/ZipArchive.st	Mon Jun 19 09:58:01 2017 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1998 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
@@ -87,7 +87,7 @@
 
 #define NEXTBYTE        (*inPtr++)
 #define XXXFLUSH(n)        slide += (n)
-#define FLUSH(n)        { bcopy(slide, outPtr, (n)); outPtr += (n); }
+#define FLUSH(n)        { memcpy(outPtr, slide, (n)); outPtr += (n); }
 
 #ifdef DEBUG
 # define Trace(x)       if (debugTrace) { console_fprintf x ; }
@@ -142,25 +142,25 @@
 
 /* Tables for deflate from PKZIP's appnote.txt. */
 static unsigned border[] = {    /* Order of the bit length code lengths */
-        16, 17, 18, 0, 8, 7, 9, 6, 10, 5, 11, 4, 12, 3, 13, 2, 14, 1, 15};
+	16, 17, 18, 0, 8, 7, 9, 6, 10, 5, 11, 4, 12, 3, 13, 2, 14, 1, 15};
 
 static ushort cplens[] = {         /* Copy lengths for literal codes 257..285 */
-        3, 4, 5, 6, 7, 8, 9, 10, 11, 13, 15, 17, 19, 23, 27, 31,
-        35, 43, 51, 59, 67, 83, 99, 115, 131, 163, 195, 227, 258, 0, 0};
-        /* note: see note #13 above about the 258 in this list. */
+	3, 4, 5, 6, 7, 8, 9, 10, 11, 13, 15, 17, 19, 23, 27, 31,
+	35, 43, 51, 59, 67, 83, 99, 115, 131, 163, 195, 227, 258, 0, 0};
+	/* note: see note #13 above about the 258 in this list. */
 
 static ushort cplext[] = {         /* Extra bits for literal codes 257..285 */
-        0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 2, 2, 2, 2,
-        3, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 5, 0, 99, 99}; /* 99==invalid */
+	0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 2, 2, 2, 2,
+	3, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 5, 0, 99, 99}; /* 99==invalid */
 
 static ushort cpdist[] = {         /* Copy offsets for distance codes 0..29 */
-        1, 2, 3, 4, 5, 7, 9, 13, 17, 25, 33, 49, 65, 97, 129, 193,
-        257, 385, 513, 769, 1025, 1537, 2049, 3073, 4097, 6145,
-        8193, 12289, 16385, 24577};
+	1, 2, 3, 4, 5, 7, 9, 13, 17, 25, 33, 49, 65, 97, 129, 193,
+	257, 385, 513, 769, 1025, 1537, 2049, 3073, 4097, 6145,
+	8193, 12289, 16385, 24577};
 static ushort cpdext[] = {         /* Extra bits for distance codes */
-        0, 0, 0, 0, 1, 1, 2, 2, 3, 3, 4, 4, 5, 5, 6, 6,
-        7, 7, 8, 8, 9, 9, 10, 10, 11, 11,
-        12, 12, 13, 13};
+	0, 0, 0, 0, 1, 1, 2, 2, 3, 3, 4, 4, 5, 5, 6, 6,
+	7, 7, 8, 8, 9, 9, 10, 10, 11, 11,
+	12, 12, 13, 13};
 
 /* And'ing with mask[n] masks the lower n bits */
 static ushort mask[] = {
@@ -173,9 +173,9 @@
 /* Macros for inflate() bit peeking and grabbing.
    The usage is:
 
-        NEEDBITS(j)
-        x = b & mask[j];
-        DUMPBITS(j)
+	NEEDBITS(j)
+	x = b & mask[j];
+	DUMPBITS(j)
 
    where NEEDBITS makes sure that b has at least j bits in it, and
    DUMPBITS removes the bits from b.  The macros use the variable k
@@ -390,79 +390,79 @@
       /* make tables up to required level */
       while (k > w + l[h])
       {
-        w += l[h++];            /* add bits already decoded */
-
-        /* compute minimum size table less than or equal to *m bits */
-        z = (z = g - w) > (unsigned)*m ? *m : z;        /* upper limit */
-        if ((f = 1 << (j = k - w)) > a + 1)     /* try a k-w bit table */
-        {                       /* too few codes for k-w bit table */
-          f -= a + 1;           /* deduct codes from patterns left */
-          xp = c + k;
-          while (++j < z)       /* try smaller tables up to z bits */
-          {
-            if ((f <<= 1) <= *++xp)
-              break;            /* enough codes to use up j bits */
-            f -= *xp;           /* else deduct codes from patterns */
-          }
-        }
-        if ((unsigned)w + j > el && (unsigned)w < el)
-          j = el - w;           /* make EOB code end at table */
-        z = 1 << j;             /* table entries for j-bit table */
-        l[h] = j;               /* set table size in stack */
-
-        /* allocate and link in new table */
-        if ((q = (struct huft *)malloc((z + 1)*sizeof(struct huft))) ==
-            (struct huft *)NULL)
-        {
-          if (h)
-            huft_free(u[0]);
-          return 3;             /* not enough memory */
-        }
-        hufts += z + 1;         /* track memory usage */
-        *t = q + 1;             /* link to list for huft_free() */
-        *(t = &(q->v.t)) = (struct huft *)NULL;
-        u[h] = ++q;             /* table starts after link */
-
-        /* connect to last table, if there is one */
-        if (h)
-        {
-          x[h] = i;             /* save pattern for backing up */
-          r.b = (uchar)l[h-1];    /* bits to dump before this table */
-          r.e = (uchar)(16 + j);  /* bits in this table */
-          r.v.t = q;            /* pointer to this table */
-          j = (i & ((1 << w) - 1)) >> (w - l[h-1]);
-          u[h-1][j] = r;        /* connect to last table */
-        }
+	w += l[h++];            /* add bits already decoded */
+
+	/* compute minimum size table less than or equal to *m bits */
+	z = (z = g - w) > (unsigned)*m ? *m : z;        /* upper limit */
+	if ((f = 1 << (j = k - w)) > a + 1)     /* try a k-w bit table */
+	{                       /* too few codes for k-w bit table */
+	  f -= a + 1;           /* deduct codes from patterns left */
+	  xp = c + k;
+	  while (++j < z)       /* try smaller tables up to z bits */
+	  {
+	    if ((f <<= 1) <= *++xp)
+	      break;            /* enough codes to use up j bits */
+	    f -= *xp;           /* else deduct codes from patterns */
+	  }
+	}
+	if ((unsigned)w + j > el && (unsigned)w < el)
+	  j = el - w;           /* make EOB code end at table */
+	z = 1 << j;             /* table entries for j-bit table */
+	l[h] = j;               /* set table size in stack */
+
+	/* allocate and link in new table */
+	if ((q = (struct huft *)malloc((z + 1)*sizeof(struct huft))) ==
+	    (struct huft *)NULL)
+	{
+	  if (h)
+	    huft_free(u[0]);
+	  return 3;             /* not enough memory */
+	}
+	hufts += z + 1;         /* track memory usage */
+	*t = q + 1;             /* link to list for huft_free() */
+	*(t = &(q->v.t)) = (struct huft *)NULL;
+	u[h] = ++q;             /* table starts after link */
+
+	/* connect to last table, if there is one */
+	if (h)
+	{
+	  x[h] = i;             /* save pattern for backing up */
+	  r.b = (uchar)l[h-1];    /* bits to dump before this table */
+	  r.e = (uchar)(16 + j);  /* bits in this table */
+	  r.v.t = q;            /* pointer to this table */
+	  j = (i & ((1 << w) - 1)) >> (w - l[h-1]);
+	  u[h-1][j] = r;        /* connect to last table */
+	}
       }
 
       /* set up table entry in r */
       r.b = (uchar)(k - w);
       if (p >= v + n)
-        r.e = 99;               /* out of values--invalid code */
+	r.e = 99;               /* out of values--invalid code */
       else if (*p < s)
       {
-        r.e = (uchar)(*p < 256 ? 16 : 15);    /* 256 is end-of-block code */
-        r.v.n = *p++;           /* simple code is just the value */
+	r.e = (uchar)(*p < 256 ? 16 : 15);    /* 256 is end-of-block code */
+	r.v.n = *p++;           /* simple code is just the value */
       }
       else
       {
-        r.e = (uchar)e[*p - s];   /* non-simple--look up in lists */
-        r.v.n = d[*p++ - s];
+	r.e = (uchar)e[*p - s];   /* non-simple--look up in lists */
+	r.v.n = d[*p++ - s];
       }
 
       /* fill code-like entries with r */
       f = 1 << (k - w);
       for (j = i >> w; j < z; j += f)
-        q[j] = r;
+	q[j] = r;
 
       /* backwards increment the k-bit code i */
       for (j = 1 << (k - 1); i & j; j >>= 1)
-        i ^= j;
+	i ^= j;
       i ^= j;
 
       /* backup over finished tables */
       while ((i & ((1 << w) - 1)) != x[h])
-        w -= l[--h];            /* don't need to update q */
+	w -= l[--h];            /* don't need to update q */
     }
   }
 
@@ -513,11 +513,11 @@
     NEEDBITS((unsigned)bl)
     if ((e = (t = tl + ((unsigned)b & ml))->e) > 16)
       do {
-        if (e == 99)
-          return 1;
-        DUMPBITS(t->b)
-        e -= 16;
-        NEEDBITS(e)
+	if (e == 99)
+	  return 1;
+	DUMPBITS(t->b)
+	e -= 16;
+	NEEDBITS(e)
       } while ((e = (t = t->v.t + ((unsigned)b & mask[e]))->e) > 16);
     DUMPBITS(t->b)
     if (e == 16)                /* then it's a literal */
@@ -525,15 +525,15 @@
       slide[w++] = (uchar)t->v.n;
       if (w == WSIZE)
       {
-        FLUSH(w);
-        w = 0;
+	FLUSH(w);
+	w = 0;
       }
     }
     else                        /* it's an EOB or a length */
     {
       /* exit if end of block */
       if (e == 15)
-        break;
+	break;
 
       /* get length of block to copy */
       NEEDBITS(e)
@@ -543,13 +543,13 @@
       /* decode distance of block to copy */
       NEEDBITS((unsigned)bd)
       if ((e = (t = td + ((unsigned)b & md))->e) > 16)
-        do {
-          if (e == 99)
-            return 1;
-          DUMPBITS(t->b)
-          e -= 16;
-          NEEDBITS(e)
-        } while ((e = (t = t->v.t + ((unsigned)b & mask[e]))->e) > 16);
+	do {
+	  if (e == 99)
+	    return 1;
+	  DUMPBITS(t->b)
+	  e -= 16;
+	  NEEDBITS(e)
+	} while ((e = (t = t->v.t + ((unsigned)b & mask[e]))->e) > 16);
       DUMPBITS(t->b)
       NEEDBITS(e)
       d = w - t->v.n - ((unsigned)b & mask[e]);
@@ -557,28 +557,24 @@
 
       /* do the copy */
       do {
-        n -= (e = (e = WSIZE - ((d &= WSIZE-1) > w ? d : w)) > n ? n : e);
+	n -= (e = (e = WSIZE - ((d &= WSIZE-1) > w ? d : w)) > n ? n : e);
 #ifndef NOMEMCPY
-        if (w - d >= e)         /* (this test assumes unsigned comparison) */
-        {
-# ifdef USE_MEMCPY
-          memcpy(slide + w, slide + d, e);
-# else
-          bcopy(slide + d, slide + w, e);
-# endif
-          w += e;
-          d += e;
-        }
-        else                      /* do it slow to avoid memcpy() overlap */
+	if (w - d >= e)         /* (this test assumes unsigned comparison) */
+	{
+	  memcpy(slide + w, slide + d, e);
+	  w += e;
+	  d += e;
+	}
+	else                      /* do it slow to avoid memcpy() overlap */
 #endif /* !NOMEMCPY */
-          do {
-            slide[w++] = slide[d++];
-          } while (--e);
-        if (w == WSIZE)
-        {
-          FLUSH(w);
-          w = 0;
-        }
+	  do {
+	    slide[w++] = slide[d++];
+	  } while (--e);
+	if (w == WSIZE)
+	{
+	  FLUSH(w);
+	  w = 0;
+	}
       } while (n);
     }
   }
@@ -681,7 +677,7 @@
       l[i] = 8;
     fixed_bl = 7;
     if ((i = huft_build(l, 288, 257, cplens, cplext,
-                        &fixed_tl, &fixed_bl)) != 0)
+			&fixed_tl, &fixed_bl)) != 0)
     {
       Trace((stderr, "incomplete code set 1\n"));
       fixed_tl = (struct huft *)NULL;
@@ -800,9 +796,9 @@
       j = 3 + ((unsigned)b & 3);
       DUMPBITS(2)
       if ((unsigned)i + j > n)
-        return 1;
+	return 1;
       while (j--)
-        ll[i++] = l;
+	ll[i++] = l;
     }
     else if (j == 17)           /* 3 to 10 zero length codes */
     {
@@ -810,9 +806,9 @@
       j = 3 + ((unsigned)b & 7);
       DUMPBITS(3)
       if ((unsigned)i + j > n)
-        return 1;
+	return 1;
       while (j--)
-        ll[i++] = 0;
+	ll[i++] = 0;
       l = 0;
     }
     else                        /* j == 18: 11 to 138 zero length codes */
@@ -821,9 +817,9 @@
       j = 11 + ((unsigned)b & 0x7f);
       DUMPBITS(7)
       if ((unsigned)i + j > n)
-        return 1;
+	return 1;
       while (j--)
-        ll[i++] = 0;
+	ll[i++] = 0;
       l = 0;
     }
   }
@@ -1021,7 +1017,7 @@
 copyright
 "
  COPYRIGHT (c) 1998 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
@@ -1039,65 +1035,65 @@
 
 
     Trailing slash.
-        Some implementations require a trailing slash in directory
-        names (such as the OpenOffice zip implementation). Others just
-        ignore external file attributes and indicate a directory entry
-        by adding a trailing slash (such as the Java zip implementation).
-
-        Since ZipArchive 1.98 a trailing slash is added for all directory
-        entries iff appendTrailingSlash instvar is set to true. By default
-        it is set to the value of DefaultAppendTrailingSlash which defaults
-        to true.
-
-        Setting appendTrailingSlash to false inhibits trailing slash
-        behavior.
+	Some implementations require a trailing slash in directory
+	names (such as the OpenOffice zip implementation). Others just
+	ignore external file attributes and indicate a directory entry
+	by adding a trailing slash (such as the Java zip implementation).
+
+	Since ZipArchive 1.98 a trailing slash is added for all directory
+	entries iff appendTrailingSlash instvar is set to true. By default
+	it is set to the value of DefaultAppendTrailingSlash which defaults
+	to true.
+
+	Setting appendTrailingSlash to false inhibits trailing slash
+	behavior.
 
 
     Caveat:
-        the only compression methods (for now) are store and deflate.
+	the only compression methods (for now) are store and deflate.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [classvars:]
-        DefaultAppendTrailingSlash...a default value for appendTralingSlash instvar.
-                                     For details, see above
+	DefaultAppendTrailingSlash...a default value for appendTralingSlash instvar.
+				     For details, see above
 
 "
 !
 
 examples
 "
-                                                        [exBegin]
+							[exBegin]
     |zip bytes|
 
     zip := ZipArchive oldFileNamed:'foo.zip'.
     bytes := zip extract:'bar'.
     zip close.
-                                                        [exEnd]
-
-                                                        [exBegin]
+							[exEnd]
+
+							[exBegin]
     |zip bytes|
 
     zip := ZipArchive oldFileNamed:'source/stx/libbasic2.zip'.
     zip entries do:[:entry |
-        Transcript showCR:entry
+	Transcript showCR:entry
     ].
     zip close.
-                                                        [exEnd]
-
-                                                        [exBegin]
+							[exEnd]
+
+							[exBegin]
     |zip bytes|
 
     zip := ZipArchive oldFileNamed:'source/stx/libbasic2.zip'.
     bytes := zip extract:'TwoByteStr.st'.
     zip close.
     Transcript showCR:(bytes asString).
-                                                        [exEnd]
+							[exEnd]
 
 
     compatibility write check with winzip (compressed with deflate)
-                                                        [exBegin]
+							[exBegin]
     |zipwr testDirectory testFileWr|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1106,10 +1102,10 @@
     zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
     zipwr addFile:'crcTest_resume_compressed.txt' withContents: 'resume'.
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     compatibility read check with winzip (compressed with deflate)
-                                                        [exBegin]
+							[exBegin]
     |ziprd testDirectory testFileRd contents|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1119,10 +1115,10 @@
     contents := ziprd extract: ziprd entries first.
     contents inspect.
     ziprd close.
-                                                        [exEnd]
+							[exEnd]
 
     compatibility write check with winzip (uncompressed)
-                                                        [exBegin]
+							[exBegin]
     |zipwr testDirectory testFileWr|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1131,15 +1127,15 @@
     zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
 
     zipwr addFile:'crcTest_resume_uncompressed.txt'
-        withContents:'resume'
+	withContents:'resume'
        compressMethod:0
-          asDirectory:false.
+	  asDirectory:false.
 
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     compatibility read check with winzip (uncompressed)
-                                                        [exBegin]
+							[exBegin]
     |ziprd testDirectory testFileRd contents|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1149,11 +1145,11 @@
     contents := ziprd extract: ziprd entries first.
     contents inspect.
     ziprd close.
-                                                        [exEnd]
+							[exEnd]
 
     read an archive with files and/or directories, fetch the entries
     and create a new archive with the same content
-                                                        [exBegin]
+							[exBegin]
     |ziprd zipwr entryDict testDirectory testFileRd testFileWr|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1163,22 +1159,22 @@
     ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
     entryDict := Dictionary new.
     ziprd entries do: [:aFileName|
-        entryDict at:aFileName put:(ziprd extract: aFileName) asString.
+	entryDict at:aFileName put:(ziprd extract: aFileName) asString.
     ].
     ziprd close.
 
     zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
     entryDict keysAndValuesDo: [:key :value|
-        (value size == 0) ifTrue: [
-            zipwr addDirectory:key.
-        ] ifFalse: [
-            zipwr addFile:key withContents:value
-        ].
+	(value size == 0) ifTrue: [
+	    zipwr addDirectory:key.
+	] ifFalse: [
+	    zipwr addFile:key withContents:value
+	].
     ].
     zipwr close.
-                                                        [exEnd]
-
-                                                        [exBegin]
+							[exEnd]
+
+							[exBegin]
     |zipwr ziprd testDirectory testFileWr testFileRd zs|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1194,9 +1190,9 @@
     zs := ziprd readStreamFor: 'crcTest_resume_compressed.txt'.
     zs inspect.
     ziprd close.
-                                                        [exEnd]
-
-                                                        [exBegin]
+							[exEnd]
+
+							[exBegin]
     |zipwr ziprd testDirectory testFileWr testFileRd rs result|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1212,17 +1208,17 @@
 
     result := ''.
     [ rs atEnd ] whileFalse: [
-        result := result, (rs nextAvailable:5).
+	result := result, (rs nextAvailable:5).
     ].
     result inspect.
     rs close.
     ziprd close.
-                                                        [exEnd]
+							[exEnd]
 
     read an archive with files and/or directories and/or zipArchives,
     fetch the entries (also from the include zip archives)
     and create a new archive
-                                                        [exBegin]
+							[exBegin]
     |ziprd zipwr entryDict testDirectory testFileRd testFileWr zipRdSub1 zipRdSub2|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1232,43 +1228,43 @@
     ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
     entryDict := Dictionary new.
     ziprd entries do: [:aFileName|
-        Transcript showCR: 'processing in top: ', aFileName.
-        (aFileName endsWith:'.zip') ifTrue: [
-            zipRdSub1 := ziprd extractArchive: aFileName.
-            zipRdSub1 entries do: [:aFileName1|
-                Transcript showCR: 'processing in sub 1: ', aFileName1.
-                (aFileName1 endsWith:'.zip') ifTrue: [
-                    zipRdSub2 := zipRdSub1 extractArchive: aFileName1.
-                    zipRdSub2 entries do: [:aFileName2|
-                        Transcript showCR: 'processing in sub 2: ', aFileName2.
-                        (aFileName2 endsWith:'.zip') ifTrue: [
-                            self halt.
-                        ] ifFalse: [
-                            entryDict at:aFileName2 put:(zipRdSub2 extract: aFileName2) asString.
-                        ].
-                    ].
-                    zipRdSub2 close.
-                ] ifFalse: [
-                    entryDict at:aFileName1 put:(zipRdSub1 extract: aFileName1) asString.
-                ].
-            ].
-            zipRdSub1 close.
-        ] ifFalse: [
-            entryDict at:aFileName put:(ziprd extract: aFileName) asString.
-        ].
+	Transcript showCR: 'processing in top: ', aFileName.
+	(aFileName endsWith:'.zip') ifTrue: [
+	    zipRdSub1 := ziprd extractArchive: aFileName.
+	    zipRdSub1 entries do: [:aFileName1|
+		Transcript showCR: 'processing in sub 1: ', aFileName1.
+		(aFileName1 endsWith:'.zip') ifTrue: [
+		    zipRdSub2 := zipRdSub1 extractArchive: aFileName1.
+		    zipRdSub2 entries do: [:aFileName2|
+			Transcript showCR: 'processing in sub 2: ', aFileName2.
+			(aFileName2 endsWith:'.zip') ifTrue: [
+			    self halt.
+			] ifFalse: [
+			    entryDict at:aFileName2 put:(zipRdSub2 extract: aFileName2) asString.
+			].
+		    ].
+		    zipRdSub2 close.
+		] ifFalse: [
+		    entryDict at:aFileName1 put:(zipRdSub1 extract: aFileName1) asString.
+		].
+	    ].
+	    zipRdSub1 close.
+	] ifFalse: [
+	    entryDict at:aFileName put:(ziprd extract: aFileName) asString.
+	].
     ].
     ziprd close.
 
     zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
     entryDict keysAndValuesDo: [:key :value|
-        (value size == 0) ifTrue: [
-            zipwr addDirectory:key.
-        ] ifFalse: [
-            zipwr addFile:key withContents:value
-        ].
+	(value size == 0) ifTrue: [
+	    zipwr addDirectory:key.
+	] ifFalse: [
+	    zipwr addFile:key withContents:value
+	].
     ].
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
 "
 !
@@ -1276,10 +1272,10 @@
 examples2
 "
     add to new zip archive a entry which is located in memory using selector
-        addFile:'crcTest_resume_compressed.txt' withContents:
+	addFile:'crcTest_resume_compressed.txt' withContents:
     and real file contents from disk (uncompressed) identified by a readStream using selector
-        addFile:rdStreamFile fromStream:
-                                                        [exBegin]
+	addFile:rdStreamFile fromStream:
+							[exBegin]
     |zipwr testDirectory testFileWr rdStreamFile rdFileStream |
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1292,13 +1288,13 @@
     zipwr addFile:rdStreamFile fromStream: rdFileStream.
 
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     read from zip archive a entry into memory using selector
-        extract:'crcTest_resume_compressed.txt'
+	extract:'crcTest_resume_compressed.txt'
     and store an uncompressed archive entry to disk using a writeStream
-        extract: intoStream:
-                                                        [exBegin]
+	extract: intoStream:
+							[exBegin]
     |ziprd testDirectory testFileRd wrStreamFile wrFileStream data1|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1310,18 +1306,18 @@
 
     wrFileStream := ('C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\', wrStreamFile) asFilename writeStream.
     (ziprd extract:'projects.zip' intoStream: wrFileStream) ifFalse: [
-        self halt.
+	self halt.
     ].
 
     ziprd close.
     wrFileStream close.
-                                                        [exEnd]
+							[exEnd]
 
     add (compressed) to new zip archive a real file contents from disk e.g. a pdf
     identified by a readStream
     using selector
-        addFile:  fromStream:  compressMethod:
-                                                        [exBegin]
+	addFile:  fromStream:  compressMethod:
+							[exBegin]
     |zipwr testDirectory testFileWr rdStreamFile rdFileStream|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1333,13 +1329,13 @@
     zipwr addFileCompressed:rdStreamFile fromStream: rdFileStream.
 
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     read from zip archive a compressed entry e.g. a pdf and store the contents
     to disk using a readStream
     using selector
-        readStreamFor: rdStreamFile
-                                                        [exBegin]
+	readStreamFor: rdStreamFile
+							[exBegin]
     |ziprd testDirectory testFileRd wrStreamFile wrFileStream|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1350,12 +1346,12 @@
 
     wrFileStream := ('C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\', wrStreamFile) asFilename writeStream.
     (ziprd extract:'test.pdf' intoStream: wrFileStream) ifFalse: [
-        self halt.
+	self halt.
     ].
 
     ziprd close.
     wrFileStream close.
-                                                        [exEnd]
+							[exEnd]
 
 "
 !
@@ -1363,8 +1359,8 @@
 examples3
 "
     add to new zip archive recursive the contents of a directory (uncompressed)
-        addArchiveDirectory:  fromOsDirectory:
-                                                        [exBegin]
+	addArchiveDirectory:  fromOsDirectory:
+							[exBegin]
     |zipwr testDirectory testFileWr zipDirectory |
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1376,12 +1372,12 @@
     zipwr addArchiveDirectory: 'attachments' fromOsDirectory: (testDirectory,zipDirectory).
 
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     read from zip archive all entries which are stored in an archive directory (uncompressed)
     and store all those entries in a directory on the file system
-        restoreOsDirectory:  fromArchiveDirectory:
-                                                        [exBegin]
+	restoreOsDirectory:  fromArchiveDirectory:
+							[exBegin]
     |ziprd testDirectory testFileRd zipDirectory|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1391,12 +1387,12 @@
     ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
     ziprd restoreOsDirectory: (testDirectory,zipDirectory) fromArchiveDirectory: 'attachments'.
     ziprd close.
-                                                        [exEnd]
+							[exEnd]
 
 
     add to new zip archive recursive the contents of a directory (compressed)
-        addArchiveDirectoryCompressed:  fromOsDirectory:
-                                                        [exBegin]
+	addArchiveDirectoryCompressed:  fromOsDirectory:
+							[exBegin]
     |zipwr testDirectory testFileWr zipDirectory |
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1408,12 +1404,12 @@
     zipwr addArchiveDirectoryCompressed: 'attachments' fromOsDirectory: (testDirectory,zipDirectory).
 
     zipwr close.
-                                                        [exEnd]
+							[exEnd]
 
     read from zip archive all entries which are stored in an archive directory (compressed)
     and store all those entries in a directory on the file system
-        restoreOsDirectory:  fromArchiveDirectory:
-                                                        [exBegin]
+	restoreOsDirectory:  fromArchiveDirectory:
+							[exBegin]
     |ziprd testDirectory testFileRd zipDirectory|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1423,7 +1419,7 @@
     ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
     ziprd restoreOsDirectory: (testDirectory,zipDirectory) fromArchiveDirectory: 'attachments'.
     ziprd close.
-                                                        [exEnd]
+							[exEnd]
 
 "
 !
@@ -1431,7 +1427,7 @@
 fileFormatDescription
 
 "/File:    APPNOTE.TXT - .ZIP File Format Specification
-"/Version: 6.3.2 
+"/Version: 6.3.2
 "/Revised: September 28, 2007
 "/Copyright (c) 1989 - 2007 PKWARE Inc., All Rights Reserved.
 "/
@@ -1443,12 +1439,12 @@
 "/----------
 "/
 "/This specification is intended to define a cross-platform,
-"/interoperable file storage and transfer format.  Since its 
-"/first publication in 1989, PKWARE has remained committed to 
-"/ensuring the interoperability of the .ZIP file format through 
-"/publication and maintenance of this specification.  We trust that 
-"/all .ZIP compatible vendors and application developers that have 
-"/adopted and benefited from this format will share and support 
+"/interoperable file storage and transfer format.  Since its
+"/first publication in 1989, PKWARE has remained committed to
+"/ensuring the interoperability of the .ZIP file format through
+"/publication and maintenance of this specification.  We trust that
+"/all .ZIP compatible vendors and application developers that have
+"/adopted and benefited from this format will share and support
 "/this commitment to interoperability.
 "/
 "/II. Contacting PKWARE
@@ -1466,9 +1462,9 @@
 "/
 "/Although PKWARE will attempt to supply current and accurate
 "/information relating to its file formats, algorithms, and the
-"/subject programs, the possibility of error or omission cannot 
-"/be eliminated. PKWARE therefore expressly disclaims any warranty 
-"/that the information contained in the associated materials relating 
+"/subject programs, the possibility of error or omission cannot
+"/be eliminated. PKWARE therefore expressly disclaims any warranty
+"/that the information contained in the associated materials relating
 "/to the subject programs and/or the format of the files created or
 "/accessed by the subject programs and/or the algorithms used by
 "/the subject programs, or any other matter, is current, correct or
@@ -1480,10 +1476,10 @@
 "/subject to change without notice.
 "/
 "/If the version of this file is marked as a NOTIFICATION OF CHANGE,
-"/the content defines an Early Feature Specification (EFS) change 
-"/to the .ZIP file format that may be subject to modification prior 
+"/the content defines an Early Feature Specification (EFS) change
+"/to the .ZIP file format that may be subject to modification prior
 "/to publication of the Final Feature Specification (FFS).  This
-"/document may also contain information on Planned Feature 
+"/document may also contain information on Planned Feature
 "/Specifications (PFS) defining recognized future extensions.
 "/
 "/IV. Change Log
@@ -1504,13 +1500,13 @@
 "/6.2.1         -Added Extra Field placeholder for       04/01/2005
 "/               POSZIP using ID 0x4690
 "/
-"/              -Clarified size field on 
+"/              -Clarified size field on
 "/               "zip64 end of central directory record"
 "/
 "/6.2.2         -Documented Final Feature Specification  01/06/2006
 "/               for Strong Encryption
 "/
-"/              -Clarifications and typographical 
+"/              -Clarifications and typographical
 "/               corrections
 "/
 "/6.3.0         -Added tape positioning storage          09/29/2006
@@ -1524,13 +1520,13 @@
 "/              -Expanded list of supported encryption
 "/               algorithms
 "/
-"/              -Added option for Unicode filename 
+"/              -Added option for Unicode filename
 "/               storage
 "/
 "/              -Clarifications for consistent use
 "/               of Data Descriptor records
 "/
-"/              -Added additional "Extra Field" 
+"/              -Added additional "Extra Field"
 "/               definitions
 "/
 "/6.3.1         -Corrected standard hash values for      04/11/2007
@@ -1547,24 +1543,24 @@
 "/
 "/  Files stored in arbitrary order.  Large .ZIP files can span multiple
 "/  volumes or be split into user-defined segment sizes. All values
-"/  are stored in little-endian byte order unless otherwise specified. 
+"/  are stored in little-endian byte order unless otherwise specified.
 "/
 "/  Overall .ZIP file format:
 "/
 "/    [local file header 1]
 "/    [file data 1]
 "/    [data descriptor 1]
-"/    . 
+"/    .
 "/    .
 "/    .
 "/    [local file header n]
 "/    [file data n]
 "/    [data descriptor n]
-"/    [archive decryption header] 
-"/    [archive extra data record] 
+"/    [archive decryption header]
+"/    [archive extra data record]
 "/    [central directory]
 "/    [zip64 end of central directory record]
-"/    [zip64 end of central directory locator] 
+"/    [zip64 end of central directory locator]
 "/    [end of central directory record]
 "/
 "/
@@ -1588,9 +1584,9 @@
 "/  B.  File data
 "/
 "/      Immediately following the local header for a file
-"/      is the compressed or stored data for the file. 
+"/      is the compressed or stored data for the file.
 "/      The series of [local file header][file data][data
-"/      descriptor] repeats for each file in the .ZIP archive. 
+"/      descriptor] repeats for each file in the .ZIP archive.
 "/
 "/  C.  Data descriptor:
 "/
@@ -1606,18 +1602,18 @@
 "/      was standard output or a non-seekable device.  For ZIP64(tm) format
 "/      archives, the compressed and uncompressed sizes are 8 bytes each.
 "/
-"/      When compressing files, compressed and uncompressed sizes 
-"/      should be stored in ZIP64 format (as 8 byte values) when a 
-"/      files size exceeds 0xFFFFFFFF.   However ZIP64 format may be 
-"/      used regardless of the size of a file.  When extracting, if 
-"/      the zip64 extended information extra field is present for 
+"/      When compressing files, compressed and uncompressed sizes
+"/      should be stored in ZIP64 format (as 8 byte values) when a
+"/      files size exceeds 0xFFFFFFFF.   However ZIP64 format may be
+"/      used regardless of the size of a file.  When extracting, if
+"/      the zip64 extended information extra field is present for
 "/      the file the compressed and uncompressed sizes will be 8
-"/      byte values.  
-"/
-"/      Although not originally assigned a signature, the value 
-"/      0x08074b50 has commonly been adopted as a signature value 
-"/      for the data descriptor record.  Implementers should be 
-"/      aware that ZIP files may be encountered with or without this 
+"/      byte values.
+"/
+"/      Although not originally assigned a signature, the value
+"/      0x08074b50 has commonly been adopted as a signature value
+"/      for the data descriptor record.  Implementers should be
+"/      aware that ZIP files may be encountered with or without this
 "/      signature marking data descriptors and should account for
 "/      either case when reading ZIP files to ensure compatibility.
 "/      When writing ZIP files, it is recommended to include the
@@ -1637,26 +1633,26 @@
 "/      its presence, the values in fields of the data descriptor
 "/      record should be set to binary zeros.
 "/
-"/  D.  Archive decryption header:  
+"/  D.  Archive decryption header:
 "/
 "/      The Archive Decryption Header is introduced in version 6.2
 "/      of the ZIP format specification.  This record exists in support
-"/      of the Central Directory Encryption Feature implemented as part of 
+"/      of the Central Directory Encryption Feature implemented as part of
 "/      the Strong Encryption Specification as described in this document.
 "/      When the Central Directory Structure is encrypted, this decryption
 "/      header will precede the encrypted data segment.  The encrypted
 "/      data segment will consist of the Archive extra data record (if
 "/      present) and the encrypted Central Directory Structure data.
 "/      The format of this data record is identical to the Decryption
-"/      header record preceding compressed file data.  If the central 
+"/      header record preceding compressed file data.  If the central
 "/      directory structure is encrypted, the location of the start of
 "/      this data record is determined using the Start of Central Directory
-"/      field in the Zip64 End of Central Directory record.  Refer to the 
+"/      field in the Zip64 End of Central Directory record.  Refer to the
 "/      section on the Strong Encryption Specification for information
 "/      on the fields used in the Archive Decryption Header record.
 "/
 "/
-"/  E.  Archive extra data record: 
+"/  E.  Archive extra data record:
 "/
 "/        archive extra data signature    4 bytes  (0x08064b50)
 "/        extra field length              4 bytes
@@ -1664,15 +1660,15 @@
 "/
 "/      The Archive Extra Data Record is introduced in version 6.2
 "/      of the ZIP format specification.  This record exists in support
-"/      of the Central Directory Encryption Feature implemented as part of 
+"/      of the Central Directory Encryption Feature implemented as part of
 "/      the Strong Encryption Specification as described in this document.
-"/      When present, this record immediately precedes the central 
+"/      When present, this record immediately precedes the central
 "/      directory data structure.  The size of this data record will be
 "/      included in the Size of the Central Directory field in the
 "/      End of Central Directory record.  If the central directory structure
 "/      is compressed, but not encrypted, the location of the start of
 "/      this data record is determined using the Start of Central Directory
-"/      field in the Zip64 End of Central Directory record.  
+"/      field in the Zip64 End of Central Directory record.
 "/
 "/
 "/  F.  Central directory structure:
@@ -1680,9 +1676,9 @@
 "/      [file header 1]
 "/      .
 "/      .
-"/      . 
+"/      .
 "/      [file header n]
-"/      [digital signature] 
+"/      [digital signature]
 "/
 "/      File header:
 "/
@@ -1714,26 +1710,26 @@
 "/        size of data                    2 bytes
 "/        signature data (variable size)
 "/
-"/      With the introduction of the Central Directory Encryption 
-"/      feature in version 6.2 of this specification, the Central 
-"/      Directory Structure may be stored both compressed and encrypted. 
+"/      With the introduction of the Central Directory Encryption
+"/      feature in version 6.2 of this specification, the Central
+"/      Directory Structure may be stored both compressed and encrypted.
 "/      Although not required, it is assumed when encrypting the
 "/      Central Directory Structure, that it will be compressed
 "/      for greater storage efficiency.  Information on the
 "/      Central Directory Encryption feature can be found in the section
-"/      describing the Strong Encryption Specification. The Digital 
+"/      describing the Strong Encryption Specification. The Digital
 "/      Signature record will be neither compressed nor encrypted.
 "/
 "/  G.  Zip64 end of central directory record
 "/
-"/        zip64 end of central dir 
+"/        zip64 end of central dir
 "/        signature                       4 bytes  (0x06064b50)
 "/        size of zip64 end of central
 "/        directory record                8 bytes
 "/        version made by                 2 bytes
 "/        version needed to extract       2 bytes
 "/        number of this disk             4 bytes
-"/        number of the disk with the 
+"/        number of the disk with the
 "/        start of the central directory  4 bytes
 "/        total number of entries in the
 "/        central directory on this disk  8 bytes
@@ -1751,15 +1747,15 @@
 "/
 "/        Size = SizeOfFixedFields + SizeOfVariableData - 12.
 "/
-"/        The above record structure defines Version 1 of the 
-"/        zip64 end of central directory record. Version 1 was 
-"/        implemented in versions of this specification preceding 
-"/        6.2 in support of the ZIP64 large file feature. The 
-"/        introduction of the Central Directory Encryption feature 
-"/        implemented in version 6.2 as part of the Strong Encryption 
-"/        Specification defines Version 2 of this record structure. 
-"/        Refer to the section describing the Strong Encryption 
-"/        Specification for details on the version 2 format for 
+"/        The above record structure defines Version 1 of the
+"/        zip64 end of central directory record. Version 1 was
+"/        implemented in versions of this specification preceding
+"/        6.2 in support of the ZIP64 large file feature. The
+"/        introduction of the Central Directory Encryption feature
+"/        implemented in version 6.2 as part of the Strong Encryption
+"/        Specification defines Version 2 of this record structure.
+"/        Refer to the section describing the Strong Encryption
+"/        Specification for details on the version 2 format for
 "/        this record.
 "/
 "/        Special purpose data may reside in the zip64 extensible data
@@ -1771,7 +1767,7 @@
 "/           Header ID  -  2 bytes
 "/           Data Size  -  4 bytes
 "/
-"/        The Header ID field indicates the type of data that is in the 
+"/        The Header ID field indicates the type of data that is in the
 "/        data block that follows.
 "/
 "/        Data Size identifies the number of bytes that follow for this
@@ -1784,10 +1780,10 @@
 "/
 "/  H.  Zip64 end of central directory locator
 "/
-"/        zip64 end of central dir locator 
+"/        zip64 end of central dir locator
 "/        signature                       4 bytes  (0x07064b50)
 "/        number of the disk with the
-"/        start of the zip64 end of 
+"/        start of the zip64 end of
 "/        central directory               4 bytes
 "/        relative offset of the zip64
 "/        end of central directory record 8 bytes
@@ -1815,11 +1811,11 @@
 "/      version made by (2 bytes)
 "/
 "/          The upper byte indicates the compatibility of the file
-"/          attribute information.  If the external file attributes 
-"/          are compatible with MS-DOS and can be read by PKZIP for 
-"/          DOS version 2.04g then this value will be zero.  If these 
-"/          attributes are not compatible, then this value will 
-"/          identify the host system on which the attributes are 
+"/          attribute information.  If the external file attributes
+"/          are compatible with MS-DOS and can be read by PKZIP for
+"/          DOS version 2.04g then this value will be zero.  If these
+"/          attributes are not compatible, then this value will
+"/          identify the host system on which the attributes are
 "/          compatible.  Software can use this information to determine
 "/          the line record format for text files etc.  The current
 "/          mappings are:
@@ -1836,22 +1832,22 @@
 "/         17 - Tandem                   18 - OS/400
 "/         19 - OS/X (Darwin)            20 thru 255 - unused
 "/
-"/          The lower byte indicates the ZIP specification version 
-"/          (the version of this document) supported by the software 
-"/          used to encode the file.  The value/10 indicates the major 
-"/          version number, and the value mod 10 is the minor version 
-"/          number.  
+"/          The lower byte indicates the ZIP specification version
+"/          (the version of this document) supported by the software
+"/          used to encode the file.  The value/10 indicates the major
+"/          version number, and the value mod 10 is the minor version
+"/          number.
 "/
 "/      version needed to extract (2 bytes)
 "/
-"/          The minimum supported ZIP specification version needed to 
-"/          extract the file, mapped as above.  This value is based on 
-"/          the specific format features a ZIP program must support to 
+"/          The minimum supported ZIP specification version needed to
+"/          extract the file, mapped as above.  This value is based on
+"/          the specific format features a ZIP program must support to
 "/          be able to extract the file.  If multiple features are
-"/          applied to a file, the minimum version should be set to the 
-"/          feature having the highest value. New features or feature 
-"/          changes affecting the published format specification will be 
-"/          implemented using higher version numbers than the last 
+"/          applied to a file, the minimum version should be set to the
+"/          feature having the highest value. New features or feature
+"/          changes affecting the published format specification will be
+"/          implemented using higher version numbers than the last
 "/          published value to avoid conflict.
 "/
 "/          Current minimum feature versions are as defined below:
@@ -1862,8 +1858,8 @@
 "/          2.0 - File is compressed using Deflate compression
 "/          2.0 - File is encrypted using traditional PKWARE encryption
 "/          2.1 - File is compressed using Deflate64(tm)
-"/          2.5 - File is compressed using PKWARE DCL Implode 
-"/          2.7 - File is a patch data set 
+"/          2.5 - File is compressed using PKWARE DCL Implode
+"/          2.7 - File is a patch data set
 "/          4.5 - File uses ZIP64 format extensions
 "/          4.6 - File is compressed using BZIP2 compression*
 "/          5.0 - File is encrypted using DES
@@ -1895,14 +1891,14 @@
 "/          versions of PKZIP older than 6.1 (5.0 or 6.0).
 "/
 "/          + Files compressed using PPMd should set the version
-"/          needed to extract field to 6.3, however, not all ZIP 
-"/          programs enforce this and may be unable to decompress 
+"/          needed to extract field to 6.3, however, not all ZIP
+"/          programs enforce this and may be unable to decompress
 "/          data files compressed using PPMd if this value is set.
 "/
 "/          When using ZIP64 extensions, the corresponding value in the
-"/          zip64 end of central directory record should also be set.  
-"/          This field should be set appropriately to indicate whether 
-"/          Version 1 or Version 2 format is in use. 
+"/          zip64 end of central directory record should also be set.
+"/          This field should be set appropriately to indicate whether
+"/          Version 1 or Version 2 format is in use.
 "/
 "/      general purpose bit flag: (2 bytes)
 "/
@@ -1938,26 +1934,26 @@
 "/          Note:  Bits 1 and 2 are undefined if the compression
 "/                 method is any other.
 "/
-"/          Bit 3: If this bit is set, the fields crc-32, compressed 
-"/                 size and uncompressed size are set to zero in the 
-"/                 local header.  The correct values are put in the 
+"/          Bit 3: If this bit is set, the fields crc-32, compressed
+"/                 size and uncompressed size are set to zero in the
+"/                 local header.  The correct values are put in the
 "/                 data descriptor immediately following the compressed
-"/                 data.  (Note: PKZIP version 2.04g for DOS only 
-"/                 recognizes this bit for method 8 compression, newer 
-"/                 versions of PKZIP recognize this bit for any 
+"/                 data.  (Note: PKZIP version 2.04g for DOS only
+"/                 recognizes this bit for method 8 compression, newer
+"/                 versions of PKZIP recognize this bit for any
 "/                 compression method.)
 "/
 "/          Bit 4: Reserved for use with method 8, for enhanced
-"/                 deflating. 
-"/
-"/          Bit 5: If this bit is set, this indicates that the file is 
-"/                 compressed patched data.  (Note: Requires PKZIP 
+"/                 deflating.
+"/
+"/          Bit 5: If this bit is set, this indicates that the file is
+"/                 compressed patched data.  (Note: Requires PKZIP
 "/                 version 2.70 or greater)
 "/
 "/          Bit 6: Strong encryption.  If this bit is set, you should
 "/                 set the version needed to extract value to at least
 "/                 50 and you must also set bit 0.  If AES encryption
-"/                 is used, the version needed to extract value must 
+"/                 is used, the version needed to extract value must
 "/                 be at least 51.
 "/
 "/          Bit 7: Currently unused.
@@ -1974,9 +1970,9 @@
 "/
 "/          Bit 12: Reserved by PKWARE for enhanced compression.
 "/
-"/          Bit 13: Used when encrypting the Central Directory to indicate 
+"/          Bit 13: Used when encrypting the Central Directory to indicate
 "/                  selected data values in the Local Header are masked to
-"/                  hide their actual values.  See the section describing 
+"/                  hide their actual values.  See the section describing
 "/                  the Strong Encryption Specification for details.
 "/
 "/          Bit 14: Reserved by PKWARE.
@@ -2015,10 +2011,10 @@
 "/
 "/          The date and time are encoded in standard MS-DOS format.
 "/          If input came from standard input, the date and time are
-"/          those at which compression was started for this data. 
-"/          If encrypting the central directory and general purpose bit 
-"/          flag 13 is set indicating masking, the value stored in the 
-"/          Local Header will be zero. 
+"/          those at which compression was started for this data.
+"/          If encrypting the central directory and general purpose bit
+"/          flag 13 is set indicating masking, the value stored in the
+"/          Local Header will be zero.
 "/
 "/      CRC-32: (4 bytes)
 "/
@@ -2035,9 +2031,9 @@
 "/          field is set to zero in the local header and the correct
 "/          value is put in the data descriptor and in the central
 "/          directory. When encrypting the central directory, if the
-"/          local header is not in ZIP64 format and general purpose 
-"/          bit flag 13 is set indicating masking, the value stored 
-"/          in the Local Header will be zero. 
+"/          local header is not in ZIP64 format and general purpose
+"/          bit flag 13 is set indicating masking, the value stored
+"/          in the Local Header will be zero.
 "/
 "/      compressed size: (4 bytes)
 "/      uncompressed size: (4 bytes)
@@ -2046,16 +2042,16 @@
 "/          respectively.  When a decryption header is present it will
 "/          be placed in front of the file data and the value of the
 "/          compressed file size will include the bytes of the decryption
-"/          header.  If bit 3 of the general purpose bit flag is set, 
-"/          these fields are set to zero in the local header and the 
+"/          header.  If bit 3 of the general purpose bit flag is set,
+"/          these fields are set to zero in the local header and the
 "/          correct values are put in the data descriptor and
 "/          in the central directory.  If an archive is in ZIP64 format
 "/          and the value in this field is 0xFFFFFFFF, the size will be
-"/          in the corresponding 8 byte ZIP64 extended information 
+"/          in the corresponding 8 byte ZIP64 extended information
 "/          extra field.  When encrypting the central directory, if the
-"/          local header is not in ZIP64 format and general purpose bit 
-"/          flag 13 is set indicating masking, the value stored for the 
-"/          uncompressed size in the Local Header will be zero. 
+"/          local header is not in ZIP64 format and general purpose bit
+"/          flag 13 is set indicating masking, the value stored for the
+"/          uncompressed size in the Local Header will be zero.
 "/
 "/      file name length: (2 bytes)
 "/      extra field length: (2 bytes)
@@ -2065,13 +2061,13 @@
 "/          fields respectively.  The combined length of any
 "/          directory record and these three fields should not
 "/          generally exceed 65,535 bytes.  If input came from standard
-"/          input, the file name length is set to zero.  
+"/          input, the file name length is set to zero.
 "/
 "/      disk number start: (2 bytes)
 "/
-"/          The number of the disk on which this file begins.  If an 
-"/          archive is in ZIP64 format and the value in this field is 
-"/          0xFFFF, the size will be in the corresponding 4 byte zip64 
+"/          The number of the disk on which this file begins.  If an
+"/          archive is in ZIP64 format and the value in this field is
+"/          0xFFFF, the size will be in the corresponding 4 byte zip64
 "/          extended information extra field.
 "/
 "/      internal file attributes: (2 bytes)
@@ -2083,13 +2079,13 @@
 "/          set, that the file apparently contains binary data.
 "/          The remaining bits are unused in version 1.0.
 "/
-"/          The 0x0002 bit of this field indicates, if set, that a 
-"/          4 byte variable record length control field precedes each 
-"/          logical record indicating the length of the record. The 
+"/          The 0x0002 bit of this field indicates, if set, that a
+"/          4 byte variable record length control field precedes each
+"/          logical record indicating the length of the record. The
 "/          record length control field is stored in little-endian byte
-"/          order.  This flag is independent of text control characters, 
-"/          and if used in conjunction with text data, includes any 
-"/          control characters in the total length of the record. This 
+"/          order.  This flag is independent of text control characters,
+"/          and if used in conjunction with text data, includes any
+"/          control characters in the total length of the record. This
 "/          value is provided for mainframe data transfer support.
 "/
 "/      external file attributes: (4 bytes)
@@ -2105,7 +2101,7 @@
 "/          This is the offset from the start of the first disk on
 "/          which this file appears, to where the local header should
 "/          be found.  If an archive is in ZIP64 format and the value
-"/          in this field is 0xFFFFFFFF, the size will be in the 
+"/          in this field is 0xFFFFFFFF, the size will be in the
 "/          corresponding 8 byte zip64 extended information extra field.
 "/
 "/      file name: (Variable)
@@ -2117,21 +2113,21 @@
 "/          backwards slashes '\' for compatibility with Amiga
 "/          and UNIX file systems etc.  If input came from standard
 "/          input, there is no file name field.  If encrypting
-"/          the central directory and general purpose bit flag 13 is set 
-"/          indicating masking, the file name stored in the Local Header 
-"/          will not be the actual file name.  A masking value consisting 
-"/          of a unique hexadecimal value will be stored.  This value will 
+"/          the central directory and general purpose bit flag 13 is set
+"/          indicating masking, the file name stored in the Local Header
+"/          will not be the actual file name.  A masking value consisting
+"/          of a unique hexadecimal value will be stored.  This value will
 "/          be sequentially incremented for each file in the archive. See
-"/          the section on the Strong Encryption Specification for details 
-"/          on retrieving the encrypted file name. 
+"/          the section on the Strong Encryption Specification for details
+"/          on retrieving the encrypted file name.
 "/
 "/      extra field: (Variable)
 "/
 "/          This is for expansion.  If additional information
-"/          needs to be stored for special needs or for specific 
-"/          platforms, it should be stored here.  Earlier versions 
-"/          of the software can then safely skip this file, and 
-"/          find the next file or header.  This field will be 0 
+"/          needs to be stored for special needs or for specific
+"/          platforms, it should be stored here.  Earlier versions
+"/          of the software can then safely skip this file, and
+"/          find the next file or header.  This field will be 0
 "/          length in version 1.0.
 "/
 "/          In order to allow different programs and different types
@@ -2162,23 +2158,23 @@
 "/          0x0008        Reserved for extended language encoding data (PFS)
 "/                        (see APPENDIX D)
 "/          0x0009        OS/2
-"/          0x000a        NTFS 
+"/          0x000a        NTFS
 "/          0x000c        OpenVMS
 "/          0x000d        UNIX
 "/          0x000e        Reserved for file stream and fork descriptors
 "/          0x000f        Patch Descriptor
 "/          0x0014        PKCS#7 Store for X.509 Certificates
-"/          0x0015        X.509 Certificate ID and Signature for 
+"/          0x0015        X.509 Certificate ID and Signature for
 "/                        individual file
 "/          0x0016        X.509 Certificate ID for Central Directory
 "/          0x0017        Strong Encryption Header
 "/          0x0018        Record Management Controls
 "/          0x0019        PKCS#7 Encryption Recipient Certificate List
-"/          0x0065        IBM S/390 (Z390), AS/400 (I400) attributes 
+"/          0x0065        IBM S/390 (Z390), AS/400 (I400) attributes
 "/                        - uncompressed
-"/          0x0066        Reserved for IBM S/390 (Z390), AS/400 (I400) 
+"/          0x0066        Reserved for IBM S/390 (Z390), AS/400 (I400)
 "/                        attributes - compressed
-"/          0x4690        POSZIP 4690 (reserved) 
+"/          0x4690        POSZIP 4690 (reserved)
 "/
 "/          Third party mappings commonly used are:
 "/
@@ -2188,7 +2184,7 @@
 "/          0x2705        ZipIt Macintosh 1.3.5+
 "/          0x2805        ZipIt Macintosh 1.3.5+
 "/          0x334d        Info-ZIP Macintosh
-"/          0x4341        Acorn/SparkFS 
+"/          0x4341        Acorn/SparkFS
 "/          0x4453        Windows NT security descriptor (binary ACL)
 "/          0x4704        VM/CMS
 "/          0x470f        MVS
@@ -2208,9 +2204,9 @@
 "/          0xa220        Microsoft Open Packaging Growth Hint
 "/          0xfd4a        SMS/QDOS
 "/
-"/          Detailed descriptions of Extra Fields defined by third 
+"/          Detailed descriptions of Extra Fields defined by third
 "/          party mappings will be documented as information on
-"/          these data structures is made available to PKWARE.  
+"/          these data structures is made available to PKWARE.
 "/          PKWARE does not guarantee the accuracy of any published
 "/          third party data.
 "/
@@ -2234,12 +2230,12 @@
 "/
 "/         -Zip64 Extended Information Extra Field (0x0001):
 "/
-"/          The following is the layout of the zip64 extended 
+"/          The following is the layout of the zip64 extended
 "/          information "extra" block. If one of the size or
 "/          offset fields in the Local or Central directory
 "/          record is too small to hold the required data,
 "/          a Zip64 extended information record is created.
-"/          The order of the fields in the zip64 extended 
+"/          The order of the fields in the zip64 extended
 "/          information record is fixed, but the fields will
 "/          only appear if the corresponding Local or Central
 "/          directory record field is set to 0xFFFF or 0xFFFFFFFF.
@@ -2250,7 +2246,7 @@
 "/          -----      ----       -----------
 "/  (ZIP64) 0x0001     2 bytes    Tag for this "extra" block type
 "/          Size       2 bytes    Size of this "extra" block
-"/          Original 
+"/          Original
 "/          Size       8 bytes    Original uncompressed file size
 "/          Compressed
 "/          Size       8 bytes    Size of compressed data
@@ -2258,10 +2254,10 @@
 "/          Offset     8 bytes    Offset of local header record
 "/          Disk Start
 "/          Number     4 bytes    Number of the disk on which
-"/                                this file starts 
+"/                                this file starts
 "/
 "/          This entry in the Local header must include BOTH original
-"/          and compressed file size fields. If encrypting the 
+"/          and compressed file size fields. If encrypting the
 "/          central directory and bit 13 of the general purpose bit
 "/          flag is set indicating masking, the value stored in the
 "/          Local Header for the original file size will be zero.
@@ -2269,7 +2265,7 @@
 "/
 "/         -OS/2 Extra Field (0x0009):
 "/
-"/          The following is the layout of the OS/2 attributes "extra" 
+"/          The following is the layout of the OS/2 attributes "extra"
 "/          block.  (Last Revision  09/05/95)
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2283,16 +2279,16 @@
 "/          EACRC       4 bytes       CRC value for uncompress block
 "/          (var)       variable      Compressed block
 "/
-"/          The OS/2 extended attribute structure (FEA2LIST) is 
-"/          compressed and then stored in it's entirety within this 
-"/          structure.  There will only ever be one "block" of data in 
+"/          The OS/2 extended attribute structure (FEA2LIST) is
+"/          compressed and then stored in it's entirety within this
+"/          structure.  There will only ever be one "block" of data in
 "/          VarFields[].
 "/
 "/         -NTFS Extra Field (0x000a):
 "/
-"/          The following is the layout of the NTFS attributes 
+"/          The following is the layout of the NTFS attributes
 "/          "extra" block. (Note: At this time the Mtime, Atime
-"/          and Ctime values may be used on any WIN32 system.)  
+"/          and Ctime values may be used on any WIN32 system.)
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
 "/
@@ -2316,7 +2312,7 @@
 "/
 "/          Tag        Size       Description
 "/          -----      ----       -----------
-"/          0x0001     2 bytes    Tag for attribute #1 
+"/          0x0001     2 bytes    Tag for attribute #1
 "/          Size1      2 bytes    Size of attribute #1, in bytes
 "/          Mtime      8 bytes    File last modification time
 "/          Atime      8 bytes    File last access time
@@ -2324,7 +2320,7 @@
 "/
 "/         -OpenVMS Extra Field (0x000c):
 "/
-"/          The following is the layout of the OpenVMS attributes 
+"/          The following is the layout of the OpenVMS attributes
 "/          "extra" block.
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2346,10 +2342,10 @@
 "/
 "/          Rules:
 "/
-"/          1. There will be one or more of attributes present, which 
-"/             will each be preceded by the above TagX & SizeX values.  
-"/             These values are identical to the ATR$C_XXXX and 
-"/             ATR$S_XXXX constants which are defined in ATR.H under 
+"/          1. There will be one or more of attributes present, which
+"/             will each be preceded by the above TagX & SizeX values.
+"/             These values are identical to the ATR$C_XXXX and
+"/             ATR$S_XXXX constants which are defined in ATR.H under
 "/             OpenVMS C.  Neither of these values will ever be zero.
 "/
 "/          2. No word alignment or padding is performed.
@@ -2362,7 +2358,7 @@
 "/         -UNIX Extra Field (0x000d):
 "/
 "/          The following is the layout of the UNIX "extra" block.
-"/          Note: all fields are stored in Intel low-byte/high-byte 
+"/          Note: all fields are stored in Intel low-byte/high-byte
 "/          order.
 "/
 "/          Value       Size          Description
@@ -2375,9 +2371,9 @@
 "/          Gid         2 bytes       File group ID
 "/          (var)       variable      Variable length data field
 "/
-"/          The variable length data field will contain file type 
+"/          The variable length data field will contain file type
 "/          specific data.  Currently the only values allowed are
-"/          the original "linked to" file names for hard or symbolic 
+"/          the original "linked to" file names for hard or symbolic
 "/          links, and the major and minor device node numbers for
 "/          character and block device nodes.  Since device nodes
 "/          cannot be either symbolic or hard links, only one set of
@@ -2401,11 +2397,11 @@
 "/  (Patch) 0x000f    2 bytes  Tag for this "extra" block type
 "/          TSize     2 bytes  Size of the total "extra" block
 "/          Version   2 bytes  Version of the descriptor
-"/          Flags     4 bytes  Actions and reactions (see below) 
-"/          OldSize   4 bytes  Size of the file about to be patched 
-"/          OldCRC    4 bytes  32-bit CRC of the file to be patched 
-"/          NewSize   4 bytes  Size of the resulting file 
-"/          NewCRC    4 bytes  32-bit CRC of the resulting file 
+"/          Flags     4 bytes  Actions and reactions (see below)
+"/          OldSize   4 bytes  Size of the file about to be patched
+"/          OldCRC    4 bytes  32-bit CRC of the file to be patched
+"/          NewSize   4 bytes  Size of the resulting file
+"/          NewCRC    4 bytes  32-bit CRC of the resulting file
 "/
 "/          Actions and reactions
 "/
@@ -2416,7 +2412,7 @@
 "/          2-3           RESERVED
 "/          4-5           Action (see below)
 "/          6-7           RESERVED
-"/          8-9           Reaction (see below) to absent file 
+"/          8-9           Reaction (see below) to absent file
 "/          10-11         Reaction (see below) to newer file
 "/          12-13         Reaction (see below) to unknown file
 "/          14-15         RESERVED
@@ -2425,7 +2421,7 @@
 "/          Actions
 "/
 "/          Action       Value
-"/          ------       ----- 
+"/          ------       -----
 "/          none         0
 "/          add          1
 "/          delete       2
@@ -2440,21 +2436,21 @@
 "/          ignore       2
 "/          fail         3
 "/
-"/          Patch support is provided by PKPatchMaker(tm) technology and is 
-"/          covered under U.S. Patents and Patents Pending. The use or 
+"/          Patch support is provided by PKPatchMaker(tm) technology and is
+"/          covered under U.S. Patents and Patents Pending. The use or
 "/          implementation in a product of certain technological aspects set
-"/          forth in the current APPNOTE, including those with regard to 
+"/          forth in the current APPNOTE, including those with regard to
 "/          strong encryption, patching, or extended tape operations requires
-"/          a license from PKWARE.  Please contact PKWARE with regard to 
-"/          acquiring a license. 
+"/          a license from PKWARE.  Please contact PKWARE with regard to
+"/          acquiring a license.
 "/
 "/         -PKCS#7 Store for X.509 Certificates (0x0014):
 "/
-"/          This field contains information about each of the certificates 
-"/          files may be signed with. When the Central Directory Encryption 
-"/          feature is enabled for a ZIP file, this record will appear in 
-"/          the Archive Extra Data Record, otherwise it will appear in the 
-"/          first central directory record and will be ignored in any 
+"/          This field contains information about each of the certificates
+"/          files may be signed with. When the Central Directory Encryption
+"/          feature is enabled for a ZIP file, this record will appear in
+"/          the Archive Extra Data Record, otherwise it will appear in the
+"/          first central directory record and will be ignored in any
 "/          other record.
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2468,9 +2464,9 @@
 "/
 "/         -X.509 Certificate ID and Signature for individual file (0x0015):
 "/
-"/          This field contains the information about which certificate in 
-"/          the PKCS#7 store was used to sign a particular file. It also 
-"/          contains the signature data. This field can appear multiple 
+"/          This field contains the information about which certificate in
+"/          the PKCS#7 store was used to sign a particular file. It also
+"/          contains the signature data. This field can appear multiple
 "/          times, but can only appear once per certificate.
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2483,10 +2479,10 @@
 "/
 "/         -X.509 Certificate ID and Signature for central directory (0x0016):
 "/
-"/          This field contains the information about which certificate in 
+"/          This field contains the information about which certificate in
 "/          the PKCS#7 store was used to sign the central directory structure.
-"/          When the Central Directory Encryption feature is enabled for a 
-"/          ZIP file, this record will appear in the Archive Extra Data Record, 
+"/          When the Central Directory Encryption feature is enabled for a
+"/          ZIP file, this record will appear in the Archive Extra Data Record,
 "/          otherwise it will appear in the first central directory record.
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2509,8 +2505,8 @@
 "/          Flags     2 bytes  Processing flags
 "/          CertData  TSize-8  Certificate decryption extra field data
 "/                             (refer to the explanation for CertData
-"/                              in the section describing the 
-"/                              Certificate Processing Method under 
+"/                              in the section describing the
+"/                              Certificate Processing Method under
 "/                              the Strong Encryption Specification)
 "/
 "/
@@ -2531,14 +2527,14 @@
 "/          DataN     SizeN    Attribute N data
 "/
 "/
-"/         -PKCS#7 Encryption Recipient Certificate List (0x0019): 
+"/         -PKCS#7 Encryption Recipient Certificate List (0x0019):
 "/
 "/          This field contains information about each of the certificates
 "/          used in encryption processing and it can be used to identify who is
-"/          allowed to decrypt encrypted files.  This field should only appear 
-"/          in the archive extra data record. This field is not required and 
-"/          serves only to aide archive modifications by preserving public 
-"/          encryption key data. Individual security requirements may dictate 
+"/          allowed to decrypt encrypted files.  This field should only appear
+"/          in the archive extra data record. This field is not required and
+"/          serves only to aide archive modifications by preserving public
+"/          encryption key data. Individual security requirements may dictate
 "/          that this data be omitted to deter information exposure.
 "/
 "/          Note: all fields stored in Intel low-byte/high-byte order.
@@ -2591,10 +2587,10 @@
 "/
 "/         -ZipIt Macintosh Extra Field (long) (0x2605):
 "/
-"/          The following is the layout of the ZipIt extra block 
-"/          for Macintosh. The local-header and central-header versions 
-"/          are identical. This block must be present if the file is 
-"/          stored MacBinary-encoded and it should not be used if the file 
+"/          The following is the layout of the ZipIt extra block
+"/          for Macintosh. The local-header and central-header versions
+"/          are identical. This block must be present if the file is
+"/          stored MacBinary-encoded and it should not be used if the file
 "/          is not stored MacBinary-encoded.
 "/
 "/          Value         Size        Description
@@ -2632,7 +2628,7 @@
 "/
 "/          The following is the layout of a shortened variant of the
 "/          ZipIt extra block for Macintosh used only for directory
-"/          entries. This variant is used by ZipIt 1.3.5 and newer to 
+"/          entries. This variant is used by ZipIt 1.3.5 and newer to
 "/          save some optional Mac-specific information about directories.
 "/          The local-header and central-header versions are identical.
 "/
@@ -2709,9 +2705,9 @@
 "/          The ComCRC32 is the standard zip CRC32 checksum of the File Comment
 "/          field in the central directory header.  This is used to verify that
 "/          the comment field has not changed since the Unicode Comment extra field
-"/          was created.  This can happen if a utility changes the File Comment 
-"/          field but does not update the UTF-8 Comment extra field.  If the CRC 
-"/          check fails, this Unicode Comment extra field should be ignored and 
+"/          was created.  This can happen if a utility changes the File Comment
+"/          field but does not update the UTF-8 Comment extra field.  If the CRC
+"/          check fails, this Unicode Comment extra field should be ignored and
 "/          the File Comment field in the header should be used instead.
 "/
 "/          The UnicodeCom field is the UTF-8 version of the File Comment field
@@ -2791,8 +2787,8 @@
 "/
 "/          The number of this disk, which contains central
 "/          directory end record. If an archive is in ZIP64 format
-"/          and the value in this field is 0xFFFF, the size will 
-"/          be in the corresponding 4 byte zip64 end of central 
+"/          and the value in this field is 0xFFFF, the size will
+"/          be in the corresponding 4 byte zip64 end of central
 "/          directory field.
 "/
 "/
@@ -2801,42 +2797,42 @@
 "/
 "/          The number of the disk on which the central
 "/          directory starts. If an archive is in ZIP64 format
-"/          and the value in this field is 0xFFFF, the size will 
-"/          be in the corresponding 4 byte zip64 end of central 
+"/          and the value in this field is 0xFFFF, the size will
+"/          be in the corresponding 4 byte zip64 end of central
 "/          directory field.
 "/
-"/      total number of entries in the central dir on 
+"/      total number of entries in the central dir on
 "/      this disk: (2 bytes)
 "/
 "/          The number of central directory entries on this disk.
-"/          If an archive is in ZIP64 format and the value in 
-"/          this field is 0xFFFF, the size will be in the 
-"/          corresponding 8 byte zip64 end of central 
+"/          If an archive is in ZIP64 format and the value in
+"/          this field is 0xFFFF, the size will be in the
+"/          corresponding 8 byte zip64 end of central
 "/          directory field.
 "/
 "/      total number of entries in the central dir: (2 bytes)
 "/
-"/          The total number of files in the .ZIP file. If an 
+"/          The total number of files in the .ZIP file. If an
 "/          archive is in ZIP64 format and the value in this field
-"/          is 0xFFFF, the size will be in the corresponding 8 byte 
+"/          is 0xFFFF, the size will be in the corresponding 8 byte
 "/          zip64 end of central directory field.
 "/
 "/      size of the central directory: (4 bytes)
 "/
 "/          The size (in bytes) of the entire central directory.
-"/          If an archive is in ZIP64 format and the value in 
-"/          this field is 0xFFFFFFFF, the size will be in the 
-"/          corresponding 8 byte zip64 end of central 
+"/          If an archive is in ZIP64 format and the value in
+"/          this field is 0xFFFFFFFF, the size will be in the
+"/          corresponding 8 byte zip64 end of central
 "/          directory field.
 "/
 "/      offset of start of central directory with respect to
 "/      the starting disk number:  (4 bytes)
 "/
 "/          Offset of the start of the central directory on the
-"/          disk on which the central directory starts. If an 
-"/          archive is in ZIP64 format and the value in this 
-"/          field is 0xFFFFFFFF, the size will be in the 
-"/          corresponding 8 byte zip64 end of central 
+"/          disk on which the central directory starts. If an
+"/          archive is in ZIP64 format and the value in this
+"/          field is 0xFFFFFFFF, the size will be in the
+"/          corresponding 8 byte zip64 end of central
 "/          directory field.
 "/
 "/      .ZIP file comment length: (2 bytes)
@@ -2857,11 +2853,11 @@
 "/
 "/  K.  Splitting and Spanning ZIP files
 "/
-"/          Spanning is the process of segmenting a ZIP file across 
-"/          multiple removable media. This support has typically only 
-"/          been provided for DOS formatted floppy diskettes. 
-"/
-"/          File splitting is a newer derivative of spanning.  
+"/          Spanning is the process of segmenting a ZIP file across
+"/          multiple removable media. This support has typically only
+"/          been provided for DOS formatted floppy diskettes.
+"/
+"/          File splitting is a newer derivative of spanning.
 "/          Splitting follows the same segmentation process as
 "/          spanning, however, it does not require writing each
 "/          segment to a unique removable medium and instead supports
@@ -2869,21 +2865,21 @@
 "/          such as file systems, local drives, folders, etc...
 "/
 "/          A key difference between spanned and split ZIP files is
-"/          that all pieces of a spanned ZIP file have the same name.  
-"/          Since each piece is written to a separate volume, no name 
-"/          collisions occur and each segment can reuse the original 
+"/          that all pieces of a spanned ZIP file have the same name.
+"/          Since each piece is written to a separate volume, no name
+"/          collisions occur and each segment can reuse the original
 "/          .ZIP file name given to the archive.
 "/
-"/          Sequence ordering for DOS spanned archives uses the DOS 
+"/          Sequence ordering for DOS spanned archives uses the DOS
 "/          volume label to determine segment numbers.  Volume labels
-"/          for each segment are written using the form PKBACK#xxx, 
-"/          where xxx is the segment number written as a decimal 
+"/          for each segment are written using the form PKBACK#xxx,
+"/          where xxx is the segment number written as a decimal
 "/          value from 001 - nnn.
 "/
 "/          Split ZIP files are typically written to the same location
 "/          and are subject to name collisions if the spanned name
-"/          format is used since each segment will reside on the same 
-"/          drive. To avoid name collisions, split archives are named 
+"/          format is used since each segment will reside on the same
+"/          drive. To avoid name collisions, split archives are named
 "/          as follows.
 "/
 "/          Segment 1   = filename.z01
@@ -2928,9 +2924,9 @@
 
 oldFileNamed:name startOfArchive: startOfArchive endOfArchive: endOfArchive
     ^ self new
-        setArchiveStartPosition:startOfArchive endPosition:endOfArchive;
-        name:name mode:#read;
-        yourself.
+	setArchiveStartPosition:startOfArchive endPosition:endOfArchive;
+	name:name mode:#read;
+	yourself.
 
     "Modified: / 17-02-2017 / 22:15:25 / stefan"
 !
@@ -2938,13 +2934,13 @@
 readingFrom:aPositionableStream
     "open an existing Zip archive - read data from aPositionableStream"
 
-    ^ self new readingFrom:aPositionableStream.    
+    ^ self new readingFrom:aPositionableStream.
 !
 
 writingTo:aPositionableStream
     "open an new Zip archive - write data to aPositionableStream"
 
-    ^ self new writingTo:aPositionableStream.    
+    ^ self new writingTo:aPositionableStream.
 ! !
 
 !ZipArchive class methodsFor:'Signal constants'!
@@ -2980,10 +2976,10 @@
 !
 
 zipFileCachingTime:seconds
-    "by default, zip files are cached for some time, 
+    "by default, zip files are cached for some time,
      in case they are reconsulted soon.
      The defualt time is 60s, but can be changed by this setter"
-     
+
     ZipFileCachingTime := seconds
 ! !
 
@@ -2991,13 +2987,13 @@
 
 initialize
     ZipFileFormatErrorSignal isNil ifTrue:[
-        ZipFileFormatErrorSignal := OpenError newSignalMayProceed:true.
-        ZipFileFormatErrorSignal nameClass:self message:#zipFileFormatErrorSignal.
-        ZipFileFormatErrorSignal notifierString:'unrecognized/bad zip file format'.
-
-        UnsupportedZipFileFormatErrorSignal := ZipFileFormatErrorSignal newSignal.
-        UnsupportedZipFileFormatErrorSignal nameClass:self message:#unsupportedZipFileFormatErrorSignal.
-        UnsupportedZipFileFormatErrorSignal notifierString:'unsupported zip file format'.
+	ZipFileFormatErrorSignal := OpenError newSignalMayProceed:true.
+	ZipFileFormatErrorSignal nameClass:self message:#zipFileFormatErrorSignal.
+	ZipFileFormatErrorSignal notifierString:'unrecognized/bad zip file format'.
+
+	UnsupportedZipFileFormatErrorSignal := ZipFileFormatErrorSignal newSignal.
+	UnsupportedZipFileFormatErrorSignal nameClass:self message:#unsupportedZipFileFormatErrorSignal.
+	UnsupportedZipFileFormatErrorSignal notifierString:'unsupported zip file format'.
     ].
 
     DefaultAppendTrailingSlash := true.
@@ -3016,7 +3012,7 @@
     "forget about cached zipArchives"
 
     FlushBlock notNil ifTrue:[
-        Processor removeTimedBlock:FlushBlock.
+	Processor removeTimedBlock:FlushBlock.
     ].
     RecentlyUsedZipArchives := nil. FlushBlock := nil.
 
@@ -3029,7 +3025,7 @@
     "forget about cached zipArchives"
 
     FlushBlock isNil ifTrue:[
-        FlushBlock := [RecentlyUsedZipArchives := nil. FlushBlock := nil].
+	FlushBlock := [RecentlyUsedZipArchives := nil. FlushBlock := nil].
     ].
     Processor addTimedBlock:FlushBlock for:Processor timeoutHandlerProcess afterSeconds:(ZipFileCachingTime ? 60).
 
@@ -3116,9 +3112,9 @@
 debugTrace:aBoolean
 %{
     if (aBoolean == true) {
-        debugTrace = 1;
+	debugTrace = 1;
     } else {
-        debugTrace = 0;
+	debugTrace = 0;
     }
 %}
 ! !
@@ -3145,16 +3141,16 @@
 
 dateToZipFileDate:aDate
     "/ data in msdos format
-    ^ (((aDate day) 
-        bitOr: (aDate month bitShift: 5)) 
-        bitOr: (((aDate year) - 1980) bitShift: 9))
+    ^ (((aDate day)
+	bitOr: (aDate month bitShift: 5))
+	bitOr: (((aDate year) - 1980) bitShift: 9))
 !
 
 timeToZipFileTime:aTime
     "/ time in msdos format
-    ^ (((aTime seconds // 2) 
-        bitOr: (aTime minutes bitShift: 5)) 
-        bitOr: (aTime hours bitShift: 11))
+    ^ (((aTime seconds // 2)
+	bitOr: (aTime minutes bitShift: 5))
+	bitOr: (aTime hours bitShift: 11))
 ! !
 
 !ZipArchive methodsFor:'Compatibility-Squeak'!
@@ -3174,7 +3170,7 @@
      see class documentation"
 
     appendTrailingSlash isNil ifTrue:[
-        appendTrailingSlash := DefaultAppendTrailingSlash 
+	appendTrailingSlash := DefaultAppendTrailingSlash
     ].
     ^appendTrailingSlash
 
@@ -3183,7 +3179,7 @@
 
 appendTrailingSlash:aBoolean
     "Sets trailing slash behavior. If true, all directory entries
-     will have a trailing slash in its nama. For details, see class 
+     will have a trailing slash in its nama. For details, see class
      documentation"
 
     appendTrailingSlash := aBoolean.
@@ -3204,7 +3200,7 @@
 
 fileSize
     stream notNil ifTrue:[
-        ^ stream size
+	^ stream size
     ].
     ^ 0
 !
@@ -3252,7 +3248,7 @@
 
 signatureInformation
     "for compatibility with SignedZipArchive"
-    
+
     ^ nil
 !
 
@@ -3270,27 +3266,27 @@
 
 = aZipArchiveToCompare
     "open both archives
-        - check file size
-        - check number of archive members
-        - perform a binary compare of the archives."
+	- check file size
+	- check number of archive members
+	- perform a binary compare of the archives."
 
     |streamBufferSize rdSize buf1 buf2 nextBlockSize stream1 stream2|
 
     self == aZipArchiveToCompare ifTrue:[
-        ^ true.
+	^ true.
     ].
     self class ~~ aZipArchiveToCompare class ifTrue:[
-        ^ false.
+	^ false.
     ].
     (self fileSize ~= aZipArchiveToCompare fileSize) ifTrue:[
-        ^ false
+	^ false
     ].
     (self numberOfEntries ~= aZipArchiveToCompare numberOfEntries) ifTrue:[
-        ^ false
+	^ false
     ].
 
     "/ perform a binary compare of the archives
-    streamBufferSize := self class streamBufferSize.    
+    streamBufferSize := self class streamBufferSize.
     rdSize           := self fileSize.
     buf1             := ByteArray new:streamBufferSize.
     buf2             := ByteArray new:streamBufferSize.
@@ -3301,20 +3297,20 @@
     stream2 reset.
 
     [rdSize > 0] whileTrue:[
-        rdSize > streamBufferSize ifTrue: [
-            nextBlockSize := streamBufferSize.
-        ] ifFalse: [
-            nextBlockSize := rdSize.
-            buf1 := ByteArray new:nextBlockSize.
-            buf2 := ByteArray new:nextBlockSize.
-        ].
-
-        stream1 nextBytes:nextBlockSize into:buf1 startingAt:1.
-        stream2 nextBytes:nextBlockSize into:buf2 startingAt:1.
-        buf1 ~= buf2 ifTrue:[    
-            ^ false.
-        ].
-        rdSize := rdSize - nextBlockSize.
+	rdSize > streamBufferSize ifTrue: [
+	    nextBlockSize := streamBufferSize.
+	] ifFalse: [
+	    nextBlockSize := rdSize.
+	    buf1 := ByteArray new:nextBlockSize.
+	    buf2 := ByteArray new:nextBlockSize.
+	].
+
+	stream1 nextBytes:nextBlockSize into:buf1 startingAt:1.
+	stream2 nextBytes:nextBlockSize into:buf2 startingAt:1.
+	buf1 ~= buf2 ifTrue:[
+	    ^ false.
+	].
+	rdSize := rdSize - nextBlockSize.
     ].
 
     ^ true
@@ -3334,10 +3330,10 @@
 
 close
     stream notNil ifTrue:[
-        self flush.
-        stream close.
-        stream := archiveName := centralDirectory := zipMembersByName := nil.
-        firstEntry := lastEntry := nil.
+	self flush.
+	stream close.
+	stream := archiveName := centralDirectory := zipMembersByName := nil.
+	firstEntry := lastEntry := nil.
     ].
 !
 
@@ -3345,7 +3341,7 @@
     "finish the zip archive, but do not close the underlying stream"
 
     (stream notNil and:[mode == #write]) ifTrue: [
-        self addCentralZipDirectory
+	self addCentralZipDirectory
     ]
 !
 
@@ -3356,14 +3352,14 @@
 
     filename := name asFilename.
     (readOrWriteMode = #read and:[filename exists not]) ifTrue:[
-        ^ OpenError raiseRequestWith:filename errorString:' - file does not exist'.
+	^ OpenError raiseRequestWith:filename errorString:' - file does not exist'.
     ].
     filename isDirectory ifTrue:[
-        ^ OpenError raiseRequestWith:filename errorString:' - file is a directory'.
+	^ OpenError raiseRequestWith:filename errorString:' - file is a directory'.
     ].
 
     stream notNil ifTrue: [
-        self close.
+	self close.
     ].
 
     archiveName := filename name.
@@ -3371,28 +3367,28 @@
 
     self openFile.
     mode ~~ #write ifTrue:[
-        |mustCloseFile|
-
-        mustCloseFile := true.
-        [
-            self readDirectory.
-            mustCloseFile := false.
-
-            mode == #append ifTrue:[
-                members := self zipMembersByName values.
-                members isEmptyOrNil ifTrue:[^ self].
-
-                maxStartPosition := members maxApplying:[:eachMember | self dataStartOf:eachMember].
-                lastMember := members detect:[:eachMember | eachMember dataStart = maxStartPosition].
-
-                stream position:(startOfArchive + lastMember dataStart + lastMember compressedSize).
-                mode := #write.
-            ].
-        ] ensure:[
-            mustCloseFile ifTrue:[self close].
-        ].
+	|mustCloseFile|
+
+	mustCloseFile := true.
+	[
+	    self readDirectory.
+	    mustCloseFile := false.
+
+	    mode == #append ifTrue:[
+		members := self zipMembersByName values.
+		members isEmptyOrNil ifTrue:[^ self].
+
+		maxStartPosition := members maxApplying:[:eachMember | self dataStartOf:eachMember].
+		lastMember := members detect:[:eachMember | eachMember dataStart = maxStartPosition].
+
+		stream position:(startOfArchive + lastMember dataStart + lastMember compressedSize).
+		mode := #write.
+	    ].
+	] ensure:[
+	    mustCloseFile ifTrue:[self close].
+	].
     ] ifFalse:[
-        zipMembersByName := Dictionary new.
+	zipMembersByName := Dictionary new.
     ].
 
     "Modified: / 31-08-2010 / 12:39:25 / sr"
@@ -3412,21 +3408,21 @@
     "initialize the archive to read from aPositionableStream"
 
     stream notNil ifTrue: [
-        stream ~~ aPositionableStream ifTrue: [
-            self close.
-        ].
+	stream ~~ aPositionableStream ifTrue: [
+	    self close.
+	].
     ].
 
     mode := #read.
     aPositionableStream binary.
     stream := aPositionableStream.
     aPositionableStream isFileStream ifTrue:[
-        archiveName := aPositionableStream pathName.
-        aPositionableStream isDirectory ifTrue:[
-            OpenError raiseWith:self errorString:(' - is a directory').
-        ].        
+	archiveName := aPositionableStream pathName.
+	aPositionableStream isDirectory ifTrue:[
+	    OpenError raiseWith:self errorString:(' - is a directory').
+	].
     ] ifFalse:[
-        archiveName := 'internal stream'.
+	archiveName := 'internal stream'.
     ].
     self readDirectory.
 
@@ -3435,9 +3431,9 @@
 
 reopenForReading
     stream isNil ifTrue:[
-        mode := #read.
-        stream := archiveName asFilename readStream.
-        stream binary
+	mode := #read.
+	stream := archiveName asFilename readStream.
+	stream binary
     ]
 
     "Created: / 21-11-2010 / 12:02:37 / cg"
@@ -3447,16 +3443,16 @@
     "initialize the archive to write to aPositionableStream"
 
     stream notNil ifTrue: [
-        self close.
+	self close.
     ].
 
     mode := #write.
     aPositionableStream binary.
     stream := aPositionableStream.
     aPositionableStream isFileStream ifTrue:[
-        archiveName := aPositionableStream pathName.
+	archiveName := aPositionableStream pathName.
     ] ifFalse:[
-        archiveName := 'internal stream'.
+	archiveName := 'internal stream'.
     ].
     zipMembersByName := Dictionary new.
 ! !
@@ -3475,38 +3471,38 @@
 dataStartOf:zipEntry
     "fetch the absolute start address of the data of a given zipEntry.
      Note: extra field and extra field length may be different from that in
-           the central directory entry. Sow e have to fetch the local header."
+	   the central directory entry. Sow e have to fetch the local header."
 
     |dataStart fileHeaderStart fileNameLength extraFieldLength|
 
     dataStart := zipEntry dataStart.
     dataStart notNil ifTrue:[
-        ^ dataStart.
+	^ dataStart.
     ].
 
     fileHeaderStart := zipEntry relativeLocalHeaderOffset + startOfArchive.
     (fileHeaderStart + 30) > endOfArchive ifTrue: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
+	^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
     ].
 
     "Now read the fileHeader:
-        0  local file header signature     4 bytes  (0x04034b50)
-        4  version needed to extract       2 bytes
-        6  general purpose bit flag        2 bytes
-        8  compression method              2 bytes
-        10 last mod file time              2 bytes
-        12 last mod file date              2 bytes
-        14 crc-32                          4 bytes
-        18 compressed size                 4 bytes
-        22 uncompressed size               4 bytes
-        26 file name length (x)            2 bytes
-        28 extra field length (y)          2 bytes
-              fixd size total len:    30
-        30 file name (variable size)
-        30+x    extra field (variable size)
-        30+x+y  data
+	0  local file header signature     4 bytes  (0x04034b50)
+	4  version needed to extract       2 bytes
+	6  general purpose bit flag        2 bytes
+	8  compression method              2 bytes
+	10 last mod file time              2 bytes
+	12 last mod file date              2 bytes
+	14 crc-32                          4 bytes
+	18 compressed size                 4 bytes
+	22 uncompressed size               4 bytes
+	26 file name length (x)            2 bytes
+	28 extra field length (y)          2 bytes
+	      fixd size total len:    30
+	30 file name (variable size)
+	30+x    extra field (variable size)
+	30+x+y  data
      Note: extra field and extra field length may be different from that in
-           the central directory entry!!
+	   the central directory entry!!
     "
 
     stream position:fileHeaderStart+26.
@@ -3516,7 +3512,7 @@
     dataStart := fileHeaderStart + 30 + fileNameLength + extraFieldLength.
 
     (dataStart + (zipEntry compressedSize)) > endOfArchive ifTrue: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
+	^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
     ].
     zipEntry dataStart:dataStart.
 
@@ -3527,17 +3523,17 @@
     |fn|
 
     stream isNil ifTrue:[
-        fn := archiveName asFilename.
-        mode ~~ #write ifTrue:[
-            mode == #append ifTrue:[
-                stream := fn readWriteStream.
-            ] ifFalse:[
-                stream := fn readStream.
-            ].
-        ] ifFalse:[
-            stream := fn writeStream
-        ].
-        stream binary.
+	fn := archiveName asFilename.
+	mode ~~ #write ifTrue:[
+	    mode == #append ifTrue:[
+		stream := fn readWriteStream.
+	    ] ifFalse:[
+		stream := fn readStream.
+	    ].
+	] ifFalse:[
+	    stream := fn writeStream
+	].
+	stream binary.
     ].
 
     "Modified: / 31-08-2010 / 12:40:41 / sr"
@@ -3548,13 +3544,13 @@
      before. In that case the archive is the complete file."
 
     startOfArchive isNil ifTrue: [
-        "/ set archive zero position
-        startOfArchive := 0.
+	"/ set archive zero position
+	startOfArchive := 0.
     ].
 
     endOfArchive isNil ifTrue: [
-        "/ set archive end position
-        endOfArchive := stream size.
+	"/ set archive end position
+	endOfArchive := stream size.
     ].
 !
 
@@ -3564,17 +3560,17 @@
     fileNameParts := zipFileName asCollectionOfSubstringsSeparatedByAny:'/\'.
 
     fileNameParts do:[:eachPart|
-        eachPart notEmptyOrNil ifTrue:[    
-            validZipFileName isNil ifTrue:[
-                validZipFileName := eachPart.
-            ] ifFalse:[
-                validZipFileName := validZipFileName, '/', eachPart.
-            ].
-        ].
+	eachPart notEmptyOrNil ifTrue:[
+	    validZipFileName isNil ifTrue:[
+		validZipFileName := eachPart.
+	    ] ifFalse:[
+		validZipFileName := validZipFileName, '/', eachPart.
+	    ].
+	].
     ].
 
     validZipFileName isEmptyOrNil ifTrue:[
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString: (' - invalid zip file name ', zipFileName).
+	^ ZipFileFormatErrorSignal raiseRequestErrorString: (' - invalid zip file name ', zipFileName).
     ].
 
     ^ validZipFileName
@@ -3596,10 +3592,10 @@
     "decode rawBytes into a byteArray"
 
     ^ self
-        decode:rawBytes 
-        method:compressionMethod 
-        size:uncompressedSize
-        asString:false
+	decode:rawBytes
+	method:compressionMethod
+	size:uncompressedSize
+	asString:false
 !
 
 decode:rawBytes method:compressionMethod size:uncompressedSize asString:asString
@@ -3608,55 +3604,55 @@
     |outBytes|
 
     compressionMethod == COMPRESSION_STORED ifTrue:[
-        "/
-        "/ uncompressed
-        "/
-        asString ifTrue:[^ rawBytes asString].
-        ^ rawBytes
+	"/
+	"/ uncompressed
+	"/
+	asString ifTrue:[^ rawBytes asString].
+	^ rawBytes
     ].
 
     compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-        "/
-        "/ deflate/inflate algorithm
-        "/
-        asString ifTrue:[
-            outBytes := String new:uncompressedSize.
-        ] ifFalse:[
-            outBytes := ByteArray new:uncompressedSize.
-        ].
-        ^ self inflate:rawBytes to:outBytes
+	"/
+	"/ deflate/inflate algorithm
+	"/
+	asString ifTrue:[
+	    outBytes := String new:uncompressedSize.
+	] ifFalse:[
+	    outBytes := ByteArray new:uncompressedSize.
+	].
+	^ self inflate:rawBytes to:outBytes
     ].
 
     "/
     "/ the other algorithms are not (yet) supported
     "/
     compressionMethod == COMPRESSION_SHRUNK ifTrue:[
-        self error:'unsupported compression method: SHRUNK'.
-        ^ nil
+	self error:'unsupported compression method: SHRUNK'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_REDUCED1 ifTrue:[
-        self error:'unsupported compression method: REDUCED1'.
-        ^ nil
+	self error:'unsupported compression method: REDUCED1'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_REDUCED2 ifTrue:[
-        self error:'unsupported compression method: REDUCED2'.
-        ^ nil
+	self error:'unsupported compression method: REDUCED2'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_REDUCED3 ifTrue:[
-        self error:'unsupported compression method: REDUCED3'.
-        ^ nil
+	self error:'unsupported compression method: REDUCED3'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_REDUCED4 ifTrue:[
-        self error:'unsupported compression method: REDUCED4'.
-        ^ nil
+	self error:'unsupported compression method: REDUCED4'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_IMPLODED ifTrue:[
-        self error:'unsupported compression method: IMPLODED'.
-        ^ nil
+	self error:'unsupported compression method: IMPLODED'.
+	^ nil
     ].
     compressionMethod == COMPRESSION_TOKENIZED ifTrue:[
-        self error:'unsupported compression method: TOKENIZED'.
-        ^ nil
+	self error:'unsupported compression method: TOKENIZED'.
+	^ nil
     ].
 
     self error:'unsupported compression method'.
@@ -3673,40 +3669,40 @@
     char *in, *out;
 
     if (__isByteArrayLike(inBytes)) {
-        in = __byteArrayVal(inBytes);
+	in = __byteArrayVal(inBytes);
     } else if (__isStringLike(inBytes)) {
-        in = __stringVal(inBytes);
+	in = __stringVal(inBytes);
     } else {
-        inflateReturnCode = @symbol(badArgument1);
-        goto badArgument;
+	inflateReturnCode = @symbol(badArgument1);
+	goto badArgument;
     }
 
     if (__isByteArray(outBytes)) {
-        out = __byteArrayVal(outBytes);
+	out = __byteArrayVal(outBytes);
     } else if (__isString(outBytes)) {
-        out = __stringVal(outBytes);
+	out = __stringVal(outBytes);
     } else {
-        inflateReturnCode = @symbol(badArgument2);
-        goto badArgument;
+	inflateReturnCode = @symbol(badArgument2);
+	goto badArgument;
     }
 
     {
-        int rc = stx_inflate(in, out);
-
-        if (rc == 0) {
-            RETURN (outBytes);
-        }
-        inflateReturnCode = __MKSMALLINT(rc);
+	int rc = stx_inflate(in, out);
+
+	if (rc == 0) {
+	    RETURN (outBytes);
+	}
+	inflateReturnCode = __MKSMALLINT(rc);
     }
 badArgument: ;
 %}.
     inflateReturnCode notNil ifTrue:[
-        inflateReturnCode isSymbol ifTrue:[
-            self primitiveFailed:inflateReturnCode
-        ].
-
-        "/ bad blockType 2
-        self error:'inflate error: ' , inflateReturnCode printString
+	inflateReturnCode isSymbol ifTrue:[
+	    self primitiveFailed:inflateReturnCode
+	].
+
+	"/ bad blockType 2
+	self error:'inflate error: ' , inflateReturnCode printString
     ].
     ^ nil.
 
@@ -3715,11 +3711,11 @@
 
 !ZipArchive methodsFor:'private - directory stuff'!
 
-addCentralZipDirectory 
+addCentralZipDirectory
     |noEntries|
 
     centralDirectory isNil ifTrue: [
-        centralDirectory := ZipCentralDirectory new default.
+	centralDirectory := ZipCentralDirectory new default.
     ].
 
     noEntries := 0.
@@ -3730,36 +3726,36 @@
     centralDirectory centralDirectoryStartOffset: stream position.
 
     self zipMembersDo:[:zipEntry |
-        noEntries := noEntries + 1.
-        stream nextPutInt32LSB: C_CENTRAL_HEADER_SIGNATURE.            
-        stream nextPutInt16LSB:zipEntry versionMadeBy.
-        stream nextPutInt16LSB:zipEntry versionNeedToExtract.
-        stream nextPutInt16LSB:zipEntry generalPurposBitFlag.
-        stream nextPutInt16LSB:zipEntry compressionMethod.
-        stream nextPutInt16LSB:zipEntry lastModFileTime.
-        stream nextPutInt16LSB:zipEntry lastModFileDate.
-        stream nextPutInt32LSB:zipEntry crc32.
-        stream nextPutInt32LSB:zipEntry compressedSize.
-        stream nextPutInt32LSB:zipEntry uncompressedSize.
-        stream nextPutInt16LSB:zipEntry fileNameLength.
-        stream nextPutInt16LSB:zipEntry extraFieldLength.
-        stream nextPutInt16LSB:zipEntry fileCommentLength.
-        stream nextPutInt16LSB:zipEntry diskNumberStart.
-        stream nextPutInt16LSB:zipEntry internalFileAttributes.
-        stream nextPutInt32LSB:zipEntry externalFileAttributes.
-        stream nextPutInt32LSB:zipEntry relativeLocalHeaderOffset.
-
-        self assert:zipEntry fileNameLength = zipEntry fileName size.
-        stream nextPutAll:zipEntry fileName.
-
-        zipEntry extraField notNil ifTrue: [
-            self assert:zipEntry extraFieldLength = zipEntry extraField size.
-            stream nextPutAll:zipEntry extraField.
-        ].
-        zipEntry fileComment notNil ifTrue: [
-            self assert:zipEntry fileCommentLength = zipEntry fileComment size.
-            stream nextPutAll:zipEntry fileComment.
-        ].
+	noEntries := noEntries + 1.
+	stream nextPutInt32LSB: C_CENTRAL_HEADER_SIGNATURE.
+	stream nextPutInt16LSB:zipEntry versionMadeBy.
+	stream nextPutInt16LSB:zipEntry versionNeedToExtract.
+	stream nextPutInt16LSB:zipEntry generalPurposBitFlag.
+	stream nextPutInt16LSB:zipEntry compressionMethod.
+	stream nextPutInt16LSB:zipEntry lastModFileTime.
+	stream nextPutInt16LSB:zipEntry lastModFileDate.
+	stream nextPutInt32LSB:zipEntry crc32.
+	stream nextPutInt32LSB:zipEntry compressedSize.
+	stream nextPutInt32LSB:zipEntry uncompressedSize.
+	stream nextPutInt16LSB:zipEntry fileNameLength.
+	stream nextPutInt16LSB:zipEntry extraFieldLength.
+	stream nextPutInt16LSB:zipEntry fileCommentLength.
+	stream nextPutInt16LSB:zipEntry diskNumberStart.
+	stream nextPutInt16LSB:zipEntry internalFileAttributes.
+	stream nextPutInt32LSB:zipEntry externalFileAttributes.
+	stream nextPutInt32LSB:zipEntry relativeLocalHeaderOffset.
+
+	self assert:zipEntry fileNameLength = zipEntry fileName size.
+	stream nextPutAll:zipEntry fileName.
+
+	zipEntry extraField notNil ifTrue: [
+	    self assert:zipEntry extraFieldLength = zipEntry extraField size.
+	    stream nextPutAll:zipEntry extraField.
+	].
+	zipEntry fileComment notNil ifTrue: [
+	    self assert:zipEntry fileCommentLength = zipEntry fileComment size.
+	    stream nextPutAll:zipEntry fileComment.
+	].
     ].
 
     centralDirectory centralDirectoryTotalNoOfEntries: noEntries.
@@ -3779,7 +3775,7 @@
     stream nextPutInt16LSB:centralDirectory zipCommentLength.
 
     centralDirectory zipCommentLength ~~ 0 ifTrue: [
-        stream nextPutAll: centralDirectory zipComment.
+	stream nextPutAll: centralDirectory zipComment.
     ].
 
     "Modified: / 19-11-2010 / 16:23:36 / cg"
@@ -3788,18 +3784,18 @@
 addMember:zmemb
     "add a zipMember"
 
-    zipMembersByName at:zmemb fileName put:zmemb ifPresent:[:oldEntry| 
-            "ignore duplicate entries for backward compatibility.
-             Argh: expecco once added wrong duplicates to the end of ets files.
-                   The first entry is valid."
-            Logger warning:'duplicate entry in ZIP file ignored: %1' with:zmemb fileName.
-            ^ oldEntry.
-        ].
+    zipMembersByName at:zmemb fileName put:zmemb ifPresent:[:oldEntry|
+	    "ignore duplicate entries for backward compatibility.
+	     Argh: expecco once added wrong duplicates to the end of ets files.
+		   The first entry is valid."
+	    Logger warning:'duplicate entry in ZIP file ignored: %1' with:zmemb fileName.
+	    ^ oldEntry.
+	].
 
     firstEntry isNil ifTrue:[
-        firstEntry := zmemb
+	firstEntry := zmemb
     ] ifFalse:[
-        lastEntry next:zmemb.
+	lastEntry next:zmemb.
     ].
     lastEntry := zmemb.
 
@@ -3816,18 +3812,18 @@
     |size|
 
     stream isNil ifTrue: [
-        ^ false
+	^ false
     ].
 
     self setDefaultArchiveBounds.
 
     size := endOfArchive - startOfArchive.
     size == 0 ifTrue:[
-        ^ false
+	^ false
     ].
 
     (size < (ECREC_SIZE+4)) ifTrue:[
-        ^ false.
+	^ false.
     ].
 
     ^ self searchForEndOfCentralDirectorySignature
@@ -3841,9 +3837,9 @@
     self openFile.
 
     ^ [
-        self checkZipArchive.
+	self checkZipArchive.
     ] ensure:[
-        self close.
+	self close.
     ].
 
     "Modified: / 17-02-2017 / 22:22:44 / stefan"
@@ -3864,18 +3860,18 @@
     nameWithSlash := name , '/'.
 
     self zipMembersDo:[:each |
-        | fn |
-
-        fn := each fileName.
-        (fn = name) ifTrue:[^ each].
-        "Try if they differ only in trailing slash"
-        ((fn size) = (name size + 1) 
-            and:[fn = nameWithSlash]) ifTrue:[ 
-                "/Here, return a copy with patched name:
-                ^each copy
-                    fileName: name;
-                    yourself.
-            ]
+	| fn |
+
+	fn := each fileName.
+	(fn = name) ifTrue:[^ each].
+	"Try if they differ only in trailing slash"
+	((fn size) = (name size + 1)
+	    and:[fn = nameWithSlash]) ifTrue:[
+		"/Here, return a copy with patched name:
+		^each copy
+		    fileName: name;
+		    yourself.
+	    ]
     ].
     ^ nil
 
@@ -3886,7 +3882,7 @@
     "find a zipMember by condition"
 
     self zipMembersDo:[:zipd |
-        (aOneArgBlock value:zipd) ifTrue:[^ zipd].
+	(aOneArgBlock value:zipd) ifTrue:[^ zipd].
     ].
     ^ nil
 
@@ -3902,15 +3898,15 @@
 
     size := endOfArchive - startOfArchive.
     (size == 0) ifTrue:[
-        ^ self
+	^ self
     ].
 
     (size < (ECREC_SIZE+4)) ifTrue:[
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipfile too short'.
+	^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipfile too short'.
     ].
 
     self searchForEndOfCentralDirectorySignature ifFalse: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - could not find end of directory signature'.
+	^ ZipFileFormatErrorSignal raiseRequestErrorString:' - could not find end of directory signature'.
     ].
 
     "/ position before end of central directory signature
@@ -3919,52 +3915,52 @@
     "/ Now we have found the end of central directory record
     centralDirectory := ZipCentralDirectory new.
     EndOfStreamNotification handle:[:ex|
-        ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error or short file: ' ,
-                                        (stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
-        ^ self.
+	ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error or short file: ' ,
+					(stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
+	^ self.
     ] do:[
-        centralDirectory readFrom:stream.
-
-        "/ set file position to start of central directory
-        (pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize) < startOfArchive ifTrue: [
-            ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory start is out of the archive bounds'.
-        ].
-
-        startOfArchive := pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize.
-        stream position:(pos0 - (centralDirectory centralDirectorySize)).
-
-        zipMembersByName := Dictionary new:centralDirectory centralDirectoryTotalNoOfEntries.
-
-        "/ read central directory entries
-        1 to:(centralDirectory centralDirectoryTotalNoOfEntries) do:[:i |
-            |zipd  centralFileHeaderSignature|
-
-            (stream position + (self class centralDirectoryMinimumSize)) > endOfArchive ifTrue: [
-                ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
-            ].
-            centralFileHeaderSignature := stream nextInt32MSB:false.            
-            centralFileHeaderSignature ~= C_CENTRAL_HEADER_SIGNATURE ifTrue:[
-                ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error - bad centralHeaderSignature in: ' ,
-                                                (stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
-                ^ self.
-            ].
-
-            zipd := ZipMember new readCentralDirectoryEntryFrom:stream.
-            self addMember:zipd.
-        ].
-
-        (stream position + 6) > endOfArchive ifTrue: [
-            "/ archive has no digital signature
-            ^ self.
-        ].
-
-        "/ check for digital signature
-        ((stream nextByte ~~ ($P codePoint))
-         or:[stream nextByte ~~ ($K codePoint)
-         or:[stream nextByte ~~ 8r005
-         or:[stream nextByte ~~ 8r005]]]) ifTrue:[
-            centralDirectory readDigitalSignatureFrom:stream.
-        ].
+	centralDirectory readFrom:stream.
+
+	"/ set file position to start of central directory
+	(pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize) < startOfArchive ifTrue: [
+	    ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory start is out of the archive bounds'.
+	].
+
+	startOfArchive := pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize.
+	stream position:(pos0 - (centralDirectory centralDirectorySize)).
+
+	zipMembersByName := Dictionary new:centralDirectory centralDirectoryTotalNoOfEntries.
+
+	"/ read central directory entries
+	1 to:(centralDirectory centralDirectoryTotalNoOfEntries) do:[:i |
+	    |zipd  centralFileHeaderSignature|
+
+	    (stream position + (self class centralDirectoryMinimumSize)) > endOfArchive ifTrue: [
+		^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
+	    ].
+	    centralFileHeaderSignature := stream nextInt32MSB:false.
+	    centralFileHeaderSignature ~= C_CENTRAL_HEADER_SIGNATURE ifTrue:[
+		ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error - bad centralHeaderSignature in: ' ,
+						(stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
+		^ self.
+	    ].
+
+	    zipd := ZipMember new readCentralDirectoryEntryFrom:stream.
+	    self addMember:zipd.
+	].
+
+	(stream position + 6) > endOfArchive ifTrue: [
+	    "/ archive has no digital signature
+	    ^ self.
+	].
+
+	"/ check for digital signature
+	((stream nextByte ~~ ($P codePoint))
+	 or:[stream nextByte ~~ ($K codePoint)
+	 or:[stream nextByte ~~ 8r005
+	 or:[stream nextByte ~~ 8r005]]]) ifTrue:[
+	    centralDirectory readDigitalSignatureFrom:stream.
+	].
     ]
 
     "
@@ -3991,36 +3987,36 @@
     or:[stream nextByte ~~ ($K codePoint)
     or:[stream nextByte ~~ 8r005
     or:[stream nextByte ~~ 8r006]]]) ifTrue:[
-        "/ search from end of archive backwards for "end of central directory signature", 
-        "/ this is necessary if the archive includes a .ZIP file comment or a digital signature
-        "/ then the end of the directory signature may be on an other position
-
-        "/ but the "end of central directory signature" must be located in the 
-        "/ last 64k of the archive
-        size > 65536 ifTrue: [
-            searchEndPos := (endOfArchive - 65536).
-        ] ifFalse: [
-            searchEndPos := startOfArchive.
-        ].
-
-        stream position: (pos0 := endOfArchive - 4).
-
-        [foundPK] whileFalse: [
-            (stream nextByte == ($P codePoint)
-            and:[stream nextByte == ($K codePoint)
-            and:[stream nextByte == 8r005
-            and:[stream nextByte == 8r006]]]) ifTrue:[
-                ^ true                
-            ].
-            stream position <= searchEndPos ifTrue: [
-                ^ false.
-            ].
-            pos0 == 0 ifTrue:[
-                ^ false.
-            ].
-            stream position: (pos0 := pos0 - 1).
-        ].
-        ^ false
+	"/ search from end of archive backwards for "end of central directory signature",
+	"/ this is necessary if the archive includes a .ZIP file comment or a digital signature
+	"/ then the end of the directory signature may be on an other position
+
+	"/ but the "end of central directory signature" must be located in the
+	"/ last 64k of the archive
+	size > 65536 ifTrue: [
+	    searchEndPos := (endOfArchive - 65536).
+	] ifFalse: [
+	    searchEndPos := startOfArchive.
+	].
+
+	stream position: (pos0 := endOfArchive - 4).
+
+	[foundPK] whileFalse: [
+	    (stream nextByte == ($P codePoint)
+	    and:[stream nextByte == ($K codePoint)
+	    and:[stream nextByte == 8r005
+	    and:[stream nextByte == 8r006]]]) ifTrue:[
+		^ true
+	    ].
+	    stream position <= searchEndPos ifTrue: [
+		^ false.
+	    ].
+	    pos0 == 0 ifTrue:[
+		^ false.
+	    ].
+	    stream position: (pos0 := pos0 - 1).
+	].
+	^ false
     ].
     ^ true
 !
@@ -4032,8 +4028,8 @@
 
     zipd := firstEntry.
     [zipd notNil] whileTrue:[
-        aBlock value:zipd.
-        zipd := zipd next
+	aBlock value:zipd.
+	zipd := zipd next
     ].
 
     "Created: / 29.3.1998 / 19:15:15 / cg"
@@ -4052,10 +4048,10 @@
 
 isValidPath: anArchivePathName
     self zipMembersByName
-        keysDo:[:eachMemberName |
-            ((eachMemberName startsWith:anArchivePathName,'/') 
-             or:[eachMemberName = anArchivePathName]) ifTrue:[^ true]
-        ].
+	keysDo:[:eachMemberName |
+	    ((eachMemberName startsWith:anArchivePathName,'/')
+	     or:[eachMemberName = anArchivePathName]) ifTrue:[^ true]
+	].
 
     ^ false.
 ! !
@@ -4073,22 +4069,22 @@
     "extract an entry identified by fileName as a byteArray or string;
      nil on errors"
 
-    self 
-        withPositionAndMemberFor:fileName 
-        do:[:zmemb :position |
-            |rawContents data|
-
-            stream position:position.
-            rawContents := stream nextBytes:(zmemb compressedSize).
-
-            data := self
-                decode:rawContents
-                method:(zmemb compressionMethod)
-                size:(zmemb uncompressedSize)
-                asString:asString.
-
-            ^ data.
-        ].
+    self
+	withPositionAndMemberFor:fileName
+	do:[:zmemb :position |
+	    |rawContents data|
+
+	    stream position:position.
+	    rawContents := stream nextBytes:(zmemb compressedSize).
+
+	    data := self
+		decode:rawContents
+		method:(zmemb compressionMethod)
+		size:(zmemb uncompressedSize)
+		asString:asString.
+
+	    ^ data.
+	].
 
     ^ nil
 
@@ -4111,54 +4107,54 @@
     osDirectory := osDirectoryName asFilename.
     directoryAlreadyCreated := osDirectory exists.
     (directoryAlreadyCreated and: [osDirectory isDirectory not]) ifTrue:[
-        "no way to create the base directory - done"
-        OperatingSystem accessDeniedErrorSignal
-            raiseRequestWith:osDirectory
-            errorString:(' - ZipArchive - cannot create base directory: ' , osDirectory asString).
-        ^ self.
+	"no way to create the base directory - done"
+	OperatingSystem accessDeniedErrorSignal
+	    raiseRequestWith:osDirectory
+	    errorString:(' - ZipArchive - cannot create base directory: ' , osDirectory asString).
+	^ self.
     ].
 
     archiveDirectoryNameSize := archiveDirectoryName size.
 
     self members do: [:eachZipArchiveMember|
-        |eachZipArchiveMemberName baseName directory fileNameOrDirectoryEntry|
-
-        eachZipArchiveMemberName := eachZipArchiveMember fileName.
-
-        ((eachZipArchiveMemberName startsWith:archiveDirectoryName)
-         and:[eachZipArchiveMemberName size = archiveDirectoryNameSize
-              or:[(eachZipArchiveMemberName at:archiveDirectoryNameSize+1) == $/]]) ifTrue: [
-
-            directoryAlreadyCreated ifFalse:[
-                osDirectory recursiveMakeDirectory.
-                directoryAlreadyCreated := true.
-            ].
-            baseName := eachZipArchiveMemberName copyFrom:(archiveDirectoryNameSize+1).
-            (baseName notEmpty and:[baseName first == $/]) ifTrue:[
-                baseName := baseName copyFrom:2.
-            ].
-
-            baseName notEmpty ifTrue:[
-                fileNameOrDirectoryEntry := osDirectory construct:baseName.
-
-                "Note, that a ZipArchive usually does not contain entries for directories!!"
-                (eachZipArchiveMember externalFileAttributes bitTest:EXTERNALFILEATTRIBUTES_ISDIRECTORY) ifTrue:[
-                    fileNameOrDirectoryEntry recursiveMakeDirectory.
-                ] ifFalse: [
-                    "make sure, that the directory exists"
-                    directory := fileNameOrDirectoryEntry directory.
-                    directory isDirectory ifFalse:[
-                        directory recursiveMakeDirectory.
-                    ].
-                    
-                    fileNameOrDirectoryEntry writingFileDo:[:aStream|
-                        self 
-                            extract:eachZipArchiveMemberName 
-                            intoStream: aStream.
-                    ].
-                ].
-            ].
-        ]
+	|eachZipArchiveMemberName baseName directory fileNameOrDirectoryEntry|
+
+	eachZipArchiveMemberName := eachZipArchiveMember fileName.
+
+	((eachZipArchiveMemberName startsWith:archiveDirectoryName)
+	 and:[eachZipArchiveMemberName size = archiveDirectoryNameSize
+	      or:[(eachZipArchiveMemberName at:archiveDirectoryNameSize+1) == $/]]) ifTrue: [
+
+	    directoryAlreadyCreated ifFalse:[
+		osDirectory recursiveMakeDirectory.
+		directoryAlreadyCreated := true.
+	    ].
+	    baseName := eachZipArchiveMemberName copyFrom:(archiveDirectoryNameSize+1).
+	    (baseName notEmpty and:[baseName first == $/]) ifTrue:[
+		baseName := baseName copyFrom:2.
+	    ].
+
+	    baseName notEmpty ifTrue:[
+		fileNameOrDirectoryEntry := osDirectory construct:baseName.
+
+		"Note, that a ZipArchive usually does not contain entries for directories!!"
+		(eachZipArchiveMember externalFileAttributes bitTest:EXTERNALFILEATTRIBUTES_ISDIRECTORY) ifTrue:[
+		    fileNameOrDirectoryEntry recursiveMakeDirectory.
+		] ifFalse: [
+		    "make sure, that the directory exists"
+		    directory := fileNameOrDirectoryEntry directory.
+		    directory isDirectory ifFalse:[
+			directory recursiveMakeDirectory.
+		    ].
+
+		    fileNameOrDirectoryEntry writingFileDo:[:aStream|
+			self
+			    extract:eachZipArchiveMemberName
+			    intoStream: aStream.
+		    ].
+		].
+	    ].
+	]
     ].
 !
 
@@ -4166,8 +4162,8 @@
     |zmemb dataStart|
 
     (stream isNil or:[mode ~~ #read]) ifTrue:[
-        ^ self error: 'ZipArchive not open for reading ...'.
-    ].    
+	^ self error: 'ZipArchive not open for reading ...'.
+    ].
 
     zmemb := self findMember:fileName.
     zmemb isNil ifTrue:[^ nil].
@@ -4185,43 +4181,43 @@
     "extract an entry identified by filename into aWriteStream"
 
     self
-        withPositionAndMemberFor:fileName
-        do:[:zmemb :position |
-            |buffer rdSize compressionMethod nextBlockSize streamBufferSize myZipStream|
-
-            stream position:position.
-
-            compressionMethod := zmemb compressionMethod.
-            rdSize := zmemb uncompressedSize.
-            nextBlockSize := streamBufferSize := self class streamBufferSize.
-            buffer := ByteArray new: streamBufferSize.
-            [
-                [rdSize > 0] whileTrue: [
-                    rdSize < streamBufferSize ifTrue: [
-                        nextBlockSize := rdSize.
-                    ].
-
-                    compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-                        myZipStream isNil ifTrue: [
-                            stream binary.
-                            myZipStream := ZipStream readOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
-                        ].
-                        myZipStream next:nextBlockSize into:buffer startingAt:1.
-                    ] ifFalse:[compressionMethod == COMPRESSION_STORED ifTrue:[
-                        stream nextBytes:nextBlockSize into:buffer startingAt:1.
-                    ] ifFalse:[
-                        UnsupportedZipFileFormatErrorSignal raiseErrorString:'unsupported compressMethod'
-                    ]].
-
-                    aWriteStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
-                    rdSize := rdSize - nextBlockSize.
-                ].
-            ] ensure:[
-                myZipStream notNil ifTrue:[
-                    myZipStream close.
-                ].
-            ].
-        ]
+	withPositionAndMemberFor:fileName
+	do:[:zmemb :position |
+	    |buffer rdSize compressionMethod nextBlockSize streamBufferSize myZipStream|
+
+	    stream position:position.
+
+	    compressionMethod := zmemb compressionMethod.
+	    rdSize := zmemb uncompressedSize.
+	    nextBlockSize := streamBufferSize := self class streamBufferSize.
+	    buffer := ByteArray new: streamBufferSize.
+	    [
+		[rdSize > 0] whileTrue: [
+		    rdSize < streamBufferSize ifTrue: [
+			nextBlockSize := rdSize.
+		    ].
+
+		    compressionMethod == COMPRESSION_DEFLATED ifTrue:[
+			myZipStream isNil ifTrue: [
+			    stream binary.
+			    myZipStream := ZipStream readOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
+			].
+			myZipStream next:nextBlockSize into:buffer startingAt:1.
+		    ] ifFalse:[compressionMethod == COMPRESSION_STORED ifTrue:[
+			stream nextBytes:nextBlockSize into:buffer startingAt:1.
+		    ] ifFalse:[
+			UnsupportedZipFileFormatErrorSignal raiseErrorString:'unsupported compressMethod'
+		    ]].
+
+		    aWriteStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
+		    rdSize := rdSize - nextBlockSize.
+		].
+	    ] ensure:[
+		myZipStream notNil ifTrue:[
+		    myZipStream close.
+		].
+	    ].
+	]
 
     "Modified: / 21-11-2010 / 11:56:51 / cg"
     "Modified (format): / 31-05-2017 / 15:03:06 / mawalch"
@@ -4233,12 +4229,12 @@
     |zipEntry dataStart|
 
     (stream isNil or:[mode ~~ #read]) ifTrue:[
-        ^ OpenError raiseRequestWith:nameOfFileInArchive errorString:'ZipArchive not open for reading ...'.
-    ].    
+	^ OpenError raiseRequestWith:nameOfFileInArchive errorString:'ZipArchive not open for reading ...'.
+    ].
 
     zipEntry := self findMember:nameOfFileInArchive.
     zipEntry isNil ifTrue:[
-        ^ OpenError raiseRequestWith:nameOfFileInArchive errorString:'ZipArchive member does not exist: '.
+	^ OpenError raiseRequestWith:nameOfFileInArchive errorString:'ZipArchive member does not exist: '.
     ].
 
     dataStart := self dataStartOf:zipEntry.
@@ -4253,7 +4249,7 @@
     "extract an entry identified by filename into aWriteStream"
 
     stream isNil ifTrue:[
-        self reopenForReading.
+	self reopenForReading.
     ].
     self extract:fileName intoStream: aWriteStream.
     stream close.
@@ -4274,23 +4270,23 @@
 
     osDirectory := osDirectoryName asFilename.
     osDirectory exists ifFalse:[
-        ^ self
+	^ self
     ].
 
     "do not create directories (isDirectory = true) - they are not compatible between operating systems"
 "/    self addDirectory: archiveDirectoryName.
     osDirectory recursiveDirectoryContentsDo: [:entry|
-        fileNameOrDirectoryEntry := osDirectory construct: entry. 
-        fileNameOrDirectoryEntry isDirectory ifTrue: [
+	fileNameOrDirectoryEntry := osDirectory construct: entry.
+	fileNameOrDirectoryEntry isDirectory ifTrue: [
 "/            self addDirectory: (archiveDirectoryName, '/', entry).
-        ] ifFalse: [
-            fileNameOrDirectoryEntry readingFileDo: [:aStream|    
-                self addFile: (archiveDirectoryName, '/', entry) 
-                     fromStream: aStream 
-                     compressMethod: theCompressMethod
-                     asDirectory:false.
-            ].
-        ].
+	] ifFalse: [
+	    fileNameOrDirectoryEntry readingFileDo: [:aStream|
+		self addFile: (archiveDirectoryName, '/', entry)
+		     fromStream: aStream
+		     compressMethod: theCompressMethod
+		     asDirectory:false.
+	    ].
+	].
     ].
 !
 
@@ -4324,35 +4320,35 @@
 addFile:aFileName fromStream:aStream compressMethod:theCompressMethodArg asDirectory:isDirectory
     "do not create directories (isDirectory = true) - they are not compatible between operating systems"
 
-    |zipEntry theZipFileName theCompressMethod streamBufferSize buffer 
+    |zipEntry theZipFileName theCompressMethod streamBufferSize buffer
      crc32 unCompressedDataSize startDataPosition nextBlockSize myZipStream|
 
     (stream isNil or: [mode ~~ #write]) ifTrue: [
-        ^ self error: 'ZipArchive not open for writing ...'.
+	^ self error: 'ZipArchive not open for writing ...'.
     ].
 
     theCompressMethod := theCompressMethodArg.
 
-    ((theCompressMethod == COMPRESSION_DEFLATED) 
+    ((theCompressMethod == COMPRESSION_DEFLATED)
     or:[ theCompressMethod == COMPRESSION_STORED ]) ifFalse:[
-        UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
-        "/ if proceeded, write as uncompressed
-        theCompressMethod := COMPRESSION_STORED
+	UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
+	"/ if proceeded, write as uncompressed
+	theCompressMethod := COMPRESSION_STORED
     ].
 
     zipEntry := ZipMember new default.
-    theZipFileName := self validZipFileNameFrom:aFileName. 
+    theZipFileName := self validZipFileNameFrom:aFileName.
 
     zipEntry fileName: theZipFileName.
     zipEntry uncompressedSize: 0.
 
     isDirectory ifTrue: [
-        theCompressMethod := COMPRESSION_STORED.
-        zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISDIRECTORY.
+	theCompressMethod := COMPRESSION_STORED.
+	zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISDIRECTORY.
     ] ifFalse: [
-        zipEntry compressionMethod: theCompressMethod.
-        zipEntry internalFileAttributes: 1.
-        zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
+	zipEntry compressionMethod: theCompressMethod.
+	zipEntry internalFileAttributes: 1.
+	zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
     ].
 
     "/ data and time in msdos format
@@ -4363,35 +4359,35 @@
 
     zipEntry writeTo:stream.
 
-    streamBufferSize := self class streamBufferSize.    
+    streamBufferSize := self class streamBufferSize.
     buffer := ByteArray new:streamBufferSize.
     crc32 := 0.
     unCompressedDataSize := 0.
     startDataPosition := stream position.
 
     [
-        [aStream atEnd] whileFalse: [
-            nextBlockSize := aStream nextBytes:streamBufferSize into:buffer startingAt:1.
-
-            nextBlockSize > 0 ifTrue: [
-                unCompressedDataSize := unCompressedDataSize + nextBlockSize.
-                crc32 := ZipStream crc32BytesIn: buffer from:1 to:nextBlockSize crc:crc32.
-                theCompressMethod == COMPRESSION_DEFLATED ifTrue: [
-                    myZipStream isNil ifTrue: [
-                        myZipStream := ZipStream writeOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
-                    ].
-                    myZipStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
-                ] ifFalse: [theCompressMethod == COMPRESSION_STORED ifTrue: [
-                    stream nextPutBytes:nextBlockSize from:buffer startingAt:1.
-                ] ifFalse:[
-                    UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
-                ]].
-            ].
-        ].
+	[aStream atEnd] whileFalse: [
+	    nextBlockSize := aStream nextBytes:streamBufferSize into:buffer startingAt:1.
+
+	    nextBlockSize > 0 ifTrue: [
+		unCompressedDataSize := unCompressedDataSize + nextBlockSize.
+		crc32 := ZipStream crc32BytesIn: buffer from:1 to:nextBlockSize crc:crc32.
+		theCompressMethod == COMPRESSION_DEFLATED ifTrue: [
+		    myZipStream isNil ifTrue: [
+			myZipStream := ZipStream writeOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
+		    ].
+		    myZipStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
+		] ifFalse: [theCompressMethod == COMPRESSION_STORED ifTrue: [
+		    stream nextPutBytes:nextBlockSize from:buffer startingAt:1.
+		] ifFalse:[
+		    UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
+		]].
+	    ].
+	].
     ] ensure:[
-        myZipStream notNil ifTrue:[
-            myZipStream close.
-        ].
+	myZipStream notNil ifTrue:[
+	    myZipStream close.
+	].
     ].
 
     zipEntry compressedSize:(stream position) - startDataPosition.
@@ -4440,21 +4436,21 @@
     "Modified: / 19-11-2010 / 17:47:26 / cg"
 !
 
-basicAddFile:aFileName withContents:data compressMethod:theCompressMethodArg asDirectory:isDirectory 
+basicAddFile:aFileName withContents:data compressMethod:theCompressMethodArg asDirectory:isDirectory
     "do not create directories (isDirectory = true) - they are not compatible between operating systems"
-    
+
     | zipEntry theCompressedData theZipFileName theCompressMethod  compressedDataOffset|
 
     (stream isNil or:[ mode ~~ #write ]) ifTrue:[
-        ^ self error:'ZipArchive not open for writing ...'.
+	^ self error:'ZipArchive not open for writing ...'.
     ].
     theCompressMethod := theCompressMethodArg.
-    ((theCompressMethod ~~ COMPRESSION_DEFLATED) 
+    ((theCompressMethod ~~ COMPRESSION_DEFLATED)
       and:[theCompressMethod ~~ COMPRESSION_STORED]) ifTrue:[
-        UnsupportedZipFileFormatErrorSignal 
-            raiseRequestErrorString:'unsupported compressMethod'.
-        "/ if proceeded, write as uncompressed
-        theCompressMethod := COMPRESSION_STORED
+	UnsupportedZipFileFormatErrorSignal
+	    raiseRequestErrorString:'unsupported compressMethod'.
+	"/ if proceeded, write as uncompressed
+	theCompressMethod := COMPRESSION_STORED
     ].
 
     zipEntry := ZipMember new default.
@@ -4462,46 +4458,46 @@
     zipEntry fileName:theZipFileName.
 
     (self appendTrailingSlash and:[isDirectory]) ifTrue:[
-        theZipFileName last == $/ ifFalse:[
-            zipEntry fileName:theZipFileName , $/.
-            zipEntry fileNameLength:theZipFileName size + 1.
-        ].
+	theZipFileName last == $/ ifFalse:[
+	    zipEntry fileName:theZipFileName , $/.
+	    zipEntry fileNameLength:theZipFileName size + 1.
+	].
     ].
 
     zipEntry uncompressedSize:data size.
     isDirectory ifTrue:[
-        zipEntry externalFileAttributes:EXTERNALFILEATTRIBUTES_ISDIRECTORY.
+	zipEntry externalFileAttributes:EXTERNALFILEATTRIBUTES_ISDIRECTORY.
     ] ifFalse:[
-        zipEntry compressionMethod:theCompressMethod.        
-        zipEntry internalFileAttributes: 1.
-        zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
+	zipEntry compressionMethod:theCompressMethod.
+	zipEntry internalFileAttributes: 1.
+	zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
     ].
-    
+
     "/ data and time in msdos format
     zipEntry setModificationTimeAndDateToNow.
 
     data notEmptyOrNil ifTrue:[
-        "/ crc32 is always required (not as written in docu to be zero in case of uncompressed mode)
-        zipEntry crc32:(ZipStream crc32BytesIn:data from:1 to:data size crc:0).
+	"/ crc32 is always required (not as written in docu to be zero in case of uncompressed mode)
+	zipEntry crc32:(ZipStream crc32BytesIn:data from:1 to:data size crc:0).
     ].
     (isDirectory not and:[ theCompressMethod == COMPRESSION_DEFLATED ]) ifTrue:[
-        |tmpCompressedDataSize|
-
-        theCompressedData := ByteArray new:(data size + 16).
-        tmpCompressedDataSize := ZipStream compress:data into:theCompressedData.
-        zipEntry compressedSize:tmpCompressedDataSize - 6.
-        compressedDataOffset := 3.
+	|tmpCompressedDataSize|
+
+	theCompressedData := ByteArray new:(data size + 16).
+	tmpCompressedDataSize := ZipStream compress:data into:theCompressedData.
+	zipEntry compressedSize:tmpCompressedDataSize - 6.
+	compressedDataOffset := 3.
     ] ifFalse:["theCompressMethod == COMPRESSION_STORED"
-        zipEntry compressedSize:zipEntry uncompressedSize.
-        theCompressedData := data.
-        compressedDataOffset := 1.
+	zipEntry compressedSize:zipEntry uncompressedSize.
+	theCompressedData := data.
+	compressedDataOffset := 1.
     ].
-    
+
     "/ ensure that the file position is at the end
     stream setToEnd.
     zipEntry writeTo:stream.
     theCompressedData notNil ifTrue:[
-        stream nextPutBytes:zipEntry compressedSize from:theCompressedData startingAt:compressedDataOffset.
+	stream nextPutBytes:zipEntry compressedSize from:theCompressedData startingAt:compressedDataOffset.
     ].
     self addMember:zipEntry.
 
@@ -4526,20 +4522,20 @@
     |zipEntry theZipFileName theCompressMethod|
 
     (stream isNil or:[mode ~~ #write]) ifTrue: [
-        ^ self error: 'ZipArchive not open for writing ...'.
+	^ self error: 'ZipArchive not open for writing ...'.
     ].
 
     theCompressMethod := theCompressMethodArg.
 
-    ((theCompressMethod == COMPRESSION_DEFLATED) 
+    ((theCompressMethod == COMPRESSION_DEFLATED)
      or:[theCompressMethod == COMPRESSION_STORED]) ifFalse:[
-        UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
-        "/ if proceeded, write as uncompressed
-        theCompressMethod := COMPRESSION_STORED
+	UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
+	"/ if proceeded, write as uncompressed
+	theCompressMethod := COMPRESSION_STORED
     ].
 
     zipEntry := ZipMember new default.
-    theZipFileName := self validZipFileNameFrom:nameOfFileInArchive. 
+    theZipFileName := self validZipFileNameFrom:nameOfFileInArchive.
 
     zipEntry fileName: theZipFileName.
     zipEntry uncompressedSize: 0.
@@ -4598,7 +4594,7 @@
 
 contentsSpecies
     "return a class of which instances will be returned, when
-     parts of the collection are asked for. 
+     parts of the collection are asked for.
      (see upTo-kind of methods in Stream)"
 
     ^ compressingStream contentsSpecies
@@ -4703,9 +4699,9 @@
     centralDirectoryTotalNoOfEntries := 0.
     centralDirectorySize := 0.
     centralDirectoryStartOffset := 0.
-    zipCommentLength := 0. 
+    zipCommentLength := 0.
     zipComment := nil.
-    digitalSignatureDataSize := 0. 
+    digitalSignatureDataSize := 0.
     digitalSignatureData := nil.
 ! !
 
@@ -4719,8 +4715,8 @@
 "/        (file position + (centralDirectory digitalSignatureDataSize)) > endOfArchive ifTrue: [
 "/            ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - digital signature entry out of archive bounds'.
 "/        ].
-        digitalSignatureData := String new:digitalSignatureDataSize.
-        aStream nextBytes:digitalSignatureDataSize into:digitalSignatureData.
+	digitalSignatureData := String new:digitalSignatureDataSize.
+	aStream nextBytes:digitalSignatureDataSize into:digitalSignatureData.
     ].
 !
 
@@ -4735,8 +4731,8 @@
     centralDirectoryStartOffset := aStream nextInt32MSB:false.
     zipCommentLength := aStream nextUnsignedInt16MSB:false.
     zipCommentLength ~~ 0 ifTrue: [
-        zipComment := String new:zipCommentLength.
-        aStream nextBytes:zipCommentLength into:zipComment.
+	zipComment := String new:zipCommentLength.
+	aStream nextBytes:zipCommentLength into:zipComment.
     ].
 ! !
 
@@ -4869,7 +4865,7 @@
 
 fileNameLength
     fileNameLength isNil ifTrue:[
-        ^ fileName size.
+	^ fileName size.
     ].
     ^ fileNameLength
 !
@@ -4937,7 +4933,7 @@
 setModificationTimeAndDateToNow
     |curTime curDate|
 
-    curTime := Time now.                                                   
+    curTime := Time now.
     curDate := Date today.
     "/ data and time in msdos format
     self lastModFileTime: (ZipArchive timeToZipFileTime:curTime).
@@ -5007,9 +5003,9 @@
 !ZipArchive::ZipMember methodsFor:'queries'!
 
 isDirectory
-    ^ 
+    ^
     ((externalFileAttributes ? 0) bitTest:EXTERNALFILEATTRIBUTES_ISDIRECTORY)
-        or:[uncompressedSize == 0 and:[fileName last = $/]].
+	or:[uncompressedSize == 0 and:[fileName last = $/]].
 
     "Created: / 28-03-2011 / 19:19:26 / cg"
     "Modified: / 19-11-2012 / 12:02:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -5020,20 +5016,20 @@
 readCentralDirectoryEntryFrom:aStream
     "read a central directory entry"
 
-    versionMadeBy := aStream nextUnsignedInt16MSB:false. 
-    versionNeedToExtract := aStream nextUnsignedInt16MSB:false. 
-    generalPurposBitFlag := aStream nextUnsignedInt16MSB:false. 
+    versionMadeBy := aStream nextUnsignedInt16MSB:false.
+    versionNeedToExtract := aStream nextUnsignedInt16MSB:false.
+    generalPurposBitFlag := aStream nextUnsignedInt16MSB:false.
     compressionMethod := aStream nextUnsignedInt16MSB:false.
-    lastModFileTime := aStream nextUnsignedInt16MSB:false.   
+    lastModFileTime := aStream nextUnsignedInt16MSB:false.
     lastModFileDate := aStream nextUnsignedInt16MSB:false.
     crc32 := aStream nextUnsignedInt32MSB: false.
-    compressedSize := aStream nextUnsignedInt32MSB:false.     
-    uncompressedSize := aStream nextUnsignedInt32MSB:false.      
-    fileNameLength := aStream nextUnsignedInt16MSB:false.   
-    extraFieldLength := aStream nextUnsignedInt16MSB:false. 
-    fileCommentLength := aStream nextUnsignedInt16MSB:false. 
-    diskNumberStart := aStream nextUnsignedInt16MSB:false.  
-    internalFileAttributes := aStream nextUnsignedInt16MSB:false.   
+    compressedSize := aStream nextUnsignedInt32MSB:false.
+    uncompressedSize := aStream nextUnsignedInt32MSB:false.
+    fileNameLength := aStream nextUnsignedInt16MSB:false.
+    extraFieldLength := aStream nextUnsignedInt16MSB:false.
+    fileCommentLength := aStream nextUnsignedInt16MSB:false.
+    diskNumberStart := aStream nextUnsignedInt16MSB:false.
+    internalFileAttributes := aStream nextUnsignedInt16MSB:false.
     externalFileAttributes := aStream nextUnsignedInt32MSB:false.
     relativeLocalHeaderOffset := aStream nextUnsignedInt32MSB:false.
 
@@ -5047,16 +5043,16 @@
 "/        (aStream position + extraFieldLength) > endOfArchive ifTrue: [
 "/            ^ ZipArchive zipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
 "/        ].
-        extraField := ByteArray new:extraFieldLength.
-        aStream nextBytes:extraFieldLength into:extraField.
+	extraField := ByteArray new:extraFieldLength.
+	aStream nextBytes:extraFieldLength into:extraField.
     ].
 
     fileCommentLength ~~ 0 ifTrue: [
 "/        (aStream position + fileCommentLength) > endOfArchive ifTrue: [
 "/            ^ ZipArchive zipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
 "/        ].
-        fileComment := String new:fileCommentLength.
-        aStream nextBytes:fileCommentLength into:fileComment.
+	fileComment := String new:fileCommentLength.
+	aStream nextBytes:fileCommentLength into:fileComment.
     ].
 !
 
@@ -5065,10 +5061,10 @@
 
     aStream position:relativeLocalHeaderOffset+14.
 
-    aStream 
-        nextPutInt32:crc32 MSB:false;
-        nextPutInt32:compressedSize MSB:false;
-        nextPutInt32:uncompressedSize MSB:false.
+    aStream
+	nextPutInt32:crc32 MSB:false;
+	nextPutInt32:compressedSize MSB:false;
+	nextPutInt32:uncompressedSize MSB:false.
 !
 
 writeTo:aStream
@@ -5076,23 +5072,23 @@
 
     relativeLocalHeaderOffset := aStream position.
 
-    aStream 
-        nextPutInt32LSB:C_LOCAL_HEADER_SIGNATURE ;
-        nextPutInt16LSB:versionNeedToExtract;
-        nextPutInt16LSB:generalPurposBitFlag;
-        nextPutInt16LSB:compressionMethod;
-        nextPutInt16LSB:lastModFileTime;
-        nextPutInt16LSB:lastModFileDate;
-        nextPutInt32LSB:crc32;
-        nextPutInt32LSB:compressedSize;
-        nextPutInt32LSB:uncompressedSize;
-        nextPutInt16LSB:self fileNameLength;
-        nextPutInt16LSB:extraFieldLength;
-        nextPutAll:fileName.
+    aStream
+	nextPutInt32LSB:C_LOCAL_HEADER_SIGNATURE ;
+	nextPutInt16LSB:versionNeedToExtract;
+	nextPutInt16LSB:generalPurposBitFlag;
+	nextPutInt16LSB:compressionMethod;
+	nextPutInt16LSB:lastModFileTime;
+	nextPutInt16LSB:lastModFileDate;
+	nextPutInt32LSB:crc32;
+	nextPutInt32LSB:compressedSize;
+	nextPutInt32LSB:uncompressedSize;
+	nextPutInt16LSB:self fileNameLength;
+	nextPutInt16LSB:extraFieldLength;
+	nextPutAll:fileName.
 
     extraField notNil ifTrue: [
-        self assert:(extraField size = extraFieldLength).
-        aStream nextPutAll:extraField.
+	self assert:(extraField size = extraFieldLength).
+	aStream nextPutAll:extraField.
     ].
 
     "Modified: / 19-11-2010 / 15:45:38 / cg"
@@ -5124,10 +5120,10 @@
     readPosition := 0.
 
     zipEntry compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-        compressingStream := ZipStream readOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
+	compressingStream := ZipStream readOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
     ] ifFalse:[
-        compressingStream := zipFileStream.
-        compressingStream text.
+	compressingStream := zipFileStream.
+	compressingStream text.
     ].
 
     "Modified: / 19-11-2010 / 15:47:14 / cg"
@@ -5152,14 +5148,14 @@
     |result|
 
     peek notNil ifTrue:[
-        result := peek.
-        peek := nil.
+	result := peek.
+	peek := nil.
     ] ifFalse:[
-        readPosition >= uncompressedDataSize ifTrue:[
-            ^ self pastEndRead.        
-        ].
-
-        result := compressingStream next.
+	readPosition >= uncompressedDataSize ifTrue:[
+	    ^ self pastEndRead.
+	].
+
+	result := compressingStream next.
     ].
 
     readPosition := readPosition + 1.
@@ -5172,14 +5168,14 @@
     |result|
 
     peek notNil ifTrue:[
-        result := peek.
-        peek := nil.
+	result := peek.
+	peek := nil.
     ] ifFalse:[
-        readPosition >= uncompressedDataSize ifTrue:[
-            ^ nil.        
-        ].
-
-        result := compressingStream next.
+	readPosition >= uncompressedDataSize ifTrue:[
+	    ^ nil.
+	].
+
+	result := compressingStream next.
     ].
 
     readPosition := readPosition + 1.
@@ -5190,11 +5186,11 @@
     "peek a character"
 
     peek notNil ifTrue:[
-        ^ peek.
+	^ peek.
     ].
 
     readPosition >= uncompressedDataSize ifTrue:[
-        ^ self pastEndRead.        
+	^ self pastEndRead.
     ].
 
     peek := compressingStream next.
@@ -5207,8 +5203,8 @@
     "finalize the data"
 
     compressingStream ~~ zipFileStream ifTrue:[
-        "close ZipStream"
-        compressingStream close.
+	"close ZipStream"
+	compressingStream close.
     ].
     compressingStream := nil.
 
@@ -5236,9 +5232,9 @@
     uncompressedDataSize := 0.
 
     zipEntry compressionMethod == COMPRESSION_DEFLATED ifTrue:[
-        compressingStream := ZipStream writeOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
+	compressingStream := ZipStream writeOpenAsZipStreamOn:zipFileStream suppressHeaderAndChecksum:true.
     ] ifFalse:[
-        compressingStream := zipFileStream.
+	compressingStream := zipFileStream.
     ].
 
     "Modified: / 19-11-2010 / 15:46:57 / cg"
@@ -5315,9 +5311,9 @@
 
     size := aCollection size.
     size = 0 ifFalse:[
-        uncompressedDataSize := uncompressedDataSize + size.
-        crc32 := ZipStream crc32BytesIn:aCollection from:1 to:size crc:crc32.
-        compressingStream nextPutAll:aCollection
+	uncompressedDataSize := uncompressedDataSize + size.
+	crc32 := ZipStream crc32BytesIn:aCollection from:1 to:size crc:crc32.
+	compressingStream nextPutAll:aCollection
     ].
 ! !