Tools__CodeView2.st
author vrany
Tue, 27 Sep 2011 20:46:15 +0200
changeset 10728 463a51112b1d
parent 10723 e9f1e0dad878
child 10731 5904065850c6
permissions -rw-r--r--
Possibly redraw-bug fix

"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

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: 'stx:libtool' }"

"{ NameSpace: Tools }"

SimpleView subclass:#CodeView2
	instanceVariableNames:'gutterView textView textViewScroller methodHolder languageHolder
		classHolder browserHolder codeAspect modifiedChannel
		showGutterChannel modeHolder serviceManager services
		syntaxElements syntaxElementSelection highlightEmphasis diffMode
		synchronizedCodeViews'
	classVariableNames:'TraceSelectors'
	poolDictionaries:''
	category:'Interface-CodeView'
!

SimpleView subclass:#GutterView
	instanceVariableNames:'codeView textView textViewScroller widthAnnotations widthDiffInfo
		firstLineShown lastLineShown'
	classVariableNames:''
	poolDictionaries:''
	privateIn:CodeView2
!

CodeView subclass:#TextView
	instanceVariableNames:'codeView gutterView diffMode deletedLines insertedLines
		lastFirstLine changedLines scrolled originDiffText emptyLines
		changedDiffText suppressNotifications'
	classVariableNames:''
	poolDictionaries:''
	privateIn:CodeView2
!

!CodeView2 class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

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

!CodeView2 class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    TraceSelectors := IdentitySet new.

    "Modified: / 14-02-2010 / 15:36:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 class methodsFor:'debugging'!

trace: aSelector

    TraceSelectors add: aSelector

    "Created: / 14-02-2010 / 09:26:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

untrace: aSelector

    TraceSelectors remove: aSelector ifAbsent:[]

    "Created: / 14-02-2010 / 09:50:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

untraceAll

    TraceSelectors := IdentitySet new

    "Created: / 14-02-2010 / 09:53:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 class methodsFor:'examples'!

example1

    | window codeView |


    window := StandardSystemView new.
    window extent: 300 @ 300.              
    window label: 'CodeView2 example1'.

    codeView := Tools::CodeView2 in: window.
    codeView
        origin: 0.1 @ 0.1
        corner: 0.9 @ 0.9.


    window open.

    "Created: / 02-09-2009 / 21:48:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 class methodsFor:'menu specs'!

debugMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:Tools::CodeView2 andSelector:#editMenu_stxStyle
     (Menu new fromLiteralArrayEncoding:(Tools::CodeView2 editMenu_stxStyle)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
              (
               (MenuItem
                  label: 'Inspect '
                  itemValue: inspectView
                  translateLabel: true
                )
               (MenuItem
                  label: 'Inspect Syntax Elements'
                  itemValue: inspectSyntaxElements
                  translateLabel: true
                )
               (MenuItem
                  label: 'Inspect selected selector'
                  itemValue: inspectSelectedSelector
                  translateLabel: true
                )
               )
              nil
              nil
            )

    "Created: / 08-07-2011 / 13:36:02 / cg"
!

editMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:Tools::CodeView2 andSelector:#editMenu
     (Menu new fromLiteralArrayEncoding:(Tools::CodeView2 editMenu)) startUp
    "

    UserPreferences current eclipseStyleMenus ifTrue:[
        ^ self editMenu_eclipseStyle
    ].
    ^ self editMenu_stxStyle

    "Modified: / 08-07-2011 / 13:23:35 / cg"
!

editMenu_eclipseStyle
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:Tools::CodeView2 andSelector:#editMenu
     (Menu new fromLiteralArrayEncoding:(Tools::CodeView2 editMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            label: 'Implementors...'
            itemValue: browseImplementorsOfIt
            translateLabel: true
            submenuChannel: implementorsMenu
            shortcutKey: ImplementorsOfIt
          )
         (MenuItem
            label: 'Senders...'
            itemValue: browseSendersOfIt
            translateLabel: true
            submenuChannel: sendersMenu
            shortcutKey: SendersOfIt
          )
         (MenuItem
            label: 'Refactor'
            translateLabel: true
            isVisible: false
            shortcutKey: Shift
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Accept'
            itemValue: accept
            translateLabel: true
            shortcutKey: Accept
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Cut'
            itemValue: cut
            translateLabel: true
            shortcutKey: Cut
          )
         (MenuItem
            label: 'Copy'
            itemValue: copySelection
            translateLabel: true
            shortcutKey: Copy
          )
         (MenuItem
            label: 'Paste'
            itemValue: pasteOrReplace
            translateLabel: true
            shortcutKey: Paste
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Undo'
            itemValue: undo
            translateLabel: true
            shortcutKey: Undo
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Do it'
            itemValue: doIt
            translateLabel: true
            shortcutKey: DoIt
          )
         (MenuItem
            label: 'Print it'
            itemValue: printIt
            translateLabel: true
            shortcutKey: PrintIt
          )
         (MenuItem
            label: 'Inspect it'
            itemValue: inspectIt
            translateLabel: true
            shortcutKey: InspectIt
          )
         (MenuItem
            label: 'Profile it'
            itemValue: profileIt
            translateLabel: true
            shortcutKey: InspectIt
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Show Gutter'
            nameKey: ShowGutter
            translateLabel: true
            indication: showGutterChannel
          )
         (MenuItem
            label: 'More'
            nameKey: More
            translateLabel: true
          )
         (MenuItem
            label: 'Services'
            translateLabel: true
            submenuChannel: servicesMenu
          )
         (MenuItem
            label: 'Debug'
            translateLabel: true
            submenu: 
           (Menu
              (
               (MenuItem
                  label: 'Inspect '
                  itemValue: inspectView
                  translateLabel: true
                )
               (MenuItem
                  label: 'Inspect Syntax Elements'
                  itemValue: inspectSyntaxElements
                  translateLabel: true
                )
               (MenuItem
                  label: 'Inspect selected selector'
                  itemValue: inspectSelectedSelector
                  translateLabel: true
                )
               )
              nil
              nil
            )
          )
         )
        nil
        nil
      )

    "Created: / 08-07-2011 / 13:20:47 / cg"
!

editMenu_stxStyle
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:Tools::CodeView2 andSelector:#editMenu_stxStyle
     (Menu new fromLiteralArrayEncoding:(Tools::CodeView2 editMenu_stxStyle)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            label: 'Undo'
            itemValue: undo
            translateLabel: true
            shortcutKey: Undo
          )
         (MenuItem
            label: 'Again'
            itemValue: again
            translateLabel: true
            shortcutKey: Again
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Cut'
            itemValue: cut
            translateLabel: true
            shortcutKey: Cut
          )
         (MenuItem
            label: 'Copy'
            itemValue: copySelection
            translateLabel: true
            shortcutKey: Copy
          )
         (MenuItem
            label: 'Paste'
            itemValue: pasteOrReplace
            translateLabel: true
            shortcutKey: Paste
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'DoIt'
            itemValue: doIt
            translateLabel: true
            shortcutKey: DoIt
          )
         (MenuItem
            label: 'PrintIt'
            itemValue: printIt
            translateLabel: true
            shortcutKey: PrintIt
          )
         (MenuItem
            label: 'InspectIt'
            itemValue: inspectIt
            translateLabel: true
            shortcutKey: InspectIt
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Accept'
            itemValue: accept
            translateLabel: true
            shortcutKey: Accept
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Refactor'
            translateLabel: true
            isVisible: false
            shortcutKey: Shift
          )
         (MenuItem
            label: 'Services'
            translateLabel: true
            submenuChannel: servicesMenu
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'More'
            nameKey: More
            translateLabel: true
            shortcutKey: Ctrl
          )
         )
        nil
        nil
      )
! !

!CodeView2 methodsFor:'accessing'!

acceptAction:aBlock

    textView acceptAction: aBlock

    "Modified: / 01-08-2010 / 20:40:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

breakpoints

    services do:[:each|
        (each isKindOf: BreakpointService) ifTrue:[
            ^each breakpoints
        ]
    ].
    ^nil

    "Created: / 06-07-2011 / 18:05:35 / jv"
