TerminalView.st
author Claus Gittinger <cg@exept.de>
Fri, 05 Jul 2013 12:03:55 +0200
changeset 4263 aacb0c4d8dc0
parent 4256 da3d21982ece
child 4265 76d3fea328d6
permissions -rw-r--r--
class: ImageView changed: #middleButtonMenu

"
 COPYRIGHT (c) 1998 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:libwidg2' }"

TextCollector subclass:#TerminalView
	instanceVariableNames:'inStream outStream readerProcess shellPid kbdSequences
		escapeSequenceTree currentSequence kbdMap escapeLeadingChars
		numberOfColumns numberOfLines shellTerminateAction rangeStartLine
		rangeEndLine state savedCursor shellCommand shellDirectory
		filterStream localEcho translateNLToCRNL inputTranslateCRToNL
		autoWrapFlag masterWindow'
	classVariableNames:'Debug'
	poolDictionaries:''
	category:'Views-TerminalViews'
!

!TerminalView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1998 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
"
    I provide terminal functionality, by interpreting data
    arriving from some stream (typically connected to a command interpreter 
    via a pty, or another system via a modem) 
    and sending my keyboard data to it.

    I am abstract providing general functionality
    - concrete terminal characteristics are defined by concrete subclasses 
    (see VT52TerminalView, VT100TerminalView).

    Concrete applications are: 
        consoles (VT100TerminalView),
        telnet-views (see TelnetTool)
        editor wrappers (if you like emacs/vi)

    Although my class protocol includes common startup protocol
    (to open a terminalView with a shell or on the output of a command),
    I can be used as a widget within an application (modem software).

    [author:]
        Claus Gittinger

    [instance variables:]
        inStream                stream where keyboard input is
                                sent to (connected to shells or commands input)

        outStream               stream where the output of the
                                shell or command arrives
                                (read here and displayed in the view)

        readerProcess           process which reads commands    
                                output and sends it to the view

    [class variables]:
        Debug := true           trace incoming characters


    [start with:]
        VT52TerminalView open
        VT100TerminalView open
        VT52TerminalView openShell
        VT100TerminalView openShell
        VT100TerminalView openOnCommand:'ls -l'
        VT100TerminalView openOnCommand:'dir'

    [see also:]
        TelNetTool
"
!

example
"
    |terminal in out inputLine|

    in := InternalPipeStream new.
    out := InternalPipeStream new.

    terminal := TerminalView openOnInput:in output:out.
    terminal localEcho:true.
    terminal inputTranslateCRToNL:true.

    out nextPutLine:'Hello world - please type at me:'.

    [
        inputLine := in nextLine asString.
        inputLine ~= '#exit' ifTrue:[
            out nextPutLine:(Compiler evaluate:inputLine) printString.
        ].
        inputLine = '#exit'
    ] whileFalse.

    terminal topView destroy.
"
! !

!TerminalView class methodsFor:'initialization'!

initialize

    Debug := false.

"
    self initialize
"
! !

!TerminalView class methodsFor:'defaults'!

defaultIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self defaultIcon inspect
     ImageEditor openOnClass:self andSelector:#defaultIcon
     Icon flushCachedIcons
    "

    <resource: #image>

    ^Icon
        constantNamed:'TerminalView class defaultIcon'
        ifAbsentPut:[(Depth8Image new) width: 48; height: 36; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@C@0LC@0LC@0LC@0LC@0LC@0LC@0LC@0LC@0L@@@@@@@@@
@@@@@@@@@@@@@@@@@@LDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PC@@@@@@@@@@@@@@@@@@@@@@@@@0PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD
@ H@@@@@@@@@@@@@@@@@@@@@@0PD@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDDA@PD@ H@@@@@@@@@@@@@@@@@@@@@@0PD@PDA@PDA@PDA@PDA@PDA@PDA@PDA
@PDAA@PD@ HB@@@@@@@@@@@@@@@@@@@@@0PD@PDEAPDE@PDE@PTEAPTA@PTA@PDA@PDAA@PD@ HB@@@@@@@@@@@@@@@@@@@@@0PD@PDA@PDA@PDA@PDA@PDA
@PDA@PDA@PDAA@PD@ HB@ @@@@@@@@@@@@@@@@@@@0PD@PDEAPTE@PTE@PTEAPDA@PDA@PDA@PDAA@PD@ HB@ @@@@@@@@@@@@@@@@@@@0PD@PDA@PDA@PDA
@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDEAPTEAPTEAPTE@PTEAPTE@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDA
@PDA@PDA@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDEAPTAAPTEAPDEAPDAAPTE@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@
@0PD@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDE@PDA@PDA@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@
@@@@@@@@@0PD@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDEAPTE@PTAAPTE@PTA@PDA@PDA@PDAA@PD@ HB@ H@
@@@@@@@@@@@@@@@@@0PD@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDAA@PD@ HB@ H@@@@@@@@@@@@@@@@@@0PD@PDE@PTEAPTA@PDA@PDA@PDA@PDA@PDAA@PD
@ HB@ H@@@@@@@@@@@@@@@@@@0PDA@DA@PDA@PDA@PDA@PDA@PDA@PDA@PDDA@PD@ HB@ @@@@@@@@@@@@@@@@@@@0PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD
A@PDA@PD@ HB@@@@@@@@@@@@@@@@@@@@@@LDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PB@ H@@@@@@@@@@@@@@@@@@@@@@@@@@@HB@ HB@ HB@ HB@ HB
@ HB@ HB@ HB@ HC@0LB@ @@@@@@@@@@@@@@@@@@@@@@@@@C@0LC@0LC@0LC@0LC@0LC@0LC@0LC@0LC@0HB@ @@@@@@@@@@@@@@@@@@@@@@@@HB@ HB@ HB
@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ @@@@@@@@@@@@@@@@@@@@@BA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD@ HB@ LC@@LC@@@@@@@@@@@@@@@BA@PD
A@PDA@PDA@PDA@PDA@PD@@@@@@@@@@PD@ HB@ @@@0@@@0@@@@@@@@@@@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HBA@PD@ HB@@@@@@@C@@@@@@@@@@@B
A@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PB@ HB@ @@@@@@@@L@@@@@@@@@@@HDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@HB@@@@@@@@@ HB@ HB@@@@
@@@@@@HDA@TEAPTEAPTEAPTEAPTEAPTEAPTDA@PDA@HB@@@@@ HB@ HC@0LB@@@@@@@@@ PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD@ H@@@@B@ PDA@HB
@0LB@@@@@@@BA@PEAPTEAPTEAPTEAPTEAPTEAPTEAPPDA@PB@ @@@@@BA@PDA@PC@0H@@@@@@@HDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@HB@@@@@@@B
@0LC@0LB@ @@@@@@@@HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ H@@@@@@@@B@ HB@ HB@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@') ; colorMapFromArray:#[0 0 0 40 58 10 80 78 80 140 140 140 196 194 190 255 255 255]; mask:((ImageMask new) width: 48; height: 36; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@O???>@@@_????@@@?????0@@?????0@@?????8@@?????8@@?????<@@?????<@@?????>@@?????>@@?????>@@?????>@@?????>@@?????>@
@?????>@@?????>@@?????>@@?????>@@?????<@@?????8@@_????0@@C????<@@A????<@@C????<@@O?????X@O????<$@?????8HA????? PC????8G8
C????8?8G????1?8O????!!?0_????A? _???>A?@@@@@@@@@') ; yourself); yourself]
!

defaultNumberOfColumns
    ^ 80

    "Created: / 4.8.1998 / 17:48:18 / cg"
    "Modified: / 4.8.1998 / 17:48:31 / cg"
!

defaultNumberOfLines
    ^ 25

    "Created: / 4.8.1998 / 17:48:18 / cg"
    "Modified: / 4.8.1998 / 17:48:31 / cg"
! !

!TerminalView class methodsFor:'opening'!

open
    ^ self openShell

    "
     VT100TerminalView open
    "

    "Created: / 10.6.1998 / 15:47:25 / cg"
    "Modified: / 9.7.1998 / 17:55:37 / cg"
!

openDummy
    "for testing purposes only - opens a dummy tty-view, which simply
     echoes whatever is typed in"

    |in vt52|

    vt52 := self new.
    in := ForwardingStream on:''.

    in fwdStream:vt52.
    vt52 inStream:in.
    vt52 outStream:in.
    vt52 open

    "
     self openDummy
    "
!

openOnCommand:aCommandString
    "start a command on a pseudo-TTY, open a terminalView on it
     (i.e. this is kind of an xterm)"

    ^ self openOnCommand:aCommandString onExit:[]

    "
     VT100TerminalView openOnCommand:'ls -l'
    "

    "Created: / 9.7.1998 / 17:50:53 / cg"
    "Modified: / 9.7.1998 / 17:57:41 / cg"
!

openOnCommand:aCommandString onExit:aBlock
    "start a command on a pseudo-TTY, open a terminalView on its output
     (i.e. this is kind of an xterm).
     When the command finishes, evaluate aBlock."

    |top scr vt|

    top := StandardSystemView new.
    scr := ScrollableView for:self in:top.
    scr origin:0.0@0.0 corner:1.0@1.0.
    vt := scr scrolledView.

    vt masterWindow: top.
    vt startCommand:aCommandString.
    vt shellTerminateAction:[
        top label:('finished: "' , aCommandString , '"'). aBlock value
    ].

    top extent:(scr preferredExtent).
    top label:('executing: "' , aCommandString , '"').
    top iconLabel:'command'.
    top icon:(self defaultIcon).
    top open.

    ^ vt

    "
     VT100TerminalView openOnCommand:'ls -lR'
     VT100TerminalView openOnCommand:'vi /etc/hosts'
    "

    "Created: / 9.7.1998 / 17:54:34 / cg"
    "Modified: / 4.8.1998 / 17:49:02 / cg"
!

openOnInput:inStream output:outStream
    "open a terminalView on the given streams (which are typically some
     kind of socket or pty). 
     Keys pressed are sent to inStream, text appearing
     from outStream is displayed in the terminal view.
     This can be used to implement things like rlogin
     or telnet views (if connected to a modem, a com-program can also be
     implemented this way)."

    |top scr|

    top := StandardSystemView new.
    scr := self openOnInput:inStream output:outStream in:top.

    top extent:(scr preferredExtent).
    top label:'shell'.
    top iconLabel:'shell'.
    top icon:(self defaultIcon).
    top open.
    ^ scr

    "Modified: / 5.5.1999 / 17:25:59 / cg"
