SyntaxHighlighter.st
author Claus Gittinger <cg@exept.de>
Tue, 13 Feb 2001 16:00:20 +0100
changeset 1150 a06cd56413ab
parent 1143 3a9ddfa26b16
child 1159 24a034278a55
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1998 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:#SyntaxHighlighter
	instanceVariableNames:'sourceText identifierColor identifierEmphasis
		argumentIdentifierColor argumentIdentifierEmphasis
		localIdentifierColor localIdentifierEmphasis
		unknownIdentifierColor unknownIdentifierEmphasis
		badIdentifierColor badIdentifierEmphasis globalIdentifierColor
		globalIdentifierEmphasis commentColor commentEmphasis
		methodSelectorEmphasis methodSelectorColor selectorEmphasis
		selectorColor stringColor stringEmphasis symbolColor
		symbolEmphasis selfColor selfEmphasis superColor superEmphasis
		hereColor hereEmphasis thisContextColor thisContextEmphasis
		booleanConstantColor booleanConstantEmphasis constantColor
		constantEmphasis bracketColor bracketEmphasis
		instVarIdentifierColor instVarIdentifierEmphasis returnColor
		returnEmphasis globalClassIdentifierColor
		globalClassIdentifierEmphasis classVariableIdentifierColor
		classVariableIdentifierEmphasis unimplementedSelectorColor
		unimplementedSelectorEmphasis currentSuperclasses
		currentSubclasses fullSelectorCheck'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler'
!

!SyntaxHighlighter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1998 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.
"


!

documentation
"
    colors a method.
"


! !

!SyntaxHighlighter class methodsFor:'highlighting'!

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.
    parser ignoreWarnings.
    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.
        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."

    |parser tree text endPos eColor|

    aString isNil ifTrue:[^ nil].

    Error handle:[:ex |
        ('SyntaxHighlighter [info]: error during highlight: ' , ex errorString) infoPrintCR.
        "/ ex suspendedContext fullPrintAll.
        ^ aString
    ] do:[
        parser := self for:(ReadStream on:aString string) in:aClass.
        parser ignoreErrors.
        parser ignoreWarnings.
        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).

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

                endPos := parser sourceStream position.
                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
    "

    "Modified: / 23.10.1998 / 22:48:45 / cg"
! !

!SyntaxHighlighter methodsFor:'accessing'!

sourceText
    "return the value of the instance variable 'sourceText' (automatically generated)"

    ^ sourceText

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

sourceText:something
    "set the value of the instance variable 'sourceText' (automatically generated)"

    sourceText := something.

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

!SyntaxHighlighter methodsFor:'error handling'!

parseError:aMessage position:position to:endPos
    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


!

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

!SyntaxHighlighter methodsFor:'initialization'!

