VDBSimpleConsoleView.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 18 Feb 2019 10:55:12 +0000
changeset 154 26937faa5a97
parent 143 df7f89efd39d
child 150 2bd269c89e8c
permissions -rw-r--r--
Use standard `#enqueueMessage:` mechanism to enqueue delayed updates rather than baking our own `#enqueueDelayedUpdate:`. The former is "standard" API defined in `ApplicationModel`. We still need to specialize that behavior in (overridden) `#enqueueMessage:for:arguments:` but API-wise, we use the standard API.

"
jv:vdb - Visual / VM Debugger
Copyright (C) 2015-now Jan Vrany

This software is licensed under 'Creative Commons Attribution-NonCommercial 4.0 International License'

You may find a full license text in LICENSE.txt or at http://creativecommons.org/licenses/by-nc/4.0/
"
"{ Package: 'jv:vdb' }"

"{ NameSpace: Smalltalk }"

TextCollector subclass:#VDBSimpleConsoleView
	instanceVariableNames:'buffer bufferPosition history historyPosition completeAction
		lastTabTime lastCompletions'
	classVariableNames:'TabTabInterval'
	poolDictionaries:''
	category:'VDB-UI-Console'
!

!VDBSimpleConsoleView class methodsFor:'documentation'!

copyright
"
jv:vdb - Visual / VM Debugger
Copyright (C) 2015-now Jan Vrany

This software is licensed under 'Creative Commons Attribution-NonCommercial 4.0 International License'

You may find a full license text in LICENSE.txt or at http://creativecommons.org/licenses/by-nc/4.0/
"
! !

!VDBSimpleConsoleView class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    TabTabInterval := 500"ms"

    "Modified: / 25-01-2019 / 21:38:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'accessing'!

completeAction
    ^ completeAction
!

completeAction:aBlock
    completeAction := aBlock.
! !

!VDBSimpleConsoleView methodsFor:'actions'!

buffer: aString
    "Set the line buffer, position the cursor at the end of
     line"

    | line |

    line := list at: cursorLine.
    line := (line copyTo: cursorCol - bufferPosition) , aString.

    list at: cursorLine put: line.
    buffer := aString.
    bufferPosition := aString size + 1.
    self cursorCol: line size + 1.
    self invalidateLine: cursorLine.

    "Created: / 26-01-2019 / 22:16:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completions: anArray"of Strings"
    "Should be called by application when completions are computed."

    | completion |

    lastCompletions := anArray.
    lastCompletions isEmptyOrNil ifTrue:[
        lastCompletions := nil.
        self flash: (resources string:'Nothing to complete').
        ^self.
    ].
    completion := lastCompletions longestCommonPrefix copyFrom: bufferPosition.

    completion isEmpty ifTrue:[ 
        self flash: (resources string:'Ambiguous')
    ] ifFalse:[
        buffer := (buffer copyTo: bufferPosition - 1) , completion , (buffer copyFrom: bufferPosition).
        self insertStringAtCursor: completion.
        bufferPosition := bufferPosition + completion size.
    ]

    "Created: / 25-01-2019 / 21:50:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completionsShow
    "Shows completion candidates"

    | currentColNr currentLineNr currentLine  |

    lastCompletions isEmptyOrNil ifTrue:[ ^ self ].
    currentColNr := cursorCol.
    currentLineNr := cursorLine.
    currentLine := self list at: currentLineNr.

    self cr.
    lastCompletions do:[:each |
        self showCR: each.
    ].
    self nextPutAll: currentLine.
    self cursorCol: currentColNr.

    "Created: / 25-01-2019 / 21:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

historyDown
    ((historyPosition + 1) between: 1 and: history size) ifTrue:[ 
        historyPosition := historyPosition + 1.
        self buffer: (history at: historyPosition)
    ] ifFalse:[
        historyPosition := history size + 1.
        self buffer: ''.
    ].

    "Created: / 26-01-2019 / 22:21:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

historyUp
    ((historyPosition - 1) between: 1 and: history size) ifTrue:[ 
        historyPosition := historyPosition - 1.
        self buffer: (history at: historyPosition)
    ] ifFalse:[
        self beep.
    ].

    "Created: / 26-01-2019 / 22:21:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'cursor handling'!

cursorMovementAllowed
    ^ false

    "Created: / 25-01-2019 / 09:40:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'event handling'!

