Workspace.st
author Claus Gittinger <cg@exept.de>
Wed, 21 Dec 2005 11:26:24 +0100
changeset 3219 e8c7679a8a94
parent 3210 75d4c266d873
child 3252 b44361e6b97a
permissions -rw-r--r--
buttonrelease behavior, when released in another view than clicked (for example, after double clicking a file in the fileBrowsers search list)

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

"{ Package: 'stx:libwidg' }"

TextCollector subclass:#Workspace
	instanceVariableNames:'doItAction codeStartPosition errorFgColor errorBgColor
		commentStrings autoDefineWorkspaceVariables simulatedSelf
		autoDefineVariables compilerClass'
	classVariableNames:'DefaultViewBackground DefaultErrorForegroundColor
		DefaultErrorBackgroundColor DefaultWarningBackgroundColor
		DefaultWarningForegroundColor WorkspaceVariables DoItHistory'
	poolDictionaries:''
	category:'Interface-Smalltalk'
!

Workspace comment:'declared from: ..\..\..\stx\libwidg\abbrev.stc'
!

!Workspace class methodsFor:'documentation'!

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

documentation
"
    a view for editable text which can evaluate expressions.
    I.e. its basically a view for editable text, with added
    'doIt', 'printIt' and 'inspectIt' functions on the popup-menu.

    The action to be performed on doIt is defined by a block,
    which can be defined by the owner of this view.
    (thus you can put a workspace into more complex widgets, and
     control what should happen on 'doIt').

    A useful default action is automatically defined, which simply 
    evaluates the selection as a smalltalk expression. 
    (but, a lisp or prolog workspace would define its own action,
     to call for another compiler/interpreter  ...)


    Caveat:
        in this version, Workspace does not yet support doIt in MVC setups.
        For now, simulate this by setting the doItAction, to notify the
        model manually about the doIt.


    [instance variables:]

      doItAction      <Block>         block to evaluate for doIt

      errorFgColor    <Color>         fg-Color to be used when highlighting errors 

      errorBgColor    <Color>         bg-Color to be used when highlighting errors

      codeStartPosition               private temporary


    [styleSheet values:]

      codeErrorSelectionForegroundColor     fg color to highlight errors
                                            (default: selection fg)

      codeErrorSelectionBackgroundColor     bg color to highlight errors
                                            (default: selection bg)

    [start with:]
        Workspace open

    [see also:]
        Workspace EditTextView 
        Parser ByteCodeCompiler

    [author:]
        Claus Gittinger
"
! !

!Workspace class methodsFor:'defaults'!

defaultLabel
    "my default window label"

    ^ 'Workspace'

    "Created: / 16.5.1998 / 16:53:37 / cg"
