SyntaxHighlighter.st
author Claus Gittinger <cg@exept.de>
Thu, 16 Apr 1998 18:58:53 +0200
changeset 686 067a8c8be462
parent 684 dd691ac07f90
child 689 42a774852fed
permissions -rw-r--r--
checkin from browser

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



Parser subclass:#SyntaxHighlighter
	instanceVariableNames:'sourceText identifierColor identifierEmphasis
		argumentIdentifierColor argumentIdentifierEmphasis
		localIdentifierColor localIdentifierEmphasis
		unknownIdentifierColor unknownIdentifierEmphasis
		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'
	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|

    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).

    tree := parser parseMethod.
    "/ 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
        formatMethod:'foo 
    ^ self bar:''hello''.

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

    "Modified: / 7.4.1998 / 09:57:19 / 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:'initialization'!

initialize
    |prefs|

    super initialize.

    prefs := UserPreferences current.
    identifierEmphasis := prefs identifierEmphasis.
    identifierColor := prefs identifierColor.
    argumentIdentifierEmphasis := prefs argumentIdentifierEmphasis.
    argumentIdentifierColor := prefs argumentIdentifierColor.
    localIdentifierEmphasis := prefs localIdentifierEmphasis.
    localIdentifierColor := prefs localIdentifierColor.
    instVarIdentifierEmphasis := prefs instVarIdentifierEmphasis.
    instVarIdentifierColor := prefs instVarIdentifierColor.
    globalIdentifierEmphasis := prefs globalIdentifierEmphasis.
    globalIdentifierColor := prefs globalIdentifierColor.
    unknownIdentifierEmphasis := prefs unknownIdentifierEmphasis.
    unknownIdentifierColor := prefs unknownIdentifierColor.
    commentEmphasis := prefs commentEmphasis.
    commentColor := prefs commentColor.
    methodSelectorEmphasis := prefs methodSelectorEmphasis.
    methodSelectorColor := prefs methodSelectorColor.
    selectorEmphasis := prefs selectorEmphasis.
    selectorColor := prefs selectorColor.
    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: / 16.4.1998 / 18:40:19 / 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"
!

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

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:clr
    |e|

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

    "Created: / 31.3.1998 / 13:26:53 / cg"
    "Modified: / 1.4.1998 / 12:51:56 / 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"
!

markSelectorFrom:pos1 to:pos2

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

    self 
        markFrom:pos1 to:pos2 
        withEmphasis:selectorEmphasis color:selectorColor

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

    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:[
        self markGlobalIdentifierFrom: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: / 16.4.1998 / 18:58:10 / cg"
! !

!SyntaxHighlighter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.12 1998-04-16 16:58:53 cg Exp $'
! !