!

openOnInput:inStream output:outStream in:aView
    "open a terminalView on the given streams 
     (which are typically some kind of socket or pty). 
     Keys pressed are sent to inStream, text appearing
     from outStream is displayed in the terminal view.
     This can be used to implement things like rlogin
     or telnet views (if connected to a modem, a com-program can also be
     implemented this way)."

    |scr vt|

    scr := ScrollableView for:self in:aView.
    scr origin:0.0@0.0 corner:1.0@1.0.
    vt := scr scrolledView.

    vt inStream:inStream.
    vt outStream:outStream.
    vt startReaderProcessWhenVisible.

    ^ scr

    "Modified: / 5.5.1999 / 17:25:59 / cg"
!

openShell
    "start a shell on a pseudo-TTY, open a terminalView on it
     (i.e. this is kind of an xterm)"

    ^ self openShellIn:nil

    "
     VT100TerminalView openShell
    "

    "Modified: / 21.7.1998 / 18:24:55 / cg"
!

openShellIn:aDirectory
    "start a shell on a pseudo-TTY, open a terminalView on it
     (i.e. this is kind of an xterm)"

    | top scr vt lbl|

    top := StandardSystemView new.
    scr := ScrollableView for:self in:top.
    scr origin:0.0@0.0 corner:1.0@1.0.
    vt := scr scrolledView.
    vt startShellIn:aDirectory.
    vt shellTerminateAction:[top destroy].
    vt masterWindow: top.

    lbl := OperatingSystem isUNIXlike ifTrue:['shell'] ifFalse:['dos'].
    top extent:(scr preferredExtent).
    top label:lbl.
    top iconLabel:lbl.
    top icon:(self defaultIcon).
    top open.

    ^ vt

    "
     VT100TerminalView openShellIn:'/etc'
    "

    "Created: / 20.7.1998 / 18:28:15 / cg"
    "Modified: / 5.5.1999 / 17:27:10 / cg"
! !

!TerminalView class methodsFor:'queries'!

isVisualStartable
    "returns whether this application class can be started via #open"

    self == TerminalView ifTrue:[^ false].
    ^ true

    "Created: / 10.6.1998 / 15:48:43 / cg"
! !

!TerminalView methodsFor:'accessing'!

filterStream:something
    "set a filter stream; if not nil, it gets all incoming data via nextPutAll:.
     (added to allow saving incoming data to a file, but can also be used to catch/filter/lookAt
      incoming data by some other program)"

    filterStream := something.

    "Created: / 28.1.2002 / 20:56:04 / micha"
    "Modified: / 28.1.2002 / 20:56:11 / micha"
!

inStream
    "set the stream, which gets all input data (i.e. keyboard input)"

    ^ inStream
!

inStream:something
    "return the stream, which gets all input data (i.e. keyboard input)"

    inStream := something.
!

inputTranslateCRToNL
    ^ inputTranslateCRToNL
!

inputTranslateCRToNL:something
    inputTranslateCRToNL := something.
!

localEcho:aBoolean
    "enable/disable local echo"

    localEcho := aBoolean

    "Created: / 5.5.1999 / 17:53:16 / cg"
!

masterWindow:something
    masterWindow := something.
!

outStream
    "return the stream, which is used to present data in the view (i.e. shell output)"

    ^ outStream
!

outStream:something
    "set the stream, which is used to present data in the view (i.e. shell output)"

    outStream := something.
!

readerProcess
    ^ readerProcess
!

shellTerminateAction:aBlock
    "set the block which is evaluated when the shell terminates.
     Can be used to close down the application in this case."

    shellTerminateAction := aBlock.

    "Created: / 12.6.1998 / 17:02:58 / cg"
!

translateNLToCRNL
    ^ translateNLToCRNL

    "Created: / 28.1.2002 / 20:32:10 / micha"
!

translateNLToCRNL:something
    translateNLToCRNL := something.

    "Created: / 28.1.2002 / 20:32:10 / micha"
! !

!TerminalView methodsFor:'cursor handling'!

