SmallSense__SmalltalkLintHighlighter.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 18 Sep 2013 00:58:49 +0100
changeset 89 8ff5fb2b27bf
parent 86 3b615594edf6
child 174 3e08d765d86f
permissions -rw-r--r--
Improvement in (Smalltalk)EditSupport. After some electric text is inserted, BackSpace will delete the inserted text instead of just last character.

"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'jv:smallsense' }"

"{ NameSpace: SmallSense }"

Object subclass:#SmalltalkLintHighlighter
	instanceVariableNames:'rules annotations formattingMethod emphasisError
		emphasisInformation emphasisWarning'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Smalltalk-Lint'
!

!SmalltalkLintHighlighter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
              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.
"
! !

!SmalltalkLintHighlighter methodsFor:'accessing'!

annotations
    ^ annotations
!

rules
    ^ rules
!

rules:aCollectionOfRules
    rules := aCollectionOfRules.

    "Modified (format): / 07-03-2012 / 17:24:02 / cg"
! !

!SmalltalkLintHighlighter methodsFor:'accessing-emphasis'!

emphasisForError
    |warnColor|

    emphasisError isNil ifTrue:[
        warnColor := Color red.
        emphasisError := Array 
            "/with: #backgroundColor -> warnColor lightened lightened 
            with: #underwave 
            with: #underlineColor -> warnColor                    
    ].
    ^emphasisError

    "Created: / 05-08-2011 / 09:31:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2012 / 03:00:51 / cg"
    "Modified: / 20-04-2012 / 18:29:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

emphasisForInformation
    |warnColor|

    emphasisInformation isNil ifTrue:[
        warnColor := Color blue lighter.
        emphasisInformation := Array 
            "/with: #backgroundColor -> warnColor lightened lightened
            with: #underwave 
            with: #underlineColor -> warnColor                    
    ].
    ^emphasisInformation

    "Created: / 05-08-2011 / 09:31:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2012 / 03:01:22 / cg"
    "Modified: / 20-04-2012 / 18:29:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

emphasisForSeverity: severity

    severity == #error ifTrue:[^self emphasisForError].
    severity == #information ifTrue:[^self emphasisForInformation].

    ^self emphasisForWarning

    "Created: / 05-08-2011 / 09:31:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

emphasisForWarning
    |warnColor|

    emphasisWarning isNil ifTrue:[
        warnColor := (Color redByte: 224 greenByte: 200 blueByte: 45).
        emphasisWarning := Array 
            "/with: #backgroundColor -> warnColor lightened lightened
            with: #underwave 
            with: #underlineColor -> warnColor                  
    ].
    ^emphasisWarning

    "Created: / 05-08-2011 / 09:31:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2012 / 03:00:19 / cg"
    "Modified: / 20-04-2012 / 18:29:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkLintHighlighter methodsFor:'formatting'!

formatClassDefinition:source in:class

    formattingMethod := false.
    ^ self format: source

    "Created: / 04-08-2011 / 23:44:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formatClassDefinition:source in:class elementsInto: elements

    formattingMethod := false.
    ^ self format: source

    "Created: / 04-08-2011 / 23:44:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formatExpression:source in:class

    formattingMethod := false.
    ^ self format: source

    "Created: / 04-08-2011 / 23:45:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formatExpression:source in:class elementsInto: elements

    formattingMethod := false.
    ^ self format: source

    "Created: / 04-08-2011 / 23:43:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formatMethod:mth source:source in:class using: preferences

    formattingMethod := true.
    ^ self format: source

    "Created: / 04-08-2011 / 23:45:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

formatMethod:mth source:source in:class using: preferences elementsInto: elements

    formattingMethod := true.
    ^ self format: source

    "Created: / 04-08-2011 / 23:42:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkLintHighlighter methodsFor:'formatting-private'!

format: text

    | tree |
    tree := RBParser parseMethod: text string onError:[:error :pos| ^ text ].
    self format: text tree: tree.
    ^text

    "Created: / 04-08-2011 / 23:51:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

format: text tree: tree

    annotations := SortedCollection new.
    rules ? #() do:[:rule|
        self format: text tree: tree rule: rule
    ].
    ^text

    "Created: / 02-02-2012 / 23:32:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

format: text tree: tree rule: rule

    | string |

    string := text string.
    rule result isParseTreeEnvironment ifTrue:[
        formattingMethod ifTrue:[
            rule result selectionIntervalsForSource: string tree: tree do: [:interval|
                interval notEmptyOrNil ifTrue:[
                    (interval first == 1 and:[interval last == text size]) ifTrue:[
                        (OperatingSystem getLoginName = 'jv') ifTrue:[
                            Transcript showCR:'>> no meaningful selection interval for ' , rule printString.
                        ].
                    ] ifFalse:[
                        self mark: text from: interval first to: interval last for: rule.
                    ]
                ]
            ].
        ].
    ] ifFalse: [
        | searches |

        searches := rule result searchStrings asSet.

        searches do:[:search|
            | i |
            i := 1.
            [ 
                i := string findString: search startingAt: i.
                i ~~ 0
            ] whileTrue:[
                self mark: text from: i to: (i + search size - 1) for: rule.
                i := i + search size + 1.
            ]
            

        ]
    ]

    "Created: / 03-02-2012 / 10:39:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkLintHighlighter methodsFor:'initialization'!

reset
    annotations := OrderedCollection new.

    "Created: / 18-02-2012 / 22:54:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-08-2013 / 12:40:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkLintHighlighter methodsFor:'markup'!

mark: text from: start to: end for: rule
    | emphasis |

    emphasis := self emphasisForSeverity: rule severity.
    text emphasisFrom: start to: end add: emphasis.     
    annotations add:
        (SmalltalkLintAnnotation from: start to: end rule: rule)

    "Created: / 30-01-2012 / 15:30:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2013 / 15:24:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !