Workspace.st
author claus
Mon, 06 Feb 1995 01:53:30 +0100
changeset 77 565b052f5277
parent 67 c986a5f327f9
child 79 6d917a89f7b7
permissions -rw-r--r--
*** empty log message ***

"
 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 
			      codeStartPosition 
			      errorFgColor errorBgColor'
       classVariableNames:'DefaultErrorForegroundColor DefaultErrorBackgroundColor'
       poolDictionaries:''
       category:'Interface-Workspace'
!

Workspace comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	     All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.14 1994-11-22 00:37:11 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.14 1994-11-22 00:37:11 claus Exp $
"
!

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 setup, which simply evaluates the
    selection as a smalltalk expression. (but, a lisp or prolog
    view could define its own action ...)

    instance variables:

    doItAction      <Block>         block to evaluate for doIt
    codeStartPosition               temporary

    errorFgColor    <Color>         fg-Color to be used when highlighting errors 
    errorBgColor    <Color>         bg-Color to be used when highlighting errors
"
! !

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

open
    "launch a new workspace"

    |scrollable scr topView workspace f|

    topView := StandardSystemView label:'Workspace' minExtent:(100 @ 100).

    scrollable := true.
    scrollable ifTrue:[
	scr := HVScrollableView "ScrollableView" for:self in:topView.
	scr origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
	workspace := scr scrolledView.
    ] ifFalse:[
	workspace := super origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:topView.
	workspace level:0.
    ].

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

    "
     Workspace open
    "
! !

!Workspace class methodsFor:'defaults'!

updateStyleCache
    DefaultErrorForegroundColor := StyleSheet colorAt:'codeErrorSelectionForegroundColor'.
    DefaultErrorBackgroundColor := StyleSheet colorAt:'codeErrorSelectionBackgroundColor'.
! !

!Workspace methodsFor:'initialize / release'!

initialize
    super initialize.

    showMatchingParenthesis := true.

    self initializeDoITAction.
!

initStyle
    super initStyle.

    errorFgColor := DefaultErrorForegroundColor.
    errorFgColor isNil ifTrue:[errorFgColor := selectionFgColor].
    errorBgColor := DefaultErrorBackgroundColor.
    errorBgColor isNil ifTrue:[
	device hasColors ifTrue:[
	    errorBgColor := Color red
	] ifFalse:[
	    errorBgColor := selectionBgColor
	]
    ].
!

initializeMiddleButtonMenu
    |idx|

    super initializeMiddleButtonMenu.

    "
     workspaces support #doIt, #printIt and #inspectIt
     add them after paste.
    "
    idx := middleButtonMenu indexOf:#paste.
    middleButtonMenu addLabel:'-'
		     selector:nil
			after:idx.
    middleButtonMenu addLabel:(resources string:'doIt')
		     selector:#doIt
			after:idx + 1.
    middleButtonMenu addLabel:(resources string:'printIt')
		     selector:#printIt
			after:idx + 2.
    middleButtonMenu addLabel:(resources string:'inspectIt')
		     selector:#inspectIt
			after:idx + 3.

    self enableOrDisableSelectionMenuEntries
!

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 |
	Compiler 
	    evaluate:theCode 
	    in:nil 
	    receiver:nil 
	    notifying:self 
	    logged:true 
	    ifFail:nil 
    ].
! !

!Workspace methodsFor:'selections'!

disableSelectionMenuEntries
    "disable relevant menu entries for a selection"

    super disableSelectionMenuEntries.
    middleButtonMenu notNil ifTrue:[
	middleButtonMenu disable:#doIt.
	middleButtonMenu disable:#printIt.
	middleButtonMenu disable:#inspectIt
    ]
!

enableSelectionMenuEntries
    "enable relevant menu entries for a selection"

    super enableSelectionMenuEntries.
    middleButtonMenu notNil ifTrue:[
	middleButtonMenu enable:#doIt.
	"
	 printit not allowed if readonly, since it pastes its result
	"
	readOnly ifTrue:[
	    middleButtonMenu disable:#printIt.
	] ifFalse:[
	    middleButtonMenu enable:#printIt.
	].
	middleButtonMenu enable:#inspectIt
    ]
! !

!Workspace methodsFor:'accessing'!

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

    doItAction := aBlock
!

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

    ^ doItAction
! !