!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style (#'codeErrorSelection.foregroundColor'
                       #'codeErrorSelection.backgroundColor'
                       #'codeView.backgroundColor' )>

    DefaultErrorForegroundColor := StyleSheet colorAt:'codeErrorSelection.foregroundColor'.
    DefaultErrorBackgroundColor := StyleSheet colorAt:'codeErrorSelection.backgroundColor'.
    DefaultViewBackground := StyleSheet colorAt:'codeView.backgroundColor'.
! !

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

open
    "launch a new workspace"

    |scr topView workspace f|

    topView := StandardSystemView 
                label:(self classResources string:(self defaultLabel)) 
                " minExtent:(100 @ 100)".

    scr := HVScrollableView for:self in:topView.
    scr origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    workspace := scr scrolledView.

    "/ adjust topViews extent according to my font

    f := workspace font.
    topView extent:((f widthOf:'x') * 40) @ (f height * 10).
    topView open.
    ^ workspace

    "
     Workspace open
    "

    "Modified: / 16.5.1998 / 16:53:53 / cg"
!

openForRemote:hostName
    "launch a new workspace to evaluate expression on some remote machine.
     Entered expressions are sent over to some partner machine, evaluated there,
     and the result is shown here.
     This requires the RemoteObjects package to be loaded."

    |server remoteCompiler workspace|

    RemoteObjectServer isNil ifTrue:[
        self warn:'no remoteObjectServer available'.
        ^ nil
    ].

    server := RemoteObjectServer on:hostName.
    remoteCompiler := server get:#Compiler.

    workspace := self open.
    workspace topView 
        label:(self classResources string:'Remote Workspace {%1}' with:hostName).

    workspace doItAction:
                [:theCode |
                    remoteCompiler 
                        evaluate:theCode 
                        in:nil 
                        receiver:nil 
                        notifying:workspace 
                        logged:true 
                        ifFail:nil 
                ]
    "
     Workspace openForRemote:'andi'
    "

    "Modified: / 16.5.1998 / 16:57:38 / cg"
!

openWith:initialText selected:selectedBoolean
    "launch a new workspace with some initial contents"

    |workspace|

    workspace := self open.
    workspace contents:initialText selected:selectedBoolean.
    ^ workspace

    "
     Workspace openWith:'Transcript showCR:''hello world'''
    "
! !

!Workspace class methodsFor:'history'!

clearDoItHistory
    DoItHistory := nil
!

doItHistory
    ^ DoItHistory
!

doItHistorySize
    "the number of remembered doIts"

    ^ 20
!

rememberDoIt:aString
    |string|

    string := aString asString string withoutSeparators.
    (string asCollectionOfWords size <= 1) ifTrue:[
        ((Scanner new scanTokens:string) size <= 1) ifTrue:[
            "its a variable only"
            ^ self
        ]
    ].

    DoItHistory isNil ifTrue:[
        DoItHistory := OrderedCollection new.
    ].
    DoItHistory remove:string ifAbsent:nil.
    DoItHistory addFirst:string.
    DoItHistory size > self doItHistorySize ifTrue:[
        DoItHistory removeLast
    ].

    Scanner
! !

!Workspace class methodsFor:'queries'!

isVisualStartable
    "returns whether this application class can be started via #open
     (i.e. via a double click on the class in the browser)"

    ^ self == Workspace

    "Created: / 16.5.1998 / 16:59:00 / cg"
    "Modified: / 16.5.1998 / 16:59:39 / cg"
! !

!Workspace class methodsFor:'workspace variables'!

addWorkspaceVariable:name
    "create a new workspace variable"

    |holder|

    WorkspaceVariables isNil ifTrue:[
        WorkspaceVariables := Dictionary new.
    ].
    holder := WorkspaceVariables at:name ifAbsentPut:[ ValueHolder new ].
    ^ holder
!

anyWorkspaceVariableIsDefined
    ^ WorkspaceVariables notEmptyOrNil

    "Created: / 20-04-2005 / 11:57:53 / cg"
!

removeAllWorkspaceVariables
    "delete all workspace variables"

    WorkspaceVariables := nil


!

removeWorkspaceVariable:name
    "delete a workspace variable"

    WorkspaceVariables notNil ifTrue:[
        WorkspaceVariables removeKey:name ifAbsent:nil.
        WorkspaceVariables isEmpty ifTrue:[
            WorkspaceVariables := nil
        ]
    ].


!

workspaceVariableAt:name
    "retrieve a workspace variable (actually, a holder onto it)"

    WorkspaceVariables isNil ifTrue:[^ nil].
    ^ WorkspaceVariables at:name ifAbsent:nil.


!

workspaceVariableNames
    "retrieve the collection of workspace variable names"

    WorkspaceVariables isNil ifTrue:[^ #()].
    ^ WorkspaceVariables keys

    "Created: / 20-04-2005 / 11:42:45 / cg"
!

workspaceVariables
    "retrieve the collection of workspace variables.
     That is a dictionary associating names to values."

    ^ WorkspaceVariables ? #()

    "Modified: / 20-04-2005 / 11:43:14 / cg"
! !

!Workspace methodsFor:'accessing'!

autoDefineVariables
    ^ autoDefineVariables 
!

autoDefineVariables:nilOrSymbol
    autoDefineVariables := nilOrSymbol.
!

commentStrings:anArrayOfCommentStrings
    "define the comment strings"

    commentStrings := anArrayOfCommentStrings

    "Created: / 9.11.1997 / 01:05:25 / cg"
!

doItAction
    "return the action to be performed when 'doIt' is selected"

    ^ doItAction
!

errorBackgroundColor
    errorBgColor notNil ifTrue:[ ^ errorBgColor ].
    DefaultErrorBackgroundColor notNil ifTrue:[ ^ DefaultErrorBackgroundColor ].
    device hasColors ifTrue:[ ^ Color red ].

    ^ selectionBgColor
!

errorForegroundColor
    errorFgColor notNil ifTrue:[ ^ errorFgColor ].
    DefaultErrorForegroundColor notNil ifTrue:[ ^ DefaultErrorForegroundColor ].
    ^ selectionFgColor
!

selectAll
    super selectAll
!

simulatedSelf:anObject
    "define what self is in an evaluation"

    simulatedSelf := anObject
!

warningBackgroundColor
    DefaultWarningBackgroundColor notNil ifTrue:[ ^ DefaultWarningBackgroundColor ].
    device hasColors ifTrue:[ ^ Color orange ].

    ^ selectionBgColor
!

warningForegroundColor
    DefaultWarningForegroundColor notNil ifTrue:[ ^ DefaultWarningForegroundColor ].
    ^ selectionFgColor
! !

!Workspace methodsFor:'compiler interface'!

compilerClass
    ^ compilerClass ? Compiler
!

compilerClass:aCompilerClass
    compilerClass := aCompilerClass
!

currentSourceCode
    "special interface to compiler - called by parser
     to get the updated source code after a corrected error"

    ^ self contents
!

wantChangeLog
    "sent by the compiler to ask if a changeLog entry should
     be written. Return true here."

    ^ true
! !

!Workspace methodsFor:'compiler interface-error handling'!

correctableError:aString position:relPos to:relEndPos from:aCompiler
    "compiler notifies 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"

    |action|

    self highlightingErrorPosition:relPos to:relEndPos do:[
        action := OptionBox 
                      request:aString
                      label:'Correctable Error'
                      image:(WarningBox iconBitmap)
                      buttonLabels:#('Cancel' 'Declare as...' 'Correct...' 'Continue')
                      values:#(#abort #declare #correct #continue)
                      default:#continue
                      onCancel:#abort.
    ].

    action == #declare ifTrue:[
        ^ action
    ].
    action == #abort ifTrue:[
        AbortOperationRequest raise.
        ^ false
    ].
    ^ action == #correct

    "Modified: / 16.11.2001 / 17:39:26 / cg"
