VT100TerminalView.st
author penk
Wed, 18 Sep 2002 16:32:06 +0200
changeset 2192 5f3bf896d334
parent 2116 f4ca2a14b8f6
child 2194 d008bb991def
permissions -rw-r--r--
vt100 perform now only cr and not cr-nl

"
 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' }"

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

!VT100TerminalView class methodsFor:'documentation'!

ansiEscapes
"
                              ANSI ESCAPE SEQUENCES
===============================================================================
Wherever you see '#', that should be replaced by the appropriate number.

        ESC code sequence                       Function
       -------------------              ---------------------------
Cursor Controls:
         ESC[#;#H or ESC[#;#f           Moves cusor to line #, column #
         ESC[#A                         Moves cursor up # lines
         ESC[#B                         Moves cursor down # lines
         ESC[#C                         Moves cursor forward # spaces
         ESC[#D                         Moves cursor back # spaces
         ESC[#;#R                       Reports current cursor line & column
         ESC[s                          Saves cursor position for recall later
         ESC[u                          Return to saved cursor position

Erase Functions:
         ESC[2J                         Clear screen and home cursor
         ESC[K                          Clear to end of line

Set Graphics Rendition:
         ESC[#;#;....;#m                Set display attributes where # is
                                            0 for normal display
                                            1 for bold on
                                            4 underline (mono only)
                                            5 blink on
                                            7 reverse video on
                                            8 nondisplayed (invisible)
                                            30 black foreground 
                                            31 red foreground 
                                            32 green foreground 
                                            33 yellow foreground 
                                            34 blue foreground 
                                            35 magenta foreground 
                                            36 cyan foreground 
                                            37 white foreground
                                            40 black background
                                            41 red background
                                            42 green background
                                            43 yellow background
                                            44 blue background
                                            45 magenta background
                                            46 cyan background
                                            47 white background

         ESC[=#;7h or                   Put screen in indicated mode where # is
         ESC[=h or                          0 for 40 x 25 black & white
         ESC[=0h or                         1 for 40 x 25 color
         ESC[?7h                            2 for 80 x 25 b&w
                                            3 for 80 x 25 color
                                            4 for 320 x 200 color graphics
                                            5 for 320 x 200 b & w graphics
                                            6 for 640 x 200 b & w graphics
                                            7 to wrap at end of line 

         ESC[=#;7l or ESC[=l or         Resets mode # set with above command
         ESC[=0l or ESC[?7l

Keyboard Reassignments:
         ESC[#;#;...p                   Keyboard reassignment. The first ASCII
         or ESC[""string""p               code defines which code is to be 
         or ESC[#;""string"";#;           changed. The remaining codes define
            #;""string"";#p               what it is to be changed to.

         E.g. Reassign the Q and q keys to the A and a keys (and vice versa).
         ESC [65;81p                    A becomes Q
         ESC [97;113p                   a becomes q
         ESC [81;65p                    Q becomes A
         ESC [113;97p                   q becomes a

         E.g. Reassign the F10 key to a DIR command.
         ESC [0;68;""dir"";13p            The 0;68 is the extended ASCII code 
                                        for the F10 key and 13 is the ASCII
                                        code for a carriage return.

         Other function key codes       F1=59,F2=60,F3=61,F4=62,F5=63
                                        F6=64,F7=65,F8=66,F9=67,F10=68
"
!

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
"
    A VT100 terminal emulator.
    Most of the functionality is inherited from my superclass,
    I redefine/specialize certain methods for VT100 escape sequences
    and vt100 keyboard codes

    BUGS:
        VT100 wrapMode (at right margin) is not supported
        this may lead to wrong display when a vi is started in a small window.

    [start with:]
        VT100TerminalView openShell

    [see also:]
        VT52TerminalView
        TelnetTool
"


! !

!VT100TerminalView methodsFor:'defaults'!

vt100KeyCodes
    "return a vt100 keyCode table"

    ^ 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'
             #Tab         '\t'

             #F1          '\eOP'
             #F2          '\eOQ'
             #F3          '\eOR'
             #F4          '\eOS'
             #F5          '\eOt'
             #F6          '\eOu'
             #F7          '\eOv'
             #F8          '\eOl'
             #F9          '\eOw'
         )

    "Created: / 10.6.1998 / 15:13:01 / cg"
    "Modified: / 5.5.1999 / 15:01:32 / cg"
! !

!VT100TerminalView methodsFor:'functions'!

addLines
    "Add the appropriate number of blank lines (param 1) 
     at the cursor position."

    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:arg
    "Clear some part of the current line, as indicated by the first parameter:
     0 - clear to EOL
     1 - clear from beginning to cursorCol
     2 - clear entire line
    "

    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 (param 1)
     at the cursor position."

    |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:p1
    "Set the current display mode (emphasis) as specified by param 1."

    |clrName|


"/    self endEntry.
    p1 == 1 ifTrue:[
        "/ ESC-[-1-m  -> bold

        "/ workaround: windows bold fonts are
        "/ wider, leading to ugly looking output
        "/ Therefore, use red color instead of bold
        device platformName = 'WIN32' ifTrue:[
            self color:Color red.
        ] ifFalse:[
            self bold.
        ].
        ^ self.
    ].
    p1 == 4 ifTrue:[
        "/ ESC-[-4-m  -> underline

        self underline.
        ^ self.
    ].
    p1 == 5 ifTrue:[
        "/ ESC-[-5-m  -> blink

        self color:Color blue.
        ^ self.
    ].
    p1 == 7 ifTrue:[
        "/ ESC-[-7-m  -> reverse

        self reverse.
        ^ self.
    ].
    p1 == 8 ifTrue:[
        "/ ESC-[-8-m  -> invisible
        ^ self.
    ].
    (p1 between:30 and:37) ifTrue:[
        "/ ESC-[-30-m  -> black fg color
        "/ ESC-[-31-m  -> red   fg color
        "/ ...
        "/ ESC-[-37-m  -> white fg color
        clrName := #(black red green yellow blue magenta cyan white) at:(p1-30+1).
        self color:(Color perform:clrName).
        ^ self.
    ].
    (p1 between:40 and:47) ifTrue:[
        "/ ESC-[-40-m  -> black bg color
        "/ ...
        "/ ESC-[-47-m  -> white bg color
        clrName := #(black red green yellow blue magenta cyan white) at:(p1-40+1).
        self bgColor:(Color perform:clrName).
        ^ self.
    ].

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

    "Created: / 10.6.1998 / 15:01:16 / cg"
    "Modified: / 5.5.1999 / 00:53:15 / cg"
!

doClearDisplay:arg
    "Clear some part of the current screen, as indicated by the first parameter.
     0 - clear to endOfScreen
     1 - clear from beginning of screen to cursorCol
     2 - clear entire screen
    "

    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 (param 1) at the cursor position."

    |s|

    s := String new:((parameters at: 1) max: 1).
    self insertStringWithoutCRs:s atLine: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) ? 1) y: ((parameters at: 1) ? 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."

    Debug ifTrue:[
        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
    "currently, only cursor position is supported (param 6)"

    (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 l2|


    l1 := (parameters at: 1).
    l2 := (parameters at: 2).
    Debug ifTrue:[
        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.

    " vt100 dont handle cr-nl, only cr ('\n') is used 
      in canonical mode the bash on the other side sends only '\n' on change line
      thats why no change of terminal input output modes is useful
      support the plain vt100 protocol
    "

    inputTranslateCRToNL := true.
    parameters := Array new:8.
    self endOfSequence

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

initializeKeyboardSequences
    "setup my keyboard sequences for a vt100"

    kbdSequences := (self vt100KeyCodes)

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

setTerminalModes

    OperatingSystem isUNIXlike ifTrue:[
        (inStream notNil 
        and:[inStream isExternalStream
        and:[inStream isOpen]]) ifTrue:[
            (OperatingSystem resetTerminalInputOutputModes:inStream fileDescriptor) ifFalse:[
                Dialog warn:'cant set terminal modes'.
            ].
        ].
    ].
    super setTerminalModes.
! !

!VT100TerminalView methodsFor:'processing - input'!

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

    | param |

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

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

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

    state := 0. 
    currentParam := 1. 
    "/ parameters := Array new:8 withAll:0.
    parameters atAllPut:nil.

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

    | processCharacterReturn |

    Debug ifTrue:[
        Transcript show:state; show:' '; showCR:char storeString.
    ].

    " Character return has code of cr in Smalltalk/X
      vt 100 sends cr for cr-nl        
    "
    (char == Character return or:[char == Character nl]) ifTrue:[ 
        (rangeEndLine notNil and:[rangeEndLine ~~ numberOfLines]) ifTrue:[
            self endEntry.
            self cursorToBeginOfLine.
        ].
        super nextPut:Character cr.
        ^ self.
    ].
    state == 0 ifTrue:[
        "/ Currently, we are in initial state.  
        "/ Decide what to do on the basis of the parameter char.
        processCharacterReturn := self processStateZero:char.
    ] ifFalse:[
        state == #gotESC ifTrue:[
            "/ Currently, we are in ESC state.  
            "/ Decide what to do on the basis of the parameter char.
            processCharacterReturn := self processStateGotESC:char.
        ] ifFalse:[
            state == #gotCSI ifTrue:[
                "/ Currently, we are in ESC-[ state.  
                "/ Decide what to do on the basis of the parameter char.
                processCharacterReturn := self processStateGotCSI:char.
            ] ifFalse:[
                state == #gotCSI2 ifTrue:[
                    "/ Currently, we are in ESC-[-? state.  
                    "/ Decide what to do on the basis of the parameter char.
                    processCharacterReturn := self processStateGotCSI2:char.
                ] ifFalse:[
                    state == #gotCSI3 ifTrue:[
                        "/ Currently, we are in ESC-(-? state.  
                        "/ Decide what to do on the basis of the parameter char.

                        "/ currently not supported
                        processCharacterReturn := self processStateGotCSI3:char.
                    ] ifFalse:[
                        state == #gotXTERMCSI ifTrue:[
                            "/ Currently, we are in ESC-] state.  
                            "/ Decide what to do on the basis of the parameter char.
                            processCharacterReturn := self processStateGotXTERMCSI:char.
                        ].
                    ]
                ]
            ]
        ]
    ].
"/    #waitForNextChar - state was changed or wait for next character
"/    #sequenceComplete - command processed
"/    #unknown - unknown character for this state
    
        Debug ifTrue:[
            Transcript showCR:'processCharacterReturn:', processCharacterReturn asString.
        ].
    processCharacterReturn == #waitForNextChar ifTrue:[
        ^ self.
    ].
    processCharacterReturn == #sequenceComplete ifTrue:[
        self endOfSequence.
        ^ self
    ].
    processCharacterReturn == #unknown ifTrue:[
        Debug ifTrue:[
            Transcript showCR:'#### cant handle char:', char asciiValue asString, ' (', char storeString, ') on state 0'.
        ].
        state == 0 ifTrue:[
            "/ character on start of sequence not processed send to view
            super nextPut:char.
        ].
        self doNothing.
        ^ self
    ].
    self doNothing.
    ^ self
    "Modified: / 28.7.1998 / 00:18:01 / cg"
    "Modified: / 28.1.2002 / 20:47:07 / micha"
!

processStateGotCSI2:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    char == $; ifTrue: [
        currentParam := (currentParam + 1) min: 8.
        ^ #waitForNextChar
    ].
    char isDigit ifTrue: [
        self addToParameter: char.
        ^ #waitForNextChar
    ].
    (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)].
        ^ #sequenceComplete
    ].
    ^ #unknown
!

processStateGotCSI3:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    ^ #unknown
!

processStateGotCSI:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    char == $? ifTrue: [
        state := #gotCSI2.
        ^ #waitForNextChar
    ].
    char == $; ifTrue:[
        currentParam := (currentParam + 1) min: 8.
        ^ #waitForNextChar
    ].
    char isDigit ifTrue: [
        self addToParameter:char.
        ^ #waitForNextChar
    ].
    char == $@ ifTrue: [
        self endEntry.
        self insertCharacters.
        ^ #sequenceComplete
    ].
    char == $A ifTrue: [
        "/ ESC[#A                         - Moves cursor up # lines
        self endEntry.
        self doCursorUp:((parameters at: 1) ? 1).
        ^ #sequenceComplete
    ].
    char == $B ifTrue: [
        "/ ESC[#B                         - Moves cursor down # lines
        self endEntry.
        self doCursorDown:((parameters at: 1) ? 1).
        ^ #sequenceComplete
    ].
    char == $C ifTrue: [
        "/ ESC[#C                         - Moves cursor forward # spaces
        self endEntry.
        self doCursorRight:((parameters at: 1) ? 1).
        ^ #sequenceComplete
    ].
    char == $D ifTrue: [
        "/ ESC[#D                         - Moves cursor back # spaces
        self endEntry.
        self doCursorLeft:((parameters at: 1) ? 1).
        ^ #sequenceComplete
    ].
    char == $H ifTrue: [
        "/ ESC[#;#H or ESC[#;#f           - Moves cusor to line #, column #
        self endEntry.
        Debug ifTrue:[
            Transcript show:'move to '; show:(parameters at:1)?1; show:'/'; showCR:(parameters at:2)?1.
        ].
        self moveToX: ((parameters at: 2) ? 1) y: ((parameters at: 1) ? 1).
        ^ #sequenceComplete
    ].
    char == $J ifTrue: [
        "/ ESC[0J                         - Clear screen from beginning 
        "/ ESC[1J                         - Clear screen to end 
        "/ ESC[2J                         - Clear entire screen and home cursor
        self endEntry.
        self doClearDisplay:((parameters at: 1) ? 0).
        ^ #sequenceComplete
    ].
    char == $K ifTrue: [
        "/ ESC[K                          - Clear to end of line
        self endEntry.
        self clearLines:((parameters at: 1) ? 0).
        Debug ifTrue:[
            Transcript showCR:'clear to EOL'.
        ].
        ^ #sequenceComplete
    ].
    char == $L ifTrue: [
        self endEntry.
        self insertLines.
        ^ #sequenceComplete
    ].
    char == $M ifTrue: [
        self endEntry.
        self deleteLines.
        ^ #sequenceComplete
    ].
    char == $P ifTrue: [
        self endEntry.
        self deleteCharacters.
        ^ #sequenceComplete
    ].
    char == $P ifTrue: [
        "/ ESC[#;#R                       - Reports current cursor line & column
    ].
    (char == $c) ifTrue:[
        "/ terminal-type query 3
        self reportTerminalType.
        ^ #sequenceComplete
    ].
    char == $f ifTrue: [
        "/ ESC[#;#H or ESC[#;#f           - Moves cusor to line #, column #
        self endEntry.
        self move.
        ^ #sequenceComplete
    ].
    char == $n ifTrue: [
        self report.
        ^ #sequenceComplete
    ].
    char == $m ifTrue: [
        self displayMode:((parameters at: 1) ? 0).
        ^ #sequenceComplete
    ].
    char == $r ifTrue: [
        self endEntry.
        self resetDefaults.
        ^ #sequenceComplete
    ].
    char == $s ifTrue: [
        "/ ESC[s                          - Saves cursor position for recall later
        self endEntry.
        ^ #sequenceComplete
    ].
    char == $u ifTrue: [
        "/ ESC[u                          - Return to saved cursor position
        self endEntry.
        ^ #sequenceComplete
    ].
    ^ #unknown
!

processStateGotESC:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    char == $[ ifTrue: [ 
        "/ ESC-[
        state := #gotCSI. 
        ^ #waitForNextChar
    ].
    char == $] ifTrue: [ 
        "/ ESC-]
        "/xterm sequence
        state := #gotXTERMCSI. 
        ^ #waitForNextChar
    ].
    char == $( ifTrue: [ 
        "/ ESC-(
        "/ todo: set-charset 0 ...
        state := #gotCSI3.
        ^ #waitForNextChar
    ].
    char == $) ifTrue: [ 
        "/ ESC-(
        "/ todo: set-charset 1 ...
        ^ #sequenceComplete
    ].
    char == $7 ifTrue:[
        "/ ESC-7
        self endEntry.
        self saveCursor.
        ^ #sequenceComplete
    ].
    char == $8 ifTrue:[
        "/ ESC-7
        self endEntry.
        self restoreCursor.
        ^ #sequenceComplete
    ].
    char == $M ifTrue:[
        "/ ESC-M
        self endEntry.
        self doCursorUp:1.
        ^ #sequenceComplete
    ].
    char == $D ifTrue:[
        "/ ESC-D
        self endEntry.
        self doCursorDown:1.
        ^ #sequenceComplete
    ].
    char == $E ifTrue:[
        "/ ESC-E
        "/ TODO add_lines
        ^ #sequenceComplete
    ].
    (char == $Z) ifTrue:[
        "/ terminal-type query 2
        self reportTerminalType.
        ^ #sequenceComplete
    ].
    char == $= ifTrue: [
        "/ enter apllication keypad mode
        "/ ESC-=
        ^ #sequenceComplete
    ].
    char == $> ifTrue: [
        "/ exit apllication keypad mode
        "/ ESC-<
        ^ #sequenceComplete
    ].
    ^ #unknown
!

processStateGotXTERMCSI:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    ^ #unknown
!

processStateZero:char
" change state or processing character; return 
    #waitForNextChar - state was changed and wait for next characters
    #sequenceComplete - command processed
    #unknown - unknown character for this state
"

    char asciiValue < 32 ifTrue:[
        (char == Character esc) ifTrue:[ 
            state := #gotESC. 
            ^ #waitForNextChar
        ].
        (char == Character backspace) ifTrue:[ 
            self endEntry.
            self cursorLeft. "/ doBackspace
            ^ #sequenceComplete
        ].
        (char == Character bell) ifTrue:[
            self beep.
            ^ #sequenceComplete
        ].
        (char == (Character value:5)) ifTrue:[
            "/ terminal-type query
            self reportTerminalType.
            ^ #sequenceComplete
        ].
        (char == (Character value:16rf)) ifTrue:[
            "/ SO shift out
            ^ #sequenceComplete
        ].
        (char == (Character value:16re)) ifTrue:[
            "/ SI shift in
            ^ #sequenceComplete
        ].
        char ~~ Character tab ifTrue:[
            char asciiValue ~~ 0 ifTrue:[
                ('VT100 [info]: unhandled control key: ' , char storeString) infoPrintCR.
            ].
            ^ #sequenceComplete
        ]
    ].
    ^ #unknown
! !

!VT100TerminalView methodsFor:'queries'!

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

    ^ 'vt100'

    "Created: / 10.6.1998 / 16:22:39 / cg"
    "Modified: / 5.5.1999 / 11:22:40 / cg"
! !

!VT100TerminalView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/VT100TerminalView.st,v 1.35 2002-09-18 14:32:03 penk Exp $'
! !