VT100TerminalView.st
author Claus Gittinger <cg@exept.de>
Tue, 28 Jul 1998 12:06:14 +0200
changeset 1020 035490ba97f2
parent 1016 2d8e8b9bb9a5
child 1056 4390f680fcce
permissions -rw-r--r--
checkin from browser

TerminalView subclass:#VT100TerminalView
	instanceVariableNames:'currentParam parameters lastCursorLine'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-TerminalViews'
!

!VT100TerminalView class methodsFor:'documentation'!

documentation
"
    VT100 terminal

    [start with:]
        VT100TerminalView openShell
"


! !

!VT100TerminalView methodsFor:'defaults'!

vt100KeyCodes
    ^ IdentityDictionary withKeysAndValues:
        #(
             #CursorUp    '\e[A'
             #CursorDown  '\e[B'
             #CursorRight '\e[C'
             #CursorLeft  '\e[D'
             #Home        '\e[H'
             #Escape      '\e'
             #BackSpace   '\b'
             #Return      '\r'
             #Delete      '\0177'
         )

    "Created: / 10.6.1998 / 15:13:01 / cg"
    "Modified: / 20.6.1998 / 17:36:33 / cg"
! !

!VT100TerminalView methodsFor:'functions'!

addLines
    "Add the appropriate number of blank lines at the position
     indicated by the cursor."

    self addLines: ((parameters at: 1) max: 1).
    self endOfSequence

    "Created: / 10.6.1998 / 14:48:03 / cg"
!

addLines: aNumber
    "Add aNumber blank lines at the position indicated by the cursor."

    aNumber timesRepeat: [
        self insertLine:'' before:cursorLine
    ]

    "Created: / 10.6.1998 / 14:49:30 / cg"
!

autoMargin:aBoolean
    "set/clear autowrap at end of line (not yet implemented)"

    "Created: / 12.6.1998 / 21:42:06 / cg"
!

clearLines
    "Clear some part of the current line, as indicated by the first parameter."

    |arg|

    arg := parameters at: 1.

    arg = 0 ifTrue: [^self doClearToEndOfLine].
    arg = 1 ifTrue: [^self doClearFromBeginningOfLine].
    arg = 2 ifTrue: [^self doClearEntireLine]

    "Created: / 10.6.1998 / 14:44:22 / cg"
    "Modified: / 21.7.1998 / 20:07:42 / cg"
!

deleteCharacters
    "Delete the appropriate number of characters at the position
     indicated by the cursor."

    |n|

    n := ((parameters at: 1) max: 1).
    self deleteFromLine:cursorLine col:cursorCol toLine:cursorLine col:cursorCol+n-1.

    "Created: / 12.6.1998 / 21:19:02 / cg"
    "Modified: / 12.6.1998 / 21:19:15 / cg"
!

displayMode: anInteger
    "Set the current display mode."

"/    self endEntry.
    (parameters at:1) == 1 ifTrue:[
        "/ ESC-[-1-m  -> bold

        self bold.
        ^ self.
    ].
    (parameters at:1) == 7 ifTrue:[
        "/ ESC-[-7-m  -> revers

        self reverse.
        ^ self.
    ].

    "/ ESC-[-any-m  -> normal
    self normal.

    "Created: / 10.6.1998 / 15:01:16 / cg"
    "Modified: / 28.7.1998 / 00:51:57 / cg"
!

doClearDisplay
    "Clear some part of the current screen, as indicated by the first parameter."

    |arg|

    arg := parameters at: 1.

    arg = 0 ifTrue: [^self doClearToEndOfScreen].
    arg = 1 ifTrue: [^self doClearFromBeginningOfScreen].
    arg = 2 ifTrue: [^self doClearEntireScreen]

    "Created: / 21.7.1998 / 20:05:07 / cg"
    "Modified: / 21.7.1998 / 20:07:36 / cg"
!

insertCharacters
    "Insert the appropriate number of spaces at the position
     indicated by the cursor."

    |s|

    s := String new:((parameters at: 1) max: 1).
    self insertStringWithoutCRsAtLine:cursorLine col:cursorCol.

    "Modified: / 12.6.1998 / 21:14:25 / cg"
    "Created: / 28.7.1998 / 00:53:51 / cg"
!

move
    "Move to the locations indicated by the first and second parameters."

    self moveToX: ((parameters at: 2) max: 1) y: ((parameters at: 1) max: 1).

    "Created: / 10.6.1998 / 14:40:01 / cg"
    "Modified: / 20.6.1998 / 18:49:12 / cg"
!

moveToX: xLocation y: yLocation
    "Position the cursor at the location given by xLocation and yLocation.
     Ignore the command if the parameters are outside the allowable range."

"/ Transcript show:'numberOfColumns '; showCR:numberOfColumns.
"/ Transcript show:'numberOfLines '; showCR:numberOfLines.

"/    (xLocation < 1 or: [xLocation > numberOfColumns]) ifTrue: [^self].
"/    (yLocation < 1 or: [yLocation > numberOfLines]) ifTrue: [^self].

    self cursorVisibleLine:yLocation col:xLocation.

    "Created: / 10.6.1998 / 14:40:49 / cg"
    "Modified: / 20.6.1998 / 20:27:11 / cg"