!

correctableSelectorWarning:aString position:relPos to:relEndPos from:aCompiler
    "compiler notifies us of a correctable selector warning;
     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"

    |action|

    self highlightingErrorPosition:relPos to:relEndPos do:[
        action := OptionBox 
                      request:aString
                      label:'Warning'
                      image:(WarningBox iconBitmap)
                      buttonLabels:(resources array:#('Cancel' 'Correct...' 'Generate' 'Continue'))
                      values:#(#abort #correct #generate #continue)
                      default:#continue
                      onCancel:#abort.
    ].

    action == #generate ifTrue:[
        ^ action
    ].

    (action isNil or:[action == #abort]) ifTrue:[
        AbortOperationRequest raise.
        ^ false
    ].
    ^ action == #correct

    "Created: / 19.1.2000 / 16:27:28 / cg"
    "Modified: / 16.11.2001 / 17:39:29 / cg"
!

error:aString position:relPos to:relEndPos asWarning:asWarning
    "obsolete - no longer invoked"

    ^ self error:aString position:relPos to:relEndPos from:nil asWarning:asWarning
!

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

    ^ self error:aString position:relPos to:relEndPos from:aCompiler asWarning:false
!

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

    |answer fg bg|

    fg := asWarning ifTrue:[ self warningForegroundColor ] ifFalse:[ self errorForegroundColor ].
    bg := asWarning ifTrue:[ self warningBackgroundColor ] ifFalse:[ self errorBackgroundColor ].

    self 
        highlightingErrorPosition:relPos to:relEndPos 
        withForeground:fg andBackground:bg
        do:[
            |box lbl doNotShowAgainHolder l1 y1 y2 l2|

            WarningSignal isHandled ifTrue:[
                WarningSignal raiseErrorString:aString.
                ^ false
            ].

            "
             ask if we should abort or continue
            "
            box := YesNoBox 
                    title:aString
                    yesText:(resources string:'Continue')
                    noText:(resources string:'Abort').

            lbl := aCompiler isNil ifTrue:['Compiler'] ifFalse:[aCompiler class name].
            asWarning ifTrue:[
                lbl := lbl , ' Warning'
            ] ifFalse:[
                lbl := lbl , ' Error'.
            ].
            box label:lbl.
            box image:(WarningBox iconBitmap).

            aCompiler class doNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
                doNotShowAgainHolder := false asValue.
                box addCheckBox:'Do not show this dialog again (reenable via Launchers Settings Dialog)' on:doNotShowAgainHolder.
            ].

            answer := box confirm.  

            doNotShowAgainHolder value == true ifTrue:[
                aCompiler class doNotShowCompilerWarningAgainActionQuery actionQuery value    
            ].

            box destroy.
        ].

    "
     do the abort if we have to
    "
    answer ifFalse:[    
        AbortOperationRequest raise.
    ].
    ^ false

    "Created: / 24.11.1995 / 22:56:34 / cg"
    "Modified: / 16.11.2001 / 17:39:31 / cg"
