PeekableStream.st
changeset 21135 7a598959b48e
parent 21033 c31725b2b658
child 21242 19fabe339f8b
child 21470 a62f56072f60
equal deleted inserted replaced
21134:8afa60876626 21135:7a598959b48e
   528     "/ self halt.
   528     "/ self halt.
   529 ! !
   529 ! !
   530 
   530 
   531 !PeekableStream methodsFor:'reading'!
   531 !PeekableStream methodsFor:'reading'!
   532 
   532 
   533 nextDecimalInteger
       
   534     "read the next integer in radix 10. 
       
   535      Does NOT skip initial whitespace.
       
   536      The streams elements should be characters.
       
   537 
       
   538      Be careful - this method returns 0 if not positioned on a digit intitially
       
   539      or if the end of the stream is encountered."
       
   540 
       
   541     |nextOne value|
       
   542 
       
   543     nextOne := self peekOrNil.
       
   544     value := 0.
       
   545     [nextOne notNil and:[nextOne isDigitRadix:10]] whileTrue:[
       
   546         value := (value * 10) + nextOne digitValue.
       
   547         self next.
       
   548         nextOne := self peekOrNil
       
   549     ].
       
   550     ^ value
       
   551 
       
   552     "
       
   553      |s|
       
   554 
       
   555      s := '1234 5678' readStream.
       
   556      s nextDecimalInteger. 
       
   557     "
       
   558 
       
   559     "
       
   560      |s|
       
   561 
       
   562      s := '1234 5678' readStream.
       
   563      s nextDecimalInteger.
       
   564      s skipSpaces.
       
   565      s nextDecimalInteger. 
       
   566     "
       
   567 !
       
   568 
       
   569 nextDelimited:terminator
   533 nextDelimited:terminator
   570     "return the contents of the receiver, up to the next terminator character. 
   534     "return the contents of the receiver, up to the next terminator element. 
   571      Doubled terminators indicate an embedded terminator character.  
   535      Doubled terminators indicate an embedded terminator element.  
   572      For example: 'this '' was a quote'. 
   536      For example: 'this '' was a quote'. 
   573      Start postioned before the initial terminator."
   537      Start positioned before the initial terminator."
   574 
   538 
   575     | out ch |
   539     | out element |
   576 
   540 
   577     self atEnd ifTrue: [^ ''].
   541     self atEnd ifTrue: [^ ''].
   578     self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
   542     self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
   579     out := WriteStream on:(self contentsSpecies new).
   543     out := WriteStream on:(self contentsSpecies new).
   580     [(ch := self next) == nil] whileFalse: [
   544     [(element := self nextOrNil) isNil and:[self atEnd]] whileFalse:[
   581         (ch == terminator) ifTrue: [
   545         element == terminator ifTrue: [
   582             self peek == terminator ifFalse: [
   546             self peek == terminator ifFalse: [
   583                 ^ out contents  "terminator is not doubled; we're done!!"
   547                 ^ out contents  "terminator is not doubled; we're done!!"
   584             ].
   548             ].
   585             self next.  "skip doubled terminator"
   549             self next.  "skip doubled terminator"
   586         ].
   550         ].
   587         out nextPut: ch.
   551         out nextPut:element.
   588     ].
   552     ].
   589     ^ out contents
   553     ^ out contents
   590 
   554 
   591     "
   555     "
   592      ('*foo bar baz* more foo' readStream nextDelimited:$*) 
   556      ('*foo bar baz* more foo' readStream nextDelimited:$*) 
   692 
   656 
   693     "Created: / 5.3.1998 / 02:56:49 / cg"
   657     "Created: / 5.3.1998 / 02:56:49 / cg"
   694     "Modified: / 5.3.1998 / 13:45:07 / cg"
   658     "Modified: / 5.3.1998 / 13:45:07 / cg"
   695 !
   659 !
   696 
   660 
       
   661 skipUntil:aBlock
       
   662     "skip all elements for which aBlock returns false.
       
   663      Return true if more elements can be read, false if eof has been reached."
       
   664 
       
   665     [self atEnd] whileFalse:[
       
   666         (aBlock value: self peek) ifTrue:[^ true].
       
   667         self next
       
   668     ].
       
   669     ^ false
       
   670 
       
   671     "
       
   672      #(1 2 3 4 5 6 7 8 9 10) readStream
       
   673         skipUntil:[:el | el >= 5];
       
   674         next
       
   675     "
       
   676 !
       
   677 
       
   678 skipWhile:aBlock
       
   679     "skip all elements for which aBlock returns true. Return true if more elements can be read,
       
   680      false if eof has been reached."
       
   681 
       
   682     [self atEnd] whileFalse:[
       
   683 	(aBlock value: self peek) ifFalse:[^ true].
       
   684 	self next
       
   685     ].
       
   686     ^ false
       
   687 
       
   688     "
       
   689      #(1 2 3 4 5 6 7 8 9 10) readStream
       
   690 	skipWhile:[:el | el <= 5];
       
   691 	next
       
   692     "
       
   693 
       
   694     "Created: / 23-09-2011 / 13:32:40 / cg"
       
   695 !
       
   696 
   697 throughAnyForWhich:checkBlock
   697 throughAnyForWhich:checkBlock
   698     "read & return a collection of all objects up-to and including 
   698     "read & return a collection of all objects up-to and including 
   699      the elements for which checkBlock returns true.
   699      the elements for which checkBlock returns true.
   700      (i.e. read until checkBlock returns false on an element)
   700      (i.e. read until checkBlock returns false on an element)
   701      If no such element is encountered, all elements up to the end are read
   701      If no such element is encountered, all elements up to the end are read
   726      Transcript showCR:(s throughAnyForWhich:[:ch | ch isSeparator not]).  
   726      Transcript showCR:(s throughAnyForWhich:[:ch | ch isSeparator not]).  
   727      Transcript showCR:s upToEnd.
   727      Transcript showCR:s upToEnd.
   728     "
   728     "
   729 
   729 
   730     "Modified: / 11.1.1998 / 15:28:04 / cg"
   730     "Modified: / 11.1.1998 / 15:28:04 / cg"
       
   731 !
       
   732 
       
   733 upToAny:aCollectionOfObjects
       
   734     "read a collection of all objects up-to a element which is contained in
       
   735      aCollectionOfObjects and return these elements, but excluding the matching one.
       
   736      The next read operation will return the element AFTER anObject.
       
   737      If no such element is encountered, all elements up to the end are read
       
   738      and returned.
       
   739      Compare this with #throughAll: which also reads up to some object
       
   740      and also positions behind it, but DOES include it in the returned
       
   741      value."
       
   742 
       
   743     |result|
       
   744 
       
   745     result := self upToBeforeAny:aCollectionOfObjects.
       
   746     self atEnd ifFalse:[
       
   747         self next.
       
   748     ].
       
   749     ^ result
       
   750 
       
   751     "
       
   752      |s|
       
   753      s := ReadStream on:'hello world'.
       
   754      Transcript showCR:(s upToAny:(Array with:Character space)).
       
   755      Transcript showCR:(s upToEnd)
       
   756 
       
   757      'Makefile' asFilename readStream upToAny:($A to:$Z)
       
   758     "
       
   759 
       
   760     "Created: / 30.8.1997 / 03:02:05 / cg"
       
   761     "Modified: / 11.1.1998 / 15:19:18 / cg"
       
   762 !
       
   763 
       
   764 upToBeforeAny:aCollectionOfObjects
       
   765     "read a collection of all objects up-to a element which is contained in
       
   766      aCollectionOfObjects and return these elements, but excluding the matching one.
       
   767      The next read operation will return the matching element.
       
   768      If no such element is encountered, all elements up to the end are read
       
   769      and returned.
       
   770      This returns the exact same as upToAny: would, but leaves the stream's position so that
       
   771      the next read returns the matching delimiter instead of skipping it.
       
   772      Caveat: this is the one which should have been called upTo: in the first place;
       
   773      however, it seems now too late for a change."
       
   774 
       
   775     |answerStream element|
       
   776 
       
   777     answerStream := WriteStream on:(self contentsSpecies new).
       
   778     [self atEnd] whileFalse:[
       
   779         element := self peek.
       
   780         (aCollectionOfObjects includes:element) ifTrue: [
       
   781             ^ answerStream contents
       
   782         ].
       
   783         answerStream nextPut:element.
       
   784         self next.
       
   785     ].
       
   786     ^ answerStream contents
       
   787 
       
   788     "
       
   789      |s|
       
   790      s := ReadStream on:'hello world'.
       
   791      Transcript showCR:(s upToBeforeAny:(Array with:Character space)).
       
   792      Transcript showCR:(s upToEnd)
       
   793 
       
   794      'Make.proto' asFilename readStream upToBeforeAny:($A to:$Z)
       
   795     "
       
   796 
       
   797     "Created: / 30.8.1997 / 03:02:05 / cg"
       
   798     "Modified: / 11.1.1998 / 15:19:18 / cg"
       
   799 !
       
   800 
       
   801 upToElementForWhich:aBlock
       
   802     "read elements until aBlock returns true for an element.
       
   803      Return the collected elements excluding that element.
       
   804      Leave the stream positioned for the next read to return that element.
       
   805      If no element matches, all elements up to the end are returned"
       
   806 
       
   807     |answerStream next|
       
   808 
       
   809     answerStream := WriteStream on:(self contentsSpecies new).
       
   810 
       
   811     [
       
   812         self atEnd
       
   813         or:[ (aBlock value: (next := self peek)) ]
       
   814     ] whileFalse:[
       
   815         answerStream nextPut:next.
       
   816         self next.
       
   817     ].
       
   818     ^ answerStream contents
       
   819 
       
   820     "
       
   821      #(1 2 3 4 5 6 7 8 9 10) readStream
       
   822         upToElementForWhich:[:el | el > 5]
       
   823     "
       
   824 ! !
       
   825 
       
   826 !PeekableStream methodsFor:'reading-numbers'!
       
   827 
       
   828 nextDecimalInteger
       
   829     "read the next integer in radix 10. 
       
   830      Does NOT skip initial whitespace.
       
   831      The streams elements should be characters.
       
   832 
       
   833      Be careful - this method returns 0 if not positioned on a digit intitially
       
   834      or if the end of the stream is encountered."
       
   835 
       
   836     |nextOne value|
       
   837 
       
   838     nextOne := self peekOrNil.
       
   839     value := 0.
       
   840     [nextOne notNil and:[nextOne isDigitRadix:10]] whileTrue:[
       
   841         value := (value * 10) + nextOne digitValue.
       
   842         self next.
       
   843         nextOne := self peekOrNil
       
   844     ].
       
   845     ^ value
       
   846 
       
   847     "
       
   848      |s|
       
   849 
       
   850      s := '1234 5678' readStream.
       
   851      s nextDecimalInteger. 
       
   852     "
       
   853 
       
   854     "
       
   855      |s|
       
   856 
       
   857      s := '1234 5678' readStream.
       
   858      s nextDecimalInteger.
       
   859      s skipSpaces.
       
   860      s nextDecimalInteger. 
       
   861     "
   731 ! !
   862 ! !
   732 
   863 
   733 !PeekableStream methodsFor:'reading-strings'!
   864 !PeekableStream methodsFor:'reading-strings'!
   734 
   865 
   735 nextAlphaNumericWord
   866 nextAlphaNumericWord