AbstractSyntaxHighlighter.st
author Stefan Vogel <sv@exept.de>
Sat, 10 Aug 2013 13:10:59 +0200
changeset 3264 1d5dd6bf1257
parent 3235 6385bfe15842
child 3342 d7aec03dc509
permissions -rw-r--r--
class: AbstractSyntaxHighlighter changed: #formatExpression:in: #formatMethod:source:in:using: use #position/#position: instead of #positionXBased

"
 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:libcomp' }"

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

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

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

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

    ^ self formatExpression:aString in:aClass

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

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 position + 1.
        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
    <resource: #obsolete>
    "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
    <resource: #obsolete>
    "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 breakPoint:#cg.

        ex creator isHandled ifTrue:[
            ex reject.    
        ].
        (ParseError 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.    
        highlighter method:methodOrNil.
        preferencesOrNil notNil ifTrue:[highlighter preferences:preferencesOrNil].
        "/ highlighter ignoreErrors:true.
        highlighter ignoreWarnings:true.
        highlighter sourceText:(text := aString string asText).

        "/ 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 position + 1) 
                    to:text size 
                    with:(#color->eColor).
            ] ifFalse:[
                "/ alternative2: take original emphasis for rest

                endPos := highlighter sourceStream position + 1.
                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: / 05-07-2011 / 11:22:20 / cg"
!

formatMethod:aMethodOrNil source:aString in:aClass using:preferencesOrNil elementsInto: elements

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

    "Created: / 05-07-2011 / 10:41:14 / cg"
    "Modified: / 20-07-2011 / 16:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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 class methodsFor:'misc'!

collectionEnumerationSelectors
    "these are considered wellknown, builtin selectors of very common
     collection enumeration methods. 
     These are optionally shown with another color (dark green)"

    ^ #(
        collect: 
        select:
        inject:into:
        count:
        collect:thenSelect:
        select:thenCollect:
    )

    "Created: / 14-02-2012 / 15:56:59 / cg"
!

controlFlowSelectors
    "these are considered wellknown, builtin selectors of very common
     control flow constructs. Correspond to syntax or special forms in other
     languages. These are optionally shown with another color (blue)"

    ^ #(
        ifTrue: ifFalse:
        ifTrue:ifFalse: ifFalse:ifTrue:
        ifNil: ifNotNil:
        ifNil:ifNotNil: ifNotNil:ifNil:
        and: or:

        whileTrue:
        whileFalse:

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

        loop
        whileTrue
        whileFalse
        doWhile:
        doUntil:

        do:
        doWithIndex:
        pairWiseDo:
        keysAndValuesDo:

        withPriority:do:
        handle:do:
        on:do:
        catch:
        ignoreIn:

        "/ newProcess
        fork:
        ensure:
        ifCurtailed:
        valueOnUnwindDo:
        valueNowOrOnUnwindDo:

        caseOf:
        caseOf:otherwise:
    )

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

debugSelectors
    "these are considered harmful if left in a deployed application:
     selectors for debugging which open a debugger (unless haltSignal is
     cought or disabled, which end-user apps should do). 
     These are optionally shown with another color (redish)"

    ^ #(
        halt halt:
    )

    "Modified (comment): / 27-07-2013 / 11:45:07 / cg"
!

errorRaisingSelectors
    "these are error raisers. 
     These are optionally shown with another color (red)"

    ^ #(
        error error:
        raise raiseRequest:
        raiseErrorString: raiseRequestErrorString:
        raiseWith: raiseRequestWith:
        raiseWith:errorString: raiseRequestWith:errorString:
    )
! !

!AbstractSyntaxHighlighter class methodsFor:'utilities'!

mark:sourceText from:pos1 to:pos2 withAddedEmphasis:addedEmphasis
    sourceText emphasisFrom:pos1 to:pos2 add:addedEmphasis

    "Created: / 01-06-2012 / 21:43:36 / cg"
!

mark:sourceText from: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: / 01-06-2012 / 21:42:41 / cg"
!

mark:sourceText from:pos1 to:pos2 withEmphasis:fontEmp color:fgClr1 ifNil:fgClr2 backgroundColor:bgClr
    |e p2 clr fgClr|

    fgClr := fgClr1 ? fgClr2.
    (fgClr isNil or:[fgClr = Color black]) ifTrue:[
        e := fontEmp
    ] ifFalse:[
        clr := fgClr onDevice:Screen current.
        fontEmp isNil ifTrue:[
            e := (#color->clr)
        ] ifFalse:[
            e := Text addEmphasis:fontEmp to:(#color->clr).
        ]
    ].
    bgClr notNil ifTrue:[
        e := Text addEmphasis:(#backgroundColor->bgClr) to:e.
    ].
    (p2 := pos2) isNil ifTrue:[
        p2 := sourceText size
    ] ifFalse:[
        p2 := p2 min:sourceText size
    ].
    sourceText emphasizeFrom:pos1 to:p2 with:e

    "Created: / 01-06-2012 / 21:44:17 / cg"
! !

!AbstractSyntaxHighlighter methodsFor:'accessing'!

method:aMethod
    "the original method, if known (for subclasses which can make use of it)"

    method := aMethod.

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

collectionEnumerationSelectors
    ^ self class collectionEnumerationSelectors
!

controlFlowSelectors
    ^ self class controlFlowSelectors
!

debugSelectors
    ^ self class debugSelectors
!

defineAsUndeclaredVariable:aName
    "redefined to NOT declare undefined vars"

    ^ VariableNode globalNamed:aName

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

errorRaisingSelectors
    ^ self class errorRaisingSelectors
!

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
    self class 
        mark:sourceText from:pos1 to:pos2 withAddedEmphasis:addedEmphasis

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

markFrom:pos1 to:pos2 withEmphasis:fontEmp color:clrIn
    self class
        mark:sourceText from:pos1 to:pos2 withEmphasis:fontEmp color:clrIn

    "Created: / 31-03-1998 / 13:26:53 / cg"
    "Modified: / 01-06-2012 / 21:43:04 / cg"
!

markFrom:pos1 to:pos2 withEmphasis:fontEmp color:fgClr1 ifNil:fgClr2 backgroundColor:bgClr
    self class
        mark:sourceText from:pos1 to:pos2 withEmphasis:fontEmp color:fgClr1 ifNil:fgClr2 backgroundColor:bgClr

    "Created: / 13-02-2012 / 11:48:09 / cg"
!

markVariable:v
    |pos endPos|

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

    "Modified: / 30-11-2010 / 14:44:28 / cg"
! !

!AbstractSyntaxHighlighter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/AbstractSyntaxHighlighter.st,v 1.27 2013-08-10 11:10:59 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libcomp/AbstractSyntaxHighlighter.st,v 1.27 2013-08-10 11:10:59 stefan Exp $'
!

version_SVN
    ^ '$ Id $'
! !