TerminalView.st
author Claus Gittinger <cg@exept.de>
Wed, 10 Jun 1998 15:47:42 +0200
changeset 928 f9a117cb2bcc
parent 926 df8d2a821687
child 929 30a2a3329055
permissions -rw-r--r--
checkin from browser

TextCollector subclass:#TerminalView
	instanceVariableNames:'inStream outStream readerProcess shellPid kbdSequences
		escapeSequenceTree currentSequence currentTree kbdMap
		escapeLeadingChars numberOfColumns numberOfLines'
	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

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

!TerminalView class methodsFor:'testing'!

open
    self openShell

    "
     VT100TerminalView open
    "

    "Modified: / 10.6.1998 / 15:06:35 / cg"
    "Created: / 10.6.1998 / 15:47:25 / cg"
!

openDummy
    |in vt52|

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

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

    "
     self openDummy
    "
!

openShell
    |in top scr vt52|

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

    vt52 startShell.

    top extent:(scr preferredExtent).
    top label:'shell'.
    top open

    "
     VT52TerminalView openShell
    "

    "Modified: / 10.6.1998 / 15:06:35 / 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.! !

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

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

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

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

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

"/    super keyPress:aKey x:x y:y

    "Modified: / 10.6.1998 / 14:01:32 / cg"
!

shellTerminated
    self warn:'shell terminated'.
    self closeDownShell.
! !

!TerminalView methodsFor:'functions'!

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

!

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

    "Created: / 10.6.1998 / 14:43:06 / cg"
    "Modified: / 10.6.1998 / 14:58:07 / cg"
!

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

    "Modified: / 10.6.1998 / 14:45:43 / cg"
!

doClearToEndOfLine
    |l|

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

    "Created: / 10.6.1998 / 14:45:01 / cg"
    "Modified: / 10.6.1998 / 15:16:05 / cg"
!

doCursorDown
    super cursorDown
!

doCursorDown:n
    n timesRepeat:[
        super cursorDown
    ]

    "Created: / 10.6.1998 / 15:15:05 / cg"
!

doCursorHome
    super cursorHome
!

doCursorLeft
    super cursorLeft
!

doCursorNewLine
    super cursorDown
!

doCursorReturn
    super cursorToBeginOfLine
!

doCursorRight
    super cursorRight
!

doCursorRight:n
    self cursorCol:(cursorCol + n)

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

doCursorUp
    super cursorUp
!

doSendInterrupt
    OperatingSystem sendSignal:(OperatingSystem sigINT) to:shellPid negated.

    "Modified: / 10.6.1998 / 15:22:22 / cg"
! !

!TerminalView methodsFor:'initialization'!

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 killProcessGroup:pid.
            OperatingSystem killProcess:pid.
            shellPid := nil.
        ].
        OperatingSystem closePid:pid.
    ].

    readerProcess notNil ifTrue:[
        readerProcess terminate.
        readerProcess := nil
    ].
    inStream notNil ifTrue:[
        inStream close.
        inStream := nil
    ].
    outStream notNil ifTrue:[
        outStream close.
        outStream := nil
    ].

    "Modified: / 10.6.1998 / 12:08:25 / 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.

    numberOfColumns := 80.
    numberOfLines := 25.

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

    self initializeKeyboardMap.

    "
     VT52TerminalView openShell
     VT100TerminalView openShell
    "

    "Modified: / 10.6.1998 / 14:47:09 / cg"
!

initializeEscapeSequences
    self subclassResponsibility.
!

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 | kbdMap removeKey:key].

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

    "
     VT52TerminalView openShell
    "
!

initializeKeyboardSequences
    self subclassResponsibility.
!

keyboardMap
    ^ kbdMap
!

