AbstractSyntaxHighlighter.st
author Claus Gittinger <cg@exept.de>
Fri, 07 May 2010 12:25:50 +0200
changeset 2392 c26d2d1dfffe
parent 2371 2348d09fb80e
child 2464 595ec0d9efa9
permissions -rw-r--r--
changed: #formatMethod:source:in:using: leftover print removed

"{ Package: 'stx:libcomp' }"

Parser subclass:#AbstractSyntaxHighlighter
	instanceVariableNames:'sourceText preferences fullSelectorCheck'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler'
!


!AbstractSyntaxHighlighter class methodsFor:'api highlighting'!

formatClassDefinition:aString in:aClass
    "format (recolor) a class definition expression in a given class.
     Return the text containing font changes and color information."

    ^ self formatExpression:aString in:aClass
!

formatExpression:aString in:aClass
    "format (recolor) an expression in a given class.
     Return the text containing font changes and color information."

    |parser tree text endPos|

    aString isNil ifTrue:[^ nil].

    parser := self for:(ReadStream on:aString string) in:aClass.
    parser ignoreErrors:true.
    parser ignoreWarnings:true.
    parser sourceText:(text := aString string asText).
    "/ use an array here - this can be changed much faster using #at:put:
    text emphasisCollection:(Array new:aString size).

    parser nextToken.
    tree := parser expression.
    "/ now, convert the emphasis-array to a runArray
    text emphasisCollection:(text emphasis asRunArray).

    tree == #Error ifTrue:[
        "/ mhmh - which is better ...
        "/ alternative1: color rest after error in red
"/        text 
"/            emphasizeFrom:(parser sourceStream position) 
"/            to:text size 
"/            with:(#color->Color red).


        "/ alternative2: take original emphasis for rest

        endPos := parser sourceStream position1Based.
        endPos >= text size ifTrue:[
            ^ text
        ].
        ^ (text copyTo:endPos) , (aString copyFrom:(endPos+1))

        "/ alternative3: no emphasis for rest.

"/        ^ text "/ aString
    ].
    ^ text

    "
     self
        formatExpression:'(1 + 2) max:5' 
        in:UndefinedObject
    "

    "Modified: / 7.4.1998 / 09:57:19 / cg"
    "Created: / 9.4.1998 / 16:57:16 / cg"
!

formatMethod:aString in:aClass
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    self obsoleteMethodWarning:'use #formatMethodSource:in:'.
    ^ self formatMethod:nil source:aString in:aClass using:nil

    "
     self
        formatMethod:'foo 
    ^ self bar:''hello''.

    ' , (Character doubleQuote asString) , 'some comment' , (Character doubleQuote asString) , '
'
        in:UndefinedObject
    "

    "Modified: / 28-04-2010 / 13:03:04 / cg"
!

formatMethod:aString in:aClass using:preferencesOrNil
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    self obsoleteMethodWarning:'use #formatMethodSource:in:using:'.
    ^ self formatMethod:nil source:aString in:aClass using:preferencesOrNil

    "Modified: / 28-04-2010 / 13:03:15 / cg"
!

formatMethod:methodOrNil source:aString in:aClass
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    ^ self formatMethod:methodOrNil source:aString in:aClass using:nil

    "
     self
        formatMethod:'foo 
    ^ self bar:''hello''.

    ' , (Character doubleQuote asString) , 'some comment' , (Character doubleQuote asString) , '
'
        in:UndefinedObject
    "

    "Created: / 28-04-2010 / 13:44:24 / cg"
!

formatMethod:methodOrNil source:aString in:aClass using:preferencesOrNil
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    |highlighter tree text endPos eColor|

    aString isNil ifTrue:[^ nil].

    Error handle:[:ex |
"/ Transcript showCR:ex description.
"/ self halt.
        ex signal isHandled ifTrue:[
            ex reject.    
        ].
        (self parseErrorSignal handles:ex) ifFalse:[
            "Parse error may happen when re-formatting incomplete code while editing"
            ('SyntaxHighlighter [info]: error during highlight: ' , ex description) infoPrintCR.
            "/ ex suspendedContext fullPrintAll.
        ].
        ^ aString
    ] do:[
        highlighter := self for:(ReadStream on:aString string) in:aClass.    
        preferencesOrNil notNil ifTrue:[highlighter preferences:preferencesOrNil].
        "/ highlighter ignoreErrors:true.
        highlighter ignoreWarnings:true.
        highlighter sourceText:(text := aString string asText).
        highlighter method:methodOrNil.

        "/ use an array here - this can be changed much faster using #at:put:
        text emphasisCollection:(Array new:aString size).

        tree := highlighter parseMethod.
        "/ now, convert the emphasis-array to a runArray
        text emphasisCollection:(text emphasis asRunArray).

        tree == #Error ifTrue:[
            eColor := UserPreferences current errorColor.
            eColor notNil ifTrue:[
                "/ mhmh - which is better ...
                "/ alternative1: color rest after error in red
                text 
                    emphasizeFrom:(highlighter sourceStream position1Based) 
                    to:text size 
                    with:(#color->eColor).
            ] ifFalse:[
                "/ alternative2: take original emphasis for rest

                endPos := highlighter sourceStream position1Based.
                endPos >= text size ifTrue:[
                    ^ text
                ].
                ^ (text copyTo:endPos) , (aString copyFrom:(endPos+1))
            ].
            "/ alternative3: no emphasis for rest.
        ].
        ^ text
    ]
    "
     self
        formatMethod:'foo 
    ^ self bar:''hello''.

    ' , (Character doubleQuote asString) , 'some comment' , (Character doubleQuote asString) , '
