SyntaxHighlighter.st
author Claus Gittinger <cg@exept.de>
Wed, 01 Apr 1998 13:17:07 +0200
changeset 672 392927bad277
parent 669 5ef61aacc5d3
child 673 0c66b7cb1d2f
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.
"



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


! !

!SyntaxHighlighter class methodsFor:'highlighting'!

formatMethod:aString in:aClass
    "format a method in a given class."

    |parser tree text|

    aString isNil ifTrue:[^ nil].

    parser := self for:(ReadStream on:aString) in:aClass.
    parser ignoreErrors.
    parser ignoreWarnings.
    parser sourceText:(text := aString asText).

    tree := parser parseMethod.
    tree == #Error ifTrue:[
text emphasizeFrom:(parser sourceStream position) to:text size with:(#color->Color red).
    ].
    ^ text

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

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

    "Modified: / 31.3.1998 / 23:43:56 / 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.
    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.

    "Created: / 31.3.1998 / 15:12:55 / cg"
    "Modified: / 1.4.1998 / 12:57:48 / 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"
!

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

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

!SyntaxHighlighter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.5 1998-04-01 11:16:32 cg Exp $'
! !