cursorDown:n
    cursorLine + n > list size ifTrue:[
        list := list , (Array new:n).
        self textChanged.
    ].
    super cursorDown:n

    "Modified: / 10.6.1998 / 17:18:41 / cg"
    "Created: / 10.6.1998 / 17:18:50 / cg"
!

cursorMovementAllowed
    "return true, if the user may move the cursor around
     (via button-click, or cursor-key with selection).
     Here false is returned - the cursor is only moved by
     cursor positioning escape sequences arriving from the
     stream."

    ^ false

    "Created: / 18.6.1998 / 14:12:02 / cg"
!

numberOfTerminalCols
    ^ numberOfColumns
!

numberOfTerminalColumns
    ^ numberOfColumns

    "Created: / 5.5.1999 / 11:46:25 / cg"
!

numberOfTerminalLines
    "/ be careful - this is NOT called numberOfLines,
    "/ since that would interfere with numberOfLines as defined
    "/ in ListView ...
    "/ ... one of the bad sides of subclassing

    ^ numberOfLines

    "Created: / 5.5.1999 / 11:46:18 / cg"
    "Modified: / 5.5.1999 / 11:47:24 / cg"
!

restoreCursor
    |l c|

    savedCursor isNil ifTrue:[
        l := c := 1.
    ] ifFalse:[
        l := savedCursor y.
        c := savedCursor x.
    ].
    self cursorLine:l col:c.

    "Created: / 14.8.1998 / 13:49:24 / cg"
!

saveCursor
    savedCursor := cursorCol @ cursorLine

    "Created: / 14.8.1998 / 13:48:45 / cg"
    "Modified: / 14.8.1998 / 13:49:32 / cg"
!

validateCursorCol:col inLine:line
    "check of col is a valid cursor position; return a new col-nr if not.
     Here, the linelength is enforced"

    col > numberOfColumns ifTrue:[
        autoWrapFlag ifTrue:[
            self endEntry.
            self cursorLine:(self cursorLine + 1) col:(col-numberOfColumns).
            ^ 1.
        ].
    ].
    ^ col min:numberOfColumns

    "Modified: / 10.6.1998 / 15:09:41 / cg"
! !

!TerminalView methodsFor:'defaults'!

anyKeyCodes
    ^ IdentityDictionary withKeysAndValues:
        #(
             #Escape      '\e'
             #BackSpace   '\b'
             #Return      '\r'
             #Delete      '\0177'
             #Tab         '\t'
         )

    "Created: / 5.5.1999 / 15:00:37 / cg"
! !

!TerminalView methodsFor:'event handling'!