!

reportTerminalType
    (parameters at: 1) == 6 ifTrue:[
        "/ report position
        self endEntry.

        inStream nextPut:(Character esc).
        inStream nextPutAll:'[' 
                            , cursorLine printString 
                            , ';' 
                            , cursorCol printString
                            , 'R'.
        ^ self
    ].
    (parameters at: 1) == 7 ifTrue:[
        "/ display name 
    ].

    "Created: / 11.6.1998 / 23:05:50 / cg"
    "Modified: / 28.7.1998 / 00:54:30 / cg"
!

resetDefaults
    "Reset the default parameters"

    |l1 c1 l2 c2|


    l1 := (parameters at: 1).
    l2 := (parameters at: 2).
"/ Transcript show:'resetDefaults:'; show:l1;show:' ';showCR:l2.
    (l1 ~~ 0 and:[l2 ~~ 0]) ifTrue:[
        rangeStartLine := l1.
        rangeEndLine := l2.
    ] ifFalse:[
"/        self halt.
    ].

"/    (rangeStartLine == 1 and:[rangeEndLine == numberOfLines]) ifTrue:[
"/        rangeEndLine := rangeStartLine := nil.
"/    ].

"/    autoLineFeed := false.
"/    autoMargin := true.
"/    displayMode := 0.                "Normal display"!! !!

    "Created: / 10.6.1998 / 14:50:53 / cg"
    "Modified: / 20.6.1998 / 20:28:26 / cg"
! !

!VT100TerminalView methodsFor:'initialization'!

initialize
    super initialize.

    self endOfSequence

    "Created: / 10.6.1998 / 14:46:07 / cg"
    "Modified: / 13.6.1998 / 13:58:01 / cg"
!

initializeKeyboardSequences
    kbdSequences := (self vt100KeyCodes)

    "Modified: / 9.6.1998 / 20:49:21 / cg"
    "Created: / 10.6.1998 / 15:12:32 / cg"
! !

!VT100TerminalView methodsFor:'processing - input'!

addToParameter: char
    "The parameter char is a digit. Add it to the current parameter."

    | param |

    param := parameters at:currentParam.
    parameters at:currentParam put:(param * 10 + char digitValue)

    "Created: / 10.6.1998 / 14:39:00 / cg"
!

doNothing
    self endOfSequence

    "Created: / 10.6.1998 / 14:31:56 / cg"
!

endOfSequence
    state := 0. 
    currentParam := 1. 
    parameters := Array new:8 withAll:0.

    "Created: / 10.6.1998 / 14:30:40 / cg"
    "Modified: / 10.6.1998 / 14:30:57 / cg"
!

nextPut:char
    "process a character (i.e. the shells output)"