!

browser

    ^self browserHolder value

    "Created: / 07-07-2011 / 12:25:59 / Jan Vrany <jan.vrant@fit.cvut,cz>"
!

codeAspect

    |app|
    codeAspect ifNotNil:[^codeAspect].
    methodHolder value ifNotNil:[^#method].

    ^((app := self topView application) notNil and:[app respondsTo: #codeAspect])
        ifTrue:[app codeAspect]
        ifFalse:[#expression]

    "Modified: / 27-07-2011 / 13:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

codeAspect:aSymbol
    codeAspect := aSymbol.
!

contents

    ^textView contents

    "Created: / 14-02-2010 / 22:13:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

contents: aStringOrStringCollection

    textView contents: aStringOrStringCollection.
    "/self update:#value with: aStringOrStringCollection from: textView model

    "Modified: / 19-07-2011 / 13:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

diffMode
    ^ diffMode
!

diffMode:aBoolean
    diffMode := aBoolean.
    textView diffMode: aBoolean

    "Modified: / 08-04-2011 / 20:50:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

font

    ^textView font

    "Created: / 16-02-2010 / 10:26:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

font: aFont

    ^textView font: aFont

    "Created: / 16-02-2010 / 10:26:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mode

    ^self modeHolder value

    "Created: / 13-06-2011 / 10:49:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mode: aSymbol

    self assert: (#(expression method) includes: aSymbol).    
    
    ^self modeHolder value: aSymbol

    "Created: / 13-06-2011 / 10:50:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-06-2011 / 16:37:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

model

    ^textView model.

    "Created: / 27-07-2011 / 12:47:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

model: aValueModel

    |oldValue newValue|

    textView model notNil ifTrue:[
        oldValue := textView model value.
        textView model removeDependent:self.
    ].
    textView model: aValueModel.
    textView model notNil ifTrue:[
        textView model addDependent:self.
    ].
    newValue := textView model value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:textView model.
    ].

    "Modified: / 27-07-2011 / 12:58:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

modified
    "return true if text was modified"

    ^ self modifiedChannel value

    "Modified: / 07-07-2011 / 12:15:43 / Jan Vrany <jan.vrant@fit.cvut,cz>"
!

modified:aBoolean
    "set/clear the modified flag"

    self modifiedChannel value:aBoolean

    "Modified: / 14-02-1997 / 16:44:05 / cg"
    "Modified: / 07-07-2011 / 12:15:39 / Jan Vrany <jan.vrant@fit.cvut,cz>"
!

scrolledView

    ^self

    "Created: / 14-02-2010 / 22:54:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

services

    ^ services

    "Created: / 05-08-2011 / 10:14:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showGutter

    ^showGutterChannel value

    "Created: / 23-06-2010 / 19:37:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

synchronizeWith: aCodeView

    self assert: aCodeView ~= self.
    (synchronizedCodeViews includes: aCodeView) ifTrue:[^self].    
    synchronizedCodeViews := synchronizedCodeViews copyWith: aCodeView.

    "Created: / 06-04-2010 / 14:13:14 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 23-06-2010 / 17:01:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'accessing - code component'!

klass

    | v |

    (v := self classHolder value) notNil ifTrue:[^v].
    (v := self methodHolder value) notNil ifTrue:[^v mclass].

    ^UndefinedObject

    "Created: / 27-07-2011 / 13:14:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

klass: aClass

    "Created: / 27-07-2011 / 13:13:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

language
    "return the value in 'languageHolder'"

    | v |

    (v := self languageHolder value) notNil ifTrue:[^v].
    (v := self methodHolder value) notNil ifTrue:[^v programmingLanguage].
    (v := self classHolder value) notNil ifTrue:[^v programmingLanguage].

    ^SmalltalkLanguage instance

    "Modified: / 17-06-2011 / 12:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

language: newValue
    "set the value in 'languageHolder'"

    self languageHolder value: newValue
!

method

    ^self methodHolder value

    "Created: / 27-07-2011 / 13:12:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

method: aMethod

    ^self methodHolder value: aMethod

    "Created: / 27-07-2011 / 13:12:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'aspects'!

browserHolder
    browserHolder ifNil:[
        browserHolder := ValueHolder new
    ].
    ^browserHolder

    "Modified: / 14-02-2010 / 19:27:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browserHolder:aValueModel
    browserHolder := aValueModel.
!

classHolder
    "return/create the 'classHolder' value holder (automatically generated)"

    classHolder isNil ifTrue:[
        classHolder := ValueHolder with: nil.
        classHolder addDependent:self.
    ].
    ^ classHolder

    "Modified: / 27-07-2011 / 13:15:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

classHolder:aValueModel
    "set the 'classHolder' value holder (automatically generated)"

    |old oldValue newValue|

    classHolder notNil ifTrue:[
        oldValue := classHolder value.
        classHolder removeDependent:self.
    ].
    classHolder := aValueModel.
    classHolder notNil ifTrue:[
        classHolder addDependent:self.
    ].
    old := methodHolder.
    newValue := classHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:classHolder.
    ].

    self changed: #classHolder with: old -> classHolder

    "Modified: / 17-06-2011 / 12:56:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

languageHolder
    languageHolder isNil ifTrue:[
        "/ cg: I dont like this default here; everyone who is not showing ST-code (expecco, filebrowser etc.)
        "/ has to explicitely clear the valueholder. I guess, it is better for the few
        "/ others to explicitely set it, if they do not provide syntaxHighlighter per method
        "/ or class.
        languageHolder := ValueHolder with: nil "SmalltalkLanguage instance".
        languageHolder addDependent:self.
    ].
    ^ languageHolder

    "Modified (format): / 26-09-2011 / 17:04:04 / cg"
!

languageHolder:aValueModel
    "set the 'languageHolder' value holder (automatically generated)"

    |old oldValue newValue|

    languageHolder notNil ifTrue:[
        oldValue := languageHolder value.
        languageHolder removeDependent:self.
    ].
    languageHolder := aValueModel.
    languageHolder notNil ifTrue:[
        languageHolder addDependent:self.
    ].
    old := languageHolder.
    newValue := languageHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:languageHolder.
    ].

    self changed: #languageHolder with: old -> languageHolder

    "Modified: / 17-06-2011 / 12:56:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

methodHolder
    "return/create the 'methodHolder' value holder (automatically generated)"

    methodHolder isNil ifTrue:[
        methodHolder := ValueHolder new.
        methodHolder addDependent:self.
    ].
    ^ methodHolder
!

methodHolder:aValueModel
    "set the 'methodHolder' value holder (automatically generated)"

    |old oldValue newValue|

    methodHolder notNil ifTrue:[
        oldValue := methodHolder value.
        methodHolder removeDependent:self.
    ].
    old := methodHolder.
    methodHolder := aValueModel.
    methodHolder notNil ifTrue:[
        methodHolder addDependent:self.
    ].
    newValue := methodHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:methodHolder.
    ].

    self changed: #methodHolder with: old -> methodHolder

    "Modified: / 17-06-2011 / 12:55:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

modeHolder
    "return/create the 'modeHolder' value holder (automatically generated)"

    modeHolder isNil ifTrue:[
        modeHolder := #expression asValue.
        modeHolder addDependent:self.
    ].
    ^ modeHolder

    "Modified: / 13-06-2011 / 10:52:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

modeHolder:something
    "set the 'modeHolder' value holder (automatically generated)"

    |oldValue newValue|

    modeHolder notNil ifTrue:[
        oldValue := modeHolder value.
        modeHolder removeDependent:self.
    ].
    modeHolder := something.
    modeHolder notNil ifTrue:[
        modeHolder addDependent:self.
    ].
    newValue := modeHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:modeHolder.
    ].

    self changed: #modeHolder with: modeHolder

    "Modified: / 17-06-2011 / 12:55:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'change & update'!

