Tools__CodeHighlightingService.st
author Claus Gittinger <cg@exept.de>
Fri, 08 Jul 2011 08:51:52 +0200
changeset 10275 1151182dcaae
parent 10272 3f3652010960
child 10353 92b1359dd74a
permissions -rw-r--r--
changed: #startSyntaxHighlightProcess do not show infos from the syntax highlighter: it clears much more useful information (inheritance etc)

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

CodeViewService subclass:#CodeHighlightingService
	instanceVariableNames:'worker workerRunning'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-CodeView'
!

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

!CodeHighlightingService class methodsFor:'accessing'!

label

    "Answers short label - for UI"

    ^'Syntax Highlighting'

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

!CodeHighlightingService methodsFor:'change & update'!

update: aspect with: param from: sender

    sender == textView modifiedChannel ifTrue:[^self codeChanged: false].
    sender == textView model ifTrue:[^self codeChanged: true].
    sender == codeView languageHolder ifTrue:[^self codeChanged: true].
    sender == codeView classHolder ifTrue:[^self codeChanged: true].

    super update: aspect with: param from: sender

    "Created: / 06-03-2010 / 19:38:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-07-2011 / 10:18:08 / cg"
! !

!CodeHighlightingService methodsFor:'private'!

codeChanged: force

    (force or:[codeView textView modified]) ifTrue:
        [self startSyntaxHighlightProcess].

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

setHighlightedCode:newCode elements: elements
    "the background synhighlighter has generated new colored text,
     with highlighted syntax.
     If there have been no modifications in the meantime, install it."

    |firstShown lastShown cursorWasOn anyChange newLines l replaceAction textView list|

    textView := codeView textView.
    textView modified ifTrue:[
        "/ new input arrived in the meantime

        ^ self
    ].
    worker notNil ifTrue:[
        "/ another coloring process has already been started.
        "/ ignore this (leftover) code.

        ^ self
    ].
    firstShown := textView firstLineShown.
    lastShown := textView lastLineShown.
    replaceAction := [:lNr :line |
            |oldLine|

            oldLine := list at:lNr ifAbsent:nil.
            oldLine notNil ifTrue:[
                line notNil ifTrue:[
                    "/ this check is needed - there is a race
                    "/ when the text is converted. This detects the
                    "/ resulting error.
                    "/ Certainly a kludge.

                    oldLine string = line string ifTrue:[
                        oldLine emphasis ~= line emphasis ifTrue:[
                            textView modifiedChannel removeDependent:self.
                            list at:lNr put:line.
                            textView modifiedChannel addDependent:self.
                            (lNr between:firstShown and:lastShown) ifTrue:[
                                anyChange ifFalse:[
                                    anyChange := true.
                                    cursorWasOn := textView hideCursor
                                ].
                                textView redrawLine:lNr
                            ]
                        ]
                    ]
                ]
            ]
        ].

    anyChange := false.
    newLines := newCode asStringCollection.
    list := textView list.
    list isNil ifTrue:[
        textView list:newLines.
    ] ifFalse:[
        "/ the cursor line first - that's where your eyes are ...
        (l := textView cursorLine) notNil ifTrue:[
            l <= newLines size ifTrue:[
                replaceAction value:l value:(newLines at:l)
            ]
        ].
        newLines keysAndValuesDo:replaceAction.
        anyChange ifTrue:[
            cursorWasOn ifTrue:[
                textView showCursor
            ]
        ]
    ].
    codeView syntaxElements: elements

    "Modified: / 09-10-2006 / 11:50:17 / cg"
    "Created: / 14-02-2010 / 16:10:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 19:58:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 06-07-2011 / 18:21:12 / cg"
!

showInfo: aString

    codeView showInfo: aString

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