computeNumberOfLinesShown
    |prevNLines prevNCols|

    prevNCols := (innerWidth // font width).
    prevNLines := nFullLinesShown.

    super computeNumberOfLinesShown.

    ((innerWidth // font width) ~~ prevNCols
    or:[prevNLines ~~ nFullLinesShown]) ifTrue:[
        self defineWindowSize.
    ]

    "Created: / 12.6.1998 / 22:34:39 / cg"
    "Modified: / 20.6.1998 / 19:45:28 / cg"
!

contentsChanged
    "this one is sent, whenever contents changes its size"

    super contentsChanged.
    "/ self defineWindowSize.

    "Modified: / 11.6.1998 / 22:51:48 / cg"
    "Created: / 5.5.1999 / 16:30:15 / cg"
!

defineWindowSize
    | delta prevNumCols prevNumLines|

"/self halt.
"/self realized ifFalse:[
"/    "/ iconfified
"/    ^ self
"/].
    prevNumCols := numberOfColumns.
    prevNumLines := numberOfLines.

    numberOfColumns := (innerWidth // font width).
    delta := numberOfLines - rangeEndLine.
    numberOfLines := nFullLinesShown.
    ((prevNumCols == numberOfColumns)
    and:[prevNumLines == numberOfLines]) ifTrue:[
        ^ self
    ].

    rangeEndLine notNil ifTrue:[
        rangeEndLine := numberOfLines - delta.
    ].

    "/ any idea, how to do this under windows ?

    OperatingSystem isUNIXlike ifTrue:[
        "/
        "/ tell the pty;
        "/ tell the shell;
        "/
        (inStream notNil 
        and:[inStream isExternalStream
        and:[inStream isOpen]]) ifTrue:[
        Debug ifTrue:[
            Transcript showCR:'VT100: changed len to ', numberOfLines printString.
        ].
            (OperatingSystem 
                setWindowSizeOnFileDescriptor:inStream fileDescriptor
                width:numberOfColumns
                height:numberOfLines) ifFalse:[
                Debug ifTrue:[
                    Transcript showCR:'VT100: cannot change windowSize'.
                ].
            ].

        ].
        shellPid notNil ifTrue:[
            OperatingSystem sendSignal:OperatingSystem sigWINCH to:shellPid
        ]
    ].

    "Created: / 11.6.1998 / 22:51:39 / cg"
    "Modified: / 5.5.1999 / 19:45:09 / cg"
!

keyPress:aKey x:x y:y
    <resource: #keyboard (#Control #Control_L #Control_R
                          #Shift #Shift_L #Shift_R
                          #Alt #Alt_L #Alt_R
                          #Cmd #Cmd_L #Cmd_R
                          #Meta #Meta_L #Meta_R
                          #Return)>

    |rest event rawKey seq|

    "/ somewhat complicated, since some characters
    "/ should go untranslated (CTRL-key),
    "/ even if defined as function keys.

    inStream isNil ifTrue:[^ self].

    Debug ifTrue:[
        Transcript showCR:'----'; show:'keyPress:' ; showCR:aKey printString.
    ].

    aKey isCharacter ifTrue:[
        self deselect.

        "/ send it down to inStream ...
        inStream nextPut:aKey.
        localEcho ifTrue:[
            self nextPut:aKey.
            self flush.
        ].
        ^ self
    ].

    (#(Control Control_L Control_R
      Shift Shift_L Shift_R
      Alt Alt_L Alt_R
      Cmd Cmd_L Cmd_R
      Meta Meta_L Meta_R) includes:aKey) ifTrue:[
        ^ self
    ].

    "/
    "/ common translations (Tab, Backspace, F-keys etc.)
    "/
    (aKey == #Return
    and:[inputTranslateCRToNL]) ifTrue:[
        seq := '\n'.
    ] ifFalse:[
        seq := kbdSequences at:aKey ifAbsent:nil.
    ].

    seq notNil ifTrue:[
        Debug ifTrue:[
            Transcript show:'->' ; showCR:seq storeString.
        ].
        seq := seq withoutCEscapes.

        inStream nextPutAll:seq.
        localEcho ifTrue:[
            seq do:[:k | self nextPut:k].
            self flush.
        ].
        ^ self
    ].

    self sensor ctrlDown ifTrue:[
        (aKey startsWith:'Ctrl') ifTrue:[
            rawKey := aKey
        ] ifFalse:[
            "/ already translated - undo it.
        
            event := WindowGroup lastEventQuerySignal query.
            rawKey := event rawKey.
            rawKey isCharacter ifTrue:[
                rawKey := 'Ctrl' , rawKey.
            ]
        ]
    ] ifFalse:[
        rawKey := self keyboardMap keyAtValue:aKey ifAbsent:aKey.
    ].

    "/
    "/ care for function-keys, which are mapped to Ctrl-x;
    "/
    Debug ifTrue:[
        Transcript show:'raw ->' ; showCR:rawKey storeString.
    ].

    seq := kbdSequences at:rawKey ifAbsent:nil.
    seq notNil ifTrue:[
        Debug ifTrue:[
            Transcript show:'->' ; showCR:seq storeString.
        ].
        inStream nextPutAll:(seq withoutCEscapes).
        ^ self
    ].

    (rawKey startsWith:'Ctrl') ifTrue:[
        rest := rawKey copyFrom:5.
        rest size == 1 ifTrue:[
            rest := rest at:1.
            (rest >= $a and:[rest <= $z]) ifTrue:[
                Debug ifTrue:[
                    Transcript show:'->' ; showCR:(Character value:(rest - $a + 1)) storeString.
                ].
                inStream nextPut:(Character value:(rest - $a + 1)).
                ^ self
            ].
            (rest >= $A and:[rest <= $Z]) ifTrue:[
                Debug ifTrue:[
                    Transcript show:'->' ; showCR:(Character value:(rest - $a + 1)) storeString.
                ].
                inStream nextPut:(Character value:(rest - $A + 1)).
                ^ self
            ].
        ]
    ].

    (rawKey startsWith:'Control') ifTrue:[
        ^ self
    ].
    (rawKey startsWith:'Shift') ifTrue:[
        ^ self
    ].
    (rawKey startsWith:'Alt') ifTrue:[
        ^ self
    ].
    (rawKey startsWith:'Cmd') ifTrue:[
        ^ super keyPress:aKey x:x y:y
    ].
    (rawKey = 'Ctrl') ifTrue:[
        ^ self
    ].

    Debug ifTrue:[
        Transcript show:'unhandled key: '; showCR:rawKey.
    ].

    "Modified: / 25-01-2012 / 10:43:06 / cg"
!

shellTerminated
    "shell has terminated"

"/Delay waitForSeconds:10.
    [self readAnyAvailableData > 0] whileTrue:[Delay waitForSeconds:0.1].
"/
    self closeDownShell.

    shellTerminateAction notNil ifTrue:[
        shellTerminateAction value
    ] ifFalse:[
        "/ may be removed ...
        self warn:(resources string:'shell terminated').
    ]

    "Modified: / 5.5.1999 / 18:43:22 / cg"
!

sizeChanged:how
    super sizeChanged:how.
    self defineWindowSize.

    "Modified: / 11.6.1998 / 22:51:48 / cg"
! !

!TerminalView methodsFor:'functions'!

doBackspace
    self cursorLeft.
    self replaceCharAtCursor:(Character space).
    self cursorLeft.

    "Modified: / 10.6.1998 / 17:09:12 / cg"
!

doClearDisplay
    "clear everything"

    self doClearEntireScreen.

    "Modified: / 21.7.1998 / 20:05:35 / cg"
!

doClearEntireLine
    "clear the cursor line. cursor position remains unchanged"

    self at:cursorLine put:''
!

doClearEntireScreen
    "clear everything"

    firstLineShown to:(list size) do:[:l |
        self at:l put:''
    ].

    "Modified: / 21.7.1998 / 20:00:19 / cg"
    "Created: / 21.7.1998 / 20:05:24 / cg"
!

doClearFromBeginningOfLine
    "clear from beginning of line to the cursorPosition"

    |l|

    l := self listAt:cursorLine.
    l notNil ifTrue:[
        (l size >= (cursorCol-1)) ifTrue:[
            l := l copy from:1 to:cursorCol-1 put:(Character space).
        ] ifFalse:[
            l := nil.
        ].
        self withoutRedrawAt:cursorLine put:l.
        self invalidateLine:cursorLine
        "/ self at:cursorLine put:l.
    ]

    "Modified: / 20.6.1998 / 19:10:21 / cg"
    "Created: / 21.7.1998 / 20:10:58 / cg"
!

doClearFromBeginningOfScreen
    "clear from beginning of the screen to the cursorPosition"

    self doClearFromBeginningOfLine.
    cursorLine-1 to:firstLineShown do:[:l |
        self at:l put:''
    ].

    "Modified: / 10.6.1998 / 14:45:43 / cg"
    "Created: / 21.7.1998 / 20:08:29 / cg"
!

doClearToEndOfLine
    "clear from the cursorPosition to the end of the line"

    |l|

    l := self listAt:cursorLine.
    (l size >= (cursorCol-1)) ifTrue:[
        l notNil ifTrue:[
            l := l copyTo:cursorCol-1.
            self withoutRedrawAt:cursorLine put:l.
            self invalidateLine:cursorLine
            "/ self at:cursorLine put:l.
        ]
    ]

    "Created: / 10.6.1998 / 14:45:01 / cg"
    "Modified: / 20.6.1998 / 19:10:21 / cg"
!

doClearToEndOfScreen
    "clear from the cursorPosition to the end of the screen"

    self doClearToEndOfLine.
    cursorLine+1 to:(list size) do:[:l |
        self at:l put:''
    ].

    "Modified: / 10.6.1998 / 14:45:43 / cg"
    "Created: / 21.7.1998 / 20:06:14 / cg"
!

doCursorDown:n
    "move the cursor down by n lines"

    |wasOn rEnd|

"/    rangeEndLine == numberOfLines ifTrue:[
"/        ^ super cursorDown:n
"/    ].
    cursorLine + 1 - firstLineShown + n <= rangeEndLine ifTrue:[
        "/ no special action req'd
        ^ super cursorDown:n
    ].

    n timesRepeat:[
        wasOn := self hideCursor.
        rEnd := rangeEndLine+firstLineShown-1.
        cursorLine ==  rEnd ifTrue:[
            self deleteLine:(rangeStartLine+firstLineShown-1).
            self insertLine:'' before:rEnd.
        ] ifFalse:[
            super cursorDown
        ].
        wasOn ifTrue:[self showCursor]. "/ self makeCursorVisibleAndShowCursor:wasOn.
    ]

    "Modified: / 20.6.1998 / 20:29:39 / cg"
!

doCursorHome
    "move the cursor to the home position"

    self cursorVisibleLine:1 col:1
    "/ super cursorHome

    "Modified: / 10.6.1998 / 20:47:31 / cg"
!

doCursorLeft:n
    "move the cursor to the left by n columns"

    n timesRepeat:[
        super cursorLeft
    ]

    "Created: / 11.6.1998 / 22:30:00 / cg"
!

doCursorNewLine
    "move the cursor down to the next line (col remains unchanged)"

    super cursorDown:1

    "Modified: / 10.6.1998 / 16:55:57 / cg"
!

doCursorReturn
    "move the cursor down and left to the beginning to the next line"

    super cursorToBeginOfLine
!

doCursorRight:n
    "move the cursor to the right by n columns"

    self cursorCol:(cursorCol + n)

    "Created: / 10.6.1998 / 15:10:08 / cg"
!

doCursorUp:n
    "move the cursor up by n lines"

    |wasOn rStart|

"/    rangeStartLine == 1 ifTrue:[
"/        ^ super cursorUp:n
"/    ].
    cursorLine + 1 - firstLineShown - n >= rangeStartLine ifTrue:[
        "/ no special action req'd
        ^ super cursorUp:n
    ].
    n timesRepeat:[
        wasOn := self hideCursor.
        rStart := rangeStartLine+firstLineShown-1.
        cursorLine == rStart ifTrue:[
            (rangeEndLine+firstLineShown-1) <= list size ifTrue:[
                self deleteLine:(rangeEndLine+firstLineShown-1).
                self insertLine:'' before:rStart.
            ].
        ] ifFalse:[
            super cursorUp
        ].
        self makeCursorVisibleAndShowCursor:wasOn.
    ]

    "Created: / 11.6.1998 / 22:29:46 / cg"
    "Modified: / 20.6.1998 / 20:30:34 / cg"
! !

!TerminalView methodsFor:'initialization & release'!

closeDownShell
    "shut down my shell process and stop the background reader thread."

    |pid|

    (pid := shellPid) notNil ifTrue:[
        Debug ifTrue:[
            Transcript print:'killing shell pid='; showCR:pid.
        ].
        OperatingSystem terminateProcessGroup:pid.
        OperatingSystem terminateProcess:pid.
        Delay waitForSeconds:1.
        shellPid notNil ifTrue:[
            OperatingSystem isMSWINDOWSlike ifFalse:[
                OperatingSystem killProcessGroup:pid.
            ].
            OperatingSystem killProcess:pid.
            shellPid := nil.
        ].
        OperatingSystem closePid:pid.
    ].

    self stopReaderProcess.

    inStream notNil ifTrue:[
        inStream isStream ifTrue:[inStream close].
        inStream := nil
    ].
    outStream notNil ifTrue:[
        outStream close.
        outStream := nil
    ].

    "Modified: / 5.5.1999 / 18:43:02 / cg"
!

escapeSequences:codes
    "setup my escape sequences"

    |tree|

    tree isNil ifTrue:[tree := escapeSequenceTree := IdentityDictionary new].

    codes do:[:specEntry |
        |sequence function|

        sequence := (specEntry at:1) withoutCEscapes.
        function := specEntry at:2.

        tree := escapeSequenceTree.

        sequence keysAndValuesDo:[:idx :char |
            |followup|

            idx == sequence size ifTrue:[
                tree at:char put:function
            ] ifFalse:[
                followup := tree at:char ifAbsent:nil.
                followup isNil ifTrue:[
                    tree at:char put:(followup := IdentityDictionary new).
                ].
                tree := followup
            ]
        ]
    ].
    escapeLeadingChars := escapeSequenceTree keys asSet.
    escapeLeadingChars add:(Character cr).
    escapeLeadingChars add:(Character return).
    escapeLeadingChars add:(Character backspace).

    escapeLeadingChars := escapeLeadingChars asArray

    "Modified: / 25-01-2012 / 10:42:46 / cg"
!

flushInput
    |sensor|

    "/ flush any leftover input-processing events
    (sensor := self sensor) notNil ifTrue:[
        sensor flushEventsFor:self withType:#processInput:n:.
    ]

    "Modified: / 21.7.1998 / 19:00:13 / cg"
    "Created: / 5.5.1999 / 18:41:42 / cg"
!

initStyle
    super initStyle.
"/    self foregroundColor:Color green.
"/    self backgroundColor:Color black.
!

initialize

    super initialize.

    showMatchingParenthesis := false.
    insertMode := false.
    alwaysAppendAtEnd := false.
    collectSize := 100.
    st80Mode := false.
    trimBlankLines := true.
    localEcho := false.
    inputTranslateCRToNL := false.
    autoWrapFlag := true.
    "/ cursorType := #block.

    numberOfColumns := 80.
    numberOfLines := 24.
    rangeStartLine := 1.
    rangeEndLine := numberOfLines.

    self setTab8.

    self initializeKeyboardSequences.
    list := OrderedCollection new:24 withAll:''.

    OperatingSystem isMSWINDOWSlike ifTrue:[
        kbdSequences at:#Return put:'\r\n'.
    ].
    self initializeKeyboardMap.

    "
     VT52TerminalView openShell
     VT100TerminalView openShell
    "

    "Modified: / 5.5.1999 / 17:54:47 / cg"
!

initializeKeyboardMap
    |keys ctrlKeys cmdKeys|

    "/ setup my own keyboardMap, where control-keys 
    "/ (and some Cmd-keys) are not translated.
    kbdMap := device keyboardMap copy.
    keys := kbdMap keys.

    ctrlKeys := keys select:[:key | key startsWith:'Ctrl'].
    ctrlKeys do:[:key | kbdMap removeKey:key].

    cmdKeys := keys select:[:key | key startsWith:'Cmd'].
    cmdKeys do:[:key | |val|
        val := kbdMap at:key.
        val isSymbol ifTrue:[
            (#(Copy Paste SaveAs Print Find FindNext FindPrev GotoLine) includes:val) ifFalse:[
                kbdMap removeKey:key
            ]
        ]
    ].

    kbdMap removeKey:#Delete ifAbsent:[].
    kbdMap removeKey:#BackSpace ifAbsent:[].

    "
     VT52TerminalView openShell
    "

    "Modified: / 29.4.1999 / 14:25:24 / cg"
!

initializeKeyboardSequences
    kbdSequences := (self anyKeyCodes)

    "Modified: / 5.5.1999 / 15:01:09 / cg"
!

keyboardMap
    "return my keyboard map. This has control keys removed and
     those will be passed unchanged to the shell"

    ^ kbdMap

    "Modified: / 10.6.1998 / 17:46:59 / cg"
!

readerProcessLoop
    "look for the commands output,
     and send me #processInput:n: events whenever something arrives."

    StreamError handle:[:ex |
        Transcript show:'Terminal(PTY-reader) [error]: '; showCR:ex description.
    ] do:[
        [true] whileTrue:[
            AbortOperationRequest handle:[:ex |
                self showCursor.
            ] do:[
                |n sensor|

                Delay waitForSeconds:0.01.
                outStream readWait.
                sensor := self sensor.
                (sensor notNil and:[sensor hasKeyPressEventFor:self]) ifTrue:[
                    true "(sensor userEventCount > 10)" ifTrue:[
                        "/ give terminalView a chance to
                        "/ send out the character.
                        Delay waitForSeconds:0.01.
                    ]
                ] ifFalse:[
                    n := self readAnyAvailableData.
                    n > 0 ifTrue:[
                        shellPid notNil ifTrue:[
                            self waitForOutputToDrain.
                        ]
                    ] ifFalse:[
                        n == 0 ifTrue:[
                            "/ Windows IPC has a bug - it always
                            "/ returns 0 (when the command is idle)
                            "/ and says its at the end (sigh)

                            OperatingSystem isMSWINDOWSlike ifTrue:[
                                Delay waitForSeconds:0.01
                            ] ifFalse:[
                                outStream atEnd ifTrue:[
                                    outStream close. outStream := nil.
                                    inStream close.  inStream := nil.
                                    Processor activeProcess terminate.
                                ] ifFalse:[
                                    "/ this should not happen.

                                    Delay waitForSeconds:0.05
                                ]
                            ].
                        ]
                    ]
                ]
            ]
        ]
    ]
!

reinitialize
    "reinit after a snapIn.
     this is invoked (by the system thread) after a snapShot image restart"

    super reinitialize.

    shellPid := nil.

    self stopReaderProcess.
    self flushInput.

    readerProcess := nil.
    inStream := outStream := nil.

    "/ must fork at low-prio (to avoid running reader at prio31)
    [
       "/ Delay waitForSeconds:0.5.
        self doClearEntireScreen.
        self cursorLine:1 col:1.
        self contents:nil.
        self flash.

        "/
        "/ all I can do is to restart the original command
        "/
        self startCommand:shellCommand in:shellDirectory.
    ] forkAt:8

    "Modified: / 5.5.1999 / 18:41:55 / cg"
!

release
    "release myself - shut down the shell, stop the reader thread."

    [self closeDownShell.
     self flushInput.
    ] fork.
    super release

    "Modified: / 5.5.1999 / 18:42:55 / cg"
!

startReaderProcess
    "Start a reader process, which looks for the commands output,
     and sends me #processInput:n: events whenever something arrives."

    self obsoleteMethodWarning.    
    self startReaderProcessWhenVisible.

    "
     VT100TerminalView openShell
    "

    "Modified: / 5.5.1999 / 17:58:02 / cg"
    "Modified: / 28.1.2002 / 21:10:13 / micha"
!

startReaderProcessNow
    "Start a reader process, which looks for the commands output,
     and sends me #processInput:n: events whenever something arrives."

    readerProcess isNil ifTrue:[
        readerProcess := [
            [
                self readerProcessLoop.
            ] ifCurtailed:[
                readerProcess := nil    
            ]
        ] fork. "/ forkAt:9.
        readerProcess name:'pty reader'.
    ]

    "
     VT100TerminalView openShell
    "

    "Modified: / 5.5.1999 / 17:58:02 / cg"
    "Modified: / 28.1.2002 / 21:10:13 / micha"
!

startReaderProcessWhenVisible
    "Start a reader process, which looks for the commands output,
     and sends me #processInput:n: events whenever something arrives."

    readerProcess isNil ifTrue:[
        readerProcess := [
            [
                self waitUntilVisible.
                self readerProcessLoop.
            ] ifCurtailed:[
                readerProcess := nil    
            ]
        ] fork. "/ forkAt:9.
        readerProcess name:'pty reader'.
    ]

    "
     VT100TerminalView openShell
    "

    "Modified: / 5.5.1999 / 17:58:02 / cg"
    "Modified: / 28.1.2002 / 21:10:13 / micha"
!

stopReaderProcess
    "stop the background reader thread"

    |sensor|

    readerProcess notNil ifTrue:[
        readerProcess terminate.
        "/ give it a chance to really terminate
        Processor yield.
        readerProcess := nil
    ].

    "/ flush any leftover input-processing events
    (sensor := self sensor) notNil ifTrue:[
        sensor flushEventsFor:self withType:#processInput:n:.
    ]
    "Modified: / 21.7.1998 / 19:00:13 / cg"
! !

!TerminalView methodsFor:'initialization-shell'!

basicStartCommand:aCommand in:aDirectory
    "start a command on a pseudo terminal. If the command arg is nil,
     a shell is started. If aDirectory is not nil, the command is
     executed in that directory.
     Also fork a reader process, to read the shells output and
     tell me, whenever something arrives"

    |pty slaveFD execFdArray blocked exitStatus 
     stxToCommandPipe commandToStxPipe cmd shell args env shellAndArgs|

    shellCommand := aCommand.
    shellDirectory := aDirectory.

    self create.  "/ need my windowID (to pass down in environment)

    OperatingSystem isMSWINDOWSlike ifTrue:[
        "use two pipes to COMMAND.COM"
        stxToCommandPipe := NonPositionableExternalStream makePipe.
        stxToCommandPipe isNil ifTrue:[
            self warn:(resources string:'Could not create pipe to COMMAND.COM.'). 
            ^ self.
        ].

        commandToStxPipe := NonPositionableExternalStream makePipe.
        commandToStxPipe isNil ifTrue:[
            self warn:(resources string:'Could not create pipe from COMMAND.COM.'). 
            ^ self.
        ].

        "/ pipe readSide is p at:1;
        "/      writeSide is p at:2

        slaveFD := (commandToStxPipe at:2) fileDescriptor.
        execFdArray := Array 
                         with:(stxToCommandPipe at:1) fileDescriptor        "stdin"
                         with:slaveFD                                       "stdout"
                         with:slaveFD.                                      "stderr"

        outStream := commandToStxPipe at:1.
        inStream  := stxToCommandPipe at:2.

        shellAndArgs := OperatingSystem commandAndArgsForOSCommand:aCommand.
        shell := shellAndArgs at:1.
        args  := (shellAndArgs at:2) ? ''.
    ] ifFalse:[
        "Use a pseudo-tty"
        pty := NonPositionableExternalStream makePTYPair.
        pty isNil ifTrue:[
            self warn:'Cannot open pty.'.
            ^ self.
        ].

        "/ pty at:1 is the master;
        "/ pty at:2 is the slave
        inStream := outStream := (pty at:1).

        self defineWindowSize.
        "/ fork a shell process on the slave-side
        slaveFD := (pty at:2) fileDescriptor.
        execFdArray := Array with:slaveFD with:slaveFD with:slaveFD.

        aCommand isNil ifTrue:[
            shell := OperatingSystem getEnvironment:'SHELL'.
            shell size == 0 ifTrue:[
                shell := '/bin/sh'.
            ].
            cmd := shell asFilename baseName.
            args := (Array with:cmd).
        ] ifFalse:[
            shell := '/bin/sh'.
            args := (Array with:'sh' with:'-c' with:aCommand).
        ].
        env := Dictionary new.
        env at:'SHELL'    put:shell.
        env at:'TERM'     put:(self terminalType).
        env at:'HOME'     put:(OperatingSystem getEnvironment:'HOME').
        env at:'USER'     put:(OperatingSystem getEnvironment:'USER').
        env at:'LINES'    put:(numberOfLines printString).
        env at:'COLUMNS'  put:(numberOfColumns printString).
        (device platformName = 'X11' and:[drawableId notNil]) ifTrue:[
            env at:'WINDOWID' put:(drawableId address printString).
        ].
    ].

    blocked := OperatingSystem blockInterrupts.

    shellPid := Processor
               monitor:[
                  OperatingSystem
                      exec:shell
                      withArguments:args
                      environment:env
                      fileDescriptors:execFdArray
                      fork:true
                      newPgrp:true
                      inDirectory:aDirectory.
               ]
               action:[:status |
                    Debug ifTrue:[
                        Transcript show:'pid:'; showCR:status pid.
                        Transcript show:'status:'; showCR:status status.
                        Transcript show:'code:'; showCR:status code.
                        Transcript show:'core:'; showCR:status core.
                    ].
                    status stillAlive ifFalse:[
                        exitStatus := status.
                        OperatingSystem closePid:shellPid.
                        shellPid := nil.
                        self pushEvent:#shellTerminated
                    ].
               ].

    blocked ifFalse:[
        OperatingSystem unblockInterrupts
    ].

    "close the slave side of the pty/pipes (only used by the child)"
    pty notNil ifTrue:[
        (pty at:2) close.
    ].

    commandToStxPipe notNil ifTrue:[
        (commandToStxPipe at:2) close.
        (stxToCommandPipe at:1) close.
    ].

    shellPid isNil ifTrue:[
        self warn:'Cannot start shell'.
        outStream close.
        inStream close.
        inStream := outStream := nil.
        ^ self.
    ].

    "Created: / 20.7.1998 / 18:19:32 / cg"
    "Modified: / 5.5.1999 / 17:28:37 / cg"
!

startCommand:aCommand
    "start a command on a pseudo terminal. If the command arg is nil,
     a shell is started. The command is started in the current directory.
     Also fork a reader process, to read the shells output and
     tell me, whenever something arrives"

    self startCommand:aCommand in:nil

    "Modified: / 20.7.1998 / 18:30:24 / cg"
!

startCommand:aCommand in:aDirectory
    "start a command on a pseudo terminal. If the command arg is nil,
     a shell is started. If aDirectory is not nil, the command is
     executed in that directory.
     Also fork a reader process, to read the shells output and
     tell me, whenever something arrives"

    self basicStartCommand:aCommand in:aDirectory.
    self startReaderProcessWhenVisible.

    "Created: / 20.7.1998 / 18:19:32 / cg"
    "Modified: / 5.5.1999 / 17:28:37 / cg"
!

startShell
    "start a shell on a pseudo terminal in the current directory.
     Also fork a reader process, to read the shells output and
     tell me, whenever something arrives"

    ^ self startCommand:nil

    "
     VT100TerminalView openShell
    "

    "Modified: / 20.7.1998 / 18:29:54 / cg"
!

startShellIn:aDirectory
    "start a shell on a pseudo terminal in some directory.
     Also fork a reader process, to read the shells output and
     tell me, whenever something arrives"

    self startCommand:nil in:aDirectory

    "
     VT100TerminalView openShellIn:'/etc'
    "

    "Modified: / 20.7.1998 / 18:29:46 / cg"
! !

!TerminalView methodsFor:'menu'!

doClear
    "reset the scroll-range etc, clear the text buffer"

    rangeStartLine := 1.
    rangeEndLine := numberOfLines.

    self normal.
    self clear.

    "Created: / 03-04-2007 / 08:58:59 / cg"
!

doReset
    "reset the scroll-range; 
     may have to reset more in the future (current font-set; color; etc)"

    rangeStartLine := 1.
    rangeEndLine := numberOfLines.

    self normal.

!

doSendInterrupt
    "send an INT-signal to the shell (UNIX only)"

    shellPid notNil ifTrue:[
        OperatingSystem sendSignal:(OperatingSystem sigINT) to:shellPid negated.
    ].

    "Modified: / 10.6.1998 / 17:49:49 / cg"
!

doSendKillSignal
    "send a KILL-signal to the shell (UNIX only)"

    shellPid notNil ifTrue:[
        OperatingSystem sendSignal:(OperatingSystem sigKILL) to:shellPid negated.
    ]
!

editMenu
    "return the views middleButtonMenu"

    <resource: #keyboard (#Copy #Paste #Print #SaveAs #Print)>
    <resource: #programMenu>

    |items subMenu m sensor|

    items := #(
                    ('Interrupt'      doSendInterrupt )  
                    ('Kill'           doSendKillSignal)  
                    ('-'                              )
                    ('Clear'          doClear         )  
                    ('Reset'          doReset         )  
              ).
    subMenu := PopUpMenu itemList:items resources:resources.

    ((sensor := self sensor) notNil and:[sensor ctrlDown]) ifTrue:[
        m := subMenu.
    ] ifFalse:[
        items := #(
                        ('Copy'         copySelection    Copy   )
                        ('Paste'        pasteOrReplace   Paste  )
                        ('-'                                    )
                        ('Search...'    search           Find)
                        ('-'                                    )
                        ('Font...'      changeFont              )
                        ('-'                                    )
                        ('Save As...'   save             SaveAs )
                        ('Print'        doPrint          Print  )
                        ('='                               )
                        ('Shell'        others           Ctrl   )
                  ).
        m := PopUpMenu itemList:items resources:resources.
        m subMenuAt:#others put:subMenu.

"/ disabled - for now;
"/ need a more intelligent filtering of control characters.
"/
"/        filterStream isNil ifTrue:[
"/           items := items , #(
"/                        ('-'                                    )
"/                        ('Start Save as ...'  startSaveAs       )
"/                        ('Start Print'        startPrint        )
"/                             )
"/        ] ifFalse:[
"/           items := items , #(
"/                        ('-'                                    )
"/                        ('Stop filter'  stopFilter              )
"/                             )
"/        ].
    ].

    self hasSelection ifFalse:[
        m disable:#copySelection.
    ].
    ^ m.

    "Modified: / 03-04-2007 / 08:58:26 / cg"
