tools/JavaSyntaxHighlighter.st
author Stefan Vogel <sv@exept.de>
Fri, 19 Apr 2013 13:40:43 +0200
changeset 2540 424e0a635765
parent 2396 fadc6d7a2f5b
child 2429 ebece4dcaab9
permissions -rw-r--r--
automatically generated by browser

"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 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.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010
"
"{ Package: 'stx:libjava/tools' }"

Object subclass:#JavaSyntaxHighlighter
	instanceVariableNames:'preferences elements cachedStringEmphasis cachedStringColor
		sourceText'
	classVariableNames:'FormattedSourceCache'
	poolDictionaries:''
	category:'Languages-Java-Tools'
!

JavaParseNodeBuilder subclass:#Builder
	instanceVariableNames:'highlighter'
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaSyntaxHighlighter
!

JavaParser subclass:#Parser
	instanceVariableNames:'stream'
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaSyntaxHighlighter
!

JavaScanner subclass:#Scanner
	instanceVariableNames:'highlighter'
	classVariableNames:''
	poolDictionaries:''
	privateIn:JavaSyntaxHighlighter
!

!JavaSyntaxHighlighter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 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.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010

"
! !


!JavaSyntaxHighlighter class methodsFor:'formatting'!

formatClass: javaClass

    ^self new formatClassDefinition: javaClass source in: javaClass

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

formatClassDefinition:source in:class

    ^self new formatClassDefinition:source in:class

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

formatClassDefinition:source in:class elementsInto: elements

    ^self new formatClassDefinition:source in:class elementsInto: elements

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

formatExpression:source in:class

    ^self new formatExpression:source in:class

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

formatExpression:source in:class elementsInto: elements

    ^self new formatExpression:source in:class elementsInto: elements

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

formatMethod:mth source:source in:class

    ^self formatMethod: mth source: source in: class using: UserPreferences current

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

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

    ^self new formatMethod:mth source:source in:class using: preferences

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

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

    ^self new formatMethod:mth source:source in:class using: preferences elementsInto: elements

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


!JavaSyntaxHighlighter methodsFor:'formatting'!

formatClassDefinition:source in:class

    ^ self format: source kind: #start in: class

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

formatClassDefinition:source in:class elementsInto: els

    elements := els.
    ^self formatClassDefinition:source in:class

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

formatExpression:source in:class

"/    self breakPoint:#jv.
    ^source.
    ^ self format: source kind: #'K_EXPRESSION' in: class

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

formatExpression:source in:class elementsInto: els

    elements := els.
    ^self formatExpression:source in:class

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

formatMethod:mth source:source in:class using: prefs

    preferences := prefs.
    ^ self format: source kind: #start in: class

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

formatMethod:mth source:source in:class using: prefs elementsInto: els

    preferences := prefs.
    elements := els.
    ^self formatMethod:mth source:source in:class using: prefs

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


!JavaSyntaxHighlighter methodsFor:'formatting - private'!

format: source kind: kind in: class

    | scanner parser builder cacheIt |

    "Optimization - if full class source is to be formatted,
     consult cache - when browsing the code or debugging, very 
     often same same source is to be highlighted"
    cacheIt := kind == #start and: [class notNil].
    cacheIt ifTrue:[
        FormattedSourceCache isNil ifTrue:[
            FormattedSourceCache := OrderedDictionary new
        ] ifFalse:[
            FormattedSourceCache 
                at: class 
                ifPresent:[:sourceAndText|
                    sourceAndText first = source ifTrue:[
                        ^sourceAndText second
                    ].

                ].
        ]
    ].


    source isText ifTrue:[
        sourceText := source copy
    ] ifFalse:[
        sourceText := source asText.
    ].

    preferences isNil ifTrue:[
        preferences := UserPreferences current.
    ].

    scanner := Scanner for: source.  
    builder := Builder new.
    builder highlighter: self.
    scanner highlighter: self.
    parser := Parser newStartingAt: kind.
    parser builder: builder.
    parser stream: scanner.
    parser parse: scanner.

    cacheIt ifTrue:[
        [ FormattedSourceCache size > 25 ] whileTrue:[
            FormattedSourceCache removeKey: FormattedSourceCache keys first.
        ].
        FormattedSourceCache at: class put: { source . sourceText }
    ].
    ^sourceText.

    "Created: / 17-03-2012 / 14:02:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter methodsFor:'syntax detection'!

markArgumentIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences argumentIdentifierEmphasis) color:(preferences argumentIdentifierColor)
!

markBadIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences badIdentifierEmphasis) 
        color:(preferences badIdentifierColor)
!

markClassVariableIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences classVariableIdentifierEmphasis) color:(preferences classVariableIdentifierColor)

    "Modified: / 31.3.1998 / 18:02:14 / cg"
!

markCommentFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences commentEmphasis) color:(preferences commentColor)
!

markConstantFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences constantEmphasis) color:(preferences constantColor)
!

markFrom:pos1 to:pos2 withEmphasis:fontEmp color:clrIn
    |e p2 clr|

    clr := clrIn onDevice:Screen current.

    clr = Color black ifTrue:[
        e := fontEmp
    ] ifFalse:[
        fontEmp isNil ifTrue:[
            e := (#color->clr)
        ] ifFalse:[
            e := Text addEmphasis:fontEmp to:(#color->clr).
        ]
    ].
    (p2 := pos2) isNil ifTrue:[
        p2 := sourceText size
    ] ifFalse:[
        p2 := p2 min:sourceText size
    ].
    sourceText emphasizeFrom:pos1 to:p2 with:e

    "Created: / 31.3.1998 / 13:26:53 / cg"
    "Modified: / 1.4.1998 / 12:51:56 / cg"
!

markFunctionNameFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences methodSelectorEmphasis) color:(preferences methodSelectorColor)
!

markGlobalClassIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences globalClassIdentifierEmphasis) color:(preferences globalClassIdentifierColor)

    "Modified: / 31.3.1998 / 18:02:14 / cg"
    "Created: / 4.3.1999 / 12:53:02 / cg"
!

markGlobalIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences globalIdentifierEmphasis) color:(preferences globalIdentifierColor)

    "Modified: / 31.3.1998 / 18:02:14 / cg"
!

markIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences identifierEmphasis) color:(preferences identifierColor)
!

markInstVarIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences instVarIdentifierEmphasis) color:(preferences instVarIdentifierColor)

    "Created: / 16.4.1998 / 18:35:40 / cg"
    "Modified: / 16.4.1998 / 18:37:30 / cg"
!

markKeyword:kw from:pos1 to:pos2
    |em clr|

    ( #( 'if' 'else'
         'while'
         'for'
         'do'
         'return'
    ) includes:kw) ifTrue:[
        em := preferences controlFlowSelectorEmphasis. 
        clr := preferences controlFlowSelectorColor.
    ] ifFalse:[
        em := preferences jsKeywordEmphasis.
        clr := preferences jsKeywordColor.
    ].
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:em color:clr

    "Modified: / 19-05-2010 / 15:07:59 / cg"
    "Modified: / 17-03-2012 / 00:14:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

markLocalIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences localIdentifierEmphasis) color:(preferences localIdentifierColor)
!

markSelector:selectorString from:pos1 to:pos2 
    | fg em |

    fg := preferences selectorColor.
    em := preferences selectorEmphasis.

    self
        markFrom:pos1 to:pos2 
        withEmphasis:em color:fg

    "Modified: / 04-10-2011 / 19:48:48 / cg"
    "Modified: / 17-03-2012 / 13:26:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 17-03-2012 / 19:12:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

markSelector:selectorString from:pos1 to:pos2 receiverNode:aReceiverNodeOrNil numArgs:numArgs
    |fg selectorSymbol check ok rec em currentEnvironment currentSuperclasses currentSubclasses classToCompileFor fullSelectorCheck|

    fg := preferences selectorColor.
    em := preferences selectorEmphasis.

