TextStream.st
author Claus Gittinger <cg@exept.de>
Tue, 26 Feb 2008 11:29:14 +0100
changeset 1930 935b2870be2e
parent 1899 b856899327a9
child 1941 3f0b0b5df9ab
permissions -rw-r--r--
arrow points reusable (class protocol)

"
 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:libbasic2' }"

WriteStream subclass:#TextStream
	instanceVariableNames:'runs currentEmphasis'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams'
!

!TextStream 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 textStream is much like a regular writeStream;
    however, in addition to collecting characters, it keeps
    track of any change of the emphasis, and returns a Text instance
    as its contents (in contrast to a String instance).
    Can be used to collect up attributed text.

    [author:]
        Claus Gittinger

    [see also:]
        WriteStream
        Text String
"

!

examples
"
                                                                [exBegin]
     |s|

     s := TextStream on:''.
     s emphasis:#italic;
       nextPutAll:'hello';
       emphasis:nil;
       space;
       emphasis:#bold;
       nextPutAll:'world'.
     s contents inspect
                                                                [exEnd]

                                                                [exBegin]
     |s|

     s := TextStream on:''.
     s emphasis:#italic;
       nextPutAll:'hello';
       emphasis:nil;
       space;
       emphasis:#bold;
       nextPutAll:'world'.

     Transcript nextPutAll:(s contents)
                                                                [exEnd]

                                                                [exBegin]
     |s|

     s := TextStream on:''.
     s emphasis:#italic;
       nextPutAll:'hello';
       emphasis:nil;
       space;
       emphasis:#bold;
       nextPutAll:'world'.

     Dialog
        warn:(s contents)
                                                                [exEnd]

                                                                [exBegin]
     |s1 s2 flipFlop|

     s1 := PipeStream readingFrom:'ls -l'.
     s2 := TextStream on:''.

     flipFlop := true.
     [s1 atEnd] whileFalse:[
        flipFlop ifTrue:[
            s2 emphasis:(#color->Color red)
        ] ifFalse:[
            s2 emphasis:nil
        ].
        flipFlop := flipFlop not.
        s2 nextPutAll:(s1 nextLine).
        s2 cr.
     ].
     s1 close.

     (EditTextView new contents:s2 contents) open
                                                                [exEnd]
"
! !

!TextStream methodsFor:'accessing'!

contents
    "return the streams collected contents"

    self closeRun.
    ^ Text string:super contents emphasisCollection:runs

    "
     |s|

     s := TextStream on:String new.
     s emphasis:#italic.
     s nextPutAll:'hello'.
     s emphasis:nil.
     s space.
     s emphasis:#bold.
     s nextPutAll:'world'.
     s contents
    "
!

emphasis
    "return the current emphasis"

    ^ currentEmphasis 
!

emphasis:newEmphasis
    "change the emphasis; all followup elements are appended with
     that emphasis in effect"

    position ~~ ZeroPosition ifTrue:[
        currentEmphasis ~= newEmphasis ifTrue:[
            self closeRun.
        ]
    ].
    currentEmphasis := newEmphasis

    "
     |s|

     s := TextStream on:String new.
     s emphasis:#italic;
       nextPutAll:'hello';
       emphasis:nil;
       space;
       emphasis:#bold;
       nextPutAll:'world'.
     s contents.
     Transcript showCr:s contents.
    "

    "Modified: / 15-10-2007 / 16:27:31 / cg"
!

stringContents
    "return the streams collected string contents"

    ^ super contents

! !

!TextStream methodsFor:'private'!

closeRun
    position ~~ ZeroPosition ifTrue:[
        runs isNil ifTrue:[
            runs := RunArray new:position-ZeroPosition withAll:currentEmphasis
        ] ifFalse:[
            runs add:currentEmphasis withOccurrences:(position-ZeroPosition-runs size)
        ]
    ]
! !

!TextStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/TextStream.st,v 1.9 2007-10-15 14:26:15 cg Exp $'
! !