!

startSaveAs
    "start saving all received data to some file"

    |fn|

    fn := Dialog requestFileName:'Save received data in file:'.
    fn size > 0 ifTrue:[
        filterStream := fn asFilename writeStream
    ].

    "Created: / 29.4.1999 / 11:06:29 / cg"
!

stopFilter
    "stop saving/printing of received data"

    filterStream close.
    filterStream := nil.

    "Created: / 29.4.1999 / 11:07:49 / cg"
    "Modified: / 29.4.1999 / 11:09:52 / cg"
! !

!TerminalView methodsFor:'misc'!

removeTrailingBlankLines
    ^ self
! !

!TerminalView methodsFor:'processing-input'!

doNothing
    "private - end of an ignored escape-sequence"

    self endOfSequence

    "Created: / 12.6.1998 / 20:40:43 / cg"
!

endOfSequence
    "private - reset state-machine at end of escape-sequence"

    state := 0.

    "Created: / 12.6.1998 / 20:39:52 / cg"
!

nextPutAll:aString
    "/ self processInput:aString n:aString size

    self pushEvent:#processInput:n: with:aString with:aString size.

    "Created: / 27.7.1998 / 15:10:59 / cg"
    "Modified: / 27.7.1998 / 23:16:19 / cg"
!

processInput:buffer n:count
    |sensor|

    filterStream notNil ifTrue:[
        filterStream nextPutAll:(buffer copyTo:count).
    ].

