VT100TerminalView.st
author Claus Gittinger <cg@exept.de>
Fri, 12 Jun 1998 23:02:29 +0200
changeset 951 a9e48f549763
parent 949 1a6071a5c370
child 952 b83678ff6770
permissions -rw-r--r--
fixed scroll-range

TerminalView subclass:#VT100TerminalView
	instanceVariableNames:'state 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      '\0377'
         )

    "Modified: / 10.6.1998 / 14:19:27 / cg"
    "Created: / 10.6.1998 / 15:13:01 / cg"
! !

!VT100TerminalView methodsFor:'event handling'!

defineWindowSize
    rangeEndLine == numberOfLines ifTrue:[
        rangeEndLine := nFullLinesShown
    ].
    super defineWindowSize

    "Created: / 12.6.1998 / 21:27:38 / 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."

    (parameters at: 1) = 0 ifTrue: [^self doClearToEndOfLine].
    (parameters at: 1) = 1 ifTrue: [^self doClearFromBeginningOfLine].
    (parameters at: 1) = 2 ifTrue: [^self doClearEntireLine]

    "Created: / 10.6.1998 / 14:44:22 / 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."

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

        currentEmphasis := #bold.
        ^ self.
    ].
    currentEmphasis := nil.

"/    displayMode _ anInteger!!

    "Created: / 10.6.1998 / 15:01:16 / cg"
    "Modified: / 12.6.1998 / 22:26:30 / cg"
!

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

    "Created: / 10.6.1998 / 14:48:03 / cg"
    "Modified: / 12.6.1998 / 21:14:25 / 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).
    self endOfSequence

    "Created: / 10.6.1998 / 14:40:01 / 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."

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

    "Created: / 10.6.1998 / 14:40:49 / cg"
    "Modified: / 12.6.1998 / 21:31:37 / cg"
!

reportTerminalType
    (parameters at: 1) == 6 ifTrue:[
        "/ report position
        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: / 11.6.1998 / 23:09:10 / cg"
!

resetDefaults
    "Reset the default parameters"

    |l1 c1 l2 c2|

    l1 := (parameters at: 1).
    l2 := (parameters at: 2).
    (l1 ~~ 0 and:[l2 ~~ 0]) ifTrue:[
        rangeStartLine := l1.
        rangeEndLine := l2.
    ] ifFalse:[
        self halt.
    ].

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

    "Created: / 10.6.1998 / 14:50:53 / cg"
    "Modified: / 12.6.1998 / 21:24:48 / cg"
! !

!VT100TerminalView methodsFor:'initialization'!

initialize
    super initialize.

    rangeStartLine := 1.
    rangeEndLine := numberOfLines.

    self endOfSequence

    "Created: / 10.6.1998 / 14:46:07 / cg"
    "Modified: / 12.6.1998 / 21:28:08 / 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 == Character esc) ifTrue:[ 
            self endEntry.
            state := #gotESC. ^ self 
        ].
        (char == Character nl) ifTrue:[ 
            self endEntry.
            ^ self doCursorDown:1
        ].
        (char == Character return) ifTrue:[ 
            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 
        ].
        ^ 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 saveCursor.
            ^ self endOfSequence
        ].
        char == $8 ifTrue:[
            "/ ESC-7
            self restoreCursor.
            ^ self endOfSequence
        ].
        char == $M ifTrue:[
            "/ ESC-M
            self doCursorUp:1.
            ^ self endOfSequence
        ].
        char == $D ifTrue:[
            "/ ESC-D
            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
        ].
        ^ self doNothing
    ].

    state == #gotCSI 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
        ].
        char == $@ ifTrue: [
            self insertCharacters.
            ^ self endOfSequence
        ].
        char == $A ifTrue: [
            self doCursorUp:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $B ifTrue: [
            self doCursorLeft:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $C ifTrue: [
            self doCursorRight:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $D ifTrue: [
            self doCursorDown:((parameters at: 1) max: 1).
            ^ self endOfSequence
        ].
        char == $H ifTrue: [
            self move.
            ^ self endOfSequence
        ].
        char == $J ifTrue: [
            self doClearDisplay.
            ^ self endOfSequence
        ].
        char == $K ifTrue: [
            self clearLines.
            ^ self endOfSequence
        ].
        char == $L ifTrue: [
            self insertLines.
            ^ self endOfSequence
        ].
        char == $M ifTrue: [
            self deleteLines.
            ^ self endOfSequence
        ].
        char == $P ifTrue: [
            self deleteCharacters.
            ^ self endOfSequence
        ].
        (char == $c) ifTrue:[
            "/ terminal-type query 3
            self reportTerminalType.
            ^ self endOfSequence
        ].
        char == $f ifTrue: [
            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 resetDefaults.
            ^ self endOfSequence
        ].
        char == $? ifTrue: [
            state := #gotCSI2.
            ^ self
        ].
        ^ 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)].
            (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: / 12.6.1998 / 22:58:06 / 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.12 1998-06-12 21:02:29 cg Exp $'
! !