TerminalView.st
author Claus Gittinger <cg@exept.de>
Tue, 27 Apr 1999 19:51:00 +0200
changeset 1341 3467ffd6eb35
parent 1339 17bdf3424085
child 1342 271a9b90688a
permissions -rw-r--r--
first attempt in supporting win32; does not work yet.

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

!TerminalView class methodsFor:'documentation'!

documentation
"
    I provide terminal functionality, by forking a command interpreter
    and comunicating with it via a pty.
    I am abstract - concrete terminal characteristics are defined
    by concrete subclasses (see VT52TerminalView).

    [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

    [start with:]
        VT52TerminalView openShell
        VT100TerminalView openShell
"
! !

!TerminalView class methodsFor:'defaults'!

defaultIcon
    ^ Image fromFile:'bitmaps/xpmBitmaps/terminal_images/xterm-icon.xpm'

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

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

    |in top scr vt52|

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

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

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

    ^ vt52

    "
     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). Keys pressed are sent to inStream, text appearing
     from outStream are displayed in the terminal view.
     This can be used to implement things like rlogin
     or telnet views (if connected to a modem, a call-unix can also be
     implemented this way)."

    |in top scr vt52|

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

    vt52 inStream:inStream.
    vt52 outStream:outStream.
    vt52 startReaderProcess.

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

    "Modified: / 4.8.1998 / 17:48: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)"

    |in top scr vt52|

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

    vt52 startShellIn:aDirectory.
    vt52 shellTerminateAction:[top destroy].

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

    ^ vt52

    "
     VT100TerminalView openShellIn:'/etc'
    "

    "Created: / 20.7.1998 / 18:28:15 / cg"
    "Modified: / 4.8.1998 / 17:48:54 / 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'!

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

    ^ inStream!

inStream:something
    "set the value of the instance variable 'inStream' (automatically generated)"

    inStream := something.!

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

    ^ outStream!

outStream:something
    "set the value of the instance variable 'outStream' (automatically generated)"

    outStream := something.!

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

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

!TerminalView methodsFor:'cursor handling'!

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

    ^ super cursorCol:(col min:numberOfColumns)

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

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

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

    ^ super cursorLine:l col:(col min:numberOfColumns)

    "Modified: / 10.6.1998 / 15:09:38 / 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"
!

restoreCursor
    |l c|

    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 min:numberOfColumns

    "Modified: / 10.6.1998 / 15:09:41 / 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"
!

defineWindowSize
    |fd delta|

    OperatingSystem isMSWINDOWSlike ifTrue:[^ self].

    (inStream notNil 
    and:[inStream isExternalStream
    and:[inStream isOpen]]) ifTrue:[
        numberOfColumns := (innerWidth // font width).
        (OperatingSystem 
            setWindowSizeOnFileDescriptor:inStream fileDescriptor
            width:numberOfColumns
            height:(nFullLinesShown)) ifFalse:[
"/            Transcript showCR:'VT100: cannot change windowSize'.
        ].
        delta := numberOfLines - rangeEndLine.
        numberOfLines := nFullLinesShown.
        rangeEndLine := numberOfLines - delta.
"/        Transcript showCR:'VT100: changed len to ', numberOfLines printString.
    ].
    shellPid notNil ifTrue:[
        OperatingSystem sendSignal:OperatingSystem sigWINCH to:shellPid
    ]

    "Created: / 11.6.1998 / 22:51:39 / cg"
    "Modified: / 27.4.1999 / 19:33:24 / cg"
!

keyPress:aKey x:x y:y
    |rest rawKey seq|

    inStream isNil ifTrue:[^ self].

"/ Transcript showCR:'----'; show:'key:' ; showCR:aKey printString.

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

    aKey == #Tab ifTrue:[
"/ Transcript show:'->' ; showCR:Character tab storeString.
        inStream nextPut:Character tab.
        ^ self
    ].

    seq := kbdSequences at:aKey ifAbsent:nil.
    seq notNil ifTrue:[
"/ Transcript show:'->' ; showCR:seq storeString.
        inStream nextPutAll:(seq withEscapes).
        ^ self
    ].

    rawKey := device keyboardMap keyAtValue:aKey ifAbsent:aKey.
    seq := kbdSequences at:rawKey ifAbsent:nil.
    seq notNil ifTrue:[
"/ Transcript show:'->' ; showCR:seq storeString.
        inStream nextPutAll:(seq withEscapes).
        ^ self
    ].

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

    Transcript show:'unhandled: '; showCR:rawKey.

    "Modified: / 12.6.1998 / 22:16:50 / cg"
!

shellTerminated
    self closeDownShell.
    shellTerminateAction notNil ifTrue:[
        shellTerminateAction value
    ] ifFalse:[
        "/ may be removed ...
        self warn:'shell terminated'.
    ]

    "Modified: / 12.6.1998 / 17:03:26 / 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
    self doClearEntireScreen.

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

