TerminalView.st
author Claus Gittinger <cg@exept.de>
Fri, 12 Jun 1998 22:20:29 +0200
changeset 950 9e5834388a79
parent 948 b93aba7db15d
child 951 a9e48f549763
permissions -rw-r--r--
fixed paste & command keys

TextCollector subclass:#TerminalView
	instanceVariableNames:'inStream outStream readerProcess shellPid kbdSequences
		escapeSequenceTree currentSequence currentTree kbdMap
		escapeLeadingChars numberOfColumns numberOfLines
		shellTerminateAction'
	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:'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 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 := ScrollableView for:self in:top.
    scr origin:0.0@0.0 corner:1.0@1.0.
    vt52 := scr scrolledView.

    vt52 startShell.
    vt52 shellTerminateAction:[top destroy].

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

    "
     VT100TerminalView openShell
    "

    "Modified: / 12.6.1998 / 21:43:41 / 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.!

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

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

defineWindowSize
    inStream notNil ifTrue:[
        OperatingSystem 
            setWindowSizeOnFileDescriptor:(inStream fileDescriptor)
            width:(innerWidth // font width)
            height:(nFullLinesShown).
"/        numberOfLines := nFullLinesShown.
    ].
    shellPid notNil ifTrue:[
        OperatingSystem sendSignal:OperatingSystem sigWINCH to:shellPid
    ]

    "Created: / 11.6.1998 / 22:51:39 / cg"
    "Modified: / 12.6.1998 / 21:43:20 / 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
    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 / 17:08:23 / cg"
!

doCursorDown
    super cursorDown:1

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

doCursorDown:n
    super cursorDown:n

    "Created: / 10.6.1998 / 15:15:05 / cg"
    "Modified: / 10.6.1998 / 16:55:25 / cg"
!

doCursorHome
    self cursorVisibleLine:1 col:1
    "/ super cursorHome

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

doCursorLeft
    super cursorLeft
!

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

doCursorRight:n
    self cursorCol:(cursorCol + n)

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

doCursorUp
    super cursorUp
!

doCursorUp:n
    n timesRepeat:[
        super cursorUp
    ]

    "Created: / 11.6.1998 / 22:29:46 / cg"
!

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

    "Modified: / 10.6.1998 / 17:49:49 / 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 / 17:53:49 / 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.

    numberOfColumns := 80.
    numberOfLines := 25.

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

    self initializeKeyboardMap.

    "
     VT52TerminalView openShell
     VT100TerminalView openShell
    "

    "Modified: / 12.6.1998 / 20:39:02 / 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"
!

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

    readerProcess isNil ifTrue:[
        readerProcess := [
            [
                self waitUntilVisible.

                Stream streamErrorSignal handle:[:ex |
                    Transcript showCR:ex errorString.
                    Transcript showCR:OperatingSystem lastErrorString.
                ] do:[
                    [true] whileTrue:[
                        Object abortSignal handle:[:ex |
                            self showCursor.
                        ] do:[
                            |buffer n|

                            outStream readWait.
                            (self sensor hasKeyPressEventFor:self) ifTrue:[
                                Processor yield
                            ] ifFalse:[
                                buffer := String new:1024.
                                n := outStream nextAvailableBytes:1024 into:buffer startingAt:1.

                                n > 0 ifTrue:[
                                    self pushEvent:#processInput:n: with:buffer with:n.
                                ] ifFalse:[
                                    n == 0 ifTrue:[
                                        outStream atEnd ifTrue:[
                                            outStream close. outStream := nil.
                                            inStream close.  inStream := nil.
                                            
                                            Processor activeProcess terminate.
                                        ]
                                    ]
                                ]
                            ]
                        ]
                    ]
                ]
            ] valueOnUnwindDo:[
                readerProcess := nil    
            ]
        ] fork.
    ]

    "
     VT100TerminalView openShell
    "

    "Modified: / 12.6.1998 / 20:59:05 / cg"
!

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

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

    self defineWindowSize.

    "/ 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:[
                  |e|

                  e := Dictionary new.
                  e at:'TERM'    put:(self terminalType).
                  e at:'LINES'   put:nil.
                  e at:'COLUMNS' put:nil.

                  OperatingSystem
                      exec:'/bin/sh'
                      withArguments:#('sh')
                      environment:e
                      fileDescriptors:execFdArray
                      closeDescriptors:#()
                      fork:true
                      newPgrp:true.
               ]
               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.

    "
     VT100TerminalView openShell
    "

    "Modified: / 12.6.1998 / 20:59:32 / cg"
! !

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

processInput:buffer n:count
    1 to:count do:[:i |
        self nextPut:(buffer at:i).
    ].

    (self sensor hasEvent:#processInput:n: for:self) ifFalse:[
        self endEntry.
        self makeCursorVisible.
    ].

    "Created: / 10.6.1998 / 17:26:09 / cg"
    "Modified: / 12.6.1998 / 20:45:52 / cg"
! !

!TerminalView methodsFor:'queries'!

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

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

terminalType
    ^ #dump

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

!TerminalView methodsFor:'selection handling'!

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.29 1998-06-12 20:20:29 cg Exp $'
! !