PeekableStream.st
changeset 21135 7a598959b48e
parent 21033 c31725b2b658
child 21242 19fabe339f8b
child 21470 a62f56072f60
--- a/PeekableStream.st	Thu Dec 15 13:55:14 2016 +0100
+++ b/PeekableStream.st	Thu Dec 15 13:57:09 2016 +0100
@@ -530,61 +530,25 @@
 
 !PeekableStream methodsFor:'reading'!
 
-nextDecimalInteger
-    "read the next integer in radix 10. 
-     Does NOT skip initial whitespace.
-     The streams elements should be characters.
-
-     Be careful - this method returns 0 if not positioned on a digit intitially
-     or if the end of the stream is encountered."
-
-    |nextOne value|
-
-    nextOne := self peekOrNil.
-    value := 0.
-    [nextOne notNil and:[nextOne isDigitRadix:10]] whileTrue:[
-        value := (value * 10) + nextOne digitValue.
-        self next.
-        nextOne := self peekOrNil
-    ].
-    ^ value
-
-    "
-     |s|
+nextDelimited:terminator
+    "return the contents of the receiver, up to the next terminator element. 
+     Doubled terminators indicate an embedded terminator element.  
+     For example: 'this '' was a quote'. 
+     Start positioned before the initial terminator."
 
-     s := '1234 5678' readStream.
-     s nextDecimalInteger. 
-    "
-
-    "
-     |s|
-
-     s := '1234 5678' readStream.
-     s nextDecimalInteger.
-     s skipSpaces.
-     s nextDecimalInteger. 
-    "
-!
-
-nextDelimited:terminator
-    "return the contents of the receiver, up to the next terminator character. 
-     Doubled terminators indicate an embedded terminator character.  
-     For example: 'this '' was a quote'. 
-     Start postioned before the initial terminator."
-
-    | out ch |
+    | out element |
 
     self atEnd ifTrue: [^ ''].
     self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
     out := WriteStream on:(self contentsSpecies new).
