NonPositionableExternalStream.st
branchjv
changeset 18120 e3a375d5f6a8
parent 18117 eb433f2c42b2
parent 17642 5988beff84f7
child 18315 e678ab267382
--- a/NonPositionableExternalStream.st	Tue Feb 04 21:09:59 2014 +0100
+++ b/NonPositionableExternalStream.st	Wed Apr 01 10:20:10 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -11,6 +13,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 ExternalStream subclass:#NonPositionableExternalStream
 	instanceVariableNames:''
 	classVariableNames:'StdInStream StdOutStream StdErrorStream'
@@ -154,16 +158,16 @@
 
     pipe := OperatingSystem makePipe.
     pipe isNil ifTrue:[
-        "/ ok, maybe someone has forgotten to close a stream; enforce finalization and try again
-        'makePipe: enforcing finalization to close any open streams' infoPrintCR.
-        ObjectMemory garbageCollect; finalize.
-        pipe := OperatingSystem makePipe.
+	"/ ok, maybe someone has forgotten to close a stream; enforce finalization and try again
+	'makePipe: enforcing finalization to close any open streams' infoPrintCR.
+	ObjectMemory garbageCollect; finalize.
+	pipe := OperatingSystem makePipe.
     ].
 
     pipe notNil ifTrue:[
-        rs := self forFileDescriptor:(pipe at:1) mode:#readonly buffered:false handleType:#pipeFilePointer.
-        ws := self forFileDescriptor:(pipe at:2) mode:#writeonly buffered:false handleType:#pipeFilePointer.
-        ^ Array with:rs with:ws
+	rs := self forFileDescriptor:(pipe at:1) mode:#readonly buffered:false handleType:#pipeFilePointer.
+	ws := self forFileDescriptor:(pipe at:2) mode:#writeonly buffered:false handleType:#pipeFilePointer.
+	^ Array with:rs with:ws
     ].
     ^ nil
 
@@ -176,24 +180,34 @@
 
      'read ...'.
      [
-         1 to:10 do:[:i |
-             Transcript showCR:rs nextLine
-         ].
-         rs close.
+	 1 to:10 do:[:i |
+	     Transcript showCR:rs nextLine
+	 ].
+	 rs close.
      ] forkAt:7.
 
      'write ...'.
      [
-         1 to:10 do:[:i |
-             ws nextPutAll:'hello world '; nextPutAll:i printString; cr
-         ].
-         ws close.
+	 1 to:10 do:[:i |
+	     ws nextPutAll:'hello world '; nextPutAll:i printString; cr
+	 ].
+	 ws close.
      ] fork.
     "
 
     "Modified: 29.2.1996 / 18:28:36 / cg"
 ! !
 
+!NonPositionableExternalStream methodsFor:'accessing'!
+
+buffered:aBoolean
+    "do not allow to change to buffered mode - ignore true here"
+
+    aBoolean ifFalse:[
+	super buffered:false.
+    ].
+! !
+
 !NonPositionableExternalStream methodsFor:'error handling'!
 
 positionError
@@ -211,7 +225,7 @@
 !NonPositionableExternalStream methodsFor:'initialization'!
 
 initialize
-    "non-positionalble streams do now work well when buffered"
+    "non-positionable streams do not work well when buffered"
 
     super initialize.
     buffered := false.
@@ -273,65 +287,14 @@
     "skip count bytes/characters, return the receiver.
      Re-redefined since PositionableStream redefined it."
 
-    "dont know how to unread ..."
+    "don't know how to unread ..."
     numberToSkip < 0 ifTrue:[
 	PositionError raiseRequest.
 	^ self
     ].
-    numberToSkip timesRepeat:self next
+    numberToSkip timesRepeat:[self next].
 
     "Modified: / 30.7.1999 / 12:42:12 / cg"
