VDBSimpleConsoleView.st
author Jan Vrany <jan.vrany@labware.com>
Tue, 26 Jul 2022 15:01:33 +0100
changeset 265 f2470f0dd9cd
parent 264 23960fcb9dac
permissions -rw-r--r--
Do not show address for (pseudo) instructions with no code While such instructions do not appear in GDB-produced disassembly, they may appear in some manually-generated instruction lists. One example of such (pseudo) instruction is label.

"
jv:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2022 LabWare

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
"
"{ 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:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2022 LabWare

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
"
! !

!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>"
    "Modified: / 01-12-2019 / 13:16:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

completion: completion matches: matches

    lastCompletions := matches.
    lastCompletions isEmptyOrNil ifTrue:[
        lastCompletions := nil.
        self flash: (resources string:'Nothing to complete').
        ^self.
    ].

    completion isEmptyOrNil ifTrue:[ 
        self flash: (resources string:'Ambiguous')
    ] ifFalse:[
        (completion startsWith: (buffer copyTo: bufferPosition - 1)) ifTrue:[
            | insertion |

            insertion := completion copyFrom: bufferPosition.
            buffer := (buffer copyTo: bufferPosition - 1) , insertion , (buffer copyFrom: bufferPosition).
            self insertStringAtCursor: insertion.
            bufferPosition := bufferPosition + insertion size.
        ] ifFalse:[
            self breakPoint: #jv
        ]
    ]

    "Created: / 12-06-2019 / 18:28:09 / jv"
    "Modified: / 12-06-2019 / 19:54:15 / jv"
    "Modified: / 24-11-2019 / 22:10:17 / 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 Shift_L Shift_R 
      Ctrl Control Control_L Control_R 
      Cmd Alt Alt_L Alt_R 
      Win_L Menu
      Caps_Lock Escape
      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>"
    "Modified: / 13-03-2019 / 14:11:13 / jv"
!

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.
    buffer := ''.
    bufferPosition := 1.

    "Created: / 24-01-2019 / 22:09:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-12-2019 / 11:58:45 / 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!