"/    self hideCursor.

    "/ the following may not be too clean, but adds a lot of speed.
    "/ instead of passing every individual character through the
    "/ escape-state machine, collect chunks of non-control text
    "/ when in state 0, and add them immediately to the pendingLines
    "/ collection of the textCollectors asynchronous update mechanism.
    "/ This helps a lot if you do something like "ls -lR /" ...
    "/ For debugging the state machine, reenable the commented lines
    "/ below.

"/1 to:count do:[:i|
"/    self nextPut:(buffer at:i).
"/].
"/self showCursor.
"/^ self.

    access critical:[
        |index controlCharIndex stringWithOutControl crnlFollows|

        index := 1.
        [index <= count] whileTrue:[
            (state == 0) ifTrue:[
                "/ in initial state.
                "/ quick scan forward for next control character ...
                controlCharIndex := buffer indexOfControlCharacterStartingAt:index.
                controlCharIndex > count ifTrue:[controlCharIndex := 0].

                controlCharIndex == 0 ifTrue:[
                    "/ no control characters - simply append all
                    "/ to the outstanding lines ...
                    stringWithOutControl := buffer copyFrom:index to:count.
                    index := count + 1. "/ leave loop.
                    crnlFollows := false.
                ] ifFalse:[
                    controlCharIndex > index ifTrue:[
                        stringWithOutControl := buffer copyFrom:index to:controlCharIndex-1.
                        index := controlCharIndex. "/ proceed withcontrol character
                        crnlFollows := false.
                        index < (count - 1) ifTrue:[
                            (buffer at:index) == Character return ifTrue:[
                                (buffer at:index+1) == Character nl ifTrue:[
                                    crnlFollows := true.
                                    index := index + 2.
                                ]
                            ]
                        ].
                    ]
                ].
            ].

            stringWithOutControl notNil ifTrue:[
                "/ self endEntry.

                "/ characterwise, for correct wrap handling at line end

                (cursorCol + outstandingLine size + stringWithOutControl size) >= numberOfColumns ifTrue:[
                    self endEntry.
                    stringWithOutControl do:[:eachCharacter |
                        self nextPut:eachCharacter.
                        self endEntry
                    ].
                    crnlFollows ifTrue:[
                        self nextPut:Character return.
                        self nextPut:Character nl.
                    ].
                    self endEntry.
                    stringWithOutControl := nil.    
                ] ifFalse:[

                    Debug ifTrue:[
                        Transcript showCR:'String:<', stringWithOutControl, '>'.
                    ].
                    currentEmphasis notNil ifTrue:[
                        stringWithOutControl := stringWithOutControl emphasizeAllWith:currentEmphasis
                    ].

                    outstandingLine size > 0 ifTrue:[
                        outstandingLine := outstandingLine , stringWithOutControl.
                    ] ifFalse:[
                        outstandingLine := stringWithOutControl.
                    ].
                    crnlFollows ifTrue:[
                        outstandingLines isNil ifTrue:[
                            outstandingLines := OrderedCollection with:outstandingLine
                        ] ifFalse:[
                            outstandingLines add:outstandingLine.
                        ].
                        outstandingLine := ''.
                    ].
                    stringWithOutControl := nil.

                    collecting ifTrue:[
                        flushPending ifFalse:[
                            self installDelayedUpdate
                        ] ifTrue:[
        "/                    outstandingLines size > collectSize ifTrue:[
        "/                        self endEntry
        "/                    ]
                        ]
                    ] ifFalse:[
                        self endEntry
                    ].
                ].
            ] ifFalse:[
                "/ no chunk to append (in an escape sequence)
                "/ must handle individual characters
                "/ to update the state machine.

                self nextPut:(buffer at:index).
                index := index + 1.
                [state ~~ 0 and:[index <= count]] whileTrue:[
                    self nextPut:(buffer at:index).
                    index := index + 1.
                ]
            ]
        ].
    ].

    state == 0 ifTrue:[
        (sensor := self sensor) notNil ifTrue:[
            "/ if there is no more output pending from the shell,
            "/ enforce update of the view (asynchronous)

            (sensor hasEvent:#processInput:n: for:self) ifFalse:[
                self endEntry.
                self showCursor.
                "/ self makeCursorVisible.
            ] ifTrue:[
                "/ if there is more output pending from the shell,
                "/ and many lines have already been collected,
                "/ also enforce update of the view (asynchronous)
                "/ Thus, it will update at least once for every
                "/ collectSize lines.

                outstandingLines size > collectSize ifTrue:[ 
                    self endEntry.
                    self showCursor.

                    "/ make certain that things are really displayed ...
                    windowGroup notNil ifTrue:[
                        windowGroup processRealExposeEventsFor:self.
                    ]
                ].
            ]
        ].
    ].

    "Created: / 10.6.1998 / 17:26:09 / cg"
    "Modified: / 29.4.1999 / 11:08:48 / cg"
    "Modified: / 28.1.2002 / 20:41:36 / micha"
