tools/JavaCompilerProblemHighlighter.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 06 Sep 2013 00:16:38 +0100
branchdevelopment
changeset 2711 a00302fe5083
parent 2645 b7a540a27521
child 2731 13f5be2bf83b
permissions -rw-r--r--
Added version_CVS to all classes and build files regenerated & cleaned. This is necessary step before updating CVS.

"
 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: 'stx:libjava/tools' }"

Object subclass:#JavaCompilerProblemHighlighter
	instanceVariableNames:'class rules annotations formattingMethod emphasisError
		emphasisInformation emphasisWarning'
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Java-Tools-Editor'
!

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

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

emphasisForProblem: problem

    ^problem isError
        ifTrue:[self emphasisForError]
        ifFalse:[self emphasisForWarning].

    "Created: / 15-04-2013 / 23:33:50 / 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>"
! !

!JavaCompilerProblemHighlighter methodsFor:'formatting'!

formatClassDefinition:source in:jclass

    class := jclass.
    ^ self format: source

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

formatClassDefinition:source in:jclass elementsInto: elements

    class := jclass.
    ^ self format: source

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

formatExpression:source in:jclass

    ^ self format: source

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

formatExpression:source in:jclass elementsInto: elements

    ^ self format: source

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

formatMethod:mth source:source in:jclass using: preferences

    class := jclass.
    ^ self format: source

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

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

    class := jclass.
    ^ self format: source

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

!JavaCompilerProblemHighlighter methodsFor:'formatting-private'!

format: text
    ^ class isJavaClass ifTrue:[
        self format: text problems: (JavaCompilerProblemRegistry problemsFor: class)
    ] ifFalse:[
        text
    ]

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

format: source problem: problem
    | start stop |

    start := problem getSourceStart.
    stop := problem getSourceEnd.

    ((start between: 0 and: source size - 1) and:[(stop between: 0 and: source size - 1)]) ifTrue:[
        self mark: source from: start + 1 to: stop + 1 for: problem.

    ]

    "Created: / 15-04-2013 / 22:22:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-04-2013 / 23:36:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

format: givenSource problems: problems
    "Highlight a list of problems in givenSource.
     Return a copy of the text if there is at least one problem"

    | source |

    problems isEmptyOrNil ifTrue:[ ^ givenSource ].
    source := givenSource deepCopy.
    problems do:[:problem|
        self format: source problem: problem.
    ].
    ^source

    "Created: / 15-04-2013 / 22:11:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompilerProblemHighlighter methodsFor:'initialization'!

reset
    annotations := #().

    "Created: / 18-02-2012 / 22:54:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompilerProblemHighlighter methodsFor:'markup'!

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

    emphasis := self emphasisForProblem: problem.
    text emphasisFrom: start to: end add: emphasis.     
"/    annotations add:
"/        (LintAnnotation from: start to: end rule: rule)

    "Created: / 30-01-2012 / 15:30:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-04-2013 / 23:32:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaCompilerProblemHighlighter class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
!

version_HG

    ^ '$Changeset: <not expanded> $'
! !