-!
-
-skipThroughAll:aCollection
-    "skip for and through the sequence given by the argument, aCollection;
-     return nil if not found, the receiver otherwise.
-     On a successful match, the next read will return elements after aCollection;
-     if no match was found, the receiver will be positioned at the end.
-     Redefined to be the same as Stream>>#skipThroughAll, to undo
-     the redefinition from PositionableStream"
-
-    |buffer l first idx|
-
-    l := aCollection size.
-    first := aCollection at:1.
-    [self atEnd] whileFalse:[
-	buffer isNil ifTrue:[
-	    buffer := self nextAvailable:l.
-	].
-	buffer = aCollection ifTrue:[
-	    ^ self
-	].
-	idx := buffer indexOf:first startingAt:2.
-	idx == 0 ifTrue:[
-	    buffer := nil
-	] ifFalse:[
-	    buffer := (buffer copyFrom:idx) , (self nextAvailable:(idx - 1))
-	]
-    ].
-    ^ nil
-
-    "
-     |s|
-     s := ReadStream on:'12345678901234567890'.
-     s skipThroughAll:'901'.
-     s upToEnd
-    "
-    "
-     |s|
-     s := ReadStream on:'12345678901234567890'.
-     s skipThroughAll:'1234'.
-     s upToEnd
-    "
-    "
-     |s|
-     s := ReadStream on:'12345678901234567890'.
-     s skipThroughAll:'999'.
-     s atEnd
-    "
-
-    "Modified: / 11.1.1997 / 19:09:06 / cg"
-    "Created: / 15.1.1998 / 23:33:37 / stefan"
 ! !
 
 !NonPositionableExternalStream methodsFor:'printing & storing'!
@@ -431,7 +394,7 @@
     handle := self handleForStderr.
     handleType := #filePointer.
     OperatingSystem isMSWINDOWSlike ifTrue:[
-        eolMode := #crlf
+	eolMode := #crlf
     ]
 !
 
@@ -457,7 +420,7 @@
     handle := self handleForStdout.
     handleType := #filePointer.
     OperatingSystem isMSWINDOWSlike ifTrue:[
-        eolMode := #crlf
+	eolMode := #crlf
     ]
 !
 
@@ -497,12 +460,24 @@
     ^ super atEnd.
 !
 
+collectionSize
+    "we do not know our size"
+
+    ^ self positionError
+!
+
 isPositionable
     "return true, if the stream supports positioning (this one is not)"
 
     ^ false
 !
 
+remainingSize
+    "we do not know our size"
+
+    ^ self positionError
+!
+
 size
     "we do not know our size"
 
@@ -560,21 +535,45 @@
 
 !NonPositionableExternalStream methodsFor:'writing'!
 
+nextPutAll:aCollection
+    "nextPutBytes handles non-blocking io in receiver"
+
+    self nextPutBytes:aCollection size from:aCollection startingAt:1.
+    ^ self.
+!
+
+nextPutAll:aCollection startingAt:start to:stop
+    "redefined, to wait until stream is writable, to avoid blocking in a write"
+
+    |count|
+
+    count := stop-start+1.
+    count ~= (self nextPutBytes:count from:aCollection startingAt:start) ifTrue:[
+        "incomplete write"    
+        self writeError.
+    ].
+!
+
 nextPutBytes:initialWriteCount from:buffer startingAt:initialOffset
     "redefined, to wait until stream is writable, to avoid blocking in a write"
 
-    |count offset remaining wasBlocking|
+    |offset remaining wasBlocking|
 
     offset := initialOffset.
     remaining := initialWriteCount.
 
     wasBlocking := self blocking:false.
     [remaining ~~ 0] whileTrue:[
+        |count|
+
         count := super nextPutBytes:remaining from:buffer startingAt:offset.
-        count ~~ remaining ifTrue:[ "Transcript showCR:'writeWait'. "self writeWait. ].
 
         remaining := remaining - count.
         offset := offset + count.
+        remaining ~~ 0 ifTrue:[ 
+            "Transcript showCR:'writeWait'." 
+            self writeWait.
+        ].
     ].
     wasBlocking ifTrue:[self blocking:true].
 
@@ -584,10 +583,10 @@
 !NonPositionableExternalStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NonPositionableExternalStream.st,v 1.67 2014-01-30 16:41:04 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NonPositionableExternalStream.st,v 1.73 2015-03-24 16:17:21 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/NonPositionableExternalStream.st,v 1.67 2014-01-30 16:41:04 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NonPositionableExternalStream.st,v 1.73 2015-03-24 16:17:21 stefan Exp $'
 ! !