startReaderProcess
    readerProcess isNil ifTrue:[
        readerProcess := [
            [
                |buffer n reading|

                reading := true.
                Stream errorSignal catch:[
                    buffer := String new:1024.
                    [true] whileTrue:[
                        Object abortSignal handle:[:ex |
                            self showCursor.
                        ] do:[
                            outStream readWait.
                            n := outStream nextAvailableBytes:1024 into:buffer startingAt:1.

                            n > 0 ifTrue:[
                                self nextPutAll:(buffer copyTo:n).
                            ] ifFalse:[
                                n == 0 ifTrue:[
                                    outStream atEnd ifTrue:[
                                        outStream close. outStream := nil.
                                        inStream close.  inStream := nil.
                                        
                                        Processor activeProcess terminate.
                                    ]
                                ]
                            ]
                        ]
                    ]
                ]
            ] valueOnUnwindDo:[
                readerProcess := nil    
            ]
        ] fork.
    ]

    "
     VT52TerminalView openShell
    "

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

startShell
    |p slaveFD execFdArray blocked exitStatus|

    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.

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

    execFdArray := Array with:slaveFD with:slaveFD with:slaveFD.

    blocked := OperatingSystem blockInterrupts.

    shellPid := Processor
               monitor:[
                  OperatingSystem
                      exec:'/bin/sh'
                      withArguments:#('sh')
                      fileDescriptors:execFdArray
                      closeDescriptors:#()
                      fork:true
                      newPgrp:true
                      inDirectory:nil.
               ]
               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 halt.
        (p at:1) close.
        (p at:2) close.
    ].

    blocked ifFalse:[
        OperatingSystem unblockInterrupts
    ].

    self startReaderProcess.

    "
     VT52TerminalView openShell
    "
! !

!TerminalView methodsFor:'menu'!

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)  
                  ).
    ] ifFalse:[
        items := #(
                        ('copy'         copySelection    Copy   )
                        ('paste'        pasteOrReplace   Paste  )
                        ('-'                                    )
                        ('save as ...'  save             SaveAs )
                        ('print'        doPrint          Print  )
                  ).
    ].

    m := PopUpMenu itemList:items resources:resources.

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

    "Modified: / 21.5.1998 / 15:52:38 / cg"


! !

!TerminalView methodsFor:'misc'!

removeTrailingBlankLines
    ^ self
! !

!TerminalView methodsFor:'processing - input'!

basicNextPut:aCharacter
    super nextPut:aCharacter
!

nextPut:aCharacter
    |where next|

"/    Transcript showCR:aCharacter asciiValue.

    where := currentTree ? escapeSequenceTree.
"/    Transcript showCR:'current: ' , where storeString.

    next := where at:aCharacter ifAbsent:nil.
"/    Transcript showCR:'next: ' , next storeString.
    next isNil ifTrue:[
        "/ something collected so far ?
        currentSequence notNil ifTrue:[
            self halt.
        ].

        self replaceCharAtCursor:aCharacter.
        "/ self cursorRight.

        currentTree := nil.
        ^ self.
    ].

    next isSymbol ifTrue:[
        self perform:next.
        currentTree := nil.
        ^ self
    ].
    currentTree := next
!

nextPutAll:aCollection
    |l idx idx2 wasOn|

    wasOn := self hideCursor.

    l := aCollection size.
    idx := 1.
    [idx <= l] whileTrue:[
"/        currentTree isNil ifTrue:[
"/            idx2 := aCollection indexOfAny:escapeLeadingChars startingAt:idx.
"/            idx2 == 0 ifTrue:[
"/                self replaceAllAtCursor:(aCollection copyFrom:idx).
"/                self makeCursorVisibleAndShowCursor:wasOn.
"/                ^ self
"/            ].
"/            self replaceAllAtCursor:(aCollection copyFrom:idx to:idx2-1).
"/            idx := idx2.
"/        ].
        self nextPut:(aCollection at:idx).
        idx := idx + 1.
    ].

    self makeCursorVisibleAndShowCursor:wasOn.

    "VT52TerminalView openShell"

    "Modified: / 9.6.1998 / 20:46:29 / cg"
! !

!TerminalView methodsFor:'queries'!

preferredExtent
    ^ (fontWidth * numberOfColumns + (leftMargin * 2)) @ (self heightForLines:numberOfLines)

    "Modified: / 10.6.1998 / 14:47:03 / cg"
! !

!TerminalView methodsFor:'selection handling'!

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

    someText asString string do:[:aChar |
        inStream nextPut:aChar
    ]
! !

!TerminalView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/TerminalView.st,v 1.13 1998-06-10 13:47:42 cg Exp $'
! !