'
        in:UndefinedObject
    "

    "Created: / 28-04-2010 / 13:01:42 / cg"
    "Modified: / 07-05-2010 / 12:24:52 / cg"
!

formatMethodSource:aString in:aClass
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    ^ self formatMethod:nil source:aString in:aClass using:nil

    "
     self
        formatMethod:'foo 
    ^ self bar:''hello''.

    ' , (Character doubleQuote asString) , 'some comment' , (Character doubleQuote asString) , '
'
        in:UndefinedObject
    "

    "Created: / 28-04-2010 / 12:58:13 / cg"
!

formatMethodSource:aString in:aClass using:preferencesOrNil
    "format (recolor) a method in a given class.
     Return the text containing font changes and color information."

    ^ self formatMethod:nil source:aString in:aClass using:preferencesOrNil

    "Modified: / 28-04-2010 / 13:02:11 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'accessing'!

method:aMethod
    "/ ignored here

    "Created: / 28-04-2010 / 13:15:33 / cg"
!

preferences:something
    preferences := something.
!

sourceText
    ^ sourceText

    "Created: / 31.3.1998 / 11:49:05 / cg"
!

sourceText:aString
    sourceText := aString.

    "Created: / 31-03-1998 / 11:49:05 / cg"
    "Modified: / 28-04-2010 / 13:22:27 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'error handling'!

parseError:aMessage position:position to:endPos
"/ Transcript showCR:aMessage.
    super parseError:aMessage position:position to:endPos.

    self 
        markFrom:position to:endPos 
        withEmphasis:nil color:UserPreferences current errorColor
!

showErrorMessage:aMessage position:pos
"/ Transcript showCR:aMessage.
    super showErrorMessage:aMessage position:pos.

    self 
        markFrom:pos to:nil 
        withEmphasis:nil color:UserPreferences current errorColor
!

syntaxError:aMessage position:position to:endPos
"/ Transcript showCR:aMessage.
    super syntaxError:aMessage position:position to:endPos.

    self 
        markFrom:position to:endPos 
        withEmphasis:nil color:UserPreferences current errorColor
!

warning:msg position:pos1 to:pos2
"/    self markUnknownIdentifierFrom:pos1 to:pos2

"/    self
"/        markFrom:pos1 to:pos2 
"/        withEmphasis:nil color:UserPreferences current errorColor

    "Modified: / 25.9.1999 / 18:42:30 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'initialization'!

initialize
    super initialize.

    foldConstants := false.
    preferences := UserPreferences current.
    fullSelectorCheck := preferences fullSelectorCheck.

    "Created: / 31-03-1998 / 15:12:55 / cg"
    "Modified: / 28-04-2010 / 13:17:45 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'misc'!

controlFlowSelectors
    ^ #(
        ifTrue:
        ifFalse:
        ifTrue:ifFalse:
        ifFalse:ifTrue:

        whileTrue:
        whileFalse:

        to:do:
        downTo:do:
        to:by:do:

        loop
        whileTrue
        whileFalse
        doWhile:
        doUntil:

        do:
        keysAndValuesDo:
    )

    "Created: / 08-09-2006 / 15:56:47 / cg"
!

defineAsUndeclaredVariable:aName
    "redefined to NOT declare undefined vars"

    ^ VariableNode globalNamed:aName

    "Modified: / 19.10.1998 / 19:38:12 / cg"
!

isSyntaxHighlighter
    ^ true

!

plausibilityCheck:aNode
    "redefined to NOT do checks"

    ^ nil

    "Modified: / 19.10.1998 / 19:38:12 / cg"
    "Created: / 19.10.1998 / 19:57:18 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'syntax detection'!

markFrom:pos1 to:pos2 withAddedEmphasis:addedEmphasis
    sourceText emphasisFrom:pos1 to:pos2 add:addedEmphasis

    "Created: / 15-01-2008 / 11:48:18 / cg"
!

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 := sourceText size
    ] ifFalse:[
        p2 := p2 min:sourceText size
    ].
    sourceText emphasizeFrom:pos1 to:p2 with:e

    "Created: / 31-03-1998 / 13:26:53 / cg"
    "Modified: / 28-04-2010 / 14:12:31 / cg"
!

markVariable:v
    "support for syntaxColoring"

    |pos endPos|

    pos := tokenPosition.
    endPos := pos+tokenName size-1.
    self markVariable:v from:pos to:endPos

    "Modified: / 16.4.1998 / 18:49:51 / cg"
! !

!AbstractSyntaxHighlighter class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libcomp/AbstractSyntaxHighlighter.st,v 1.2 2010-05-07 10:25:50 cg Exp $'
! !