update:aspect with:param from:sender

    sender == showGutterChannel ifTrue: [
        self updateGutterVisibility.
        ^self.
    ].

    services do:[:each | 
        each isEnabled ifTrue:[
            each update:aspect with:param from:sender 
        ]
    ].

    super update:aspect with:param from:sender

    "Modified: / 23-06-2010 / 19:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-07-2011 / 12:07:04 / Jan Vrany <jan.vrant@fit.cvut,cz>"
    "Modified (format): / 05-09-2011 / 05:12:18 / cg"
!

updateGutterVisibility

    self showGutterChannel value ifTrue:[        
        textViewScroller origin:(gutterView width @ 0.0) corner:(1.0 @ 1.0).
        gutterView beVisible.
    ] ifFalse:[
        textViewScroller origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
        gutterView beInvisible.
    ]

    "Created: / 23-06-2010 / 19:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'channels'!

modifiedChannel
    "return the valueHolder holding true if text was modified"

    ^ textView modifiedChannel
"/    ^ modifiedChannel

    "Modified: / 07-07-2011 / 12:07:26 / Jan Vrany <jan.vrant@fit.cvut,cz>"
!

modifiedChannel:aValueHolder
    "set the valueHolder holding true if text was modified"

    textView modifiedChannel removeDependent:self.
    textView modifiedChannel:aValueHolder.
    textView modifiedChannel addDependent:self.

"/    |prev|
"/
"/    prev := modifiedChannel.
"/    modifiedChannel := aValueHolder.
"/    self setupChannel:aValueHolder for:nil withOld:prev

    "Created: / 30-01-1998 / 14:51:32 / cg"
    "Modified: / 07-07-2011 / 12:07:43 / Jan Vrany <jan.vrant@fit.cvut,cz>"
    "Modified: / 05-09-2011 / 05:13:27 / cg"
!

showGutterChannel

    ^showGutterChannel

    "Created: / 23-06-2010 / 19:02:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showGutterChannel:aValueHolder
    "set the valueHolder holding true if text was modified"

    |prev|

    prev := showGutterChannel.
    showGutterChannel := aValueHolder.
    self setupChannel:aValueHolder for:nil withOld:prev

    "Created: / 23-06-2010 / 19:03:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'code services'!

browseMethod: method

    self browseMethod: method label: nil.

    "Created: / 14-02-2010 / 19:41:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseMethod: method label: label

    self browser ifNil: [^NewSystemBrowser openInMethod:method].
    (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
        or:[self browser navigationState modified])  
        ifTrue:
            [self browser 
                spawnFullBrowserInClass: method mclass 
                selector:method selector 
                in:#newBuffer]
        ifFalse:
            [self browser 
                switchToClass: method containingClass 
                selector: method selector].

    "Modified: / 19-02-2008 / 10:15:17 / janfrog"
    "Created: / 19-10-2008 / 08:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 25-07-2010 / 13:34:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseMethods: methods label: label

    methods size = 1 ifTrue:
        [^self browseMethod: methods anyOne label: label].

    self browser 
        ifNil: [NewSystemBrowser browseMethods: methods title: label]
        ifNotNil:[self browser spawnMethodBrowserFor:methods in:#newBuffer label:label]

    "Created: / 26-12-2007 / 11:32:04 / janfrog"
    "Modified: / 19-10-2008 / 08:17:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

extractSelectorAndSelectedTextFrom: givenSelectedText

    | selector selectedText compilerClass na |
    selectedText := givenSelectedText.
    compilerClass := self language compilerClass.
    selectedText size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            "/ hack, for now and expecco; must ask the Parser eventually...
            (compilerClass notNil and:[compilerClass includesBehavior:JavaScriptParser]) ifTrue:[
                "/ selector is in one piece anyway
                (selectedText includes:$_) ifFalse:[
                    "/ zero or one args - sigh (need to parse more to figure this out)
                    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:1.
                    selectedText := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:0.
                ] ifTrue:[
                    "/ count _#s plus one arg - sigh
                    na := (selectedText occurrencesOf:$_) + 1. 
                    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:na
                ].
            ] ifFalse:[
                selector := SystemBrowser extractSelectorFrom:selectedText.
            ].
        ]
    ].
    ^Array with: selector with: selectedText

    "Created: / 30-06-2011 / 19:49:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