doClearEntireScreen
    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
    |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
    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
    |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
    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
    |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
    self cursorVisibleLine:1 col:1
    "/ super cursorHome

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

doCursorLeft:n
    n timesRepeat:[
        super cursorLeft
    ]

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

doCursorNewLine
    super cursorDown:1

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

doCursorReturn
    super cursorToBeginOfLine
!

doCursorRight:n
    self cursorCol:(cursorCol + n)

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

doCursorUp:n
    |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-shell'!

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"

    |p slaveFD execFdArray closeFdArray blocked exitStatus 
     stxToCommandPipe commandToStxPipe cmd shell args env wDir shellAndArgs|

    shellCommand := aCommand.
    shellDirectory := aDirectory.

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

    OperatingSystem isMSWINDOWSlike ifTrue:[
        "/ must use another mechanism

        stxToCommandPipe := OperatingSystem makePipe.
        stxToCommandPipe isNil ifTrue:[
            ^ self warn:'Could not create pipe.'.
        ].
        commandToStxPipe := OperatingSystem makePipe.
        commandToStxPipe isNil ifTrue:[
            ^ self warn:'Could not create pipe.'.
        ].

        shellAndArgs := OperatingSystem commandAndArgsForOSCommand:aCommand.
        shell := shellAndArgs at:1.
        args  := (shellAndArgs at:2) ? ''.

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

        execFdArray := Array 
                         with:(stxToCommandPipe at:1)
                         with:(commandToStxPipe at:2)
                         with:(commandToStxPipe at:2).

        closeFdArray := #(). 
"/                        Array 
"/                         with:(stxToCommandPipe at:2)
"/                         with:(commandToStxPipe at:1).


        outStream := ExternalStream forReadingFromFileDescriptor:(commandToStxPipe at:1).
        inStream := ExternalStream forWritingToFileDescriptor:(stxToCommandPipe at:2).
        outStream buffered:false.
        inStream buffered:false.
    ] ifFalse:[
        p := ExternalStream makePTYPair.
        p isNil ifTrue:[
            self warn:'Cannot open pty'.
            ^ self.
        ].

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

        self defineWindowSize.

        "/ fork a shell process on the slave-side
        slaveFD := (p at:2) fileDescriptor.

        execFdArray := Array with:slaveFD with:slaveFD with:slaveFD.
        closeFdArray := #().
        
        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).
        ].
    ].

    blocked := OperatingSystem blockInterrupts.

    shellPid := Processor
               monitor:[
                  OperatingSystem isMSWINDOWSlike ifTrue:[
                      OperatingSystem
                          exec:shell
                          withArguments:args
                          fileDescriptors:execFdArray
                          closeDescriptors:closeFdArray
                          fork:true
                          newPgrp:true
                          inDirectory:aDirectory.
                  ] ifFalse:[
                      env := Dictionary new.
                      env at:'TERM'     put:(self terminalType).
                      env at:'LINES'    put:(numberOfLines printString).
                      env at:'COLUMNS'  put:(numberOfColumns printString).
                      drawableId notNil ifTrue:[
                          env at:'WINDOWID' put:(drawableId address printString).
                      ].
                      env at:'SHELL'  put:shell.

                      OperatingSystem
                          exec:shell
                          withArguments:args
                          environment:env
                          fileDescriptors:execFdArray
                          closeDescriptors:closeFdArray
                          fork:true
                          newPgrp:true
                          inDirectory:aDirectory.
                  ]
               ]
               action:[:status |
"/                  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
                  ].
               ].

    shellPid isNil ifTrue:[
        self warn:'Cannot start shell'.
        (p at:1) close.
        (p at:2) close.
    ].

    blocked ifFalse:[
        OperatingSystem unblockInterrupts
    ].

    self startReaderProcess.

    "Created: / 20.7.1998 / 18:19:32 / cg"
    "Modified: / 27.4.1999 / 19:31:39 / 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:'initialize / release'!

closeDownShell
    |pid|

    (pid := shellPid) notNil 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: / 27.4.1999 / 19:31:18 / cg"
!

destroy
    self closeDownShell.
    super destroy
!

