FilteringStream.st
author Claus Gittinger <cg@exept.de>
Mon, 22 May 2000 13:11:30 +0200
changeset 889 b3bfa0862f55
parent 885 c31412b26306
child 955 97f0f14a61f4
permissions -rw-r--r--
added #peek

"
 COPYRIGHT (c) 1996 by Claus Gittinger
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


"{ Package: 'stx:goodies' }"

PeekableStream subclass:#FilteringStream
	instanceVariableNames:'inputStream outputStream filter readAhead'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams-Misc'
!

!FilteringStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by Claus Gittinger
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"
    A FilteringStream can be connected to some input
    (from which elements are read via the ReadStream protocol),
    and/or to some output (to which elements are written via
    the WriteStream protocol.

    The FilteringStream itself performs filtering/processing
    on the elements as they arrive, optionally suppressing
    elements.

    A FilteringStream can be operated in pull-mode, by asking
    it for the next element; it will then ask its inputStream for
    and element, process it and return it.

    Or, in pushMode, by having someone else writing elements via
    nextPut:; it will then process the element, and send it to its 
    output stream.

    Mixing modes does not make sense, since if pulled, data will not
    be written to the outputStream (unless the puller does it).

    The connected streams need not be real streams; anything which
    responds to the basic Stream protocol can be connected
    (a Transcript, a RandomNumber generator or even a Plug will do as well).

    [instance variables:]
	inputStream     <Stream>  the stream from which elements are read
	outputStream    <Stream>  the stream to which elements are written
	filter          <Block>   the filter block;
	unbound         <Boolean> if true, the stream is unbound.

    [author:]
	Claus Gittinger

    [See also:]
	ReadStream WriteStream
"

!

examples
"
  pushing the contents of a stream onto another stream
  (here, the Transcript) without a need to read everything into a
  buffer or to reinvent the read-loop:
  (notice, a FilteringLineStream does this with less overhead,
   due to the byte-wise reading done here)
                                                                [exBegin]
    |in pusher|

    in := 'Makefile' asFilename readStream.
    pusher := FilteringStream readingFrom:in writingTo:Transcript.
    pusher filterUpToEnd
                                                                [exEnd]


  filter random numbers:
                                                                [exBegin]
    |in filter|

    in := Random new.

    filter := FilteringLineStream readingFrom:in.
    filter filter:[:num | ((num >= 0.5) and:[num <= 0.6]) ifTrue:[num] ifFalse:[nil]].

    20 timesRepeat:[
        Transcript showCR:(filter next printString).
    ]
                                                                [exEnd]

  filtering prime numbers:
                                                                [exBegin]
    |num generator primeFilter addFilter|

    num := 1.
    generator := Plug new.
    generator respondTo:#next
                   with:[num := num + 1. num].
    generator respondTo:#atEnd
                   with:[false].

    addFilter := [:prime | |newFilter|
        newFilter := FilteringStream basicNew.
        newFilter filter:[:num | (num \\ prime) == 0 ifTrue:[
                                    nil
                                 ] ifFalse:[
                                    num
                                 ]
                         ].
        newFilter inputStream:primeFilter.
        primeFilter := newFilter
    ].

    addFilter value:2.
    primeFilter inputStream:generator.

    10000 timesRepeat:[
        |nextPrime|

        nextPrime := primeFilter next.
        addFilter value:nextPrime.
        Transcript showCR:nextPrime.
    ]
                                                                [exEnd]
"



! !

!FilteringStream class methodsFor:'instance creation'!

new
    "create and return a new filteringStream.
     The resulting stream must be connected to some other stream,
     before being used"

    ^ self basicNew initialize.

    "Created: 11.1.1997 / 15:31:30 / cg"
    "Modified: 11.1.1997 / 15:33:13 / cg"
!

on:something
    "create and return a new filteringStream, which reads from
     something (which must be convertable to a stream)"

    ^ self readingFrom:something readStream

    "Created: 11.1.1997 / 19:19:34 / cg"
!

readingFrom:aReadStream
    "create and return a new filteringStream, which reads from
     another stream"

    ^ self basicNew initialize inputStream:aReadStream.

    "Created: 11.1.1997 / 15:32:15 / cg"
!

readingFrom:aReadStream writingTo:aWriteStream
    "create and return a new filteringStream, which reads from
     aReadStream and writes to aWriteStream."

    |newStream|

    newStream := self basicNew initialize.
    newStream inputStream:aReadStream.
    newStream outputStream:aWriteStream.
    ^ newStream

    "Created: 11.1.1997 / 15:32:28 / cg"
!

writingTo:aWriteStream
    "create and return a new filteringStream, which writes to
     another stream"

    ^ self basicNew initialize outputStream:aWriteStream.

    "Created: 11.1.1997 / 15:32:36 / cg"
! !

!FilteringStream methodsFor:'access - pull-reading'!

filterUpToEnd
    "pull input from inputStream up to the end,
     push it filtered into the outputStream."

    [inputStream atEnd] whileFalse:[
	self nextPut:(inputStream next)
    ].

    "Created: 2.7.1996 / 21:06:42 / cg"
    "Modified: 11.1.1997 / 16:08:35 / cg"
!

next
    "pull input from inputStream and
     push it filtered into the outputStream"

    |input output|

    "/ readAhead input has already been filtered
    "/ (see #atEnd)

    readAhead notNil ifTrue:[
	input := readAhead.
	readAhead := nil.
	^ input
    ].

    [inputStream atEnd] whileFalse:[
	"/ get an element
	input := inputStream next.
	filter isNil ifTrue:[
	    ^ input
	].

	"/ filter it - this may return nil, to eat it
	output := filter value:input.
	output notNil ifTrue:[
	    "/ good - output it
	    ^ output.
	].
    ].
    ^ nil

    "Created: 2.7.1996 / 21:09:58 / cg"
    "Modified: 11.1.1997 / 17:17:27 / cg"
!

peek
    "peek ahead for the next character"

    |input output|

    readAhead notNil ifTrue:[
        ^ readAhead
    ].

    [inputStream atEnd] whileFalse:[
        "/ get an element
        input := inputStream peek.
        filter isNil ifTrue:[
            ^ input
        ].

        "/ filter it - this may return nil, to eat it
        inputStream next.
        output := filter value:input.
        output notNil ifTrue:[
            "/ good - output it
            readAhead := output.
            ^ output.
        ].
    ].
    ^ self pastEnd

!

peekOrNil
    "peek ahead for the next character, or return nil"

    |input output|

    readAhead notNil ifTrue:[
        ^ readAhead
    ].

    [inputStream atEnd] whileFalse:[
        "/ get an element
        input := inputStream peek.
        filter isNil ifTrue:[
            ^ input
        ].

        "/ filter it - this may return nil, to eat it
        inputStream next.
        output := filter value:input.
        output notNil ifTrue:[
            "/ good - output it
            readAhead := output.
            ^ output.
        ].
    ].
    ^ nil
! !

!FilteringStream methodsFor:'access - push-writing'!

nextPut:something
    "push something through the filter"

    |output|

    "/ filter it
    filter isNil ifTrue:[
	outputStream nextPut:something
    ] ifFalse:[
	output := filter value:something.
	output notNil ifTrue:[
	    outputStream nextPut:output
	]
    ]

    "Modified: 11.1.1997 / 16:12:52 / cg"
! !

!FilteringStream methodsFor:'accessing'!

filter
    "return the filter"

    ^ filter

    "Modified: 2.7.1996 / 21:03:36 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
!

filter:something
    "set the filter"

    filter := something.

    "Modified: 2.7.1996 / 21:03:40 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
!

inputStream
    "return the inputStream"

    ^ inputStream

    "Modified: 2.7.1996 / 21:03:43 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
!

inputStream:something
    "set the inputStream"

    inputStream := something.

    "Modified: 2.7.1996 / 21:03:46 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
!

outputStream
    "return the outputStream"

    ^ outputStream

    "Modified: 2.7.1996 / 21:03:49 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
!

outputStream:something
    "set the outputStream"

    outputStream := something.

    "Modified: 2.7.1996 / 21:03:52 / cg"
    "Created: 2.7.1996 / 21:06:42 / cg"
! !

!FilteringStream methodsFor:'misc'!

close
    "when I am closed, close my input - if any"

    inputStream notNil ifTrue:[
	inputStream close
    ]

    "Created: 11.1.1997 / 15:27:17 / cg"
! !

!FilteringStream methodsFor:'queries'!

atEnd
    "return true, if the receiver stream is at the end"

    |nextElement|

    readAhead notNil ifTrue:[^ false].

    filter isNil ifTrue:[
	"/ then, its easy
	^ inputStream atEnd
    ].

    "/ with a filter, things are more complicated, 
    "/ since we cannot tell, without asking the filter ...


    [inputStream atEnd] whileFalse:[
	nextElement := inputStream next.
	readAhead := filter value:nextElement.
	readAhead notNil ifTrue:[^ false].
    ].

    ^ true

    "Modified: 11.1.1997 / 17:16:45 / cg"
!

contentsSpecies
    "return the kind of collection I should return when asked
     for multiple elements."

    ^ inputStream contentsSpecies

    "Created: 11.1.1997 / 16:23:22 / cg"
! !

!FilteringStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/FilteringStream.st,v 1.7 2000-05-22 11:11:30 cg Exp $'
! !