implementorsOf: selector

    selector ifNil:[^#()].
    ^SystemBrowser
        findImplementorsOf: selector
        in: Smalltalk allClasses
        ignoreCase: false

    "Created: / 26-12-2007 / 11:37:11 / janfrog"
!

sendersOf: selector

    selector ifNil:[^#()].
    ^SystemBrowser
        findSendersOf: selector
        in: Smalltalk allClasses
        ignoreCase: false

    "Created: / 26-12-2007 / 11:37:22 / janfrog"
    "Modified: / 30-06-2011 / 19:32:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'delegation'!

doesNotUnderstand: aMessage

    ((textView respondsTo: aMessage selector) 
    and:[(TraceSelectors includes:aMessage selector) not])
        ifTrue:[^aMessage sendTo: textView].
    ^super doesNotUnderstand: aMessage

    "Created: / 13-02-2010 / 23:27:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-02-2010 / 09:53:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hasSelection

    ^textView hasSelection

    "Created: / 14-02-2010 / 09:53:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'delegation - drawing'!

drawLine:lineNo in: view atX:x y:y width: w height:h from:startCol to:endColOrNil with:fg and:bg
    "See the comment in
     CodeViewService>>drawLine:in:atX..."

    services do:[:each|
        each drawLine:lineNo in: view atX:x y:y width: w height:h from:startCol to:endColOrNil with:fg and:bg
    ]

    "Created: / 17-06-2011 / 13:50:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawVisibleLine: visLineNr

    "Created: / 07-03-2010 / 14:44:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawVisibleLine:visLine col:colNr

    "Modified: / 05-11-2007 / 17:35:53 / cg"
    "Modified: / 07-03-2010 / 14:45:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawVisibleLine:visLine from:startCol

    "Modified: / 07-03-2010 / 14:46:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawVisibleLine:visLine from:startCol to:endCol

    "Modified: / 07-03-2010 / 14:46:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'delegation - events'!

buttonMotion: button x:x y:y in: view

    "Delegates events to services. Answers true iff at least
     one service handler method returns true. In that case,
     the event is is NOT processes by the view."

    ^services
        inject: false
        into:
            [:processed :service|
            service isEnabled 
                ifFalse:
                    [processed]
                ifTrue:
                    [processed | ((service buttonMotion: button x:x y:y in: view) == true)]].

    "Modified: / 07-03-2010 / 13:53:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buttonPress: button x:x y:y in: view

    "Delegates events to services. Answers true iff at least
     one service handler method returns true. In that case,
     the event is is NOT processes by the view."

    ^services
        inject: false
        into:
            [:processed :service|
            service isEnabled 
                ifFalse:
                    [processed]
                ifTrue:
                    [processed | ((service buttonPress: button x:x y:y in: view) == true)]].

    "Modified: / 07-03-2010 / 13:53:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress: key x:x y:y in: view

    "Delegates events to services. Answers true iff at least
     one service handler method returns true. In that case,
     the event is is NOT processes by the view."

    ^services
        inject: false
        into:
            [:processed :service|
            service isEnabled 
                ifFalse:
                    [processed]
                ifTrue:
                    [processed | ((service keyPress: key x:x y:y in: view) == true)]].

    "Modified: / 07-03-2010 / 13:54:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyRelease: key x:x y:y in: view

    "Delegates events to services. Answers true iff at least
     one service handler method returns true. In that case,
     the event is is NOT processes by the view."

    ^services
        inject: false
        into:
            [:processed :service|
            service isEnabled 
                ifFalse:
                    [processed]
                ifTrue:
                    [processed | ((service keyRelease: key x:x y:y in: view) == true)]].

    "Modified: / 07-03-2010 / 13:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

linesDeletedFrom: start to: end

    services do: [:each |
        each isEnabled ifTrue: [
            each linesDeletedFrom: start to: end
        ]
    ].

    "Created: / 06-07-2011 / 17:12:54 / jv"
!

linesInsertedFrom: start to: end

    services do: [:each |
        each isEnabled ifTrue: [
            each linesInsertedFrom: start to: end
        ]
    ].

    "Created: / 06-07-2011 / 17:12:48 / jv"
!

linesModifiedFrom: start to: end

    services do: [:each |
        each isEnabled ifTrue: [
            each linesModifiedFrom: start to: end
        ]
    ].

    "Created: / 06-07-2011 / 17:12:58 / jv"
!

scrollDown: nLines in: view

    view == textView 
        ifTrue:
            ["/my text view scrolled...
            synchronizedCodeViews do:[:codeView|codeView scrollDown: nLines in: view]]
        ifFalse:
            ["/other code view scrolls and I'm notified about that
            textView basicScrollDown: nLines]

    "Created: / 06-04-2010 / 14:02:39 / Jakub <zelenja7@fel.cvut.cz>"
!

scrollUp: nLines in: view

    view == textView 
        ifTrue:
            ["/my text view scrolled...
            synchronizedCodeViews do:[:codeView|codeView scrollUp: nLines in: view]]
        ifFalse:
            ["/other code view scrolls and I'm notified about that
            textView basicScrollUp: nLines]

    "Created: / 06-04-2010 / 14:02:39 / Jakub <zelenja7@fel.cvut.cz>"
! !

!CodeView2 methodsFor:'diff mode'!

recomputeDiff:view 
    |t1 t2 pom diffHelper view2|

    t1 := view getNewOriginText.
    synchronizedCodeViews do:[:codeView | 
        view2 := codeView
    ].
    view changedDiffText:false.
    view2 changedDiffText:false.
    t2 := view2 getNewOriginText.
    pom := DiffCodeView2 new.
    (view == textView) ifTrue:[
        diffHelper := pom computeDiffDataForText1:t1 text2:t2.
        (view) contents:(diffHelper text1).
        (view) deletedLines:(diffHelper deleted).
        (view) changedLines:(diffHelper changed).
        (view) originDiffText:t1.
        (view) emptyLines:(diffHelper inserted).
        (view) changedLines:(diffHelper changed).
        (view2) contents:(diffHelper text2).
        (view2) insertedLines:(diffHelper inserted).
        (view2) changedLines:(diffHelper changed).
        (view2) originDiffText:t2.
        (view2) emptyLines:(diffHelper deleted).
    ].

    "Modified: / 22-06-2010 / 23:35:41 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 23-06-2010 / 17:25:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."
    "Call super initialize"
    
    super initialize.
     "Now set up some visual properties"
    self level:-1.
     "Now initialize sub-views"
    showGutterChannel := (ValueHolder with: true).
    showGutterChannel addDependent: self.     
    self initializeGutterView.
    self initializeTextView.
    gutterView setCodeView:self.
    textView setCodeView:self.
    modifiedChannel := ValueHolder with:false.    
    diffMode := false.
    synchronizedCodeViews := #().
    services := OrderedCollection new.

    "Modified: / 14-12-2009 / 13:59:53 / Jindra <a>"
    "Modified: / 06-04-2010 / 13:56:35 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified (comment): / 27-07-2011 / 11:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeGutterView

    gutterView := CodeView2::GutterView new.
    gutterView origin:(0.0 @ 0.0) corner:(gutterView preferredWidth @ 1.0).
    showGutterChannel value ifTrue:[self addSubView: gutterView].

    "Created: / 02-09-2009 / 21:35:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-06-2010 / 19:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeServices

    | serviceClasses |

    serviceClasses := CodeViewService availableServices sort:[:a :b|name < b name].
    serviceClasses do:
        [:cls|
        self registerService: cls new].

    "Modified: / 27-07-2011 / 11:37:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeTextView

    "Initialize textView. gutterView have to be 
     already initialized!!"

    textViewScroller := HVScrollableView for: CodeView2::TextView in: self.
    textViewScroller
        origin: ((self showGutter ifTrue:[gutterView width] ifFalse:[0.0]) @ 0.0)
        corner: 1.0@1.0;
        level: 0.
    textView := textViewScroller scrolledView.
    textView level: 0.

    textView modifiedChannel addDependent: self.

    "Created: / 02-09-2009 / 21:36:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-06-2010 / 19:38:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'menu actions'!

accept
    textView accept

    "Created: / 07-09-2011 / 21:29:07 / cg"
!

again
    textView again

    "Created: / 16-02-2010 / 19:36:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 22-07-2011 / 17:44:31 / cg"
!

browseImplementorsOfIt

    textView browseImplementorsOfIt

    "Modified: / 30-06-2011 / 19:22:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseSendersOfIt

    textView browseSendersOfIt

    "Modified: / 30-06-2011 / 19:22:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

copySelection

    textView copySelection

    "Created: / 16-02-2010 / 19:36:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

cut

    textView cut

    "Created: / 16-02-2010 / 19:36:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doIt

    textView doIt

    "Modified: / 16-02-2010 / 19:38:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inspectIt

    textView inspectIt

    "Modified: / 16-02-2010 / 19:38:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inspectSelectedSelector

    self error: 'Not yet implemented'

    "Modified: / 14-02-2010 / 15:58:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inspectSyntaxElements

    syntaxElements inspect

    "Modified: / 14-02-2010 / 15:57:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

inspectView

    self inspect

    "Modified: / 25-03-2010 / 17:58:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

pasteOrReplace

    textView pasteOrReplace

    "Created: / 16-02-2010 / 19:37:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

printIt

    textView printIt

    "Modified: / 16-02-2010 / 19:38:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

profileIt

    textView profileIt

    "Created: / 27-08-2010 / 22:12:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

undo

    textView undo

    "Created: / 16-02-2010 / 19:35:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'menus-dynamic'!

editMenu
    | editMenu superEditMenu moreMenu moreMenuItem showGutterItem |

    editMenu := self class editMenu decodeAsLiteralArray.
    superEditMenu := textView superEditMenu.
    moreMenu := superEditMenu subMenuAt: superEditMenu numberOfItems.
    moreMenuItem := editMenu menuItemLabeled: 'More'.
    showGutterItem := editMenu atNameKey: #ShowGutter.
    showGutterItem notNil ifTrue:[ showGutterItem indication: showGutterChannel ].
    moreMenuItem submenu: moreMenu asMenu.
    editMenu findGuiResourcesIn: self.
    ^editMenu

    "Created: / 25-12-2007 / 10:10:01 / janfrog"
    "Modified: / 25-12-2007 / 19:50:53 / janfrog"
    "Modified: / 18-10-2008 / 20:31:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 23-06-2010 / 19:13:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2011 / 13:35:31 / cg"
!

implementorsMenu

    | selectorAndSelectedText selector selectedText  implementors |

    selectedText := textView selectionAsString.
    selectedText size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            selectorAndSelectedText := self extractSelectorAndSelectedTextFrom:  selectedText.
            selector := selectorAndSelectedText first.
            selectedText := selectorAndSelectedText second.

            (selector notNil and:[selector = selectedText]) ifTrue:[
                implementors := (SystemBrowser 
                                findImplementorsOfAny:(Array with:selectedText) 
                                in:(Smalltalk allClasses) 
                                ignoreCase:false)

                ] ifFalse:[
                implementors := (SystemBrowser 
                                findImplementorsOfAny:(Array with:selectedText with: selector) 
                                in:(Smalltalk allClasses) 
                                ignoreCase:false)
                ].
            ] 
    ] ifFalse:[
        implementors := #().
    ].

    ^self implementorsMenu: implementors selector: (selector ? selectedText)

    "Modified: / 19-10-2008 / 08:16:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 30-06-2011 / 19:28:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

implementorsMenu: implementors selector: selector  
    | menu|

    menu := Menu new.
    implementors isEmptyOrNil ifTrue:[
        menu addItem:(MenuItem label:'No implementors found') disable
    ] ifFalse:[
        menu addItem:(MenuItem 
                    label:(selector storeString , (' (all implementors) ') asText allItalic)
                    value:[
                        self browseMethods:implementors
                            label:'Implementors of ' , selector storeString
                    ]).
        menu addSeparator.
        implementors do:[:mth | 
            menu 
                addItem:(MenuItem label:(selector storeString 
                                , (' in ' , mth containingClass name asText allBold))
                        value:[ self browseMethod:mth label: 'Implementor of ' , selector storeString  ])
        ]
    ].
    ^ menu

    "Modified: / 19-10-2008 / 08:16:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 14-02-2010 / 19:39:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2011 / 19:05:15 / cg"
!

sendersMenu

    | selectorAndSelectedText selector selectedText  senders |

    selectedText := textView selectionAsString.
    selectedText size > 0 ifTrue:[
        self windowGroup withWaitCursorDo:[
            selectorAndSelectedText := self extractSelectorAndSelectedTextFrom:  selectedText.
            selector := selectorAndSelectedText first.
            selectedText := selectorAndSelectedText second.

            (selector notNil and:[selector = selectedText]) ifTrue:[
                senders := (SystemBrowser 
                                findSendersOfAny:(Array with:selectedText) 
                                in:(Smalltalk allClasses) 
                                ignoreCase:false)

                ] ifFalse:[
                senders := (SystemBrowser 
                                findSendersOfAny:(Array with:selectedText with: selector) 
                                in:(Smalltalk allClasses) 
                                ignoreCase:false)
                ].
            ] 
    ] ifFalse:[
        senders := #().
    ].

    ^self sendersMenu: senders selector: (selector ? selectedText)

    "Modified: / 19-10-2008 / 08:16:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 30-06-2011 / 19:28:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sendersMenu: senders  selector: selector  
    | menu shownSenderItems numCut|

    menu := Menu new.
    senders isEmptyOrNil ifTrue:[
        menu addItem:(MenuItem label:'No senders found') disable
    ] ifFalse:[
        menu addItem:(MenuItem 
                    label:(selector storeString , (' (all senders)') asText allItalic)
                    value:[
                        self browseMethods:senders
                            label:'Senders of ' , selector storeString
                    ]).
        menu addSeparator.
        shownSenderItems := (senders size > 20) ifTrue:[senders copyTo:20] ifFalse:[senders].
        numCut := senders size - 20.
        shownSenderItems do:[:mth | 
            menu 
                addItem:(MenuItem label:(mth selector storeString 
                                , (' in ' , mth containingClass name asText allBold))
                        value:[ self browseMethod:mth label: 'Sender of ' , selector storeString ])
        ].
        numCut > 0 ifTrue:[
            menu addSeparator.
            menu addItem:(MenuItem label:('... %1 more senders not shown here' bindWith:numCut)) disable
        ].
    ].
    ^ menu

    "Modified: / 19-10-2008 / 08:17:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 14-02-2010 / 19:40:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-07-2011 / 14:51:54 / jv"
    "Modified: / 21-08-2011 / 11:44:00 / cg"
!