startSyntaxHighlightProcess
    "start a background process, which does the syntax coloring.
     When it finishes, it pushes a user event to show the new text in the codeView.
     (This is done as an event to synchronize the coloring with modifications
      done to the text - the colored text will discarded, if there were
      any new modifications in the meanwhile)"

    |dontDoIt oldCodeList highlighterClass prio textView|

    textView := codeView textView.

    highlighterClass := self syntaxHighlighterClass.

    dontDoIt := highlighterClass isNil.
    "dontDoIt := dontDoIt
                or:[self doSyntaxColoring value ~~ true
                or:[(self doImmediateSyntaxColoring) value ~~ true]]."
    dontDoIt ifTrue:[^self].

    "/ this clobbers the codeViews modified state; therefore, we have to remember
    "/ this info somewhere ...
    codeView browser ifNotNil:[
        textView modified ifTrue:[
            codeView browser navigationState realModifiedState: true
        ].
        textView modifiedChannel setValue:false.
    ].

    worker notNil ifTrue:[
        workerRunning ~~ true ifTrue:[
            "/ process already created, but did not get a change to start yet;
            ^ self
        ].
        self stopSyntaxHighlightProcess
    ].
    prio := Processor userBackgroundPriority - 1.
    textView shown ifFalse:[
        prio := prio - 1 max:1
    ].

    worker := [
                [
                    |oldCode newCode elements cls sensor mthd|

                    workerRunning := true.
                    codeView syntaxElements: nil.
                    codeView syntaxElementSelection: nil.
                    cls := codeView classHolder value.
                    (cls notNil and:[cls isObsolete]) ifTrue:[
                        cls isMeta ifTrue:[
                            cls := (Smalltalk at:cls theNonMetaclass name) class
                        ] ifFalse:[
                            cls := Smalltalk at:cls name
                        ].
                    ].
                    mthd := codeView methodHolder value.

                    textView modified ifFalse:[
                        oldCodeList := textView list copy.
                        textView modified ifFalse:[
                            oldCodeList isNil ifFalse:[
                                oldCode := oldCodeList asStringWithoutEmphasis.
                                textView modified ifFalse:[
                                    Screen currentScreenQuerySignal answer:codeView device
                                    do:[
                                        Parser::ParseError handle:[:ex |
                                            |errMsg|

                                            errMsg := ex description asStringCollection first asString.

                                            "/ Transcript topView raiseDeiconified.
                                            "/ Transcript showCR:'ParseError: ', ex description.
"/ self halt.
                                            "/ self showInfo:(errMsg colorizeAllWith:Color red).
                                            newCode := nil.
                                        ] do:[
                                            elements := SortedCollection new.
                                            codeView codeAspect == #method ifTrue:[
                                                newCode := highlighterClass formatMethod:mthd source:oldCode in:cls using: nil elementsInto: elements.
                                            ] ifFalse:[
                                                codeView codeAspect == #expression ifTrue:[
                                                    newCode := highlighterClass formatExpression:oldCode in:cls elementsInto: elements.
                                                ] ifFalse:[
                                                    codeView codeAspect == #classDefinition ifTrue:[                                            
                                                        newCode := highlighterClass formatClassDefinition:oldCode in:cls elementsInto: elements.
                                                    ]
                                                ].
                                            ].
                                        ]
                                    ].
                                    newCode notNil ifTrue:[
                                        textView modified ifFalse:[
                                            newCode := newCode asStringCollection.
                                            textView modified ifFalse:[
                                                worker := nil.
                                                (textView := codeView textView) notNil ifTrue:[
                                                    "/ must add this event - and not been interrupted
                                                    "/ by any arriving key-event.
                                                    "/ self showInfo:nil.
                                                    codeView sensor
                                                        pushUserEvent:#setHighlightedCode:elements:
                                                        for:self
                                                        withArguments:(Array with:newCode with: elements).
                                                    "/self delayedUpdateBufferLabelWithCheckIfModified
                                                ]
                                            ]
                                        ]
                                    ]
                                ]
                            ]
                        ]
                    ]
                ] ensure:[
                    workerRunning := false.
                    worker := nil
                ]
            ] forkAt:prio

    "Modified: / 10-04-2011 / 18:21:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-07-2011 / 12:26:12 / Jan Vrany <jan.vrant@fit.cvut,cz>"
    "Modified: / 08-07-2011 / 08:35:49 / cg"
!

stopSyntaxHighlightProcess
    "stop any syntax coloring background process."

    |p|

    (p := worker) ifNil:[^self].
    worker := nil.
    p terminate.
    "/ raise its prio to make it terminate quickly
    p priority:(Processor userSchedulingPriority + 1)

    "Modified: / 03-09-2010 / 22:27:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

syntaxHighlighterClass
    | lang cls mthd |

    cls := (lang := codeView languageHolder value)
                ifNil:[nil]
                ifNotNil:[lang syntaxHighlighterClass].

    "Ugly hack because I don't want to branch libcomp :-)"
    cls == SyntaxHighlighter ifTrue:[
        "/ hack
        mthd := codeView methodHolder value.
        "/ what about method-language ?
        (mthd notNil and:[codeView browserHolder value notNil]) ifTrue:[
            cls := codeView browserHolder value syntaxHighlighterForMethod:mthd.
        ].
        cls == SyntaxHighlighter ifTrue:[
            cls := SyntaxHighlighter2
        ]
    ].
    ^ cls

    "Created: / 14-02-2010 / 12:39:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 19:39:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-07-2011 / 11:10:11 / cg"
! !

!CodeHighlightingService class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeHighlightingService.st,v 1.8 2011-07-08 06:51:52 cg Exp $'
!

version_SVN
    ^ '§Id: Tools__CodeHighlightingService.st 7715 2011-04-10 16:32:58Z vranyj1 §'
! !