!

highlightingErrorLine:lineNr do:aBlock
    "evaluate aBlock while some selection is shown highlighted with error colors."

    |linePosition|

    linePosition := self characterPositionOfLine:lineNr col:1.
    self highlightingErrorPosition:linePosition to:nil do:aBlock
!

highlightingErrorPosition:relPos to:relEndPos do:aBlock
    "evaluate aBlock while some selection is shown highlighted with error colors."

    self 
        highlightingErrorPosition:relPos to:relEndPos 
        withForeground:(self errorForegroundColor) andBackground:(self errorBackgroundColor) 
        do:aBlock
!

highlightingErrorPosition:relPos to:relEndPos withForeground:hilightFg andBackground:hilightBg do:aBlock
    "evaluate aBlock while some selection is shown highlighted with colors passed as args."

    |absPosition oldFg oldBg|

    "
     change color of selection & hide cursor
    "
    oldFg := selectionFgColor.
    oldBg := selectionBgColor.
    selectionBgColor := hilightBg.
    selectionFgColor := hilightFg.
    self hideCursor.

    "
     select the text - relEndPos may be nil in which case the whole line is selected
     we have to adjust the positions given by the compiler, since they
     are relative to the texts start (the compiler did stream-read the code).
    "
    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.

    device flush.

    aBlock ensure:[
        "
         undo selection color change and show cursor again
        "
        selectionFgColor := oldFg.
        selectionBgColor := oldBg.
        self showCursor.
    ].
!

highlightingWarningPosition:relPos to:relEndPos do:aBlock
    "evaluate aBlock while some selection is shown highlighted with warning colors."

    self 
        highlightingErrorPosition:relPos to:relEndPos 
        withForeground:(self warningForegroundColor) andBackground:(self warningBackgroundColor) 
        do:aBlock
!

unusedVariableWarning:aString position:relPos to:relEndPos from:aCompiler
    "compiler notifies us of a (or some) unused variables;
     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"

    |action|

    self highlightingWarningPosition:relPos to:relEndPos do:[
        action := OptionBox 
                      request:aString
                      label:'Warning'
                      image:(WarningBox iconBitmap)
                      buttonLabels:#('Cancel' 'Remove Variable(s)' 'Continue')
                      values:#(#abort #correct #continue)
                      default:#continue.
    ].

    action == #abort ifTrue:[
        AbortOperationRequest raise.
        ^ false
    ].
    ^ action == #correct

    "Modified: / 16.11.2001 / 17:39:34 / cg"
!

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

    self error:aString position:relPos to:relEndPos from:aCompiler asWarning:true 
! !

!Workspace methodsFor:'editing'!

commentFrom:line1 to:line2
    "convenient function to comment out a block.
     All lines from line1 to line2 get an end-of-line comment
     in the first col 
     (if no eol comment is available, a bracketing comment is used)."

    |eolComment opening closing|

    eolComment := commentStrings at:1.
    eolComment isNil ifTrue:[
        opening := (commentStrings at:2) at:1.
        closing := (commentStrings at:2) at:2.
        (opening isNil or:[closing isNil]) ifTrue:[^ self].
    ].

    line1 to:line2 do:[:lineNr |
        |l|

        l := self listAt:lineNr.
        l isNil ifTrue:[l := ''].
        eolComment notNil ifTrue:[
            l := eolComment , l
        ] ifFalse:[
            l := opening , l , closing
        ].
        self at:lineNr basicPut:l
    ].
    self textChanged.

    "Modified: / 7.1.1997 / 20:15:06 / cg"
    "Created: / 9.11.1997 / 01:05:35 / cg"