servicesMenu
    |menu item anyService|

    menu := Menu new.

    item := MenuItem label:(resources string:'Show Gutter').
    item indication:(self showGutterChannel).
    menu addItem:item.
    menu addSeparator.

    anyService := false.
    services do:[:service | 
        |item|

        item := MenuItem label:(resources string:service label).
        item indication:((AspectAdaptor forAspect:#enabled) subject:service).
        menu addItem:item.
        anyService := true.
    ].

    anyService ifTrue:[
        menu addSeparator.
    ].

    item := MenuItem label:(resources string:'Debug').
    item submenuChannel:[ self class debugMenu ].
    menu addItem:item.

    ^ menu

    "Created: / 07-03-2010 / 14:03:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2011 / 13:38:50 / cg"
! !

!CodeView2 methodsFor:'private'!

codeCompletion
    |cls 
"/     crsrPos interval node checkedNode
"/     char start stop selectorSoFar matchingSelectors
    |


    cls := self classHolder value.
    cls isNil ifTrue:[
        self showInfo:'No class'.
        ^ self.
    ].
    UserInformation handle:[:ex |
        self showInfo:(ex messageText).
        ex proceed.
    ] do:[
        self withWaitCursorDo:[
            DoWhatIMeanSupport codeCompletionForClass:cls codeView:self.
        ]
    ].
    ^ self.

"/
"/    interval := self selectedInterval.
"/    interval isEmpty ifTrue:[
"/        crsrPos := codeView characterPositionOfCursor - 1.
"/        char := codeView characterUnderCursor.
"/        [crsrPos > 1 and:[char isSeparator or:['.' includes:char]]] whileTrue:[
"/            crsrPos := crsrPos - 1.
"/            char := codeView characterAtCharacterPosition:crsrPos.
"/        ].
"/        interval := crsrPos to:crsrPos.
"/    ].
"/
"/    node := self findNodeForInterval:interval allowErrors:true.
"/    [node isNil] whileTrue:[
"/        "/ expand to the left ...
"/        interval start > 1 ifFalse:[
"/            self showInfo:'No parseNode found'.
"/            ^ self.
"/        ].
"/        interval start:(interval start - 1).
"/        node := self findNodeForInterval:interval allowErrors:true.
"/    ].
"/
"/    node isVariable ifTrue:[
"/        self codeCompletionForVariable:node inClass:cls.
"/        ^ self.
"/    ].
"/
"/    checkedNode := node.
"/    [checkedNode notNil] whileTrue:[
"/        checkedNode isMessage ifTrue:[
"/            self codeCompletionForMessage:checkedNode inClass:cls.
"/            ^ self
"/        ].
"/        checkedNode isMethod ifTrue:[
"/            self codeCompletionForMethod:checkedNode inClass:cls.
"/            ^ self.
"/        ].
"/        checkedNode := checkedNode parent.
"/    ].
"/
"/    self showInfo:'Node is neither variable nor message.'.

    "Modified: / 04-07-2006 / 18:48:26 / fm"
    "Modified: / 20-11-2006 / 12:30:59 / cg"
    "Modified: / 16-02-2010 / 10:53:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

reallyModified
    "check for modified code by comparing the source against
     the codeViews contents.
     Thats the true modified value (in case user undid its changes,
     and the displayed text is actually original"

    |modified changedSource originalSource s1 s2|

    textView modified ifTrue:[^true].

    "/ higher prio to prevent it from being changed while we convert it (by editing)
    Processor activeProcess
        withHigherPriorityDo:[
            changedSource :=  textView contentsAsString asStringCollection.
        ].
    changedSource := changedSource collect:[:line | line string withoutTrailingSeparators withTabsExpanded].
    changedSource := changedSource collect:[:line | line isEmpty ifTrue:[nil] ifFalse:[line]].
    [changedSource size > 0 and:[changedSource last isNil]] whileTrue:[
        changedSource := changedSource copyWithoutLast:1
    ].
    changedSource := changedSource asString.

        originalSource := textView model value ? ''.

        originalSource := originalSource asStringCollection.
        originalSource := originalSource collect:[:line | line string withoutTrailingSeparators withTabsExpanded].
        originalSource := originalSource collect:[:line | line isEmpty ifTrue:[nil] ifFalse:[line]].
        [originalSource size > 0 and:[originalSource last isNil]] whileTrue:[
            originalSource := originalSource copyWithoutLast:1
        ].

        s1 := originalSource asString.
        s2 := changedSource asString.
        modified := (s1 ~= s2).

    ^ modified

    "Created: / 06-02-2010 / 19:59:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showInfo: message

    | app |
    (app := self topView application) ifNotNil:
        [(app respondsTo: #showInfo:) ifTrue:
            [app showInfo: message]].

    "Modified: / 13-02-2010 / 23:25:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'private-accessing'!

gutterView

    ^gutterView

    "Created: / 14-02-2010 / 15:21:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

syntaxElementSelection
    ^ syntaxElementSelection
!

syntaxElementSelection:something
    syntaxElementSelection := something.
!

syntaxElements
    ^ syntaxElements
!

syntaxElements:something
    syntaxElements := something.
!

textView

    ^textView

    "Created: / 14-02-2010 / 15:21:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

textViewScroller

    ^textViewScroller

    "Created: / 14-02-2010 / 15:21:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'realization'!

postRealize

    self initializeServices

    "Created: / 27-07-2011 / 11:36:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'services'!

registerService: aCodeViewService

    services add: aCodeViewService.
    aCodeViewService registerIn: self

    "Created: / 06-03-2010 / 19:19:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

underService: aCodeViewService

    services remove: aCodeViewService ifAbsent:[^self].
    aCodeViewService unregister.

    "Created: / 06-03-2010 / 19:21:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2 methodsFor:'testing'!

isCodeView2

    ^true

    "Created: / 20-07-2010 / 15:43:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isTextView

    ^true

    "Created: / 14-02-2010 / 22:13:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::GutterView methodsFor:'accessing'!

setTextView: aTextView

    self assert: textView isNil message:'Attempting to set textView twice'.
    textView := aTextView.

    "/ self backgroundPaint: textView backgroundPaint darkened lighter.
    self viewBackground: (View defaultBackgroundColor). "/ textView backgroundPaint darkened lighter.
    self paint: textView paint.
    self font: textView font.

    "Created: / 02-09-2009 / 21:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-12-2009 / 15:09:29 / Jindra <a>"
    "Modified: / 09-02-2010 / 20:03:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-08-2011 / 15:15:09 / cg"
!

setTextViewScroller:aScr
    textViewScroller := aScr.

    "Created: / 07-12-2009 / 22:36:31 / Jindra <a>"
! !

!CodeView2::GutterView methodsFor:'accessing-dimensions'!

padding

    ^self paddingLeft + self paddingRight 
        + (widthAnnotations ? 0) 
        + (widthDiffInfo ? 0)

    "Created: / 14-02-2010 / 22:28:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-06-2011 / 14:01:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

paddingLeft

    ^0"px"

    "Created: / 14-02-2010 / 22:27:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-06-2011 / 13:47:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

paddingRight

    ^0"px"

    "Created: / 14-02-2010 / 22:27:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-06-2011 / 13:47:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

preferredExtent

    | w h |

    explicitExtent ifNotNil:[^explicitExtent].
    preferredExtent ifNotNil:[^preferredExtent].

    w := (self font widthOf:'00') + self padding.
    h := textView ifNotNil:[textView height] ifNil:[self font height * 12].

    ^preferredExtent := w @ h

    "Modified: / 16-06-2011 / 14:03:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::GutterView methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    self shown ifFalse:[^self].

    (changedObject == textView) ifTrue:[
        (something == #sizeOfContents) ifTrue:[
            "/ cg: with that test, it does not update when the text becomes smaller...
"/            (firstLineShown ~= textView firstLineShown 
"/            or:[lastLineShown ~= (textView lastLineShown - 1)]) ifTrue:[
                self invalidate.
                ^self.
"/            ]
        ].
    ].

    "/ changedObject == someOfMyValueHolders ifTrue:[
    "/     self doSomethingApropriate.
    "/     ^ self.
    "/ ].
    super update:something with:aParameter from:changedObject

    "Modified: / 12-07-2011 / 17:19:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 15-07-2011 / 20:14:04 / cg"
! !

!CodeView2::GutterView methodsFor:'event handling'!

buttonPress: btn x: x y: y

    "Do not allow clicking on line numbers..."

    ((x < (self paddingLeft + widthAnnotations)) or:
        [x > (self width - self paddingRight - widthDiffInfo)])
        ifTrue:[
            (codeView buttonPress: btn x:x y:y in: self)
                ifFalse:[super buttonPress: btn x: x y: y]
        ] ifFalse:[
            super buttonPress: btn x: x y: y
        ]

    "Created: / 17-06-2011 / 13:02:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::GutterView methodsFor:'initialization'!

initialize

    super initialize.
    widthAnnotations := 16.
    widthDiffInfo := 5.

    "Created: / 16-06-2011 / 13:47:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setCodeView: aCodeView2

    codeView := aCodeView2.
    codeView addDependent: self.
    textView := aCodeView2 textView.
    textView addDependent: self.
    textViewScroller := aCodeView2 textViewScroller.
    "/ self backgroundPaint: (textView viewBackground "backgroundPaint" blendWith: (Color gray:80)).
    self viewBackground: (View defaultBackgroundColor).

    "Created: / 14-02-2010 / 15:19:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-06-2011 / 12:43:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-08-2011 / 15:15:55 / cg"
! !

!CodeView2::GutterView methodsFor:'queries'!

displayedString: line
    "get text to display in gutter for specified list line number"

    ^(line asString).

    "Created: / 14-12-2009 / 13:37:47 / Jindra <a>"
!

lineColor:line
    "return special color for given line if required, nil otherwise"
    "used only if lineFont return nil"

    ^nil

    "Created: / 14-12-2009 / 15:01:31 / Jindra <a>"
!

lineDisplayable:line
    "true if this list line can be displayed"
    ^(textView listLineIsVisible:line)

    "Created: / 14-12-2009 / 13:38:23 / Jindra <a>"
!

lineFont:line
    "return special font for given line if required, nil otherwise"

    ^nil

    "Created: / 14-12-2009 / 14:40:17 / Jindra <a>"
!

yOfTextViewLine:line
    ^(textView yOfLine:line) + 1

    "Created: / 14-12-2009 / 13:35:07 / Jindra <a>"
! !

!CodeView2::GutterView methodsFor:'redrawing'!

redrawBackgroundX:x y:y width:w height:h
    "redraws gutter background"

    "background is filled with background color"
    self 
        fillRectangleX:x
        y:y
        width:w
        height:h
        color: self viewBackground "backgroundPaint".

    "separator line is drawn with foreground color"
    self 
        displayLineFromX:(self width - 2)
        y:y
        toX:(self width - 2)
        y:(y+h).

    "Created: / 14-12-2009 / 13:15:53 / Jindra <a>"
    "Modified: / 14-12-2009 / 15:09:54 / Jindra <a>"
    "Modified: / 17-08-2011 / 15:12:47 / cg"
!

redrawLine:line 

    ^self redrawLine:line cleared: false.

    "Modified: / 17-06-2011 / 14:12:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawLine:line cleared: cleared
    "redraws specified line. Returns width of drawn object. Color of drawn objects should be taken from lineFont, lineColor"
    
    |lineString y0 textW requiredW oldFont newFont oldColor newColor|

    lineString := self displayedString:line.
    textW := (lineString widthOn:self).
    requiredW := textW + self padding.

    oldFont := self font.
    oldColor := self paint.
    newFont := self lineFont:line.
    newFont 
        ifNotNil:[ self font:newFont. ]
        ifNil:[
            newColor := self lineColor:line.
            newColor ifNotNil:[ self paint:newColor ].
        ].

    y0 := (self yOfTextViewLine:line) + ((self font) ascentOn:device).

    cleared ifFalse:[
        self clearRectangleX:0 y:y0 - font height width: self width - 2 height: font height + font descent.
    ].

    "Let the services to draw annotations and other stuff"
    codeView
        drawLine:line in: self 
        atX: self paddingLeft y:y0 width: widthAnnotations height: font height
        from:nil to:nil with:self paint and: self backgroundColor.

    self 
        displayString:lineString
        x:(self width - textW - self paddingRight - widthDiffInfo)
        y:y0.
    newFont 
        ifNotNil:[
            self font:oldFont.
            self paint:oldColor
        ]
        ifNil:[ newColor ifNotNil:[ self paint:oldColor ]. ].
    ^ requiredW.

    "Modified: / 14-12-2009 / 15:30:44 / Jindra <a>"
    "Created: / 17-06-2011 / 14:11:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawLinesFrom:start

    start to: (textView lastLineShown - 1 min: textView list size) do:[:line|
        self redrawLine:line cleared: false.
    ]

    "Created: / 06-07-2011 / 17:25:36 / jv"
    "Modified: / 12-07-2011 / 17:14:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

redrawX:x y:y width:w height:h 
    | requiredW currentW |

    self redrawBackgroundX:x y:y width:w height:h.

    firstLineShown := textView firstLineShown.
    lastLineShown := textView lastLineShown - 1 min: textView list size.

    currentW := requiredW := self width.
    firstLineShown to:lastLineShown do:
        [:line | 
        requiredW := requiredW max: (self redrawLine:line cleared: true)].

    (requiredW > self width) ifTrue:[
        self corner:(requiredW @ 1.0).
        textViewScroller origin:(requiredW @ 0.0) corner:(1.0 @ 1.0).
        self invalidate.
    ].

    "Created: / 03-09-2009 / 08:22:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-12-2009 / 14:13:14 / Jindra <a>"
    "Modified (format): / 12-07-2011 / 17:15:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'accessing'!

changedDiffText
    ^ changedDiffText
!

changedDiffText:something
    changedDiffText := something.
!

changedLines
    ^ changedLines

    "Created: / 26-04-2010 / 20:30:32 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 26-04-2010 / 21:48:13 / Jakub <zelenja7@fel.cvut.cz>"
!

changedLines:something 
    changedLines := something.

    "Created: / 26-04-2010 / 20:30:19 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 19:13:32 / Jakub <zelenja7@fel.cvut.cz>"
!

deletedLines
    ^  deletedLines

    "Modified: / 26-04-2010 / 21:48:23 / Jakub <zelenja7@fel.cvut.cz>"
!

deletedLines:something
deletedLines:=something.

    "Modified: / 26-04-2010 / 21:48:54 / Jakub <zelenja7@fel.cvut.cz>"
!

diffMode
    ^ diffMode
!

diffMode:something
    diffMode := something.
!

emptyLines
    ^ emptyLines
!

emptyLines:something
    emptyLines := something.
!

insertedLines
    ^  insertedLines

    "Modified: / 26-04-2010 / 21:48:27 / Jakub <zelenja7@fel.cvut.cz>"
!

insertedLines:something
insertedLines:=something.

    "Modified: / 26-04-2010 / 21:48:59 / Jakub <zelenja7@fel.cvut.cz>"
!

modifiedChannel: aValueHolder

    super modifiedChannel: aValueHolder

    "Created: / 07-07-2011 / 12:27:11 / Jan Vrany <jan.vrant@fit.cvut,cz>"
!

originDiffText
    ^ originDiffText
!

originDiffText:something
    originDiffText := something.
! !

!CodeView2::TextView methodsFor:'accessing - colors'!

colorChanged
    ^ Color redByte:240 greenByte: 192 blueByte: 192

    "Modified: / 24-06-2010 / 14:05:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

colorDeleted

    ^ self colorInserted.
    
    "/^ Color pink

    "Modified: / 24-06-2010 / 14:16:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

colorInserted
    ^ Color redByte: 239 greenByte: 225 blueByte: 152

    "Modified: / 24-06-2010 / 14:13:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'actions'!

cancel

    self halt.

    "Created: / 08-02-2010 / 09:29:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'drawing'!

drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg 

    super 
        drawFromVisibleLine:startVisLineNr
        to:endVisLineNr
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 12:08:38 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:46:04 / Jakub <zelenja7@fel.cvut.cz>"
!

drawLine:line fromX:x inVisible:visLineNr with:fg and:bg 

    super 
        drawLine:line
        fromX:x
        inVisible:visLineNr
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 12:07:07 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:46:00 / Jakub <zelenja7@fel.cvut.cz>"
!

drawLine:lineStringArg inVisible:visLineNr col:col with:fg and:bg 

    super 
        drawLine:lineStringArg
        inVisible:visLineNr
        col:col
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 11:49:42 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:45:56 / Jakub <zelenja7@fel.cvut.cz>"
!

drawLine:lineStringArg inVisible:visLineNr from:startCol to:endColOrNil with:fg and:bg 

    super 
        drawLine:lineStringArg
        inVisible:visLineNr
        from:startCol
        to:endColOrNil
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 11:54:54 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:45:52 / Jakub <zelenja7@fel.cvut.cz>"
!

drawLine:lineString inVisible:visLineNr from:startCol with:fg and:bg 

    super 
        drawLine:lineString
        inVisible:visLineNr
        from:startCol
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 11:54:26 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:45:48 / Jakub <zelenja7@fel.cvut.cz>"
!

drawVisibleLine:visLineNr with:fg and:bg 

    super 
        drawVisibleLine:visLineNr
        with:fg
        and:bg.
    self redrawLines.

    "Created: / 05-04-2010 / 11:49:42 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:45:44 / Jakub <zelenja7@fel.cvut.cz>"
!

redraw
    "/ thisContext fullPrintAll.   
    super redraw.

    "Created: / 30-06-2011 / 11:04:32 / cg"
!

redrawLines
    |i pom|

    diffMode ifFalse:[^self].

    pom := self hasSelection.
    (pom) ifTrue:[ ^ self. ].
    i := 1.
    [
        i <= (deletedLines size)
    ] whileTrue:[
        ((deletedLines at:i) > 0) ifTrue:[
            super 
                drawVisibleLine:(deletedLines at:i)
                with:fgColor
                and:self colorDeleted.
        ].
        i := i + 1.
    ].
    i := 1.
    [
        i <= (insertedLines size)
    ] whileTrue:[
        ((insertedLines at:i) > 0) ifTrue:[
            super 
                drawVisibleLine:(insertedLines at:i)
                with:fgColor
                and:self colorInserted.
        ].
        i := i + 1.
    ].
    i := 1.
    [
        i <= (changedLines size)
    ] whileTrue:[
        ((changedLines at:i) > 0) ifTrue:[
            super 
                drawVisibleLine:(changedLines at:i)
                with:fgColor
                and:self colorChanged.
        ].
        i := i + 1.
    ].

    "Created: / 26-04-2010 / 21:04:31 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 22-06-2010 / 23:28:30 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 08-04-2011 / 20:52:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'editing'!

contentsChanged
    super contentsChanged.
    "
    codeView diffMode ifTrue:[
        changedDiffText ifTrue:[
            codeView recomputeDiff:self.
        ] ifFalse:[
            changedDiffText := true.
        ].  
    ]
    "

    "Created: / 22-06-2010 / 23:13:24 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 01-08-2010 / 20:33:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getNewOriginText
    |i size pole pom text helperText|

    i := 1.
    pole := list.
    size := list size.
    text:=''.
    emptyLines ifNil:[emptyLines := #()].
    [ i <= size ] whileTrue:[
        pom := emptyLines indexOf:i.
        (pom = 0) ifFalse:[
            helperText := pole at:i.
            (helperText = '') ifFalse:[
                (helperText isNil)ifTrue:[helperText:=''].
                helperText:=helperText,Character cr.
                text := text asString , helperText asString.
            ].
        ] ifTrue:[
            helperText := pole at:i.
            (helperText isNil)ifTrue:[helperText:=''].
            helperText:=helperText,Character cr.
            text := text asString , helperText asString.
        ].
    i:=i+1.
    ].
^text

    "Created: / 22-06-2010 / 22:33:27 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 24-06-2010 / 14:27:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'editing-basic'!

basicDeleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
    "delete characters from startCol to endCol in line lineNr"

    self notifyLinesModifiedFrom: lineNr to: lineNr.
    super basicDeleteCharsAtLine:lineNr fromCol:startCol toCol:endCol

    "Created: / 16-09-2011 / 15:13:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

basicDeleteFromLine:startLineNr toLine:endLineNr 

    super basicDeleteFromLine:startLineNr toLine:endLineNr.
    self notifyLinesDeletedFrom:startLineNr to:endLineNr.

    "Created: / 28-06-2011 / 09:09:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

basicDeleteLineWithoutRedraw:lineNr

    super basicDeleteLineWithoutRedraw:lineNr.
    self notifyLinesDeletedFrom: lineNr to: lineNr.

    "Created: / 28-06-2011 / 09:10:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

basicInsert:aCharacter atLine:lineNr col:colNr
    "insert a single character at lineNr/colNr;
     set emphasis to character at current position"

    super basicInsert:aCharacter atLine:lineNr col:colNr.
    self notifyLinesModifiedFrom: lineNr to: lineNr.

    "Created: / 16-09-2011 / 15:14:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

basicMergeLine:lineNr removeBlanks:removeBlanks

    super basicMergeLine:lineNr removeBlanks:removeBlanks.
    self notifyLinesDeletedFrom: lineNr + 1 to: lineNr + 1.

    "Created: / 28-06-2011 / 09:13:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

basicSplitLine:lineNr before:colNr

    super basicSplitLine:lineNr before:colNr.
    self notifyLinesInsertedFrom: lineNr +1 to: lineNr + 1.

    "Created: / 28-06-2011 / 09:14:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'event handling'!

buttonMotion:button x:x y:y

    (codeView buttonMotion:button x:x y:y in: self)
        ifFalse:[super buttonMotion:button x:x y:y].

    "Created: / 14-02-2010 / 16:23:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 20:10:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buttonPress: button x: x y: y
    | ctrlDown  |

    (codeView buttonPress:button x:x y:y in: self)
        ifFalse:[super buttonPress:button x:x y:y].
    "
    ((ctrlDown := self sensor ctrlDown) and: [ codeView syntaxElementSelection notNil]) 
        ifTrue: [codeView buttonPressInTextView: button x:x y:y ctrlDown: ctrlDown].
    super 
        buttonPress: button
        x: x
        y: y
    "

    "Created: / 14-02-2010 / 18:12:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 20:37:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

exposeX:x y:y width:w height:h 
    super 
        exposeX:x
        y:y
        width:w
        height:h.
    self redrawLines.

    "Created: / 05-04-2010 / 10:07:50 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 18:41:07 / Jakub <zelenja7@fel.cvut.cz>"
!

keyPress:key x:x y:y
    (codeView keyPress:key x:x y:y in: self)
        ifFalse:[super keyPress:key x:x y:y].

    "Modified: / 06-03-2010 / 20:34:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-04-2010 / 09:55:52 / Jakub <zelenja7@fel.cvut.cz>"
!

keyRelease: key x: x y: y

    (codeView keyRelease:key x:x y:y in: self)
        ifFalse:[super keyRelease:key x:x y:y].
    "
    (key = #Control_L) ifTrue:
        [ codeView highlightClear. self redraw ].

    ^ super 
        keyRelease: key
        x: x
        y: y
    "

    "Created: / 14-02-2010 / 16:38:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 21:04:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'initialization'!

initialize

    super initialize.

    changedDiffText := true.
    diffMode := false.
    suppressNotifications := false.
    autoIndent := UserPreferences current codeView2AutoIndent.

    self enableMotionEvents.

    "Created: / 23-06-2010 / 17:28:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-07-2011 / 17:46:31 / jv"
    "Modified: / 07-08-2011 / 12:58:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 10:09:29 / cg"
!

setCodeView: aCodeView2

    codeView := aCodeView2.
    codeView addDependent: self.
    gutterView := aCodeView2 gutterView.

    "Created: / 14-02-2010 / 15:22:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-06-2011 / 12:43:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setGutterView: aGutterView

    self assert: gutterView isNil message:'Attempting to set gutterView twice'.
    gutterView := aGutterView.
    gutterView setTextView: self.

    "Created: / 02-09-2009 / 21:57:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'menu & menu actions'!

editMenu

    ^codeView editMenu

    "Created: / 14-02-2010 / 15:49:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'notification'!

notifyLinesDeletedFrom: startLine to: endLine

    suppressNotifications ifTrue:[^self].
    codeView linesDeletedFrom: startLine to: endLine.
    suppressNotifications := true.

    "Created: / 28-06-2011 / 09:12:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-07-2011 / 17:47:05 / jv"
!

notifyLinesInsertedFrom: startLine to: endLine

    suppressNotifications ifTrue:[^self].
    codeView linesInsertedFrom: startLine to: endLine.
    suppressNotifications := true.

    "Created: / 28-06-2011 / 09:12:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-07-2011 / 17:47:20 / jv"
!

notifyLinesModifiedFrom: startLine to: endLine

    suppressNotifications ifTrue:[^self].
    codeView linesModifiedFrom: startLine to: endLine.
    suppressNotifications := true.

    "Modified: / 06-07-2011 / 17:47:20 / jv"
    "Created: / 16-09-2011 / 15:12:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'private'!

superEditMenu

    ^super editMenu

    "Created: / 14-02-2010 / 15:48:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'scrolling'!

basicScrollDown:nLines 
    |i|

    (lastFirstLine isNil) ifTrue:[
        lastFirstLine := firstLineShown.
    ].
    super scrollDown:nLines.
    (lastFirstLine = firstLineShown) ifFalse:[
        i := 1.
        [
            i <= changedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(changedLines at:i)
                with:fgColor
                and:Color white.
            changedLines at:i put:(changedLines at:i) - nLines.
            i := i + 1.
        ].
        i := 1.
        [
            i <= insertedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(insertedLines at:i)
                with:fgColor
                and:Color white.
            insertedLines at:i put:(insertedLines at:i) - nLines.
            i := i + 1.
        ].
        i := 1.
        [
            i <= deletedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(deletedLines at:i)
                with:fgColor
                and:Color white.
            deletedLines at:i put:(deletedLines at:i) - nLines.
            i := i + 1.
        ].
        lastFirstLine := firstLineShown.
        self redrawLines.
    ].

    "Created: / 06-04-2010 / 14:03:28 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 19:29:23 / Jakub <zelenja7@fel.cvut.cz>"
!

basicScrollUp:nLines 
    |i|

    (scrolled isNil) ifTrue:[
        scrolled := false.
    ].
    (lastFirstLine isNil) ifTrue:[
        lastFirstLine := firstLineShown.
    ].
    super scrollUp:nLines.
    (lastFirstLine = firstLineShown) ifFalse:[
        i := 1.
        [
            i <= insertedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(insertedLines at:i)
                with:fgColor
                and:Color white.
            insertedLines at:i put:(insertedLines at:i) + nLines.
            i := i + 1.
        ].
        i := 1.
        [
            i <= deletedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(deletedLines at:i)
                with:fgColor
                and:Color white.
            deletedLines at:i put:(deletedLines at:i) + nLines.
            i := i + 1.
        ].
        i := 1.
        [
            i <= changedLines size
        ] whileTrue:[
            super 
                drawVisibleLine:(changedLines at:i)
                with:fgColor
                and:Color white.
            changedLines at:i put:(changedLines at:i) + nLines.
            i := i + 1.
        ].
        lastFirstLine := firstLineShown.
        self redrawLines.
    ].

    "Created: / 06-04-2010 / 14:03:46 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 02-05-2010 / 19:19:27 / Jakub <zelenja7@fel.cvut.cz>"
!

originChanged:delta

    super originChanged:delta.

    gutterView invalidate.

    "Created: / 07-12-2009 / 21:50:49 / Jindra <a>"
!

scrollDown:nLines

    codeView scrollDown: nLines in: self.
    self basicScrollDown: nLines.

    "Modified: / 06-04-2010 / 14:04:28 / Jakub <zelenja7@fel.cvut.cz>"
!

scrollUp:nLines

    codeView scrollUp: nLines in: self.
    self basicScrollUp: nLines.

    "Modified: / 06-04-2010 / 14:05:40 / Jakub <zelenja7@fel.cvut.cz>"
! !

!CodeView2::TextView methodsFor:'undo & again'!

nonUndoableDo: aBlock

    super nonUndoableDo: aBlock.
    suppressNotifications := false.

    "Created: / 06-07-2011 / 17:48:27 / jv"
!

undoableDo: aBlock info: into

    super undoableDo: aBlock info: into.
    suppressNotifications := false.

    "Created: / 06-07-2011 / 17:48:49 / jv"
! !

!CodeView2 class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeView2.st,v 1.25 2011-09-27 18:46:15 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeView2.st,v 1.25 2011-09-27 18:46:15 vrany Exp $'
!

version_SVN
    ^ '§Id: Tools__CodeView2.st 7797 2011-06-28 07:45:06Z vranyj1 §'
! !

CodeView2 initialize!