SplittingWriteStream.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5462 83d68b10da13
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1999 by eXept Software AG
              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:libbasic2' }"

"{ NameSpace: Smalltalk }"

Stream subclass:#SplittingWriteStream
	instanceVariableNames:'outStream1 outStream2'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams-Misc'
!

!SplittingWriteStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1999 by eXept Software AG
              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 stream duplicator - everything written onto a splittingWriteStream
    is written to two real streams.
    Useful, if you have to send something to two files/destinations
    simultaneously, and do not want to (or cannot) buffer it.

    Especially useful, to generate a checksum, 
    while sending something to a file 
    (if one of the output streams is a checksummer).

    Also, to duplicate some output to a Transcript.
    The second stream can be closed and nilled, if no longer needed.
    
    [author:]
        Claus Gittinger (cg@exept)

    [see also:]
        WriteStream

    [instance variables:]
        outStream1      <Stream>       actual output streams
        outStream2      <Stream>

    [class variables:]
"
!

examples
"
  writes to two files simultaneously:

                                                                [exBegin]
    |s1 s2 splitter|

    s1 := '/tmp/foo1' asFilename writeStream.
    s2 := '/tmp/foo2' asFilename writeStream.
    splitter := SplittingWriteStream on:s1 and:s2.
    splitter nextPutAll:'hello world'.
    splitter close.
                                                                [exEnd]

  generates a hash on the fly:
                                                                [exBegin]
    |s1 s2 splitter hash|

    s1 := '/tmp/foo1' asFilename writeStream.
    s2 := SHA1Stream new.
    splitter := SplittingWriteStream on:s1 and:s2.
    splitter nextPutAll:'hello world'.
    splitter close.
    hash := s2 hashValue. 
    self assert:(hash = (SHA1Stream hashValueOf:'hello world'))
                                                                [exEnd]

  make the Transcript write its lines to a logging file:
                                                                [exBegin]
    |originalEntryStream fileStream splitter hash|

    originalEntryStream := Transcript entryStream.
    fileStream := 'transcript.log' asFilename writeStream.
    splitter := SplittingWriteStream on:fileStream and:originalEntryStream.
    [
        Transcript entryStream:splitter.
        1 to:10 do:[:i | Transcript nextPutLine:('line%1' bindWith:i)].
    ] ensure:[
        Transcript entryStream:originalEntryStream.
        fileStream close.
    ].
                                                                [exEnd]
"
! !

!SplittingWriteStream class methodsFor:'instance creation'!

on:stream1 and:stream2
    ^ self basicNew setOutStream1:stream1 outStream2:stream2
! !

!SplittingWriteStream methodsFor:'accessing'!

outStream1
    "return the value of the instance variable 'outStream1' (automatically generated)"

    ^ outStream1
!

outStream1:aStream
    "set the value of the instance variable 'outStream1' (automatically generated)"

    outStream1 := aStream.

    "Modified (format): / 04-11-2018 / 21:53:51 / Claus Gittinger"
!

outStream2
    "return the value of the instance variable 'outStream2' (automatically generated)"

    ^ outStream2
!

outStream2:aStreamOrNil
    "set the value of the instance variable 'outStream2' (automatically generated)"

    outStream2 := aStreamOrNil.

    "Modified (format): / 04-11-2018 / 21:54:02 / Claus Gittinger"
! !

!SplittingWriteStream methodsFor:'private access'!

setOutStream1:stream1 outStream2:stream2
    outStream1 := stream1.
    outStream2 := stream2.

! !

!SplittingWriteStream methodsFor:'redirect messages'!

doesNotUnderstand:aMessage
    "if my superclass implements the message, it can be forwarded to both streams."

    |retVal|
    
    (outStream1 class canUnderstand:aMessage selector) ifTrue:[
        retVal := aMessage sendTo:outStream1.
        outStream2 notNil ifTrue:[
            aMessage sendTo:outStream2.
        ].
        ^ retVal
    ].
    ^ super doesNotUnderstand:aMessage.

    "
        |sp s1 s2|

        s1 := TextStream on:''.
        s2 := TextStream on:''.

        sp := SplittingWriteStream on:s1 and:s2.

        sp nextPutAllText:('ABC' allBold); closeRun.
        s2 contents inspect.
    "

    "Modified: / 04-11-2018 / 21:52:43 / Claus Gittinger"
! !

!SplittingWriteStream methodsFor:'writing'!

clear
    outStream1 isStream ifFalse:[ outStream1 clear ]. 
    outStream2 notNil ifTrue:[ 
        outStream2 isStream ifFalse:[ outStream2 clear ].
    ].

    "Modified: / 04-11-2018 / 21:51:20 / Claus Gittinger"
!

close
    outStream1 close.
    outStream2 notNil ifTrue:[ 
        outStream2 close.
    ]

    "Modified: / 04-11-2018 / 21:51:29 / Claus Gittinger"
!

contents
    ^ outStream1 contents 
!

cr
    outStream1 cr.
    outStream2 notNil ifTrue:[
        outStream2 cr.
    ]

    "Created: / 12-11-2018 / 14:35:52 / Claus Gittinger"
!

endEntry
    outStream1 endEntry.
    outStream2 notNil ifTrue:[
        outStream2 endEntry.
    ]

    "Modified: / 04-11-2018 / 21:52:55 / Claus Gittinger"
!

flush
    "write out all buffered data"

    outStream1 flush.
    outStream2 notNil ifTrue:[
        outStream2 flush.
    ]

    "Modified: / 04-11-2018 / 21:53:09 / Claus Gittinger"
!

nextPut:anObject
    "append something to all of my out streams.
     Answer anObject"

    outStream1 nextPut:anObject.
    outStream2 notNil ifTrue:[
        outStream2 nextPut:anObject.
    ].
    ^ anObject

    "Modified: / 04-11-2018 / 21:53:16 / Claus Gittinger"
!

nextPutAll:aCollection
    "append all elements from aCollection into the underlying streams.
     Answer the receiver"

    outStream1 nextPutAll:aCollection.
    outStream2 notNil ifTrue:[
        outStream2 nextPutAll:aCollection.
    ]

    "Modified: / 04-11-2018 / 21:53:25 / Claus Gittinger"
!

nextPutAll:aCollection startingAt:start to:stop
    "append the elements from first index to last index
     of the argument, aCollection onto the receiver (i.e. both outstreams)"

    outStream1 nextPutAll:aCollection startingAt:start to:stop.
    outStream2 notNil ifTrue:[
        outStream2 nextPutAll:aCollection startingAt:start to:stop.
    ]

    "Modified: / 04-11-2018 / 21:53:33 / Claus Gittinger"
    "Modified (comment): / 01-04-2019 / 17:12:42 / Claus Gittinger"
!

nextPutAllUnicode:aString
    outStream1 nextPutAllUnicode:aString.
    outStream2 notNil ifTrue:[
        outStream2 nextPutAllUnicode:aString.
    ]

    "Created: / 21-09-2017 / 11:58:13 / cg"
    "Modified: / 04-11-2018 / 21:53:40 / Claus Gittinger"
!

show:something
    outStream1 show:something.
    outStream2 notNil ifTrue:[
        outStream2 show:something.
    ]

    "Created: / 12-11-2018 / 14:35:45 / Claus Gittinger"
! !

!SplittingWriteStream class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !