TextCollector.st
author Stefan Vogel <sv@exept.de>
Thu, 05 Nov 2009 14:46:11 +0100
changeset 4073 5b4cf996f5d6
parent 4045 0b461045f76a
child 4105 c2c3a96f8757
permissions -rw-r--r--
added: #tab

"
 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.
"
"{ Package: 'stx:libwidg' }"

EditTextView subclass:#TextCollector
	instanceVariableNames:'entryStream lineLimit destroyAction outstandingLines
		outstandingLine flushBlock flushPending inFlush collecting
		timeDelay access currentEmphasis alwaysAppendAtEnd collectSize
		autoRaise'
	classVariableNames:'TranscriptQuerySignal'
	poolDictionaries:''
	category:'Views-Text'
!

!TextCollector class methodsFor:'documentation'!

copyright
"
 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.
"
!

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, errorLogs 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 total number of lines kept is controlled by lineLimit, if more lines 
    than this limit are added at the bottom, the textcollector will forget lines 
    at the top. 
    You can set linelimit to nil (i.e. no limit), but you may need a lot 
    of memory then ...

    [StyleSheet paramters (transcript only):]

        transcriptForegroundColor       defaults to textForegroundColor
        transcriptBackgroundColor'      defaults to textBackgroundColor.

        transcriptCursorForegroundColor
        transcriptCursorBackgroundColor

    [author:]
        Claus Gittinger

    [see also:]
        CodeView EditTextView
        ActorStream
"
! !

!TextCollector class methodsFor:'instance creation'!

initialize
    TranscriptQuerySignal := QuerySignal new.

!

newTranscript
    "create and open a new transcript.
     This is a leftOver method from times were the Launcher & Transcript
     were two different views. It is no longer recommended."

    ^ self newTranscript:#Transcript

    "
     TextCollector newTranscript.
     Transcript lineLimit:3000.
    "

    "Modified: 17.2.1997 / 18:20:27 / cg"
!

newTranscript:name
    "create and open a new transcript.
     This is a leftOver method from times were the Launcher & Transcript
     were two different views. It is no longer recommended."

    |topView transcript defSz f v lines cols|

    topView := StandardSystemView label:name "minExtent:(100 @ 100)".

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

    f := transcript font.

    "
     should add the height of the frame & scrollbars to be exact ...
    "
    defSz := self defaultTranscriptSize.
    cols := defSz x.
    lines := defSz y.
    topView extent:(((f widthOf:'x') * cols) @ (f height * lines)).

    transcript beTranscript:name.

    "
     run it at a slightly higher prio, to allow for
     delayed buffered updates to be performed
    "
    topView openWithPriority:(Processor userSchedulingPriority + 1).

    ^ transcript

    "
     TextCollector newTranscript:#T2.
     T2 showCR:'Hello world'.
    "

    "Modified: 17.2.1997 / 18:20:27 / cg"
! !

!TextCollector class methodsFor:'Signal constants'!

transcriptQuerySignal
    ^ TranscriptQuerySignal
! !

!TextCollector class methodsFor:'defaults'!

defaultCollectSize
    "the number of lines buffered for delayed update"

    ^ 50

    "Modified: / 27.7.1998 / 16:14:51 / cg"
!

defaultLineLimit
    "the number of lines remembered by default"

    ^ 600
!

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

    ^ 0.3 
!

defaultTranscriptSize
    "the number of cols/lines by which the Transcript should come up"

    ^ 70@11
! !

!TextCollector methodsFor:'Compatibility-ST80'!

deselect
    self unselect
!

flush
    self endEntry.
    super flush
! !

!TextCollector methodsFor:'accessing'!

autoRaise
    ^ autoRaise ? false
!

autoRaise:something
    autoRaise := something.
!

beginEntry
    "noop for now, ST80 compatibility"

    ^ self

    "Created: / 4.3.1998 / 11:08:14 / stefan"
!

collect:aBoolean
    "turn on/off collecting - if on, do not output immediately
     but collect text and output en-bloque after some time delta"

    collecting := aBoolean
!

collectSize:numberOfLines
    "set the collect buffer size. If collect is enabled,
     the receiver will force update of the view, 
     whenever that many lines have been collected
     (or the updateTimeDelay interval has passed).
     With collect turned off, an immediate update is performed."

    collectSize := numberOfLines

    "Modified: / 27.7.1998 / 16:16:00 / cg"
!

destroyAction:aBlock
    "define the action to be performed when I get destroyed.
     This is a special feature, to allow resetting Transcript to Stderr
     when closed. (see TextCollectorclass>>newTranscript)"

    destroyAction := aBlock
!

endEntry
    "flush collected output; displaying all that has been buffered so far"

    |nLines lines|

    shown ifFalse:[
        "/ when iconified or not yet shown, keep
        "/ collecting. But not too much ...
        outstandingLines size < 300 ifTrue:[
            flushPending ifFalse:[
                self installDelayedUpdate.
            ].
            ^ self
        ]
    ].

    inFlush ifTrue:[^ self].
    collecting ifTrue:[
        flushBlock notNil ifTrue:[
            Processor removeTimedBlock:flushBlock.
        ].
        flushPending ifFalse:[^ self].
    ].

    access critical:[
        inFlush := true.
        [
            flushPending := false.
            outstandingLines size ~~ 0 ifTrue:[
                "insert the bunch of lines - if any"
                lines := outstandingLines.
                outstandingLines := nil.

                nLines := lines size.
                (nLines ~~ 0) ifTrue:[
                    self isInInsertMode ifTrue:[
                        self insertLines:lines withCR:true.
                    ] ifFalse:[
                        self replaceLines:lines withCR:true
                    ].
                    alwaysAppendAtEnd ifTrue:[
                        self cursorToEnd.
                    ].
                    (cursorLine >= (firstLineShown + nFullLinesShown)) ifTrue:[
                        self withCursorOffDo:[
                            self scrollDown:nLines
                        ]
                    ].
                ].
            ].

            "and the last partial line - if any"
            outstandingLine size ~~ 0 ifTrue:[
                self isInInsertMode ifTrue:[
                    self insertStringAtCursor:outstandingLine.
                ] ifFalse:[
                    self replaceStringAtCursor:outstandingLine.
                ].
                outstandingLine := ''.
            ].
            self checkLineLimit.
            "/ device flush.
        ] ensure:[
            inFlush := false.
        ]
    ].
    flushPending ifTrue:[
        flushPending := false.
        self installDelayedUpdate
    ]

    "Modified: / 9.11.1998 / 21:17:56 / cg"
!

lineLimit
    "return the number of text-lines I am supposed to hold"

    ^ lineLimit

    "
     Transcript lineLimit:5000
     Transcript lineLimit
    "

    "Modified: / 16.5.1998 / 01:33:52 / cg"
!

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

    lineLimit := aNumber

    "
     Transcript lineLimit:5000
    "

    "Modified: / 16.5.1998 / 01:33:52 / cg"
!

updateTimeDelay:seconds
    "if collect is enabled, the receiver will update its view, 
     after that time delay (i.e. it collects more output during that period),
     or when collectSize lines have been collected without update.
     With collect turned off, an immediate update is performed."

    timeDelay := seconds

    "Modified: / 27.7.1998 / 16:16:41 / cg"
! !

!TextCollector methodsFor:'event handling'!

exposeX:x y:y width:w height:h
    "flush buffered text when exposed"

    super exposeX:x y:y width:w height:h.
    self endEntry
! !

!TextCollector methodsFor:'initialization & release'!

destroy
    "destroy this view"

    destroyAction value.
    super destroy

    "Modified: / 9.11.1998 / 21:18:17 / cg"
!

editMenu
    "return my popUpMenu; thats the superClasses menu,
     minus any accept item."

    <resource: #programMenu>

    |m idx|

    m := super editMenu.

    "
     textcollectors do not support #accept
     remove it from the menu (and the preceeding separating line)
    "
    idx := m indexOf:#accept.
    idx ~~ 0 ifTrue:[
        m remove:idx.
        (m labels at:(idx - 1)) = '-' ifTrue:[
            m remove:idx - 1
        ].
    ].
    ^ m

    "Modified: 3.7.1997 / 13:54:11 / cg"
!

initialize
    super initialize.

    scrollWhenUpdating := #endOfText.

    outstandingLines := nil.
    alwaysAppendAtEnd := true.
    collectSize := self class defaultCollectSize.

    flushPending := inFlush := false.
    collecting := true.
    timeDelay := self class defaultTimeDelay.
    access := RecursionLock new. "/ Semaphore forMutualExclusion.
    access name:'TextCollector access lock'.

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

    "Modified: / 14.12.1999 / 21:13:54 / cg"
!

mapped
    "view became visible - show collected lines (if any)"

    super mapped.
    self endEntry
!

reinitialize
    "reinit after a snapIn.
     recreate access-semaphore; image could have been save (theoretically)
     with the semaphore locked - in this case, we had a deadlock"

    flushPending := false.
    access := RecursionLock new. "/ Semaphore forMutualExclusion.
    super reinitialize.

    "Modified: / 5.3.1998 / 10:09:14 / stefan"
!

release
    flushBlock notNil ifTrue:[
        Processor removeTimedBlock:flushBlock.
        flushBlock := nil.
    ].
    outstandingLines := nil.
    outstandingLine := ''.

    super release

    "Modified: / 9.11.1998 / 21:18:17 / cg"
! !

!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 newCursorLine|

    lineLimit notNil ifTrue:[
        (cursorLine > lineLimit) ifTrue:[
            nDel := list size - lineLimit.
            list removeFromIndex:1 toIndex:nDel.
            newCursorLine := cursorLine - nDel.
            firstLineShown := firstLineShown - nDel.
            (firstLineShown < 1) ifTrue:[
                newCursorLine := newCursorLine - firstLineShown + 1.
                firstLineShown := 1
            ].
            self setCursorLine:newCursorLine.
            self contentsChanged.
            self invalidate.
        ]
    ].
    self autoRaise ifTrue:[
        self topView 
            raise;
            "/ setForegroundWindow;
            yourself.
    ].

    "Modified: / 26-07-2006 / 16:02:15 / fm"
!

installDelayedUpdate
    "arrange for collecting input for some time,
     and output all buffered strings at once after a while.
     This makes output to the transcript much faster on systems
     with poor scrolling performance (i.e. dumb vga cards ...)."

    |p|

    flushPending ifFalse:[
        flushPending := true.
        inFlush ifFalse:[
            "
             we could run under a process, which dies in the meantime;
             therefore, we have to arrange for the transcript process to
             be interrupted and do the update.
            "
            windowGroup isNil ifTrue:[
                p := Processor activeProcess
            ] ifFalse:[
                p := windowGroup process
            ].
            (p isNil or:[p isSystemProcess]) ifTrue:[
                self endEntry
            ] ifFalse:[
                flushBlock isNil ifTrue:[
                    flushBlock := [self endEntry].
                ].
                Processor addTimedBlock:flushBlock for:p afterSeconds:timeDelay.
            ].
            p := nil.   "avoid dangling references to p through the home context of flushBlock"
        ]
    ]

    "Modified: / 17.4.1997 / 13:03:15 / stefan"
    "Modified: / 9.11.1998 / 14:34:07 / cg"
! !

!TextCollector methodsFor:'queries'!

current
    "return the current (your screens) transcript.
     In multiDisplay applications, this need NOT be the main transcript.
     But typically, this is the same as Transcript."

    |theTranscript app|

    theTranscript := TranscriptQuerySignal query.
    theTranscript isNil ifTrue:[
        app := self topView application class current.
        (app notNil and:[thisContext isRecursive not]) ifTrue:[
            theTranscript := (app transcript ? Stderr).
        ] ifFalse:[
            theTranscript := Stderr.
        ]
    ].
    ^ theTranscript

    "
     Transcript current flash
    "

    "Created: 5.7.1996 / 14:14:34 / cg"
    "Modified: 5.7.1996 / 14:14:52 / cg"
! !

!TextCollector methodsFor:'scrolling'!

scrollTo:anOrigin redraw:doRedraw
    access critical:[
        super scrollTo:anOrigin redraw:doRedraw
    ]
! !

!TextCollector methodsFor:'stream messages'!

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

    access critical:[
        collecting ifTrue:[
            outstandingLine notNil ifTrue:[  "/ mhmh - is never nil
                outstandingLines isNil ifTrue:[
                    outstandingLines := OrderedCollection with:outstandingLine
                ] ifFalse:[
                    outstandingLines add:outstandingLine.
                ]
            ].
            outstandingLine := ''.
        ] ifFalse:[
            self cursorReturn.
            self checkLineLimit.
            self cursorToEnd.
        ].
    ].

    collecting ifTrue:[
        flushPending ifFalse:[
            self installDelayedUpdate
        ]
    ].

    "Modified: 11.1.1997 / 14:39:00 / cg"
!

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!!"

    ^ aMessage sendTo:entryStream
!

lineLength
    "to make a textCollector (somewhat) compatible with printer
     streams, support the lineLength query"

    ^ width // (font width)

    "Modified: 11.1.1997 / 14:42:41 / cg"
!

nextPut:something
    "append somethings printString to my displayed text.
     This allows TextCollectors to be used Stream-wise"

    |txt|

    (something isCharacter) ifTrue:[
        ((something == Character cr) or:[something == Character nl]) ifTrue:[
            ^ self cr
        ].
    ].

    txt := something asString.
    currentEmphasis notNil ifTrue:[
        txt := txt emphasizeAllWith:currentEmphasis
    ].
    self show:txt.

"/    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 flush

    "Modified: 11.1.1997 / 14:43:05 / cg"
!

nextPutAll:something
    "append all of something to my displayed text.
     This allows TextCollectors to be used Stream-wise"

    self show:(currentEmphasis notNil 
                ifTrue:[something emphasizeAllWith:currentEmphasis]
                ifFalse:[something])

    "Modified: 11.1.1997 / 14:43:26 / cg"
!

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

    |printString lines|

    printString := anObject printString.

    (printString includes:(Character cr)) ifTrue:[
        lines := printString asStringCollection.
        lines keysAndValuesDo:[:nr :line |
            (nr == lines size 
            and:[(printString endsWith:(Character cr)) not]) ifTrue:[
                "/ the last one.
                self show:line
            ] ifFalse:[
                self showCR:line
            ].
        ].
        ^ self.
    ].

    access critical:[
        outstandingLine size ~~ 0 ifTrue:[
            outstandingLine := outstandingLine , printString
        ] ifFalse:[
            outstandingLine := printString
        ].
        collecting ifTrue:[
            flushPending ifFalse:[
                self installDelayedUpdate
            ] ifTrue:[
                outstandingLines size > collectSize ifTrue:[
                    self endEntry
                ]
            ]
        ] ifFalse:[
            self endEntry
        ]
    ].

    "Modified: / 10.6.1998 / 19:34:25 / cg"
!

showCR:anObject
    "insert the argument aString at current cursor position,
     and advance to the next line. This is the same as a #show:
     followed by a #cr."

    |printString lines|

    printString := anObject printString.
    printString size == 0 ifTrue:[
        self cr.
        ^ self.
    ].

    (printString includesAny:(String with:(Character cr) with:(Character return))) ifTrue:[
        lines := printString asStringCollection.
        lines do:[:line|
            (line endsWith:Character return) ifTrue:[
                self showCR:(line copyWithoutLast:1).
            ] ifFalse:[
                self showCR:line
            ]
        ].
        ^ self.
    ].

    access critical:[
        outstandingLine size ~~ 0 ifTrue:[
            outstandingLine := outstandingLine , printString
        ] ifFalse:[
            outstandingLine := printString
        ].
        outstandingLines isNil ifTrue:[
            outstandingLines := OrderedCollection with:outstandingLine
        ] ifFalse:[
            outstandingLines add:outstandingLine.
        ].
        outstandingLine := ''.

        collecting ifTrue:[
            flushPending ifTrue:[
                outstandingLines size > collectSize ifTrue:[
                    self endEntry
                ]
            ] ifFalse:[
                self installDelayedUpdate
            ]
        ] ifFalse:[
            self endEntry.
            self cursorReturn.
            self checkLineLimit.
            self cursorToEnd.
        ]
    ].

    "Created: / 28.7.1998 / 00:31:46 / cg"
    "Modified: / 28.7.1998 / 00:34:58 / cg"
!

tab
    "append a tab-character to the stream.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character tab)
! !

!TextCollector methodsFor:'stream messages-emphasis'!

bgColor:aColor
    currentEmphasis := #backgroundColor->aColor
!

bold
    "switch to bold - followup text sent via show/nextPutAll: will be inserted in
     a bold font."

    currentEmphasis := #bold

    "Modified: / 26.3.1999 / 14:28:58 / cg"
!

color:aColor
    currentEmphasis := #color->aColor

    "Modified: / 26.3.1999 / 14:29:21 / cg"
!

italic
    currentEmphasis := #italic
!

normal
    currentEmphasis := nil
!

reverse
    currentEmphasis := Array with:#color->bgColor
                             with:#backgroundColor->fgColor.

    "Created: / 20.6.1998 / 20:10:45 / cg"
!

underline
    currentEmphasis := #underline

    "Created: / 26.3.1999 / 14:27:07 / cg"
! !

!TextCollector methodsFor:'transcript specials'!

beTranscript
    "make the receiver be the systemTranscript; this one
     is accessable via the global Transcript and gets relevant
     system messages from various places."

    self beTranscript:#Transcript

    "Modified: / 2.11.1997 / 22:34:47 / cg"
!

beTranscript:name
    "make the receiver be the systemTranscript; this one
     is accessable via the global Transcript and gets relevant
     system messages from various places."

    |fg bg cFg cBg|

    Smalltalk at:name put:self.

    "
     fancy feature: whenever Transcript is closed, reset to StdError
    "
    self destroyAction:[
        self == (Smalltalk at:name) ifTrue:[
            Smalltalk at:name put:Stderr
        ]
    ].

    "/ user may prefer a special color for this one;
    "/ look into the style definitions ...

    fg := styleSheet colorAt:'transcript.foregroundColor' default:self foregroundColor.
    bg := styleSheet colorAt:'transcript.backgroundColor' default:self backgroundColor.
    self foregroundColor:fg backgroundColor:bg.
    self viewBackground:bg.

    cFg := styleSheet colorAt:'transcript.cursorForegroundColor' default:bg.
    cBg := styleSheet colorAt:'transcript.cursorBackgroundColor' default:fg.
    self cursorForegroundColor:cFg backgroundColor:cBg. 

    "self lineLimit:1000. " "or whatever you think makes sense"

    "Modified: / 2.11.1997 / 22:34:47 / cg"
!

clear
    self endEntry.
    self contents:nil.

    "
     Transcript clear
    "
!

flash
    "make sure everything is visible, before flashing"

    self endEntry.
    super flash.
! !

!TextCollector class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/TextCollector.st,v 1.99 2009-11-05 13:46:11 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libwidg/TextCollector.st,v 1.99 2009-11-05 13:46:11 stefan Exp $'
! !

TextCollector initialize!