tools/JavaSyntaxHighlighter_Eclipse.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 24 May 2013 17:55:42 +0100
branchbuiltin-class-support
changeset 2629 cedb88626902
parent 2515 bcfe9f4dca6b
child 2711 a00302fe5083
permissions -rw-r--r--
Closing branch.

"{ Package: 'stx:libjava/tools' }"

Object subclass:#JavaSyntaxHighlighter_Eclipse
	instanceVariableNames:'preferences elements text cachedStringEmphasis cachedStringColor'
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Java-Tools-Eclipse'
!


!JavaSyntaxHighlighter_Eclipse 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_Eclipse methodsFor:'error handling (interop)'!

doesNotUnderstand:aMessage

    | method  selector class args|
    selector := aMessage selector.
    args := aMessage arguments.
    class := self class.

    JavaLookup isNil ifTrue:[
        (Smalltalk loadPackage: 'stx:libjava/experiments') ifFalse:[
            self error: 'You should load package stx:libjava/experiments if you want some interop - still experimental' mayProceed: true.
            ^nil                        
        ]        
    ].

    method := JavaLookup instance lookupMethodForSelector: selector
                directedTo: class
                for: self
                withArguments: args
                from: thisContext sender sender
                ilc: nil.

    method isNil ifTrue:[
        ^super doesNotUnderstand:aMessage
    ] ifFalse:[
        ^ method valueWithReceiver: self arguments: args
    ].

    "Created: / 06-09-2011 / 22:16:26 / Jan Kurs <kursjan@fit.cvut.cz>"
    "Modified: / 15-12-2011 / 23:42:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSyntaxHighlighter_Eclipse methodsFor:'formatting'!

formatClassDefinition:source in:class

    ^ self format: source kind: #K_COMPILATION_UNIT

    "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 format: source kind: #'K_EXPRESSION'

    "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: #K_COMPILATION_UNIT

    "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_Eclipse methodsFor:'formatting - private'!

format: source kind: kindSym

    | kind jhighlighter |


    kindSym == #K_EXPRESSION ifTrue:[
        kind := 1
    ] ifFalse:[kindSym == #K_STATEMENTS ifTrue:[
        kind := 2        
    ] ifFalse:[kindSym == #K_CLASS_BODY_DECLARATIONS ifTrue:[
        kind := 4
    ] ifFalse:[kindSym == #K_COMPILATION_UNIT ifTrue:[
        kind := 8
    ] ifFalse:[
        self error: 'Unknown source kind'
    ]]]].

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

    JavaVM booted ifFalse:[ ^ text ].

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

    jhighlighter := (JavaVM classForName:'stx.libjava.tools.SyntaxHighlighter') newCleared.
    jhighlighter instVarNamed: #handler put: self.


    kindSym == #K_COMPILATION_UNIT ifTrue:[    
        | ast |

        ast := JavaParser_Eclipse new parseClassSource: source.
        jhighlighter format: ast.
    ] ifFalse:[
        jhighlighter perform: #'format([CI)V' with: source string with: kind.
    ].




    ^text.

    "Created: / 17-11-2011 / 23:24:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSyntaxHighlighter_Eclipse methodsFor:'markup'!

markClassName:start length: length
    self 
        markFrom:start + 1 to: start + length
        withEmphasis:(preferences globalClassIdentifierEmphasis) color:(preferences globalClassIdentifierColor)

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

markComment: start length: length

    self 
        markFrom:start + 1 to: start + 1 + length 
        withEmphasis:(preferences commentEmphasis) 
        color:(preferences commentColor)

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

markConstant:start length:length
    self 
        markFrom:start + 1 to:start + length 
        withEmphasis:(preferences constantEmphasis) color:(preferences constantColor)

    "Created: / 20-12-2011 / 09:44:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

markKeyword: start length: length

    | em clr |

    em := preferences jsKeywordEmphasis.
    clr := preferences jsKeywordColor.

    self 
        markFrom:start +1 to:start + length
        withEmphasis:em color:clr

    "Created: / 19-12-2011 / 23:53:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

markString: start length: length

    cachedStringEmphasis isNil ifTrue:[
        cachedStringEmphasis := preferences stringEmphasis.
        cachedStringColor := preferences stringColor.
    ].
    self 
        markFrom:start + 1 to:start + length 
            withEmphasis:cachedStringEmphasis 
                color:cachedStringColor

    "Created: / 19-11-2011 / 12:50:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSyntaxHighlighter_Eclipse methodsFor:'markup-basic'!

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

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

    "Created: / 31-03-1998 / 13:26:53 / cg"
    "Modified: / 28-04-2010 / 14:12:31 / cg"
    "Modified: / 14-12-2011 / 19:55:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaSyntaxHighlighter_Eclipse class methodsFor:'documentation'!

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

version_HG

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

version_SVN
    ^ '§Id§'
! !