"/ Transcript show:state; show:' '; showCR:char storeString.

    state == #gotReturn ifTrue:[
        state := 0.
        char == Character nl ifTrue:[
            "/ cr-nl
            "/ stay in buffering mode.
            super nextPut:Character cr.
            ^ self.
        ].
        self endEntry.
        self cursorToBeginOfLine.
        "/ continue in initial state
    ].

    state == 0 ifTrue:[
        "/ Currently, we are in initial state.  
        "/ Decide what to do on the basis of the parameter char.

        char asciiValue < 32 ifTrue:[
            (char == Character esc) ifTrue:[ 
                state := #gotESC. 
                ^ self 
            ].
            (char == Character nl) ifTrue:[ 
                self endEntry.
                ^ self doCursorDown:1.
            ].
            (char == Character return) ifTrue:[ 
                (rangeEndLine notNil and:[rangeEndLine ~~ numberOfLines]) ifTrue:[
                    self endEntry.
                    self cursorToBeginOfLine.
                ] ifFalse:[
                    state := #gotReturn.
                ].
                ^ self.
            ].
            (char == Character backspace) ifTrue:[ 
                self endEntry.
                ^ self cursorLeft. "/ doBackspace
            ].
            (char == Character bell) ifTrue:[
                self beep.
                ^ self 
            ].
            (char == (Character value:5)) ifTrue:[
                "/ terminal-type query
                self reportTerminalType.
                ^ self 
            ].
            (char == (Character value:16rf)) ifTrue:[
                "/ SO
                ^ self 
            ].
            (char == (Character value:16re)) ifTrue:[
                "/ SI
                ^ self 
            ].
            char ~~ Character tab ifTrue:[
                char asciiValue ~~ 0 ifTrue:[
                    Transcript show:'unhandled control key: '; showCR:char storeString.
                ].
                ^ self.
            ]
        ].
        ^ super nextPut:char
    ].

    state == #gotESC ifTrue:[
        "/ Currently, we are in ESC state.  
        "/ Decide what to do on the basis of the parameter char.

        char == $[ ifTrue: [ 
            "/ ESC-[
            state := #gotCSI. 
            ^ self
        ].
        char == $] ifTrue: [ 
            "/ ESC-]
            "/xterm sequence
            state := #gotXTERMCSI. 
            ^ self
        ].
        char == $( ifTrue: [ 
            "/ ESC-(
            "/ todo: set-charset 0 ...
            ^ self doNothing
        ].
        char == $) ifTrue: [ 
            "/ ESC-(
            "/ todo: set-charset 1 ...
            ^ self doNothing
        ].
        char == $7 ifTrue:[
            "/ ESC-7
            self endEntry.
            self saveCursor.
            ^ self endOfSequence
        ].
        char == $8 ifTrue:[
            "/ ESC-7
            self endEntry.
            self restoreCursor.
            ^ self endOfSequence
        ].
        char == $M ifTrue:[
            "/ ESC-M
            self endEntry.
            self doCursorUp:1.
            ^ self endOfSequence
        ].
        char == $D ifTrue:[
            "/ ESC-D
            self endEntry.
            self doCursorDown:1.
            ^ self endOfSequence
        ].
        char == $E ifTrue:[
            "/ ESC-E
            "/ TODO add_lines
            ^ self doNothing
        ].
        (char == $Z) ifTrue:[
            "/ terminal-type query 2
            self reportTerminalType.
            ^ self endOfSequence
        ].
        char == $= ifTrue: [
            "/ ESC-=
            ^ self doNothing
        ].
        char == $< ifTrue: [
            "/ ESC-<
            ^ self doNothing
        ].
        ^ self doNothing
    ].

    state == #gotCSI ifTrue:[
        "/ Currently, we are in ESC-[ state.  
        "/ Decide what to do on the basis of the parameter char.

        char == $? ifTrue: [
            state := #gotCSI2.
            ^ self
        ].
        char == $; ifTrue:[
            currentParam := (currentParam + 1) min: 8.
            ^ self
        ].
        char isDigit ifTrue: [
            ^ self addToParameter:char
        ].
        char == $@ ifTrue: [
            self endEntry.
            self insertCharacters.
            ^ self endOfSequence
        ].
        char == $A ifTrue: [
            self endEntry.
            self doCursorUp:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $B ifTrue: [
            self endEntry.
            self doCursorDown:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $C ifTrue: [
            self endEntry.
            self doCursorRight:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $D ifTrue: [
            self endEntry.
            self doCursorLeft:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $H ifTrue: [
            self endEntry.
            self move.
            ^ self endOfSequence
        ].
        char == $J ifTrue: [
            self endEntry.
            self doClearDisplay.
            ^ self endOfSequence
        ].
        char == $K ifTrue: [
            self endEntry.
            self clearLines.
            ^ self endOfSequence
        ].
        char == $L ifTrue: [
            self endEntry.
            self insertLines.
            ^ self endOfSequence
        ].
        char == $M ifTrue: [
            self endEntry.
            self deleteLines.
            ^ self endOfSequence
        ].
        char == $P ifTrue: [
            self endEntry.
            self deleteCharacters.
            ^ self endOfSequence
        ].
        (char == $c) ifTrue:[
            "/ terminal-type query 3
            self reportTerminalType.
            ^ self endOfSequence
        ].
        char == $f ifTrue: [
            self endEntry.
            self move.
            ^ self endOfSequence
        ].
        char == $n ifTrue: [
            self report.
            ^ self endOfSequence
        ].
        char == $m ifTrue: [
            self displayMode: (parameters at: 1).
            ^ self endOfSequence
        ].
        char == $r ifTrue: [
            self endEntry.
            self resetDefaults.
            ^ self endOfSequence
        ].
        ^ self doNothing
    ].

    state == #gotCSI2 ifTrue:[
        "/ Currently, we are in ESC-[-? state.  
        "/ Decide what to do on the basis of the parameter char.

        char == $; ifTrue: [
            currentParam := (currentParam + 1) min: 8.
            ^ self
        ].
        char isDigit ifTrue: [
            self addToParameter: char.
            ^ self
        ].
        (char == $l 
        or:[char == $h]) ifTrue: [
            "/ (parameters at: 1) = 1 ifTrue: [app_cur_keys:(char == $h)].
            "/ (parameters at: 1) = 2 ifTrue: [mode132:(char == $h)].
            "/ (parameters at: 1) = 4 ifTrue: [smoothScroll:(char == $h)].
            "/ (parameters at: 1) = 5 ifTrue: [reverseVideo:(char == $h)].
            "/ (parameters at: 1) = 6 ifTrue: [decom:(char == $h)].
            self endEntry.
            (parameters at: 1) = 7 ifTrue: [self autoMargin:(char == $h)].
            ^ self endOfSequence
        ].
        ^ self doNothing
    ].

    state == #gotXTERMCSI ifTrue:[
        "/ Currently, we are in ESC-] state.  
        "/ Decide what to do on the basis of the parameter char.
        ^ self doNothing
    ].

    self doNothing

    "Modified: / 28.7.1998 / 00:18:01 / cg"
! !

!VT100TerminalView methodsFor:'queries'!

terminalType
    ^ #vt100

    "Created: / 10.6.1998 / 16:22:39 / cg"
! !

!VT100TerminalView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/VT100TerminalView.st,v 1.21 1998-07-28 10:06:14 cg Exp $'
! !