!

readAnyAvailableData
    "read data from the stream,
     and sends me #processInput:n: events if something arrived.
     Returns the amount of data read."

    |buffer n bufferSize|

    outStream isNil ifTrue:[^ 0].

    bufferSize := 512. "/ 1024.

    buffer := String new:bufferSize.
    ExternalStream readErrorSignal handle:[:ex |
        n := 0
    ] do:[
        n := outStream nextAvailableBytes:bufferSize into:buffer startingAt:1.
    ].
    n > 0 ifTrue:[
        self pushEvent:#processInput:n: with:buffer with:n.
    ].

    ^ n

    "Created: / 5.5.1999 / 17:57:39 / cg"
    "Modified: / 8.5.1999 / 20:14:14 / cg"
    "Modified: / 28.1.2002 / 21:10:25 / micha"
!

sendLine:aString
    inStream nextPutAll:aString.
    OperatingSystem isMSDOSlike ifTrue:[
        inStream nextPut:Character return.
        inStream nextPut:Character linefeed.
    ] ifFalse:[
        inStream nextPut:Character return.
    ].
!

sync
    self waitForOutputToDrain

    "Created: / 27.7.1998 / 23:49:44 / cg"
!

waitForOutputToDrain
    |sensor|

    sensor := self sensor.
    (sensor notNil and:[sensor userEventCount > 30]) ifTrue:[
        [sensor userEventCount > 5] whileTrue:[
            "/ give terminalView a chance to
            "/ catch up.
            Delay waitForSeconds:0.1.
        ]
    ].

    "Created: / 27.7.1998 / 23:47:22 / cg"
    "Modified: / 5.5.1999 / 18:51:00 / cg"