!

commentSelection
    "convenient function to comment out a block.
     All lines from line1 to line2 get an end-of-line comment
     in the first col."

    |e commentPair opening closing|

    (self checkModificationsAllowed) ifFalse:[ ^ self].
    commentStrings isNil ifTrue:[ self beep. ^ self].

    selectionStartLine isNil ifTrue:[ 
        self 
            undoableDo:[
                self commentFrom:cursorLine to:cursorLine
            ].
        ^ self
    ].

    self 
        undoableDo:
            [
                (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
                    self commentFrom:selectionStartLine to:selectionEndLine-1
                ] ifFalse:[
                    commentPair := commentStrings at:2 ifAbsent:nil.
                    commentPair isNil ifTrue:[
                        self beep.
                    ] ifFalse:[
                        opening := commentPair at:1.
                        closing := commentPair at:2.
                        (opening isNil or:[closing isNil]) ifTrue:[^ self].

                        e := selectionEndCol.

                        self insertString:closing atLine:selectionEndLine col:e+1.
                        self insertString:opening atLine:selectionStartLine col:selectionStartCol.

                        selectionStartLine == selectionEndLine ifTrue:[e := e + opening size].
                        self selectFromLine:selectionStartLine col:selectionStartCol
                                     toLine:selectionEndLine col:e+closing size.
                    ]
                ]
            ]
        info:'comment'

    "Created: / 9.11.1997 / 01:05:40 / cg"
    "Modified: / 5.4.1998 / 16:52:23 / cg"
!

uncommentFrom:line1 to:line2
    "convenient function to comment out a block.
     All lines from line1 to line2 get an end-of-line comment
     in the first col.
     (if no eol comment is available, a bracketing comment is removed)"

    |eolComment opening closing rest|

    eolComment := commentStrings at:1.
    eolComment isNil ifTrue:[
        opening := (commentStrings at:2) at:1.
        closing := (commentStrings at:2) at:2.
        (opening isNil or:[closing isNil]) ifTrue:[^ self].
    ] ifFalse:[
        rest := eolComment size + 1.
    ].

    line1 to:line2 do:[:lineNr |
        |l|

        l := self listAt:lineNr.
        l notNil ifTrue:[
            eolComment notNil ifTrue:[
                (l startsWith:eolComment) ifTrue:[
                    l := l copyFrom:rest
                ]
            ] ifFalse:[
                ((l startsWith:opening)
                and:[l endsWith:closing]) ifTrue:[
                    l := l copyFrom:opening size + 1.
                    l := l copyWithoutLast:closing size.
                ]
            ].
            self at:lineNr basicPut:l
        ]
    ].
    self textChanged.

    "Modified: / 7.1.1997 / 20:17:44 / cg"
    "Created: / 9.11.1997 / 01:05:43 / cg"
!

uncommentSelection
    "convenient function to comment out a block.
     All lines from line1 to line2 get an end-of-line comment
     in the first col."

    |e commentPair opening closing sz1 sz2|

    (self checkModificationsAllowed) ifFalse:[ ^ self].
    selectionStartLine isNil ifTrue:[ 
        self 
            undoableDo:[
                self uncommentFrom:cursorLine to:cursorLine
            ].
        ^ self
    ].

    self 
        undoableDo:
            [
                (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
                    self uncommentFrom:selectionStartLine to:selectionEndLine-1
                ] ifFalse:[
                    commentPair := commentStrings at:2.
                    opening := commentPair at:1.
                    closing := commentPair at:2.
                    (opening isNil or:[closing isNil]) ifTrue:[^ self].

                    sz1 := opening size.
                    sz2 := closing size.

                    ((self 
                        stringAtLine:selectionStartLine 
                        from:selectionStartCol
                        to:selectionStartCol+sz1 - 1) = opening
                    and:[(self 
                        stringAtLine:selectionEndLine 
                        from:selectionEndCol - sz2 + 1
                        to:selectionEndCol) = closing ]) ifTrue:[

                        self deleteCharsAtLine:selectionEndLine fromCol:selectionEndCol-sz2+1 toCol:selectionEndCol.
                        self deleteCharsAtLine:selectionStartLine fromCol:selectionStartCol toCol:selectionStartCol+sz1-1.

                        e := selectionEndCol - sz2.
                        selectionStartLine == selectionEndLine ifTrue:[e := e - sz1].
                        self selectFromLine:selectionStartLine col:selectionStartCol
                                     toLine:selectionEndLine col:e.
                    ]
                ]
            ]
        info:'uncomment'

    "Modified: / 7.1.1997 / 20:13:32 / cg"
    "Created: / 9.11.1997 / 01:05:46 / cg"