"/    (currentEnvironment notNil
"/    and:[ (((currentEnvironment _localVariables ? #()) contains:[:local | local name = selectorString]) 
"/          or:[((currentEnvironment _argVariables ? #()) contains:[:local | local name = selectorString])])
"/    ])
"/    ifTrue:[
"/        "/ a local call
"/    ] ifFalse:[
"/        selectorSymbol := (self translatedSmalltalkSelectorFor:selectorString numArgs:numArgs) asSymbolIfInterned.
"/        selectorSymbol isNil ifTrue:[
"/            fg := Color red.
"/        ] ifFalse:[
"/            fullSelectorCheck == true ifTrue:[
"/                aReceiverNodeOrNil notNil ifTrue:[
"/                    check := [:cls | (cls includesSelector:selectorSymbol)
"/                                     or:[cls class includesSelector:selectorSymbol]].
"/
"/                    ok := false.
"/
"/                    "/ limit search if possible
"/                    (classToCompileFor notNil
"/                     and:[aReceiverNodeOrNil isSelf or:[aReceiverNodeOrNil isSuper]]) ifTrue:[
"/                        currentSuperclasses isNil ifTrue:[
"/                            currentSuperclasses := classToCompileFor withAllSuperclasses.
"/                        ].
"/                        ok := currentSuperclasses contains:check.
"/                        (ok not and:[aReceiverNodeOrNil isSelf]) ifTrue:[
"/                            currentSubclasses isNil ifTrue:[
"/                                currentSubclasses := classToCompileFor allSubclasses.
"/                            ].
"/                            ok := currentSubclasses contains:check.
"/                        ].
"/                    ] ifFalse:[
"/                        aReceiverNodeOrNil isConstant ifTrue:[
"/                            ok := aReceiverNodeOrNil evaluate class withAllSuperclasses contains:check.
"/                        ] ifFalse:[
"/                            (aReceiverNodeOrNil isGlobal 
"/                            and:[(rec := aReceiverNodeOrNil evaluate) isBehavior]) ifTrue:[
"/                                ok := rec class withAllSuperclasses contains:check.
"/                            ] ifFalse:[
"/                                ok := Smalltalk allClasses contains:check
"/                            ]
"/                        ]
"/                    ].
"/
"/                    ok ifFalse:[
"/                        em := preferences unimplementedSelectorEmphasis.
"/                        fg := preferences unimplementedSelectorColor.
"/                    ]
"/                ]
"/            ]
"/        ].
"/    ].
    self
        markFrom:pos1 to:pos2 
        withEmphasis:em color:fg

    "Modified: / 04-10-2011 / 19:48:48 / cg"
    "Modified: / 17-03-2012 / 13:26:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

markSelfFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences selfEmphasis) color:(preferences selfColor)
!

markStringFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences stringEmphasis) color:(preferences stringColor)
!

markUnknownIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:(preferences unknownIdentifierEmphasis) color:(preferences unknownIdentifierColor)
!