escapeSequences:codes
    |tree|

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

    codes do:[:specEntry |
        |sequence function|

        sequence := (specEntry at:1) withEscapes.
        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: / 9.6.1998 / 19:43:12 / cg"
!

initialize
    super initialize.

    showMatchingParenthesis := false.
    insertMode := false.
    alwaysAppendAtEnd := false.
    collectSize := 100.
    st80Mode := false.
    trimBlankLines := true.

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

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

    self initializeKeyboardMap.

    "
     VT52TerminalView openShell
     VT100TerminalView openShell
    "

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

initializeKeyboardMap
    |ctrlKeys cmdKeys|

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

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

    cmdKeys := kbdMap keys select:[:key | key startsWith:'Cmd'].
    cmdKeys do:[:key | 
        (#(Copy Paste SaveAs Print) includes:(kbdMap at:key)) ifFalse:[
            kbdMap removeKey:key
        ]
    ].

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

    "
     VT52TerminalView openShell
    "

    "Modified: / 12.6.1998 / 22:18:23 / cg"
!

initializeKeyboardSequences
    self subclassResponsibility.
!

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

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

    super reinitialize.

    shellPid := nil.

    self stopReaderProcess.
    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
!

startReaderProcess
    "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.

                Stream streamErrorSignal handle:[:ex |
                    Transcript show:'Terminal [error]: '; showCR:ex errorString.
                    Transcript show:'Terminal [info]: '; showCR:OperatingSystem lastErrorString.
                ] do:[
                    [true] whileTrue:[
                        Object abortSignal handle:[:ex |
                            self showCursor.
                        ] do:[
                            |buffer n sensor|

                            outStream readWait.
                            (sensor := self sensor hasKeyPressEventFor:self) ifTrue:[
                                true "(sensor userEventCount > 10)" ifTrue:[
                                    "/ give terminalView a chance to
                                    "/ send out the character.
                                    Delay waitForSeconds:0.01.
                                ]
                            ] ifFalse:[
                                buffer := String new:1024.
                                n := outStream nextAvailableBytes:1024 into:buffer startingAt:1.
                                n > 0 ifTrue:[
                                    self pushEvent:#processInput:n: with:buffer with:n.
                                    self waitForOutputToDrain.
                                ] ifFalse:[
                                    n == 0 ifTrue:[
                                        outStream atEnd ifTrue:[
                                            outStream close. outStream := nil.
                                            inStream close.  inStream := nil.
                                            
                                            Processor activeProcess terminate.
                                        ] ifFalse:[
                                            "/ this should not happen.

                                            Delay waitForSeconds:0.05
                                        ]
                                    ]
                                ]
                            ]
                        ]
                    ]
                ]
            ] valueOnUnwindDo:[
                readerProcess := nil    
            ]
        ] fork. "/ forkAt:9.
        readerProcess name:'pty reader'.
    ]

    "
     VT100TerminalView openShell
    "

    "Modified: / 27.7.1998 / 23:47:55 / cg"
!

stopReaderProcess
    |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:'menu'!

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
    OperatingSystem sendSignal:(OperatingSystem sigINT) to:shellPid negated.

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

editMenu
    "return the views middleButtonMenu"

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

    |items m sub shortKeys sensor|

    ((sensor := self sensor) notNil and:[sensor ctrlDown]) ifTrue:[
        items := #(
                        ('Interrupt'      doSendInterrupt)  
                        ('-'                                    )
                        ('Reset'          doReset)  
                  ).
    ] ifFalse:[
        items := #(
                        ('copy'         copySelection    Copy   )
                        ('paste'        pasteOrReplace   Paste  )
                        ('-'                                    )
                        ('font ...'     changeFont              )
                        ('-'                                    )
                        ('save as ...'  save             SaveAs )
                        ('print'        doPrint          Print  )
                  ).
    ].

    m := PopUpMenu itemList:items resources:resources.

    self hasSelection not ifTrue:[
        m disable:#copySelection.
    ].
    ^ m.

    "Modified: / 12.6.1998 / 22:33:33 / cg"
! !

!TerminalView methodsFor:'misc'!

removeTrailingBlankLines
    ^ self
! !

!TerminalView methodsFor:'processing - input'!

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|

"/    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:[
        |i i2 s crnlFollows|

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

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

            s notNil ifTrue:[
                currentEmphasis notNil ifTrue:[
                    s := s emphasizeAllWith:currentEmphasis
                ].

                outstandingLine size > 0 ifTrue:[
                    outstandingLine := outstandingLine , s.
                ] ifFalse:[
                    outstandingLine := s.
                ].
                crnlFollows ifTrue:[
                    outstandingLines isNil ifTrue:[
                        outstandingLines := OrderedCollection with:outstandingLine
                    ] ifFalse:[
                        outstandingLines add:outstandingLine.
                    ].
                    outstandingLine := ''.
                ].
                s := 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:i).
                i := i + 1.
                [state ~~ 0 and:[i <= count]] whileTrue:[
                    self nextPut:(buffer at:i).
                    i := i + 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: / 14.8.1998 / 13:43:35 / cg"
!

sync
    self waitForOutputToDrain

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

waitForOutputToDrain
    |sensor|

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

    "Modified: / 27.7.1998 / 23:16:19 / cg"
    "Created: / 27.7.1998 / 23:47:22 / cg"
! !

!TerminalView methodsFor:'queries'!

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

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

terminalType
    ^ #dump

    "Modified: / 10.6.1998 / 14:47:03 / cg"
    "Created: / 10.6.1998 / 16:22:30 / cg"
! !

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

    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 |
        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.71 1999-04-27 17:51:00 cg Exp $'
! !