! !

!Workspace methodsFor:'events'!

keyPress:key x:x y:y
    <resource: #keyboard (#DoIt #InspectIt #PrintIt #BrowseIt)>

    (key == #DoIt)      ifTrue:[^ self doIt].
    (key == #InspectIt) ifTrue:[^ self inspectIt].
    (key == #PrintIt)   ifTrue:[^ self printIt].
    (key == #BrowseIt)  ifTrue:[^ self browseIt].

    super keyPress:key x:x y:y
! !

!Workspace methodsFor:'executing'!

do:code withValueDo:aBlock
    "helper for doIt, printIt and inspectIt. 
     Evaluate the selection and, if all went well, evaluate the argument, 
     aBlock with the value.
     Most work is in preparing for proper cleanup in case of abort
     or other exception while the evaluation is performed.
     (restore cursor, selectionColors etc.)"

    |selLine selCol endLine endCol cLine cCol cleanUp|

    code notNil ifTrue:[
        code asString withoutSeparators isEmpty ifTrue:[ ^ self ].

        codeStartPosition := self characterPositionOfSelection.

        "
         remember selection for later - if there is an error,
         the notification method will highlight it.
         thus destroying the current selection
        "
        selLine := selectionStartLine.
        selCol := selectionStartCol.
        endLine := selectionEndLine.
        endCol := selectionEndCol.
        cCol := cursorCol.
        cLine := cursorLine.

        "
         cleanup: restore previous selection and cursor positions
        "
        cleanUp := [
                self selectFromLine:selLine col:selCol toLine:endLine col:endCol.
                cLine notNil ifTrue:[
                    self cursorLine:cLine col:cCol
                ].
        ].

        "
         perform the action.
         Be careful to release the reference to the value;
         otherwise, we could keep lots of garbage from being freed
         until the view gets closed
        "
        self topView withExecuteCursorDo:[
            [
                AbortOperationRequest handle:[:ex |
                     ex return
                ] do:[
                    |value|

                    doItAction notNil ifTrue:[
                        value := doItAction value:(code asString).
                        cleanUp value. cleanUp := nil.
                        aBlock value:value.
                        value := nil.
                        self class rememberDoIt:code.
                    ]
                ]
            ] ensure:[
                cleanUp notNil ifTrue:[
                    cleanUp value. cleanUp := nil
                ].
            ]
        ].
    ]

    "Modified: / 22.4.1998 / 21:56:13 / ca"
    "Created: / 22.4.1998 / 21:57:05 / ca"
    "Modified: / 26.9.2001 / 17:32:59 / cg"
! !

!Workspace methodsFor:'initialization & release'!

doItAction:aOneArgBlock
    "define the action to be performed when 'doIt' is selected.
     The block will be evaluated, passing the selection as a String argument. 
     A default doItAction is set for you in the initialize method."

    doItAction := aOneArgBlock

    "Modified: 27.2.1996 / 15:31:37 / cg"
!

executeDoIt:theCode
    ^ self compilerClass 
        evaluate:theCode 
        in:nil 
        receiver:simulatedSelf 
        notifying:self 
        logged:true 
        ifFail:nil 
!

initStyle
    "setup viewStyle specifics"

    super initStyle.

    DefaultViewBackground notNil ifTrue:[
        viewBackground := DefaultViewBackground.
        self backgroundColor:viewBackground.
    ].
!

initialize
    super initialize.

    scrollWhenUpdating := #beginOfText.
    showMatchingParenthesis := true.
    commentStrings := #(
                        '"/'
                        ('"' '"')
                       ).

    self initializeDoITAction.

    "Modified: / 9.11.1997 / 01:10:18 / cg"
!

initializeDoITAction
    "set up the block to be evaluated for doIts.
     This is done here in a separate method to allow easier
     redefinition in subclasses"

    doItAction := [:theCode | self executeDoIt:theCode].
! !

!Workspace methodsFor:'menu & menu actions'!

browseClass
    "user selected 'browseClass' from menu; evaluate the code
     and open a browser on the resulting class (if it evaluates to one)"

    ^ self 
        do:(self selection) 
        withValueDo:[:result | result isBehavior ifTrue:[
                                  result browserClass openInClass:result selector:nil
                               ] ifFalse:[
                                  self warn:'Selection does not evaluate to a class'
                               ]
                    ].

    "Modified: / 26.9.2001 / 17:37:35 / cg"
!

browseImplementorsOfIt
    "open a browser on the implementors of the selected text"

    |selectedText selector browserClass|

    selectedText := self selectionAsString.
    selectedText size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            selector := Parser selectorInExpression:selectedText.

            browserClass := UserPreferences current systemBrowserClass.

            (selector notNil and:[selector ~~ selectedText]) ifTrue:[
                browserClass browseImplementorsOfAny:(Set with:selector with:selectedText)
            ] ifFalse:[
                browserClass browseImplementorsOf:(selector ? selectedText)
            ]
        ]
    ].

    "Created: / 5.11.2001 / 17:32:23 / cg"
    "Modified: / 19.11.2001 / 22:15:17 / cg"
!

browseIt
    "evaluate the code and open a browser on the resulting class (if it evaluates to one),
     or the class of the resulting object (if it does not evaluate to a class).

     Added feature: if selection is of the form class >> selector,  immediately switch to that selector."

    |codeToEvaluate idx selector|

    codeToEvaluate := self selection asString withoutSeparators.
    idx := codeToEvaluate indexOfSubCollection:'>>'.
    idx ~~ 0 ifTrue:[
        selector := (codeToEvaluate copyFrom:idx+2) withoutSeparators string.
        (selector startsWith:'#') ifTrue:[
            selector := Symbol readFrom:selector.
        ].
        codeToEvaluate := codeToEvaluate copyTo:idx-1.   
    ].

    ^ self 
        do:codeToEvaluate 
        withValueDo:[:result | result isBehavior ifTrue:[
                                  result browserClass openInClass:result selector:selector
                               ] ifFalse:[
                                  result class browserClass openInClass:(result class) selector:nil
                               ]
                    ].

    "Modified: / 26.9.2001 / 17:37:50 / cg"
!

browseItsClass
    "user selected 'browseItsClass' from menu; evaluate the code
     and open a browser on the results class"

    ^ self 
        do:(self selection) 
        withValueDo:[:result | 
                        result class browserClass openInClass:result class selector:nil
                    ]

    "Modified: / 26.9.2001 / 17:38:06 / cg"
!

browseReferencesToIt
    "open a browser on all references to the selected global"

    |sel|

    sel := self selectionAsString.
    sel size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            (UserPreferences current systemBrowserClass)
                browseReferendsOf:sel
        ].
    ].

    "Created: / 5.11.2001 / 17:32:23 / cg"
    "Modified: / 5.11.2001 / 17:32:38 / cg"