markVariable:v from:pos to:endPos
    "support for syntaxColoring"

    |type globalValue nameSym|

    type := v type.
    (type == #BlockArg
    or:[type == #MethodArg]) ifTrue:[
        self markArgumentIdentifierFrom:pos to:endPos.
        ^ self
    ].
    (type == #BlockVariable
    or:[type == #MethodVariable]) ifTrue:[
        self markLocalIdentifierFrom:pos to:endPos.
        ^ self
    ].
    (type == #GlobalVariable) ifTrue:[
        nameSym := v name asSymbolIfInterned.
        (nameSym isNil 
        or:[(Smalltalk includesKey:nameSym) not]) ifTrue:[
            self markUnknownIdentifierFrom:pos to:endPos.
            ^ self
        ].
        globalValue := Smalltalk at:nameSym ifAbsent:nil.
        globalValue isBehavior ifTrue:[
            self markGlobalClassIdentifierFrom:pos to:endPos.
        ] ifFalse:[
            self markGlobalIdentifierFrom:pos to:endPos.
        ].
        ^ self
    ].
    (type == #ClassVariable) ifTrue:[
        self markClassVariableIdentifierFrom:pos to:endPos.
        ^ self
    ].
    (type == #InstanceVariable) ifTrue:[
        self markInstVarIdentifierFrom:pos to:endPos.
        ^ self
    ].

    self markIdentifierFrom:pos to:endPos.

    "Created: / 16.4.1998 / 18:49:34 / cg"
    "Modified: / 4.3.1999 / 12:56:13 / cg"
! !


!JavaSyntaxHighlighter::Builder methodsFor:'accessing'!

highlighter
    ^ highlighter
!

highlighter:something
    highlighter := something.
! !


!JavaSyntaxHighlighter::Builder methodsFor:'building'!

newComment: text

    highlighter markCommentFrom:start to: stop.
    ^super newComment: text

    "Created: / 09-03-2012 / 17:11:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

newJavaDoc: text

    highlighter markCommentFrom:start to: stop.
    ^super newJavaDoc: text

    "Created: / 09-03-2012 / 17:11:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

newStringLiteral: string

    highlighter markStringFrom:start to: stop.
    ^super newStringLiteral: string

    "Created: / 17-03-2012 / 17:32:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Parser methodsFor:'accessing'!

highlighter

    ^builder highlighter

    "Created: / 17-03-2012 / 19:11:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stream
    ^ stream
!

stream:something
    stream := something.
! !


!JavaSyntaxHighlighter::Parser methodsFor:'grammar-classes-method'!

constructorNameIdentifier

    ^super constructorNameIdentifier ==> [:token|
        self highlighter
            markSelector: token value 
                    from: token startPosition to: token endPosition
    ]

    "Created: / 17-03-2012 / 19:12:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

identifier

    ^(JavaParserI::TokenParser for: #Identifier)

    "Created: / 16-12-2012 / 10:29:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-01-2013 / 11:10:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

methodNameIdentifier

    ^super methodNameIdentifier ==> [:token|
        self highlighter
            markSelector: token value 
                    from: token startPosition to: token endPosition
    ]

    "Created: / 17-03-2012 / 19:13:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

typeNameIdentifier

    ^super typeNameIdentifier ==> [:token|
        self highlighter
            markSelector: token value 
                    from: token startPosition to: token endPosition
    ]

    "Created: / 17-03-2012 / 19:44:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Parser methodsFor:'grammar-literals-string'!

stringLiteral 

    ^super stringLiteral ==> [:stringToken|
        builder 
            start: stringToken startPosition 
            stop: stringToken endPosition;
            newStringLiteral: stringToken value
    ]

    "Created: / 17-03-2012 / 17:31:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Parser methodsFor:'utility'!

tokenFor: aString

"/    | p |
"/
"/    p := keywords at: aString ifAbsent:[nil].
"/    p notNil ifTrue:[ 
"/        ^ (self asToken: p) ==> [:token| 
"/            | start stop |
"/
"/            stop := stream position.
"/            start := stop - keyword size.
"/            builder highlighter markKeyword: keyword from:start to:stop
"/        ].
"/    ].

    ^super tokenFor: aString

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


!JavaSyntaxHighlighter::Scanner methodsFor:'accessing'!

highlighter
    ^ highlighter
!

highlighter:aJavaSyntaxHighlighter
    highlighter := aJavaSyntaxHighlighter.
! !


!JavaSyntaxHighlighter::Scanner methodsFor:'error handling'!

syntaxError:aMessage position:position to:endPos
    "a syntax error happened"

    endPos notNil ifTrue:[
        highlighter markBadIdentifierFrom:position to: endPos.
    ]

    "Created: / 13-04-2012 / 18:31:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Scanner methodsFor:'initialization'!

initialize
    "initialize the scanner"

    super initialize.
    saveComments := true

    "Created: / 17-03-2012 / 00:02:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Scanner methodsFor:'private'!

checkForKeyword:string
    | isKW |

    isKW := super checkForKeyword:string.
    isKW ifTrue:[
        highlighter markKeyword:string from:tokenStartPosition + 1 to:tokenStartPosition + string size
    ].
    ^isKW

    "Created: / 17-03-2012 / 00:15:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter::Scanner methodsFor:'reading next token'!

nextToken
    |t|

    [
        t := super nextToken.
        tokenEndPosition := source position.
        t isNil
    ] whileTrue.
    Verbose == true ifTrue:[
        Transcript 
            show:'JavaScanner nextToken => ';
            show: t storeString;
            show: ' | ';
            showCR: tokenValue.
    ].
    ^ t

    "Created: / 14-05-1998 / 15:48:04 / cg"
    "Modified: / 16-05-1998 / 19:12:29 / cg"
    "Modified: / 17-03-2012 / 17:35:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 17-03-2012 / 19:15:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

skipComment
    super skipComment.
    highlighter markCommentFrom:((tokenStartPosition + 1) max: 1) to: source position.
    ^nil

    "Created: / 17-03-2012 / 00:04:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

skipEOLComment
    super skipEOLComment.
    highlighter markCommentFrom:((tokenStartPosition - 1) max: 1) to: source position.
    ^nil

    "Created: / 17-03-2012 / 00:05:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


!JavaSyntaxHighlighter class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libjava/tools/JavaSyntaxHighlighter.st,v 1.2 2013-02-25 11:15:35 vrany Exp $'
!

version_HG

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

version_SVN
    ^ 'Id'
! !