CodeView.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jan 1996 18:29:28 +0100
changeset 274 6df4bb990f04
parent 206 2363a64a7c88
child 365 cb7a40a691f3
permissions -rw-r--r--
handle accept where acceptAction is define (this was a historic leftover)

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

Workspace subclass:#CodeView
	 instanceVariableNames:'explainAction'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Interface-Workspace'
!

!CodeView 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 text which is known to be smalltalk code. 
    It adds explain to the menu, and defines another action: 
      explainAction to be performed for explain.

    This action is to be defined by the user of this view 
    (i.e. ususally the owning browser)

    If used with a model, accept sends the changeMsg to it (as defined in EditTextView).
    (however, it is possible to define moth changeMsg and acceptAction)


    Caveat:
	in this version, CodeView does not yet support MVC setups for doIt
	and explain.
	If required, simulate this by setting the doItAction and
	explainAction, to notify the model manually about whats going on.
"
! !

!CodeView methodsFor:'accessing'!

explainAction:aBlock
    "set the action to be performed on explain"

    explainAction := aBlock
! !

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

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

	l := self listAt:lineNr.
	l isNil ifTrue:[l := ''].
	self at:lineNr put:(('"' , '/') , l)
    ].
    self textChanged.
!

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

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

	l := self listAt:lineNr.
	(l notNil and:[l startsWith:('"' ,'/')]) ifTrue:[
	    self at:lineNr put:(l copyFrom:3)
	]
    ].
    self textChanged.
! !

!CodeView methodsFor:'event handling'!

keyPress:key x:x y:y
    "catch keyboard shortcuts"

    <resource: #keyboard (#Explain #Help 
	       #CommentSelection #UncommentSelection)>

    (key == #Explain) ifTrue:[^ self explain].
    (key == #Help)    ifTrue:[^ self explain].
    (key == #CommentSelection)    ifTrue:[^ self commentSelection].
    (key == #UncommentSelection)  ifTrue:[^ self uncommentSelection].

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

!CodeView methodsFor:'initialization'!

editMenu
    "return the popUpMenu;
     to make this independent from what is defined in superclasses,
     get the superclass menu and add my functions."

    |m sub idx|

    m := super editMenu.

    self sensor ctrlDown ifTrue:[
	m addLabels:(resources array:#('-' 'commentIt' 'uncommentIt'))
	  selectors:#(nil commentSelection uncommentSelection)
	  after:(m labels size).
	self hasSelection ifFalse:[
	    m disableAll:#(commentSelection uncommentSelection) 
	].
    ] ifFalse:[

	"
	 codeViews do support #accept
	 ... add it after #inspectIt
	"
	idx := m indexOf:#inspectIt.
	idx ~~ 0 ifTrue:[
	    m addLabels:(resources array:#('-' 'accept'))
	      selectors:#(nil accept)
	      after:idx.
	].

	"
	 and add #explain after $gotoLine in the extra menu
	"
	sub := m subMenuAt:#others.
	sub notNil ifTrue:[
	    idx := sub indexOf:#gotoLine.
	    sub addLabels:(resources array:#('-' 'explain'))
		selectors:#(nil explain)
		after:idx.
	    self hasSelection ifFalse:[
		sub disable:#explain 
	    ].
	].
    ].
    ^ m.
! !

!CodeView methodsFor:'user actions'!

accept
    "redefined accept action;
     save cursor and selection to allow restore in case of an error
     (we are typically compiling here ... and the compiler may show
     errors by highlighting them)"

    codeStartPosition := 1.
    [
	Object abortSignal handle:[:ex |
	    self cursor:Cursor normal.
	    "redraw selection in normal color"
	    self selectFromLine:selectionStartLine col:selectionStartCol 
			 toLine:selectionEndLine col:selectionEndCol.
	    ex return
	] do:[
	    super accept.
	]
    ] valueNowOrOnUnwindDo:[
	self unselect.
    ]
!

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|

    (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
	self commentFrom:selectionStartLine to:selectionEndLine-1
    ] ifFalse:[
	self insert:$" atLine:selectionStartLine col:selectionStartCol.
	e := selectionEndCol + 1.
	selectionStartLine == selectionEndLine ifTrue:[e := e + 1].
	self insert:$" atLine:selectionEndLine col:e.
	self selectFromLine:selectionStartLine col:selectionStartCol
		     toLine:selectionEndLine col:e.
    ]
!

explain
    "explain action;
     evaluate the explainBlock passing whole contents and 
     selection as arguments."

    |text|

    explainAction notNil ifTrue:[
	text := self selection.
	text notNil ifTrue:[
	    explainAction value:(self contents) value:(text asString)
	]
    ]
!

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|

    (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
	self uncommentFrom:selectionStartLine to:selectionEndLine-1
    ] ifFalse:[
	((self characterAtLine:selectionStartLine col:selectionStartCol) == $"
	and:[(self characterAtLine:selectionEndLine col:selectionEndCol) == $"]) ifTrue:[
	    self deleteCharAtLine:selectionEndLine col:selectionEndCol.
	    self deleteCharAtLine:selectionStartLine col:selectionStartCol.
	    e := selectionEndCol - 1.
	    selectionStartLine == selectionEndLine ifTrue:[e := e - 1].
	    self selectFromLine:selectionStartLine col:selectionStartCol
			 toLine:selectionEndLine col:e.
	]
    ]
! !

!CodeView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/CodeView.st,v 1.24 1996-01-09 17:29:25 cg Exp $'
! !