TextColl.st
author claus
Mon, 20 Dec 1993 18:24:24 +0100
changeset 15 0dbce35d3c69
parent 7 15a9291b9bd0
child 22 ac872628ef2d
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 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.
"

EditTextView subclass:#TextCollector
       instanceVariableNames:'entryStream lineLimit destroyAction
                              outstandingLines outstandingLine
                              flushBlock flushPending collecting timeDelay'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Text'
!

TextCollector comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Attic/TextColl.st,v 1.5 1993-12-20 17:24:21 claus Exp $
written winter-89 by claus
'!

!TextCollector class methodsFor:'documentation'!

documentation
"
a view for editable text, which also understands some stream messages.
Instances of this view can take the place of a stream and display the received
text; its main use in the system is the Transcript, but it can also be used for
things like trace-windows etc.

If collecting is turned on, a Textcollector will not immediately display entered
text, but wait for some short time (timeDelay) and collect incoming data - finally
updating the whole chunk in one piece. This helps slow display devices, which would
otherwise scroll a lot. (on fast displays this is less of a problem).

The number of lines kept is controlled by lineLimit, if more lines are entered at
the bottom, the textcollector will forget lines at the top. Linelimit can also be
set to nil (i.e. no limit), but you may need a lot of memory then ...
"
! !

!TextCollector class methodsFor:'defaults'!

defaultLineLimit
    "the number of lines remembered by default"

    ^ 600
! 

defaultTimeDelay
    "the time in seconds to wait & collect by default"

    ^ 0.2
! !

!TextCollector class methodsFor:'instance creation'!

newTranscript
    |topView transcript f v|

    topView := StandardSystemView label:'Transcript' minExtent:(100 @ 100).

    v := ScrollableView for:self in:topView.
    v origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    transcript := v scrolledView.
    "transcript partialLines:false."

    f := transcript font.
    topView extent:(((f widthOf:'x') * 70) @ (f height * 10)).

    Smalltalk at:#Transcript put:transcript.

    "fancy feature: whenever Transcript is closed, reset to StdError"
    transcript destroyAction:[Smalltalk at:#Transcript put:Stderr].

    topView realize.
    "transcript lineLimit:1000. " "or whatever you think makes sense"

    ^ transcript
! !

!TextCollector methodsFor:'initialize / release'!

initialize
    super initialize.

    outstandingLines := OrderedCollection new.
    flushBlock := [self endEntry].
    flushPending := false.
    collecting := true.
    timeDelay := self class defaultTimeDelay.

    lineLimit := self class defaultLineLimit.
    entryStream := ActorStream new.
    entryStream nextPutBlock:[:something | self nextPut:something].
    entryStream nextPutAllBlock:[:something | self nextPutAll:something]
!

destroy
    destroyAction notNil ifTrue:[
        destroyAction value
    ].
    flushBlock notNil ifTrue:[
        Processor removeTimedBlock:flushBlock
    ].
    super destroy
! !

!TextCollector methodsFor:'accessing'!

collect:aBoolean
    "turn on collecting - i.e. do not output immediately
     but collect text and output en-bloque after some time delta"

    collecting := aBoolean
!

lineLimit:aNumber
    "define the number of text-lines I am supposed to hold"

    lineLimit := aNumber
!

destroyAction:aBlock
    "define the action to be performed when I get destroyed"

    destroyAction := aBlock
!

endEntry
    "flush collected output"

    |nLines|

    Processor removeTimedBlock:flushBlock.
    flushPending := false.

    "insert the bunch of lines - if any"
    nLines := outstandingLines size.
    (nLines ~~ 0) ifTrue:[
        self insertLines:outstandingLines withCr:true.
        self withCursorOffDo:[
            (cursorLine >= (firstLineShown + nFullLinesShown)) ifTrue:[
                self scrollDown:nLines
            ]
        ].
        outstandingLines grow:0
    ].
    "and the last partial line - if any"
    outstandingLine notNil ifTrue:[
        flushPending := false.
        self nextPut:outstandingLine.
        outstandingLine := nil
    ].
    self checkLineLimit
! !

!TextCollector methodsFor:'private'!

checkLineLimit
    "this method checks if the text has become too large (> lineLimit)
     and cuts off some lines at the top if so; it must be called whenever lines
     have been added to the bottom"

    |nDel|

    lineLimit notNil ifTrue:[
        (cursorLine > lineLimit) ifTrue:[
            nDel := list size - lineLimit.
            list removeFromIndex:1 toIndex:nDel.
            cursorLine := cursorLine - nDel.
            firstLineShown := firstLineShown - nDel.
            (firstLineShown < 1) ifTrue:[
                cursorLine := cursorLine - firstLineShown + 1.
                firstLineShown := 1
            ].
            self contentsChanged
        ]
    ]
! !

!TextCollector methodsFor:'stream messages'!

lineLength
    ^ width // (font width)
!

nextPut:something
    "this allows TextCollectors to be used Stream-wise"

    flushPending ifTrue:[
        self endEntry
    ].
    (something isMemberOf:Character) ifTrue:[
        ((something == Character cr) or:[something == Character nl]) ifTrue:[
            ^ self cr
        ].
        self insertCharAtCursor:something
    ] ifFalse:[
        self insertStringAtCursor:(something printString).
        self checkLineLimit
    ].
    device synchronizeOutput
!

nextPutAll:something
    "this allows TextCollectors to be used Stream-wise"

    ^ self nextPut:something
!

cr
    "output a carriage return, finishing the current line"

    collecting ifTrue:[
        outstandingLines add:outstandingLine.
        outstandingLine := nil.
        flushPending ifFalse:[
            Processor addTimedBlock:flushBlock after:timeDelay.
            flushPending := true
        ] ifTrue:[
            Processor evaluateTimeouts
        ]
    ] ifFalse:[
        self cursorReturn.
        self checkLineLimit
    ]
!

show:anObject
    "insert the argument aString at current cursor position"

    |aString|

    aString := anObject printString.
    collecting ifTrue:[
        outstandingLine notNil ifTrue:[
            outstandingLine := outstandingLine , aString
        ] ifFalse:[
            outstandingLine := aString
        ].
        flushPending ifFalse:[
            Processor addTimedBlock:flushBlock after:timeDelay.
            flushPending := true
        ]
    ] ifFalse:[
        self nextPut:aString
    ]
!

showCr:aString
    "insert the argument aString followed by a newline
     at current cursor position"

    self show:aString.
    self cr
!

doesNotUnderstand:aMessage
    "this is funny: all message we do not understand, are passed
     on to the stream which will send the characters via nextPut:
     This way, we understand all Stream messages - great isn't it !!
    "
     ^ entryStream perform:(aMessage selector) withArguments:(aMessage arguments)
! !