-    [(ch := self next) == nil] whileFalse: [
-        (ch == terminator) ifTrue: [
+    [(element := self nextOrNil) isNil and:[self atEnd]] whileFalse:[
+        element == terminator ifTrue: [
             self peek == terminator ifFalse: [
                 ^ out contents  "terminator is not doubled; we're done!!"
             ].
             self next.  "skip doubled terminator"
         ].
-        out nextPut: ch.
+        out nextPut:element.
     ].
     ^ out contents
 
@@ -694,6 +658,42 @@
     "Modified: / 5.3.1998 / 13:45:07 / cg"
 !
 
+skipUntil:aBlock
+    "skip all elements for which aBlock returns false.
+     Return true if more elements can be read, false if eof has been reached."
+
+    [self atEnd] whileFalse:[
+        (aBlock value: self peek) ifTrue:[^ true].
+        self next
+    ].
+    ^ false
+
+    "
+     #(1 2 3 4 5 6 7 8 9 10) readStream
+        skipUntil:[:el | el >= 5];
+        next
+    "
+!
+
+skipWhile:aBlock
+    "skip all elements for which aBlock returns true. Return true if more elements can be read,
+     false if eof has been reached."
+
+    [self atEnd] whileFalse:[
+	(aBlock value: self peek) ifFalse:[^ true].
+	self next
+    ].
+    ^ false
+
+    "
+     #(1 2 3 4 5 6 7 8 9 10) readStream
+	skipWhile:[:el | el <= 5];
+	next
+    "
+
+    "Created: / 23-09-2011 / 13:32:40 / cg"
+!
+
 throughAnyForWhich:checkBlock
     "read & return a collection of all objects up-to and including 
      the elements for which checkBlock returns true.
@@ -728,6 +728,137 @@
     "
 
     "Modified: / 11.1.1998 / 15:28:04 / cg"
+!
+
+upToAny:aCollectionOfObjects
+    "read a collection of all objects up-to a element which is contained in
+     aCollectionOfObjects and return these elements, but excluding the matching one.
+     The next read operation will return the element AFTER anObject.
+     If no such element is encountered, all elements up to the end are read
+     and returned.
+     Compare this with #throughAll: which also reads up to some object
+     and also positions behind it, but DOES include it in the returned
+     value."
+
+    |result|
+
+    result := self upToBeforeAny:aCollectionOfObjects.
+    self atEnd ifFalse:[
+        self next.
+    ].
+    ^ result
+
+    "
+     |s|
+     s := ReadStream on:'hello world'.
+     Transcript showCR:(s upToAny:(Array with:Character space)).
+     Transcript showCR:(s upToEnd)
+
+     'Makefile' asFilename readStream upToAny:($A to:$Z)
+    "
+
+    "Created: / 30.8.1997 / 03:02:05 / cg"
+    "Modified: / 11.1.1998 / 15:19:18 / cg"
+!
+
+upToBeforeAny:aCollectionOfObjects
+    "read a collection of all objects up-to a element which is contained in
+     aCollectionOfObjects and return these elements, but excluding the matching one.
+     The next read operation will return the matching element.
+     If no such element is encountered, all elements up to the end are read
+     and returned.
+     This returns the exact same as upToAny: would, but leaves the stream's position so that
+     the next read returns the matching delimiter instead of skipping it.
+     Caveat: this is the one which should have been called upTo: in the first place;
+     however, it seems now too late for a change."
+
+    |answerStream element|
+
+    answerStream := WriteStream on:(self contentsSpecies new).
+    [self atEnd] whileFalse:[
+        element := self peek.
+        (aCollectionOfObjects includes:element) ifTrue: [
+            ^ answerStream contents
+        ].
+        answerStream nextPut:element.
+        self next.
+    ].
+    ^ answerStream contents
+
+    "
+     |s|
+     s := ReadStream on:'hello world'.
+     Transcript showCR:(s upToBeforeAny:(Array with:Character space)).
+     Transcript showCR:(s upToEnd)
+
+     'Make.proto' asFilename readStream upToBeforeAny:($A to:$Z)
+    "
+
+    "Created: / 30.8.1997 / 03:02:05 / cg"
+    "Modified: / 11.1.1998 / 15:19:18 / cg"
+!
+
+upToElementForWhich:aBlock
+    "read elements until aBlock returns true for an element.
+     Return the collected elements excluding that element.
+     Leave the stream positioned for the next read to return that element.
+     If no element matches, all elements up to the end are returned"
+
+    |answerStream next|
+
+    answerStream := WriteStream on:(self contentsSpecies new).
+
+    [
+        self atEnd
+        or:[ (aBlock value: (next := self peek)) ]
+    ] whileFalse:[
+        answerStream nextPut:next.
+        self next.
+    ].
+    ^ answerStream contents
+
+    "
+     #(1 2 3 4 5 6 7 8 9 10) readStream
+        upToElementForWhich:[:el | el > 5]
+    "
+! !
+
+!PeekableStream methodsFor:'reading-numbers'!
+
+nextDecimalInteger
+    "read the next integer in radix 10. 
+     Does NOT skip initial whitespace.
+     The streams elements should be characters.
+
+     Be careful - this method returns 0 if not positioned on a digit intitially
+     or if the end of the stream is encountered."
+
+    |nextOne value|
+
+    nextOne := self peekOrNil.
+    value := 0.
+    [nextOne notNil and:[nextOne isDigitRadix:10]] whileTrue:[
+        value := (value * 10) + nextOne digitValue.
+        self next.
+        nextOne := self peekOrNil
+    ].
+    ^ value
+
+    "
+     |s|
+
+     s := '1234 5678' readStream.
+     s nextDecimalInteger. 
+    "
+
+    "
+     |s|
+
+     s := '1234 5678' readStream.
+     s nextDecimalInteger.
+     s skipSpaces.
+     s nextDecimalInteger. 
+    "
 ! !
 
 !PeekableStream methodsFor:'reading-strings'!