!

browseSendersOfIt
    "open a browser on the senders of the selected text"

    |selectedText selector|

    selectedText := self selectionAsString.
    selectedText size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            selector := Parser selectorInExpression:selectedText.
            (UserPreferences current systemBrowserClass)
                browseAllCallsOn:(selector ? selectedText)
        ]
    ].

    "Created: / 5.11.2001 / 17:32:23 / cg"
    "Modified: / 19.11.2001 / 22:15:27 / cg"
!

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

    ^ self 
        do:(self selection) 
        withValueDo:[:result | ]

    "Modified: / 16.5.1998 / 16:45:01 / cg"
!

editMenu
    "return my popUpMenu; thats the superclasses menu
     PLUS st-evaluation items: doIt, printIt and inspectIt."

    <resource: #keyboard (#DoIt #PrintIt #InspectIt 
                          #CommentSelection #UncommentSelection
                          #BrowseIt #ImplementorsOfIt
                         )>
    <resource: #programMenu>

    |m sub subsub idx sensor s s2|

    m := super editMenu.
    ((sensor := self sensor) notNil and:[sensor ctrlDown]) ifTrue:[
        sub := m.
        m := nil.
    ] ifFalse:[
        sub := m subMenuAt:#others.
    ].

    sub notNil ifTrue:[

        "
         workspaces support #browse, implementors etc. add them after paste.
        "
        sub 
            addItemList:#(
                ('-'                                                               )
                ('Browse'               browseIt                BrowseIt            )
                ('Senders of It'        browseSendersOfIt                           )
                ('Implementors of It'   browseImplementorsOfIt  ImplementorsOfIt    )
                ('References to It'     browseReferencesToIt                        )
                ('-'                                                                )
                ('TimeIt'               timeIt                                      )
                ('SpyOnIt'              spyOnIt                                     ))
          resources:resources  
          after:#gotoLine.

        subsub := sub subMenuAt:#tools.
        subsub notNil ifTrue:[
            subsub
                addItemList:#(
                    ('-'                                                                )
                    ('Comment'              commentSelection        CommentSelection    )
                    ('Uncomment'            uncommentSelection      UncommentSelection  ))
              resources:resources  
              after:#'indent'.
        ].

        self hasSelection ifFalse:[
            sub disableAll:#(browseIt browseImplementorsOfIt browseSendersOfIt browseReferencesToIt timeIt spyOnIt
                              commentSelection uncommentSelection ) 
        ] ifTrue:[
            s := self selectionAsString.
            s2 := Parser selectorInExpression:s.
            s2 notNil ifTrue:[
                s2 := s2 asSymbolIfInterned.
            ].
            s notNil ifTrue:[
                s := s asSymbolIfInterned.
            ].
            (s2 isNil and:[s isNil]) ifTrue:[
                sub disableAll:#(browseImplementorsOfIt browseSendersOfIt).
            ].
            (s isNil 
            or:[(Smalltalk includesKey:s) not])
            ifTrue:[
                sub disable:#browseReferencesToIt.
            ].
            self isReadOnly ifTrue:[
                sub disableAll:#(commentSelection uncommentSelection) 
            ].
        ].
    ].

    m notNil ifTrue:[
        "
         workspaces support #doIt, #printIt and #inspectIt
         add them after paste.
        "
        idx := m indexOf:#paste.
        idx == 0 ifTrue:[idx := m indexOf:#pasteOrReplace].
        idx ~~ 0 ifTrue:[
            m 
              addItemList:#(
                ('-'                                )
                ('DoIt'         doIt        DoIt     )
                ('PrintIt'      printIt     PrintIt  )
                ('InspectIt'    inspectIt   InspectIt))
              resources:resources  
              after:idx.
            
        ].

        self hasSelection ifFalse:[
            m disableAll:#(printIt doIt inspectIt) 
        ].
        self isReadOnly ifTrue:[
            m disable:#printIt 
        ].
    ].

    ^ m ? sub.

    "Modified: / 22.4.1998 / 21:49:06 / ca"
    "Modified: / 19.11.2001 / 23:12:01 / cg"