!Workspace methodsFor:'error handling'!

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

    |absPosition fg bg|

    "
     change color of selection & hide cursor
    "
    fg := selectionFgColor.
    bg := selectionBgColor.
    selectionBgColor := errorBgColor.
    selectionFgColor := errorFgColor.
    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 synchronizeOutput.

    aBlock valueNowOrOnUnwindDo:[
	"
	 undo selection color change and show cursor again
	"
	selectionFgColor := fg.
	selectionBgColor := bg.
	self showCursor.
    ].
!

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

    self error:aString position:relPos to:relEndPos
!

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

    |answer|

    self highlightingErrorPosition:relPos to:relEndPos do:[
	|box|

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

	answer := box confirm.
    ].

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

correctableError:aString position:relPos to:relEndPos
    "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:[
	|box|

	"
	 start dialog - make certain cleanup is done
	"
	box := OptionBox title:aString numberOfOptions:3.
	box buttonTitles:#('abort' 'correct' 'continue').
	box actions:(Array with:[action := #abort]
			   with:[action := #correct]
			   with:[action := #continue]).
	box showAtPointer
    ].

    action == #abort ifTrue:[
	Object abortSignal raise.
	^ false
    ].
    ^ action == #correct 
!

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

    ^ self contents
! !

!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 cLine cCol cleanUp|

    code := self selection.
    code notNil ifTrue:[
	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 := [
		self selectFromLine:selLine col:selCol toLine:endLine col:endCol.
		cLine notNil ifTrue:[
		    self cursorLine:cLine col:cCol
		].
	].

	self topView withCursor:Cursor execute do:[
	    Object abortSignal catch:[
		[
		    value := doItAction value:code asString.
		    cleanUp value.
		    aBlock value:value.
		    value := nil.
		] valueOnUnwindDo:cleanUp
	    ]
	].
    ]
!

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 displayString "printString")
    ]
! !

!Workspace methodsFor:'events'!

keyPress:key x:x y:y
    |cmd commands|

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

    "
     Ctrl-Fn or Cmd-Fn evaluates a key-sequence
     (I added Ctrl-Fn, because some windowmanagers already use cmd-fn)
     see TextView>>keyPress:x:y:
    "

    (#(F1 F2 F3 F4 F5 F6 F7 F8 F9 f1 f2 f3 f4 f5 f6 f7 f8 f9) includes:key) ifTrue:[
	(device metaDown or:[device controlDown]) ifTrue:[
	    commands := Smalltalk at:#FunctionKeySequences ifAbsent:[nil].
	    commands notNil ifTrue:[
		cmd := commands at:key ifAbsent:[nil].
		cmd notNil ifTrue:[
		    Parser evaluate:cmd asString
			   receiver:self
			  notifying:nil.
		    ^ self
		]
	    ]
	]
    ].

    super keyPress:key x:x y:y

    "
     example uses of funtion keys:

     to set tab-distance to 4-cols,
     select the following:

       self setTab4

     then, press shift-F2 to define the sequence;
     press cmd-F2 to execute it (some window managers have cmd-Fn redefined;
     use Ctrl-Fn then).
     voila: you have set 4-tabs.

     to switch back, perform the same procedure with:

	self setTab8

     Within the expression, 'self' is bound to the view. Thus, you can do
     all kinds of fancy things.
     For example:
       if you like a browser to come up on the selection when pressing F3:
       select:

	|sel|
	sel := self selection asString withoutSeparators.
	(Smalltalk includesKey:sel asSymbol) ifTrue:[
	    (Smalltalk at:sel asSymbol) isClass ifTrue:[
		SystemBrowser browseClass:(Smalltalk at:sel asSymbol)
	    ]
	]

     then, press shift-F3 to define the command.
     press cmd-F3 to execute it (select some classname before).
     (notice: on the Indy, Cmd-F3 is already used by the window manager)

     if you like a file-include command on F4:
     select:

	|sel|
	sel := self selection.
	sel notNil ifTrue:[
	    sel := sel asString withoutSeparators.
	    s := FileStream readonlyFileNamed:sel.
	    s notNil ifTrue:[
		self paste:(s contents asString).
		s close
	    ]
	]

    this will paste the contents of the file at the current cusor position.
    (select above expression, press Shift-F4,
     then select any filename and press Cmd-F4)
	try it here: /etc/passwd 
    "
! !