#BUGFIX by stefan
authorStefan Vogel <sv@exept.de>
Wed, 10 Jan 2018 23:57:44 +0100
changeset 22416 3d6e05b588a1
parent 22415 769a6b3f0a19
child 22417 20114bc54506
#BUGFIX by stefan Fix methods for use with EncodedStream returning 16-bit Characters class: PeekableStream added: #upToMatching: #upToSeparator comment/format in: #nextUpTo: #throughAnyForWhich: #upToBeforeAny: #upToElementForWhich: changed: #nextAlphaNumericWord #nextDelimited: category of: #nextDelimited:
PeekableStream.st
--- a/PeekableStream.st	Wed Jan 10 23:01:58 2018 +0100
+++ b/PeekableStream.st	Wed Jan 10 23:57:44 2018 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
 	      All Rights Reserved
@@ -718,34 +720,6 @@
 
 !PeekableStream methodsFor:'reading'!
 
-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."
-
-    | out element |
-
-    self atEnd ifTrue: [^ ''].
-    self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
-    out := WriteStream on:(self contentsSpecies new).
-    [(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:element.
-    ].
-    ^ out contents
-
-    "
-     ('*foo bar baz* more foo' readStream nextDelimited:$*) 
-     ('*foo bar **baz***' readStream nextDelimited:$*)   
-    "
-!
-
 nextPeek
     "advance to next element and return the peeked element"
 
@@ -768,16 +742,11 @@
      and returned, and the stream is positioned at the end.
      Compare this with #upTo: which positions behind anObject"
 
-    |answerStream element|
+    |answerStream|
 
-    answerStream := WriteStream on:(self contentsSpecies new).
-    [self atEnd] whileFalse:[
-	element := self peek.
-	(element = anObject) ifTrue: [
-	    ^ answerStream contents
-	].
-	answerStream nextPut:element.
-	self next.
+    answerStream := self contentsSpecies writeStream.
+    [self atEnd or:[anObject = self peek]] whileFalse:[
+        answerStream nextPut:self next.
     ].
     ^ answerStream contents
 
@@ -803,8 +772,8 @@
      Transcript showCR:s next
     "
 
-    "Created: 24.1.1997 / 14:08:35 / cg"
-    "Modified: 24.1.1997 / 14:09:49 / cg"
+    "Created: / 24-01-1997 / 14:08:35 / cg"
+    "Modified: / 10-01-2018 / 18:29:47 / stefan"
 !
 
 peek 
@@ -889,23 +858,18 @@
      If no such element is encountered, all elements up to the end are read
      and returned."
 
-    |answerStream element|
+    |answerStream|
 
-    answerStream := WriteStream on:(self contentsSpecies new).
-    [self atEnd] whileFalse:[
-        element := self peek.
-        (checkBlock value:element) ifFalse:[
-            ^ answerStream contents
-        ].
-        answerStream nextPut:element.
-        self next.
+    answerStream := self contentsSpecies writeStream.
+    [self atEnd or:[(checkBlock value:self peek) not]] whileFalse:[
+        answerStream nextPut:self next.
     ].
     ^ answerStream contents
 
     "
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s throughAny:#(3 4 5)).  
+     Transcript showCR:(s throughAnyForWhich:[:e| e <= 4]).  
      Transcript showCR:s next
 
      |s|
@@ -915,7 +879,9 @@
      Transcript showCR:s upToEnd.
     "
 
-    "Modified: / 11.1.1998 / 15:28:04 / cg"
+    "Modified: / 11-01-1998 / 15:28:04 / cg"
+    "Modified: / 10-01-2018 / 18:29:51 / stefan"
+    "Modified (comment): / 10-01-2018 / 23:18:08 / stefan"
 !
 
 upToAny:aCollectionOfObjects
@@ -960,16 +926,11 @@
      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|
 
-    answerStream := WriteStream on:(self contentsSpecies new).
-    [self atEnd] whileFalse:[
-        element := self peek.
-        (aCollectionOfObjects includes:element) ifTrue: [
-            ^ answerStream contents
-        ].
-        answerStream nextPut:element.
-        self next.
+    answerStream := self contentsSpecies writeStream.
+    [self atEnd or:[aCollectionOfObjects includes:self peek]] whileFalse:[
+        answerStream nextPut:self next.
     ].
     ^ answerStream contents
 
@@ -982,8 +943,9 @@
      'Make.proto' asFilename readStream upToBeforeAny:($A to:$Z)
     "
 
-    "Created: / 30.8.1997 / 03:02:05 / cg"
-    "Modified: / 11.1.1998 / 15:19:18 / cg"
+    "Created: / 30-08-1997 / 03:02:05 / cg"
+    "Modified: / 11-01-1998 / 15:19:18 / cg"
+    "Modified: / 10-01-2018 / 18:29:57 / stefan"
 !
 
 upToElementForWhich:aBlock
@@ -992,16 +954,11 @@
      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).
+    |answerStream|
 
-    [
-        self atEnd
-        or:[ (aBlock value: (next := self peek)) ]
-    ] whileFalse:[
-        answerStream nextPut:next.
-        self next.
+    answerStream := self contentsSpecies writeStream.
+    [self atEnd or:[aBlock value:self peek]] whileFalse:[
+        answerStream nextPut:self next.
     ].
     ^ answerStream contents
 
@@ -1009,6 +966,58 @@
      #(1 2 3 4 5 6 7 8 9 10) readStream
         upToElementForWhich:[:el | el > 5]
     "
+
+    "Modified: / 10-01-2018 / 18:30:03 / stefan"
+!
+
+upToMatching:aBlock
+    "Return the next elements up to but not including the next element
+     for which aBlock returns true.
+     The next read will return that matching element.
+     If none matches, the remaining elements up to the end are returned."
+
+    ^ self upToElementForWhich:aBlock
+
+    "
+     'hello world' readStream upToMatching:[:c | c isSeparator].
+    "
+    "
+     'helloworld' readStream upToMatching:[:c | c isSeparator].
+    "
+    "
+     |s|
+
+     s := 'hello world' readStream.
+     s upToMatching:[:c | c isSeparator].
+     s upToEnd
+    "
+
+    "Modified: / 26-02-1997 / 12:20:57 / cg"
+    "Modified (comment): / 10-01-2018 / 23:20:32 / stefan"
+!
+
+upToSeparator
+    "Return the next elements up to but not including the next separator.
+     The next read will return the separator.
+     If no separator is encountered, the contents up to the end is returned.
+     The elements are supposed to understand #isSeparator
+     (i.e. the receiver is supposed to be a character-stream)."
+
+    ^ self upToElementForWhich:[:ch | ch isSeparator]
+
+    "
+     'hello world' readStream upToSeparator
+     'helloworld' readStream upToSeparator
+     'helloworld' readStream upToSeparator
+     '' readStream upToSeparator
+
+     |s|
+     s := 'hello world' readStream.
+     s upToSeparator.
+     s upToEnd
+    "
+
+    "Modified: 4.1.1997 / 23:38:05 / cg"
 ! !
 
 !PeekableStream methodsFor:'reading-numbers'!
@@ -1073,8 +1082,7 @@
     ] whileFalse.
 
     "second: get the alphanumeric word"
-    s := WriteStream on:(self contentsSpecies new:100).
-
+    s := self contentsSpecies writeStream:100.
     [
         s nextPut:c.
         c := self peekOrNil.
@@ -1102,13 +1110,44 @@
     "
      |s|
 
-     s := 'hello +++ #world ###123###abc### 1234 foo1 foo2++++' asUnicodeString readStream.
+     s := 'hello +++ #world привiт ###123###abc### 1234 foo1 foo2++++' asUnicodeString readStream.
      [s atEnd] whileFalse:[
         Transcript showCR:(s nextAlphaNumericWord).
      ].
     "
 
-    "Modified: 15.5.1996 / 17:51:42 / cg"
+    "Modified: / 15-05-1996 / 17:51:42 / cg"
+    "Modified: / 10-01-2018 / 18:34:42 / stefan"
+!
+
+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."
+
+    | out element |
+
+    self atEnd ifTrue: [^ ''].
+    self peek = terminator ifTrue: [self next].       "absorb initial terminator"
+    out := self contentsSpecies writeStream.
+    [(element := self nextOrNil) isNil and:[self atEnd]] whileFalse:[
+        element = terminator ifTrue: [
+            self peek ~= terminator ifTrue: [
+                ^ out contents  "terminator is not doubled; we're done!!"
+            ].
+            self next.  "skip doubled terminator"
+        ].
+        out nextPut:element.
+    ].
+    ^ out contents
+
+    "
+     ('*foo bar baz* more foo' readStream nextDelimited:$*) 
+     ('*foo bar **baz***' readStream nextDelimited:$*)   
+    "
+
+    "Modified: / 10-01-2018 / 18:29:42 / stefan"
 !
 
 nextMatching:matchBlock1 thenMatching:matchBlock2