!

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

    |shifted|

    shifted := self sensor shiftDown.

    ^ self 
        do:(self selection) 
        withValueDo:[:result | shifted ifTrue:[result basicInspect] ifFalse:[result inspect] ]

    "Modified: / 16.5.1998 / 16:44:56 / cg"
!

printIt
    "user selected 'printIt' from menu; use doIt to evaluate the code
     and insert result of evaluation into my text.
     If the text is readOnly, do nothing."

    self isReadOnly ifTrue:[
        self beep
    ] ifFalse:[ 
        self 
            do:(self selection) 
            withValueDo:[:result | 
                self cursorLine:selectionEndLine col:(selectionEndCol + 1).
                self insertSelectedStringAtCursor:(result displayString "printString")
            ]
    ]

    "Modified: / 16.5.1998 / 16:44:44 / cg"
!

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

    |code|

    code := 'MessageTally spyOn:[' , self selection asString string, ']'.
    self do:code withValueDo:[:result | ]

    "Modified: / 22.4.1998 / 22:03:53 / ca"
!

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

    |code|

    code := '|t| t := Time millisecondsToRun:[' , self selection asString string, '].

    Transcript showCR:''execution time: '' , t printString , '' ms''.'.
    self do:code withValueDo:[:result | ]

    "Modified: / 22.4.1998 / 22:03:51 / ca"
! !

!Workspace methodsFor:'queries'!

isWorkspace
    ^ true
! !

!Workspace class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.152 2005-10-06 15:38:16 cg Exp $'
! !