Workspace.st
author claus
Wed, 13 Oct 1993 03:49:56 +0100
changeset 5 7b4fb1b170e5
parent 3 9d7eefb5e69f
child 7 15a9291b9bd0
permissions -rw-r--r--
(none)

"
 COPYRIGHT (c) 1989 by Claus Gittinger
              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.
"

TextCollector subclass:#Workspace
       instanceVariableNames:'doItAction 
                              errorBox correctErrorBox
                              abortBlock codeStartPosition 
                              errorFgColor errorBgColor'
       classVariableNames:''
       poolDictionaries:''
       category:'Interface-Workspace'
!

Workspace comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
             All Rights Reserved

a view for editable text which can evaluate expressions.

instance variables:

doItAction      <Block>         block to evaluate for doIt

errorBox        <Box>           queryBox used in case of errors,
                                kept for fast pop-up
correctErrorBox <Box>           same for correctable errors
abortBlock      <Block>         internal use: to jump out of doIt
                                in case of abort from box
codeStartPosition               temporary
errorFgColor    <Color>         fg-color used when highlighting error 
errorBgColor    <Color>         bg-Color used when highlighting error

$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.3 1993-10-13 02:49:53 claus Exp $
written winter-89 by claus
'!

!Workspace class methodsFor:'getting a System Workspace'!

start
    "launch a new workspace"

    |topView workspace f|

    topView := StandardSystemView label:'Workspace' minExtent:(100 @ 100).
    workspace := super origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:topView.
    workspace level:0.

    "adjust topViews extent"
    f := workspace font.
    topView extent:((f widthOf:'x') * 40) @ (f height * 10).

    topView realize.
    ^ topView

    "Workspace start"
! !

!Workspace methodsFor:'initialize / release'!

initialize
    super initialize.

    doItAction := [:theCode |
        Compiler evaluate:theCode notifying:self
    ].
    errorFgColor := selectionFgColor.
    device hasColors ifTrue:[
        errorBgColor := Color name:'Red' 
    ] ifFalse:[
        errorBgColor := selectionBgColor
    ]
!

initializeMiddleButtonMenu
    |labels|

    labels := resources array:#(
                                       "
                                       'undo'
                                       '-'
                                       "
                                       'copy'
                                       'cut'
                                       'paste'
                                       'replace'
                                       '-'
                                       'font'
                                       '-'
                                       'search'
                                       'goto'
                                       '-'
                                       'save'
                                       'print'
                                   "   'fileIn' "
                                       '-'
                                       'doIt'
                                       'printIt'
                                       'inspectIt').

    self middleButtonMenu:(PopUpMenu 
                                labels:labels
                             selectors:#(copySelection
                                         cut
                                         paste 
                                         replace
                                         nil 
                                         changeFont
                                         nil 
                                         search
                                         gotoLine
                                         nil 
                                         save
                                         print
                                       "  fileItIn "
                                         nil 
                                         doIt 
                                         printIt
                                         inspectIt)
                                receiver:self
                                     for:self).

!

destroy
    errorBox notNil ifTrue:[errorBox destroy].
    correctErrorBox notNil ifTrue:[correctErrorBox destroy].
    super destroy
! !

!Workspace methodsFor:'selections'!

disableSelectionMenuEntries
    "disable relevant menu entries for a selection"

    super disableSelectionMenuEntries.
    middleButtonMenu disable:#doIt.
    middleButtonMenu disable:#printIt.
    middleButtonMenu disable:#inspectIt
!

enableSelectionMenuEntries
    "enable relevant menu entries for a selection"

    super enableSelectionMenuEntries.
    middleButtonMenu enable:#doIt.
    middleButtonMenu enable:#printIt.
    middleButtonMenu enable:#inspectIt
! !

!Workspace methodsFor:'accessing'!

doItAction:aBlock
    "define the action to be performed when 'doIt' is selected"

    doItAction := aBlock
!

abortAction:aBlock
    "define the action to be performed when an error occurs during
     evaluation and user selects 'abort' in ErrorBox;
     (this will usually be a block long-returning back)"

    abortBlock := aBlock
! !

!Workspace methodsFor:'error handling'!