extendSelectionToX:x y:y setPrimarySelection:aBoolean
    | savCursorLine savCursorCol |

    savCursorLine := cursorLine.
    savCursorCol := cursorCol.        
    super extendSelectionToX:x y:y setPrimarySelection:aBoolean.
    self cursorLine:savCursorLine col:savCursorCol.

    "Created: / 26-01-2019 / 23:00:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress: key x: x y: y

    key == #Tab ifTrue:[ 
        self keyPressTab.
        ^ self
    ] ifFalse:[ 
        lastTabTime := lastCompletions := nil.
    ].

    key isCharacter ifTrue:[
        buffer := (buffer copyTo:bufferPosition-1)
                      , key
                      , (buffer copyFrom:bufferPosition).
        self insertCharAtCursor:key.
        bufferPosition := bufferPosition + 1. 
        ^ self
    ].
    key == #Return ifTrue:[ 
        self keyPressReturn.
        ^ self.
    ].
    key == #BackSpace ifTrue:[ 
        self keyPressBackSpace.
        ^ self.
    ].
    key == #Delete ifTrue:[ 
        self keyPressDelete.
        ^ self.
    ].
    key == #CursorLeft ifTrue:[ 
        self keyPressCursorLeft.
        ^ self.
    ].
    key == #CursorRight ifTrue:[ 
        self keyPressCursorRight.
        ^ self.
    ].
    key == #CursorUp ifTrue:[ 
        self keyPressCursorUp.
        ^ self.
    ].
    key == #CursorDown ifTrue:[ 
        self keyPressCursorDown.
        ^ self.
    ].
    ((key == #BeginOfLine) or:[key == #Ctrla]) ifTrue:[ 
        self keyPressBeginOfLine.
        ^ self
    ].
    ((key == #EndOfLine) or:[key == #Ctrle]) ifTrue:[ 
        self keyPressEndOfLine.
        ^ self
    ].

    (#(Shift_L Shift_R 
      Control_L Control_R 
      Alt_L Alt_R 
      Caps_Lock 
      PreviousPage NextPage
      Copy Paste Insert
    ) includes: key) ifTrue:[
         ^ super keyPress: key x:x y:y
    ].

    "/ Unhandled key
    self beep; flash

    "Created: / 24-01-2019 / 22:02:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-01-2019 / 22:36:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressBackSpace
    bufferPosition == 1 ifTrue:[ 
        self beep.
        ^ self.
    ].
    buffer := (buffer copyTo: bufferPosition - 2) , (buffer copyFrom: bufferPosition).
    self deleteCharBeforeCursor.
    bufferPosition := bufferPosition - 1.

    "Created: / 24-01-2019 / 22:09:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressBeginOfLine
    self cursorCol: self cursorCol - bufferPosition + 1.
    bufferPosition := 1.

    "Created: / 25-01-2019 / 10:43:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressCursorDown
    self historyDown.

    "Created: / 24-01-2019 / 22:18:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-01-2019 / 22:19:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressCursorLeft
    (bufferPosition < 2) ifTrue:[ 
        self beep.
        ^ self.
    ].
    bufferPosition := bufferPosition - 1.
    self cursorLeft.

    "Created: / 24-01-2019 / 22:18:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-01-2019 / 10:29:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressCursorRight
    (bufferPosition > buffer size) ifTrue:[ 
        self beep.
        ^ self.
    ].
    bufferPosition := bufferPosition + 1.
    self cursorRight.

    "Created: / 24-01-2019 / 22:19:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-01-2019 / 10:30:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressCursorUp
    self historyUp.

    "Created: / 24-01-2019 / 22:19:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-01-2019 / 22:19:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressDelete
    bufferPosition == (buffer size + 1) ifTrue:[ 
        self beep.
        ^ self.
    ].
    buffer := (buffer copyTo: bufferPosition - 1) , (buffer copyFrom: bufferPosition + 1).
    self deleteCharAtCursor.

    "Created: / 25-01-2019 / 10:33:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressEndOfLine
    self cursorCol: self cursorCol - bufferPosition + buffer size + 1.
    bufferPosition := buffer size + 1.

    "Created: / 25-01-2019 / 11:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressReturn
    acceptAction value: buffer.
    history add: buffer.
    historyPosition := history size + 1.
    self cr.
    buffer := ''.
    bufferPosition := 1.

    "Created: / 24-01-2019 / 22:09:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-01-2019 / 22:22:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPressTab 
    | now |

    "/ No completion installed, do nothing
    completeAction isNil ifTrue:[ 
        self flash: (resources string: 'Command completion not supported').
        ^ self 
    ].
    now := OperatingSystem getMillisecondTime.
    (lastTabTime notNil and:[(now - lastTabTime) < TabTabInterval]) ifTrue:[ 
        "/ Tab Tab has been pressed, show completion history.
        lastTabTime := nil.
        self completionsShow.
    ] ifFalse:[
        "/ A single Tab has been pressed, trigger completion.
        lastTabTime := now.
        completeAction value: (buffer copyTo: bufferPosition - 1)  

    ].

    "Created: / 25-01-2019 / 21:35:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-01-2019 / 22:38:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'initialization & release'!

initialize
    super initialize.
    buffer := ''.
    bufferPosition := 1.
    history := OrderedCollection new.
    historyPosition := 1.

    "Created: / 24-01-2019 / 22:12:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-01-2019 / 22:22:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'menu & menu actions'!

copySelection
    | savCursorLine savCursorCol |

    savCursorLine := cursorLine.
    savCursorCol := cursorCol.
    super copySelection.
    self cursorLine:savCursorLine col:savCursorCol.

    "Created: / 26-01-2019 / 22:59:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

paste:someText withCR:withCR
    "/ (For now) disallow pasting text with newlines...
    (someText includes: Character cr) ifTrue:[ 
        self beep.
        ^ self.
    ].
    buffer := (buffer copyTo: bufferPosition - 1) , someText , (buffer copyFrom: bufferPosition).
    self insertStringAtCursor: someText.
    bufferPosition := bufferPosition + someText size.

    "Created: / 26-01-2019 / 22:40:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'selections'!

selectWordAtLine:line col:col
    | savCursorLine savCursorCol |

    savCursorLine := cursorLine.
    savCursorCol := cursorCol.
    super selectWordAtLine:line col:col.
    self cursorLine:savCursorLine col:savCursorCol.

    "Created: / 26-01-2019 / 22:55:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView methodsFor:'stream messages'!

show:anObject
    super show: anObject.
    self endEntry.

    "Created: / 25-01-2019 / 09:55:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBSimpleConsoleView class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !


VDBSimpleConsoleView initialize!