! !

!TerminalView methodsFor:'queries'!

preferredExtent
    "return my preferred extent - this is computed from my numberOfLines,
     numberOfCols and font size"

    ^ (fontWidth * self class defaultNumberOfColumns + (leftMargin + margin * 2))
      @ 
      ((self heightForLines:self class defaultNumberOfLines) + 8)

    "Modified: / 20.6.1998 / 20:06:57 / cg"
!

terminalType
    "returns a string describing this terminal (usually, this is
     passed down to the shell as TERM environment variable).
     Here, 'dump' is returned."

    ^ 'dump'

    "Created: / 10.6.1998 / 16:22:30 / cg"
    "Modified: / 5.5.1999 / 11:22:32 / cg"
! !

!TerminalView methodsFor:'searching'!

startPositionForSearchBackward
    ^ self startPositionForSearchBackwardBasedOnSelection
!

startPositionForSearchForward
    ^ self startPositionForSearchForwardBasedOnSelection
! !

!TerminalView methodsFor:'selection handling'!

autoMoveCursorToEndOfSelection
    "Redefined to return false since the cursor should
     not be affected by selecting"

    ^ false

!

paste:someText
    "paste - redefined to send the chars to the shell instead
     of pasting into the view"

    |s nLines|

    inStream isNil ifTrue:[
        self flash.
        ^ self           "/ already closed
    ]. 

    s := someText.
    s isString ifTrue:[
        s := s asStringCollection
    ] ifFalse:[
        (s isKindOf:StringCollection) ifFalse:[
            self warn:'selection (' , s class name , ') is not convertable to Text'.
            ^ self
        ]
    ].
    (nLines := s size) == 0 ifTrue:[^ self].
    (nLines == 1 and:[(s at:1) size == 0]) ifTrue:[^ self].
    s keysAndValuesDo:[:idx :line |
        line notNil ifTrue:[inStream nextPutAll:line].
        idx ~~ nLines ifTrue:[
            inStream nextPut:(Character return).
        ]
    ].

    "Modified: / 12.6.1998 / 22:12:47 / cg"
! !

!TerminalView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/TerminalView.st,v 1.140 2013-06-27 13:54:28 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libwidg2/TerminalView.st,v 1.140 2013-06-27 13:54:28 cg Exp $'
! !


TerminalView initialize!