VT100TerminalView.st
author Claus Gittinger <cg@exept.de>
Wed, 10 Jun 1998 20:48:15 +0200
changeset 939 54698a16b65c
parent 937 9823aad16498
child 941 137464350e42
permissions -rw-r--r--
*** empty log message ***

TerminalView subclass:#VT100TerminalView
	instanceVariableNames:'state currentParam parameters'
	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:'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"
!

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

displayMode: anInteger
    "Set the current display mode."

"/    displayMode _ anInteger!!

    "Created: / 10.6.1998 / 15:01:16 / 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 cursorLine:yLocation col:xLocation.

    "Created: / 10.6.1998 / 14:40:49 / cg"
    "Modified: / 10.6.1998 / 14:53:02 / cg"
!

resetDefaults
    "Reset the default parameters"

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

    "Created: / 10.6.1998 / 14:50:53 / cg"
    "Modified: / 10.6.1998 / 15:02:58 / cg"
! !

!VT100TerminalView methodsFor:'initialization'!

initialize
    super initialize.
    self endOfSequence

    "Created: / 10.6.1998 / 14:46:07 / cg"
    "Modified: / 10.6.1998 / 14:46:30 / cg"
!

initializeEscapeSequences
    ^ self

    "Modified: / 9.6.1998 / 20:49:21 / cg"
    "Created: / 10.6.1998 / 16:29:31 / 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 asciiValue.

    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 := 1. ^ self 
        ].
        (char == Character nl) ifTrue:[ 
            self endEntry.
            ^ self cursorDown:1
        ].
        (char == Character return) ifTrue:[ 
            state := #gotReturn.
            ^ self.
"/            self endEntry.
"/            ^ self cursorToBeginOfLine
        ].
        (char == Character backspace) ifTrue:[ 
            self endEntry.
            ^ self doBackspace
        ].
        (char == Character bell) ifTrue:[
            self beep.
            ^ self 
        ].
"/        (char == Character tab) ifTrue:[
"/            self endEntry.
"/            super nextPut:char.
"/            self endEntry.
"/            ^ self.
"/        ].
        ^ super nextPut:char
    ].

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

        char == $[ ifTrue: [ 
            "/ ESC-[
            state := 2. 
            ^ self
        ].
        char == $M ifTrue:[
            "/ ESC-M
            self cursorUp:1.
            ^ self endOfSequence
        ].
        char == $D ifTrue:[
            "/ ESC-D
            self cursorDown:1.
            ^ self endOfSequence
        ].
        ^ self doNothing
    ].

    state == 2 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
        ].
        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 addLines.
            ^ self endOfSequence
        ].
        char == $M ifTrue: [
            self deleteLines.
            ^ self endOfSequence
        ].
        char == $P ifTrue: [
            self deleteCharacters.
            ^ self endOfSequence
        ].
        char == $m ifTrue: [
            self displayMode: (parameters at: 1).
            ^ self endOfSequence
        ].
        char == $r ifTrue: [
            self resetDefaults.
            ^ self endOfSequence
        ].
        char == $? ifTrue: [
            state := 3.
            ^ self
        ].
        ^ self doNothing
    ].

    state == 3 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 ifTrue: [
            (parameters at: 1) = 7 ifTrue: [self autoMargin: false].
            ^ self doNothing
        ].
        char == $h ifTrue: [
            (parameters at: 1) = 7 ifTrue: [self autoMargin: true].
            ^ self doNothing
        ].
        ^ self doNothing
    ].

    self doNothing

    "Modified: / 10.6.1998 / 20:46:08 / 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.8 1998-06-10 18:48:15 cg Exp $'
! !