initialize
    |prefs|

    super initialize.

    foldConstants := false.
    allowDollarInIdentifier := true.

    prefs := UserPreferences current.

    fullSelectorCheck := prefs fullSelectorCheck.
    identifierEmphasis := prefs identifierEmphasis.
    identifierColor := prefs identifierColor.
    argumentIdentifierEmphasis := prefs argumentIdentifierEmphasis.
    argumentIdentifierColor := prefs argumentIdentifierColor.
    localIdentifierEmphasis := prefs localIdentifierEmphasis.
    localIdentifierColor := prefs localIdentifierColor.
    returnEmphasis := prefs returnEmphasis.
    returnColor := prefs returnColor.
    instVarIdentifierEmphasis := prefs instVarIdentifierEmphasis.
    instVarIdentifierColor := prefs instVarIdentifierColor.
    globalIdentifierEmphasis := prefs globalIdentifierEmphasis.
    globalIdentifierColor := prefs globalIdentifierColor.
    globalClassIdentifierEmphasis := prefs globalClassIdentifierEmphasis.
    globalClassIdentifierColor := prefs globalClassIdentifierColor.
    classVariableIdentifierEmphasis := prefs classVariableIdentifierEmphasis.
    classVariableIdentifierColor := prefs classVariableIdentifierColor.
    unknownIdentifierEmphasis := prefs unknownIdentifierEmphasis.
    unknownIdentifierColor := prefs unknownIdentifierColor.
    badIdentifierEmphasis := prefs badIdentifierEmphasis.
    badIdentifierColor := prefs badIdentifierColor.
    commentEmphasis := prefs commentEmphasis.
    commentColor := prefs commentColor.
    methodSelectorEmphasis := prefs methodSelectorEmphasis.
    methodSelectorColor := prefs methodSelectorColor.
    selectorEmphasis := prefs selectorEmphasis.
    selectorColor := prefs selectorColor.
    unimplementedSelectorEmphasis := prefs unimplementedSelectorEmphasis.
    unimplementedSelectorColor := prefs unimplementedSelectorColor.
    stringEmphasis := prefs stringEmphasis.
    stringColor := prefs stringColor.
    symbolEmphasis := prefs symbolEmphasis.
    symbolColor := prefs symbolColor.
    selfEmphasis := prefs selfEmphasis.
    selfColor := prefs selfColor.
    hereEmphasis := prefs hereEmphasis.
    hereColor := prefs hereColor.
    superEmphasis := prefs superEmphasis.
    superColor := prefs superColor.
    thisContextEmphasis := prefs thisContextEmphasis.
    thisContextColor := prefs thisContextColor.
    constantEmphasis := prefs constantEmphasis.
    constantColor := prefs constantColor.
    booleanConstantEmphasis := prefs booleanConstantEmphasis.
    booleanConstantColor := prefs booleanConstantColor.
    bracketEmphasis := prefs bracketEmphasis.
    bracketColor := prefs bracketColor.

    "Created: / 31.3.1998 / 15:12:55 / cg"
    "Modified: / 5.1.1980 / 00:44:03 / cg"
! !

!SyntaxHighlighter methodsFor:'misc'!

defineAsUndeclaredVariable:aName
    "redefined to NOT declare undefined vars"

    ^ VariableNode type:#GlobalVariable name: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"
! !

!SyntaxHighlighter methodsFor:'syntax detection'!

markArgumentIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:argumentIdentifierEmphasis color:argumentIdentifierColor

    "Modified: / 31.3.1998 / 18:01:27 / cg"
!

markBadIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:badIdentifierEmphasis color:badIdentifierColor

!

markBooleanConstantFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:booleanConstantEmphasis color:booleanConstantColor

    "Created: / 31.3.1998 / 18:09:01 / cg"
    "Modified: / 31.3.1998 / 19:36:44 / cg"
!

markBracketAt:pos
    self 
        markFrom:pos to:pos 
        withEmphasis:bracketEmphasis color:bracketColor

    "Created: / 31.3.1998 / 18:09:01 / cg"
    "Modified: / 31.3.1998 / 19:36:44 / cg"
!

markClassVariableIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:classVariableIdentifierEmphasis color:classVariableIdentifierColor

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

markCommentFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:commentEmphasis color:commentColor

    "Modified: / 31.3.1998 / 18:01:55 / cg"
!

markConstantFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:constantEmphasis color:constantColor

    "Modified: / 31.3.1998 / 18:01:44 / cg"
    "Created: / 31.3.1998 / 18:09:22 / cg"
!

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

markGlobalClassIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:globalClassIdentifierEmphasis color: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:globalIdentifierEmphasis color:globalIdentifierColor

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

markHereFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:hereEmphasis color:hereColor

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

markIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:identifierEmphasis color:identifierColor

    "Modified: / 31.3.1998 / 18:02:39 / cg"
    "Created: / 31.3.1998 / 18:04:56 / cg"
!

markInstVarIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:instVarIdentifierEmphasis color:instVarIdentifierColor

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

markLocalIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:localIdentifierEmphasis color:localIdentifierColor

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

markMethodSelectorFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:methodSelectorEmphasis color:methodSelectorColor

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

markReturnAt:pos
    self 
        markFrom:pos to:pos 
        withEmphasis:returnEmphasis color:returnColor

    "Modified: / 31.3.1998 / 19:36:44 / cg"
    "Created: / 5.1.1980 / 00:44:27 / cg"
!

markSelector:selectorString from:pos1 to:pos2 receiverNode:aReceiverNode
    |fg bg sel check ok rec em|

"/ uncommenting the code below
"/ will suppress highlighting of common selectors ...
"/
"/    (#(
"/        'ifTrue:' 
"/        'ifFalse:'
"/        'not'
"/        'and:'
"/        'or:'
"/        '='
"/        '=='
"/        '~='
"/        '~~'
"/    ) includes:sel) ifTrue:[
"/        ^ self
"/    ].

    fg := selectorColor.
    em := selectorEmphasis.
    selectorString knownAsSymbol ifFalse:[
        fg := Color red.
    ] ifTrue:[
        fullSelectorCheck == true ifTrue:[
            sel := selectorString asSymbol.

            check := [:cls | (cls includesSelector:sel)
                             or:[cls class includesSelector:sel]].

            ok := false.

            "/ limit search if possible
            (classToCompileFor notNil
             and:[aReceiverNode isSelf or:[aReceiverNode isSuper]]) ifTrue:[
                currentSuperclasses isNil ifTrue:[
                    currentSuperclasses := classToCompileFor withAllSuperclasses.
                ].
                ok := currentSuperclasses contains:check.
                (ok not and:[aReceiverNode isSelf]) ifTrue:[
                    currentSubclasses isNil ifTrue:[
                        currentSubclasses := classToCompileFor allSubclasses.
                    ].
                    ok := currentSubclasses contains:check.
                ].
            ] ifFalse:[
                aReceiverNode isConstant ifTrue:[
                    ok := aReceiverNode evaluate class withAllSuperclasses contains:check.
                ] ifFalse:[
                    (aReceiverNode isGlobal 
                    and:[(rec := aReceiverNode evaluate) isBehavior]) ifTrue:[
                        ok := rec class withAllSuperclasses contains:check.
                    ] ifFalse:[
                        ok := Smalltalk allClasses contains:check
                    ]
                ]
            ].

            ok ifFalse:[
                em := unimplementedSelectorEmphasis.
                fg := unimplementedSelectorColor.
            ]
        ]
    ].
    self
        markFrom:pos1 to:pos2 
        withEmphasis:em color:fg

    "Modified: / 1.4.1998 / 13:14:43 / cg"
!

markSelfFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:selfEmphasis color:selfColor

    "Modified: / 31.3.1998 / 18:03:10 / cg"
!

markStringFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:stringEmphasis color:stringColor

    "Modified: / 31.3.1998 / 18:03:18 / cg"
!

markSuperFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:superEmphasis color:superColor

    "Modified: / 31.3.1998 / 18:03:26 / cg"
!

markSymbolFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:symbolEmphasis color:symbolColor

    "Created: / 1.4.1998 / 12:56:47 / cg"
    "Modified: / 1.4.1998 / 12:58:00 / cg"
!

markThisContextFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:thisContextEmphasis color:thisContextColor

    "Modified: / 31.3.1998 / 18:03:36 / cg"
!

markUnknownIdentifierFrom:pos1 to:pos2
    self 
        markFrom:pos1 to:pos2 
        withEmphasis:unknownIdentifierEmphasis color:unknownIdentifierColor

    "Created: / 31.3.1998 / 19:09:26 / cg"
    "Modified: / 31.3.1998 / 19:10:30 / 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"
!

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 notNil ifTrue:[
            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"
! !

!SyntaxHighlighter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.34 2001-02-13 15:00:20 cg Exp $'
! !