error:aString position:relPos to:relEndPos
    "compiler notifys us of an error; hilight the error (relPos to relEndPos) 
     and show a Box asking for continue/abort"

    |absPosition fg bg|

    "change color of selection"

    fg := selectionFgColor.
    bg := selectionBgColor.
    selectionBgColor := errorBgColor.
    selectionFgColor := errorFgColor.

    "select the text - relEndPos may be nil in which case the whole line is selected"
    codeStartPosition isNil ifTrue:[codeStartPosition := 1].
    absPosition := codeStartPosition + relPos - 1.
    relEndPos isNil ifTrue:[
        self selectLineWhereCharacterPosition:absPosition
    ] ifFalse:[
        self selectFromCharacterPosition:absPosition to:(codeStartPosition + relEndPos - 1)
    ].
    self makeSelectionVisible.
    self hideCursor.

    "start Dialog - make certain, that dialog-actions clean up correctly"
    device synchronizeOutput.
    errorBox isNil ifTrue:[
        errorBox := OptionBox title:aString numberOfOptions:2.
        errorBox buttonTitles:#('abort' 'continue')
    ].
    errorBox actions:(Array with:[selectionFgColor := fg.
                                  selectionBgColor := bg.
                                  self showCursor.
                                  abortBlock value.
                                  ^ false]
                            with:[selectionFgColor := fg.
                                  selectionBgColor := bg.
                                  self showCursor.
                                  self unselect.
                                  ^ false]).
    (errorBox title:aString) showAtPointer
!

warning:aString position:relPos to:relEndPos
    "compiler notifys us of a  warning - same behavior as error"

    self error:aString position:relPos to:relEndPos
!

correctableError:aString position:relPos to:relEndPos
    "compiler notifys us of a correctable error;
     hilight the error (relPos to relEndPos) and show a Box asking for continue/correct/abort;
     this method should return true to the compiler if user wants the error
     to be corrected; false otherwise"

    |absPosition fg bg|

    "change selection color"

    fg := selectionFgColor.
    bg := selectionBgColor.
    selectionBgColor := errorBgColor.
    selectionFgColor := errorFgColor.

    "select the error"
    codeStartPosition isNil ifTrue:[codeStartPosition := 1].
    absPosition := codeStartPosition + relPos - 1.
    relEndPos isNil ifTrue:[
        self selectLineWhereCharacterPosition:absPosition
    ] ifFalse:[
        self selectFromCharacterPosition:absPosition to:(codeStartPosition + relEndPos - 1)
    ].
    self makeSelectionVisible.
    self hideCursor.

    "start dialog - make certain cleanup is done"
    device synchronizeOutput.
    correctErrorBox isNil ifTrue:[
        correctErrorBox := OptionBox title:aString numberOfOptions:3.
        correctErrorBox buttonTitles:#('abort' 'correct' 'continue')
    ].
    correctErrorBox actions:(Array with:[selectionFgColor := fg.
                                         selectionBgColor := bg.
                                         self showCursor.
                                         abortBlock value.
                                         ^ false]
                                   with:[selectionFgColor := fg.
                                         selectionBgColor := bg.
                                         self showCursor.
                                         ^ true]
                                   with:[selectionFgColor := fg.
                                         selectionBgColor := bg.
                                         self showCursor.
                                         self unselect. 
                                         ^ false]).
    (correctErrorBox title:aString) showAtPointer
! !

!Workspace methodsFor:'execution'!

doItWithValueDo:aBlock
    "helper for doIt, printIt and inspectIt. Evaluate the selection and,
     if all went well, evaluate the argument, aBlock with the value."

    |code value selLine selCol endLine endCol|

    code := self selection.
    code notNil ifTrue:[
        codeStartPosition := self characterPositionOfSelection.
        selLine := selectionStartLine.
        selCol := selectionStartCol.
        endLine := selectionEndLine.
        endCol := selectionEndCol.

        self cursor:Cursor execute.
        abortBlock := [self cursor:Cursor normal.
                       self selectFromLine:selLine col:selCol
                                    toLine:endLine col:endCol.
                       abortBlock := nil.
                       ^ nil].
        [
            value := doItAction value:(code asString)
        ] valueNowOrOnUnwindDo:[
            self cursor:Cursor normal.
            self selectFromLine:selLine col:selCol toLine:endLine col:endCol.
            abortBlock := nil
        ].
        aBlock value:value
    ]
!

doIt
    "user selected 'doIt' from menu; show a wait-cursor, evaluate the code
     and finally restore cursor; return result of evaluation"

    self doItWithValueDo:[:result | ]
!

inspectIt
    "user selected 'inspectIt' from menu; use doIt to evaluate the code
     and start an inspector on the result"

    self doItWithValueDo:[:result | result inspect]
!

printIt
    "user selected 'printIt' from menu; use doIt to evaluate the code
     and insert result of evaluation into my text"

    self doItWithValueDo:[:result | 
        self cursorLine:selectionEndLine col:(selectionEndCol + 1).
        self insertSelectedStringAtCursor:(result printString)
    ]
! !

!Workspace methodsFor:'events'!

keyPress:key x:x y:y
    (key == #Cmdd) ifTrue:[^ self doIt].
    (key == #Cmdi) ifTrue:[^ self inspectIt].
    (key == #Cmdp) ifTrue:[^ self printIt].
    super keyPress:key x:x y:y
! !