UserPreferences.st
author Claus Gittinger <cg@exept.de>
Wed, 17 Jan 2001 18:38:02 +0100
changeset 5784 c6458c4f3c49
parent 5712 c723e5d4cd83
child 5790 83f92b49caae
permissions -rw-r--r--
oops - usage of new tools could not be turned off

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

IdentityDictionary subclass:#UserPreferences
	instanceVariableNames:''
	classVariableNames:'CurrentPreferences DefaultPreferences'
	poolDictionaries:''
	category:'System-Support'
!

!UserPreferences 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
"
    A Dictionary for user preference values.
    For non-existing keys, either a defaultValue (false),
    or the value from a defaultDictionary is returned.

    This will eventually keep track of ALL user preferences.
    (which are currently spread over the system).
    For now, only a few preferences are found here - but this
    will change over time.

    UserPreferences current at:#foo
"
! !

!UserPreferences class methodsFor:'initialization'!

initializeDefaultPreferences
    DefaultPreferences := self new.

    #(
	#useNewChangesBrowser           false
	#useNewInspector                false

	#autoFormatting                 false
	#syntaxColoring                 true
	#fullSelectorCheck              false

	#defaultSyntaxColor             (Color black)
	#defaultSyntaxEmphasis          normal

	#errorColor                     (Color red)

	#commentColor                   (Color 12.5 12.5 100)
	#commentEmphasis                normal

	#methodSelectorEmphasis         bold
	#selectorEmphasis               bold
	#unimplementedSelectorColor     (Color red)
	#unimplementedSelectorEmphasis  normal

"/ I prefer red-underwave over red identifier ...
"/        #badIdentifierColor             (Color red)

	#constantColor                  (Color 25 0 0)

	#showClockInLauncher            true
     ) pairWiseDo:[:k :v |
	DefaultPreferences at:k put:v decodeAsLiteralArray.
    ].

"/ I prefer red-underwave over red identifier ...
    DefaultPreferences at:#badIdentifierEmphasis put:(Array with:#underwave with:(#underlineColor->Color red)).

    "
     self initializeDefaultPreferences
    "

    "Modified: / 4.2.2000 / 20:06:53 / cg"
! !

!UserPreferences class methodsFor:'accessing'!

current
    CurrentPreferences isNil ifTrue:[
	CurrentPreferences := self new.
	CurrentPreferences declareAllFrom:(self default).
    ].
    ^ CurrentPreferences.

    "Created: / 31.3.1998 / 13:43:03 / cg"
!

default
    DefaultPreferences isNil ifTrue:[
	self initializeDefaultPreferences
    ].
    ^ DefaultPreferences.

    "
     DefaultPreferences := nil.
    "
!

reset
    "resets the CurrentPreferences to its default values"

    CurrentPreferences := nil
!

syntaxColorKeys
    "returns the keys of syntax color items"

    ^#(
	argumentIdentifierColor
	  argumentIdentifierEmphasis
	booleanConstantColor
	  booleanConstantEmphasis
	bracketColor
	  bracketEmphasis
	classVariableIdentifierColor
	  classVariableIdentifierEmphasis
	constantColor
	  constantEmphasis
	commentColor
	  commentEmphasis
	defaultSyntaxColor
	  defaultSyntaxEmphasis
	errorColor
	globalIdentifierColor
	  globalIdentifierEmphasis
	globalClassIdentifierColor
	  globalClassIdentifierEmphasis
	hereColor
	  hereEmphasis
	identifierColor
	  identifierEmphasis
	instVarIdentifierColor
	  instVarIdentifierEmphasis
	localIdentifierColor
	  localIdentifierEmphasis
	methodSelectorColor
	  methodSelectorEmphasis
	returnColor
	  returnEmphasis
	selectorColor
	  selectorEmphasis
	selfColor
	  selfEmphasis
	stringColor
	  stringEmphasis
	superColor
	  superEmphasis
	symbolColor
	  symbolEmphasis
	thisContextColor
	  thisContextEmphasis
	unknownIdentifierColor
	  unknownIdentifierEmphasis
	unimplementedSelectorColor
	  unimplementedSelectorEmphasis
    )

    "Modified: / 5.1.1980 / 00:48:09 / cg"
!

syntaxColorNames
    "returns the syntax colors for the settings in the launcher"

"/ warning, the strings below are presented to the user
"/ as the syntax-color boxes comboList - however, they are
"/ also used (without separators) as key into myself.
"/ Therefore, do not change the strings below.
"/ I know - this is bad coding ....

^#(
'Argument Identifier Color'
'Boolean Constant Color'
'Bracket Color'
'Class Variable Identifier Color'
'Constant Color'
'Comment Color'
'Global Identifier Color'
'Global Class Identifier Color'
'Here Color'
'Identifier Color'
'InstVar Identifier Color'
'Local Identifier Color'
'Method Selector Color'
'Return Color'
'Selector Color'
'Self Color'
'String Color'
'Super Color'
'Symbol Color'
'This Context Color'
'Unknown Identifier Color'
'Unimplemented Selector Color'
)

    "Modified: / 5.1.1980 / 00:48:09 / cg"
! !

!UserPreferences methodsFor:'accessing-pref''d tools'!

changesBrowserClass
    self useNewChangesBrowser ifTrue:[
	^ NewChangesBrowser
    ].
    ^ ChangesBrowser

    "Created: / 17.10.1998 / 14:37:46 / cg"
!

inspectorClass
    self useNewInspector ifTrue:[
	^ NewInspector::NewInspectorView
    ].
    ^ InspectorView
!

systemBrowserClass
    self useNewSystemBrowser ifTrue:[
	^ NewSystemBrowser
    ].
    ^ SystemBrowser
!

useNewChangesBrowser
    "using new or old change browser"

    ^ self at:#useNewChangesBrowser ifAbsentPut:false

    "Modified: / 13.10.1998 / 15:53:05 / cg"
!

useNewChangesBrowser:aBoolean
    "using new or old changeBrowser"

    aBoolean ifTrue:[
        NewChangesBrowser isNil ifTrue:[
            'UserPreferences [warning]: no NewChangesBrowser class in system' infoPrintCR.
            ^ self
        ].
        Autoload autoloadFailedSignal handle:[:ex |
            'UserPreferences [warning]: autoload of NewChangesBrowser failed' infoPrintCR.
        ] do:[
            NewChangesBrowser autoload.
        ]
    ].
    self at:#useNewChangesBrowser put:aBoolean

    "
     UserPreferences current useNewChangesBrowser
    "

    "Modified: / 13.10.1998 / 15:53:21 / cg"
!

useNewInspector
    "using new or old inspector"

    ^ self at:#useNewInspector ifAbsentPut:false

    "
     UserPreferences current useNewInspector
    "

    "Modified: / 17.10.1998 / 14:45:12 / cg"
!

useNewInspector:aBoolean
    "using new or old inspector"

    aBoolean ifTrue:[
        NewInspector::NewInspectorView isNil ifTrue:[
            'UserPreferences [warning]: no NewInspector class in system' infoPrintCR.
            ^ self
        ].
        Autoload autoloadFailedSignal handle:[:ex |
            'UserPreferences [warning]: autoload of NewInspector failed' infoPrintCR.
        ] do:[
            NewInspector::NewInspectorView autoload.
        ]
    ].
    self at:#useNewInspector put:aBoolean

    "
     UserPreferences current useNewInspector
    "
!

useNewSystemBrowser
    "using new or old system browser"

    ^ self at:#useNewSystemBrowser ifAbsentPut:false

    "Modified: / 13.10.1998 / 15:53:05 / cg"
!

useNewSystemBrowser:aBoolean
    "using new or old systemBrowser"

    aBoolean ifTrue:[
        NewSystemBrowser isNil ifTrue:[
            'UserPreferences [warning]: no NewSystemBrowser class in system' infoPrintCR.
            ^ self.
        ].
        Autoload autoloadFailedSignal handle:[:ex |
            'UserPreferences [warning]: autoload of NewSystemBrowser failed' infoPrintCR.
        ] do:[
            NewSystemBrowser autoload.
        ]
    ].
    self at:#useNewSystemBrowser put:aBoolean

    "
     UserPreferences current useNewSystemBrowser:true
    "

    "Modified: / 13.10.1998 / 15:53:21 / cg"
!

useNewVersionDiffBrowser
    "using new or old version diff viewer"

    ^ self at:#useNewVersionDiffBrowser ifAbsentPut:false

    "Modified: / 13.10.1998 / 15:53:05 / cg"
!

useNewVersionDiffBrowser:aBoolean
    "using new or old useNewVersionDiffBrowser"

    aBoolean ifTrue:[
        VersionDiffBrowser isNil ifTrue:[
            'UserPreferences [warning]: no VersionDiffBrowser class in system' infoPrintCR.
            ^ self
        ].
        Autoload autoloadFailedSignal handle:[:ex |
            'UserPreferences [warning]: autoload of VersionDiffBrowser failed' infoPrintCR.
        ] do:[
            VersionDiffBrowser autoload.
        ]
    ].
    self at:#useNewVersionDiffBrowser put:aBoolean

    "
     UserPreferences current useNewVersionDiffBrowser
    "

    "Modified: / 13.10.1998 / 15:53:21 / cg"
!

versionDiffViewerClass
    self useNewVersionDiffBrowser ifTrue:[
	^ VersionDiffBrowser
    ].
    ^ DiffTextView
! !

!UserPreferences methodsFor:'accessing-prefs'!

autoFormatting
    "return the flag which controls automatic formatting of code (in some browsers)
     Notice, the regular browser does not (yet) do automatic formating."

    ^ self at:#autoFormatting ifAbsentPut:false

    "
     UserPreferences current autoFormatting
    "

    "Created: / 4.2.2000 / 20:08:08 / cg"
    "Modified: / 5.2.2000 / 15:38:33 / cg"
!

autoFormatting:aBoolean
    "turn on/off automatic formatting of code (in some browsers);
     Notice, the regular browser does not (yet) do automatic formating."

    ^ self at:#autoFormatting put:aBoolean

    "
     UserPreferences current autoFormatting:true
     UserPreferences current autoFormatting:false
    "

    "Created: / 4.2.2000 / 20:08:26 / cg"
    "Modified: / 5.2.2000 / 15:38:20 / cg"
!

beepEnabled
    "return the flag which controls the beeper"

    ^ self at:#beepEnabled ifAbsentPut:true

    "
     UserPreferences current beepEnabled
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
    "Created: / 3.12.1999 / 17:09:49 / ps"
!

beepEnabled:aBoolean
    "set/clear the flag which controls the beeper"

    ^ self at:#beepEnabled put:aBoolean

    "
     UserPreferences current beepEnabled:false
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
    "Created: / 3.12.1999 / 17:10:27 / ps"
!

focusFollowsMouse
    "return the flag which controls if the keyboard focus should
     follow the mouse (as in X) - as opposed to click mode (as in MS-win).
     This only affects certain widgets (EditFields, EditTextViews and SelectionInListViews).
     The returned value has 3 states: true/false and nil, which means: as defined in styleSheet."

    ^ self at:#focusFollowsMouse ifAbsent:nil

    "
     UserPreferences current focusFollowsMouse
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

focusFollowsMouse:aBooleanOrNil
    "set/clear the flag which controls if the keyboard focus should
     follow the mouse (as in X) - as opposed to click mode (as in MS-win).
     This only affects certain widgets (EditFields, EditTextViews and SelectionInListViews).
     Allowed are: true/false and nil, which means: as defined in styleSheet."

    ^ self at:#focusFollowsMouse put:aBooleanOrNil

    "
     UserPreferences current focusFollowsMouse:true
     UserPreferences current focusFollowsMouse:false
     UserPreferences current focusFollowsMouse
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

functionKeySequences
    "return the collection of function-key macros.
     Thats a dictionary, which assigns code to F-keys"

    ^ self at:#functionKeySequences ifAbsentPut:[Dictionary new]

    "
     UserPreferences current functionKeySequences
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

opaqueVariablePanelResizing
    "return the flag which controls if variable panel resizing should be done
     animated (opaque)"

    ^ self at:#opaqueVariablePanelResizing ifAbsentPut:false

    "
     UserPreferences current opaqueVariablePanelResizing
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"

!

opaqueVariablePanelResizing:aBoolean
    "change the flag which controls if variable panel resizing should be done
     animated (opaque)"

    ^ self at:#opaqueVariablePanelResizing put:aBoolean

    "
     UserPreferences current opaqueVariablePanelResizing:true
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

showClockInLauncher
    "return the flag which controls if a clock is shown in the launcher"

    ^ self at:#showClockInLauncher ifAbsentPut:false

    "
     UserPreferences current showClockInLauncher
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

showClockInLauncher:aBooleanOrNil
    "set/clear the flag which controls if a clock is shown in the launcher"

    ^ self at:#showClockInLauncher put:aBooleanOrNil

    "
     UserPreferences current showClockInLauncher:false.
     NewLauncher open.   

     UserPreferences current showClockInLauncher:true.
     NewLauncher open.   
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

syntaxColoring
    "return the flag which controls syntax coloring (in the browsers)"

    ^ self at:#syntaxColoring ifAbsentPut:true

    "
     UserPreferences current syntaxColoring
    "

    "Modified: / 11.9.1998 / 00:09:59 / cg"
!

syntaxColoring:aBoolean
    "turn on/off syntaxColoring (in the browsers)."

    ^ self at:#syntaxColoring put:aBoolean

    "
     UserPreferences current syntaxColoring:true
     UserPreferences current syntaxColoring:false
    "

    "Created: / 31.3.1998 / 13:44:00 / cg"
    "Modified: / 1.4.1998 / 13:23:03 / cg"
! !

!UserPreferences methodsFor:'accessing-syntaxColoring prefs'!

argumentIdentifierColor
    "the color used for argument identifiers;
     If syntaxColoring is turned on."

    ^ self at:#argumentIdentifierColor ifAbsentPut:[self identifierColor]

    "Created: / 31.3.1998 / 15:08:20 / cg"
    "Modified: / 1.4.1998 / 13:19:58 / cg"
!

argumentIdentifierEmphasis
    "the emphasis used for argument identifiers;
     If syntaxColoring is turned on."

    ^ self at:#argumentIdentifierEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 15:16:40 / cg"
    "Modified: / 1.4.1998 / 13:19:55 / cg"
!

badIdentifierColor
    "the color used for illegal identifiers;
     If syntaxColoring is turned on."

    ^ self at:#badIdentifierColor ifAbsentPut:[self identifierColor]

!

badIdentifierEmphasis
    "the emphasis used for illegal identifiers;
     If syntaxColoring is turned on."

    ^ self at:#badIdentifierEmphasis ifAbsentPut:[UserPreferences default at:#badIdentifierEmphasis]

    "Modified: / 7.7.1999 / 00:30:00 / cg"
!

booleanConstantColor
    "the color used for boolean constants;
     If syntaxColoring is turned on."

    ^ self at:#booleanConstantColor ifAbsentPut:[self constantColor]

    "Created: / 31.3.1998 / 18:12:06 / cg"
    "Modified: / 1.4.1998 / 13:20:07 / cg"
!

booleanConstantEmphasis
    "the emphasis used for boolean constants;
     If syntaxColoring is turned on."

    ^ self at:#booleanConstantEmphasis ifAbsentPut:[self constantEmphasis]

    "Created: / 31.3.1998 / 18:12:46 / cg"
    "Modified: / 1.4.1998 / 13:26:01 / cg"
!

bracketColor
    "the color used for brackets;
     If syntaxColoring is turned on."

    ^ self at:#bracketColor ifAbsentPut:[self defaultSyntaxColor]

    "
     self current at:#bracketColor  put:Color red.
     self current at:#bracketEmphasis  put:#bold

     self current bracketColor 
     self current bracketEmphasis 
    "

    "Created: / 31.3.1998 / 19:11:38 / cg"
    "Modified: / 1.4.1998 / 13:22:33 / cg"
!

bracketEmphasis
    "the emphasis used for brackets;
     If syntaxColoring is turned on."

    ^ self at:#bracketEmphasis ifAbsentPut:[self defaultSyntaxEmphasis]

    "
     self current at:#bracketEmphasis  put:#bold
     self current bracketEmphasis 
    "

    "Created: / 31.3.1998 / 19:11:38 / cg"
    "Modified: / 1.4.1998 / 13:22:33 / cg"
!

classVariableIdentifierColor
    "the color used for classVar/classInstVar identifiers
     If syntaxColoring is turned on."

    ^ self at:#classVariableIdentifierColor ifAbsentPut:[self globalIdentifierColor]

    "Modified: / 1.4.1998 / 13:20:47 / cg"
    "Created: / 4.3.1999 / 12:50:31 / cg"
!

classVariableIdentifierEmphasis
    "the color used for classVar/classInstVar identifiers
     If syntaxColoring is turned on."

    ^ self at:#classVariableIdentifierEmphasis ifAbsentPut:[self globalIdentifierEmphasis]

    "Modified: / 1.4.1998 / 13:20:47 / cg"
    "Created: / 4.3.1999 / 12:50:31 / cg"
!

commentColor
    "the color used for comments;
     If syntaxColoring is turned on."

    ^ self at:#commentColor ifAbsentPut:[UserPreferences default at:#commentColor]

    "Created: / 31.3.1998 / 15:10:23 / cg"
    "Modified: / 11.9.1998 / 19:24:04 / cg"
!

commentEmphasis
    "the emphasis used for comments;
     If syntaxColoring is turned on."

    ^ self at:#commentEmphasis ifAbsentPut:[UserPreferences default at:#commentEmphasis]

    "Created: / 31.3.1998 / 15:09:59 / cg"
    "Modified: / 1.4.1998 / 13:25:53 / cg"
!

commentEmphasisAndColor
    ^ Text addEmphasis:(self commentEmphasis) to:(#color->self commentColor).


!

constantColor
    "the color used for constants;
     If syntaxColoring is turned on."

    ^ self at:#constantColor ifAbsentPut:[UserPreferences default at:#constantColor]

    "Created: / 31.3.1998 / 18:13:15 / cg"
    "Modified: / 1.4.1998 / 13:20:37 / cg"
!

constantEmphasis
    "the emphasis used for constants;
     If syntaxColoring is turned on."

    ^ self at:#constantEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 18:13:23 / cg"
    "Modified: / 1.4.1998 / 13:25:43 / cg"
!

defaultSyntaxColor
    "the color used for anything else;
     If syntaxColoring is turned on."

    ^ self at:#defaultSyntaxColor ifAbsentPut:[UserPreferences default at:#defaultSyntaxColor]

!

defaultSyntaxEmphasis
    "the emphasis used for anything else;
     If syntaxColoring is turned on."

    ^ self at:#defaultSyntaxEmphasis ifAbsentPut:[UserPreferences default at:#defaultSyntaxEmphasis]

!

doesNotUnderstand:aMessage
    |k def|

    k := aMessage selector.
    (self includesKey:k) ifTrue:[
	^ self at:k
    ].
    ((def := self class default) includesKey:k) ifTrue:[
	^ def at:k
    ].
    aMessage selector numArgs == 0 ifTrue:[
	^ self defaultValue
    ].
    ^ super doesNotUnderstand:aMessage
!

errorColor
    "the color used for illegal identifiers;
     If syntaxColoring is turned on."

    ^ self at:#errorColor ifAbsentPut:[UserPreferences default at:#errorColor]

!

fullSelectorCheck
    "with fullSelector check, selectors are searched immediately for
     being implemented in the system. This may not be useful on slow machines"

    ^ self at:#fullSelectorCheck ifAbsentPut:[UserPreferences default at:#fullSelectorCheck]

    "Created: / 31.3.1998 / 15:09:41 / cg"
    "Modified: / 1.4.1998 / 13:25:06 / cg"
!

globalClassIdentifierColor
    "the color used for global identifiers which are known to be classes;
     If syntaxColoring is turned on."

    ^ self at:#globalClassIdentifierColor ifAbsentPut:[self globalIdentifierColor]

    "Modified: / 1.4.1998 / 13:20:47 / cg"
    "Created: / 4.3.1999 / 12:50:31 / cg"
!

globalClassIdentifierEmphasis
    "the emphasis used for global variable identifiers which are known to be classes;
     If syntaxColoring is turned on."

    ^ self at:#globalClassIdentifierEmphasis ifAbsentPut:[self globalIdentifierEmphasis]

    "Modified: / 1.4.1998 / 13:25:31 / cg"
    "Created: / 4.3.1999 / 12:51:00 / cg"
!

globalIdentifierColor
    "the color used for global identifiers;
     If syntaxColoring is turned on."

    ^ self at:#globalIdentifierColor ifAbsentPut:[self identifierColor]

    "Created: / 31.3.1998 / 15:18:49 / cg"
    "Modified: / 1.4.1998 / 13:20:47 / cg"
!

globalIdentifierEmphasis
    "the emphasis used for global variable identifiers;
     If syntaxColoring is turned on."

    ^ self at:#globalIdentifierEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 15:18:29 / cg"
    "Modified: / 1.4.1998 / 13:25:31 / cg"
!

hereColor
    "the color used for the here pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#hereColor ifAbsentPut:[self selfColor]

    "Created: / 31.3.1998 / 17:38:09 / cg"
    "Modified: / 1.4.1998 / 13:20:57 / cg"
!

hereEmphasis
    "the emphasis used for the hre special variable;
     If syntaxColoring is turned on."

    ^ self at:#hereEmphasis ifAbsentPut:[self selfEmphasis]

    "Created: / 31.3.1998 / 17:35:13 / cg"
    "Modified: / 1.4.1998 / 13:25:17 / cg"
!

identifierColor
    "the color used for other identifiers;
     If syntaxColoring is turned on."

    ^ self at:#identifierColor ifAbsentPut:[self defaultSyntaxColor]

    "
     UserPreferences current at:#identifierColor put:Color green darkened darkened.
     UserPreferences current at:#identifierColor put:Color black.
    "

    "Created: / 31.3.1998 / 17:35:55 / cg"
    "Modified: / 2.4.1998 / 10:39:42 / cg"
!

identifierEmphasis
    "the emphasis used for other identifiers;
     If syntaxColoring is turned on."

    ^ self at:#identifierEmphasis ifAbsentPut:[self defaultSyntaxEmphasis]

    "Created: / 31.3.1998 / 15:09:41 / cg"
    "Modified: / 1.4.1998 / 13:25:06 / cg"
!

instVarIdentifierColor
    "the color used for instance variable identifiers;
     If syntaxColoring is turned on."

    ^ self at:#instVarIdentifierColor ifAbsentPut:[self identifierColor]

    "
     UserPreferences current at:#instVarIdentifierColor put:Color green darkened.
     UserPreferences current at:#instVarIdentifierColor put:Color black.
     UserPreferences current instVarIdentifierColor 
    "

    "Created: / 16.4.1998 / 18:31:29 / cg"
    "Modified: / 16.4.1998 / 18:57:06 / cg"
!

instVarIdentifierEmphasis
    "the emphais used for instance variable identifiers;
     If syntaxColoring is turned on."

    ^ self at:#instVarIdentifierEmphasis ifAbsentPut:[self identifierEmphasis]

    "Modified: / 1.4.1998 / 13:24:42 / cg"
    "Created: / 16.4.1998 / 18:40:05 / cg"
!

localIdentifierColor
    "the color used for local variable identifiers;
     If syntaxColoring is turned on."

    ^ self at:#localIdentifierColor ifAbsentPut:[self identifierColor]

    "
     UserPreferences current at:#localIdentifierColor put:Color green darkened.
     UserPreferences current at:#localIdentifierColor put:Color black.
    "

    "Created: / 31.3.1998 / 15:18:07 / cg"
    "Modified: / 2.4.1998 / 10:40:05 / cg"
!

localIdentifierEmphasis
    "the emphais used for local variable identifiers;
     If syntaxColoring is turned on."

    ^ self at:#localIdentifierEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 15:16:56 / cg"
    "Modified: / 1.4.1998 / 13:24:42 / cg"
!

methodSelectorColor
    "the color used for a methods selector pattern;
     If syntaxColoring is turned on."

    ^ self at:#methodSelectorColor ifAbsentPut:[self defaultSyntaxColor]

    "Created: / 31.3.1998 / 15:11:24 / cg"
    "Modified: / 1.4.1998 / 13:24:26 / cg"
!

methodSelectorEmphasis
    "the emphasis used for a methods selector pattern;
     If syntaxColoring is turned on."

    ^ self at:#methodSelectorEmphasis ifAbsentPut:[UserPreferences default at:#methodSelectorEmphasis]

    "Created: / 31.3.1998 / 15:11:16 / cg"
    "Modified: / 1.4.1998 / 13:24:20 / cg"
!

returnColor
    "the color used for the return expression;
     If syntaxColoring is turned on."

    ^ self at:#returnColor ifAbsentPut:[self defaultSyntaxColor]

    "Modified: / 5.1.1980 / 00:43:52 / cg"
!

returnEmphasis
    "the emphasis used for returns;
     If syntaxColoring is turned on."

    ^ self at:#returnEmphasis ifAbsentPut:[self defaultSyntaxEmphasis]

    "Created: / 5.1.1980 / 00:43:39 / cg"
!

selectorColor
    "the color used for message selectors;
     If syntaxColoring is turned on."

    ^ self at:#selectorColor ifAbsentPut:[self defaultSyntaxColor]

    "Created: / 31.3.1998 / 15:19:19 / cg"
    "Modified: / 1.4.1998 / 13:24:04 / cg"
!

selectorEmphasis
    "the emphasis used for message selectors;
     If syntaxColoring is turned on."

    ^ self at:#selectorEmphasis ifAbsentPut:[UserPreferences default at:#selectorEmphasis]

    "Created: / 31.3.1998 / 15:19:09 / cg"
    "Modified: / 1.4.1998 / 13:23:59 / cg"
!

selfColor
    "the color used for the self pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#selfColor ifAbsentPut:[self identifierColor]

    "Created: / 31.3.1998 / 17:35:45 / cg"
    "Modified: / 1.4.1998 / 13:21:07 / cg"
!

selfEmphasis
    "the emphasis used for the self pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#selfEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 17:34:57 / cg"
    "Modified: / 1.4.1998 / 13:21:51 / cg"
!

stringColor
    "the color used for string constants;
     If syntaxColoring is turned on."

    ^ self at:#stringColor ifAbsentPut:[self constantColor]

    "Created: / 31.3.1998 / 15:19:50 / cg"
    "Modified: / 1.4.1998 / 13:22:06 / cg"
!

stringEmphasis
    "the emphasis used for string constants;
     If syntaxColoring is turned on."

    ^ self at:#stringEmphasis ifAbsentPut:[self constantEmphasis]

    "Created: / 31.3.1998 / 15:19:09 / cg"
    "Modified: / 1.4.1998 / 13:22:00 / cg"
!

superColor
    "the color used for the super pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#superColor ifAbsentPut:[self selfColor]

    "Created: / 31.3.1998 / 17:37:56 / cg"
    "Modified: / 1.4.1998 / 13:21:15 / cg"
!

superEmphasis
    "the emphasis used for the super pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#superEmphasis ifAbsentPut:[self selfEmphasis]

    "Created: / 31.3.1998 / 17:35:08 / cg"
    "Modified: / 1.4.1998 / 13:21:41 / cg"
!

symbolColor
    "the color used for symbol constants;
     If syntaxColoring is turned on."

    ^ self at:#symbolColor ifAbsentPut:[self constantColor]

    "Created: / 1.4.1998 / 12:57:35 / cg"
    "Modified: / 1.4.1998 / 13:22:16 / cg"
!

symbolEmphasis
    "the emphasis used for symbol constants;
     If syntaxColoring is turned on."

    ^ self at:#symbolEmphasis ifAbsentPut:[self constantEmphasis]

    "Created: / 1.4.1998 / 12:57:43 / cg"
    "Modified: / 1.4.1998 / 13:23:43 / cg"
!

thisContextColor
    "the color used for the thisContext pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#thisContextColor ifAbsentPut:[self identifierColor]

    "Created: / 31.3.1998 / 17:37:49 / cg"
    "Modified: / 1.4.1998 / 13:21:24 / cg"
!

thisContextEmphasis
    "the emphasis used for the thisContext pseudoVariable;
     If syntaxColoring is turned on."

    ^ self at:#thisContextEmphasis ifAbsentPut:[self identifierEmphasis]

    "Created: / 31.3.1998 / 17:35:27 / cg"
    "Modified: / 1.4.1998 / 13:21:30 / cg"
!

unimplementedSelectorColor
    "the color used for bad message selectors;
     If syntaxColoring is turned on."

    ^ self at:#unimplementedSelectorColor ifAbsentPut:[UserPreferences default at:#unimplementedSelectorColor]
!

unimplementedSelectorEmphasis
    "the emphasis used for bad message selectors;
     If syntaxColoring is turned on."

    ^ self at:#unimplementedSelectorEmphasis ifAbsentPut:[UserPreferences default at:#unimplementedSelectorEmphasis]

    "Created: / 31.3.1998 / 15:19:09 / cg"
    "Modified: / 1.4.1998 / 13:23:59 / cg"
!

unknownIdentifierColor
    "the color used for unknown identifiers;
     If syntaxColoring is turned on."

    ^ self at:#unknownIdentifierColor ifAbsentPut:[self badIdentifierColor]

    "
     self current at:#unknownIdentifierColor  put:Color red.
     self current at:#unknownIdentifierEmphasis  put:#bold

     self current unknownIdentifierColor
     self current unknownIdentifierEmphasis
    "

    "Created: / 31.3.1998 / 19:11:38 / cg"
    "Modified: / 1.4.1998 / 13:22:33 / cg"
!

unknownIdentifierEmphasis
    "the emphasis used for unknown identifiers;
     If syntaxColoring is turned on."

    ^ self at:#unknownIdentifierEmphasis ifAbsentPut:[self badIdentifierEmphasis]

    "Created: / 31.3.1998 / 19:11:55 / cg"
    "Modified: / 1.4.1998 / 13:22:45 / cg"
! !

!UserPreferences methodsFor:'default settings'!

resetSyntaxColors
    "resets the colors in the CurrentPreferences to their default values"

    self class syntaxColorKeys do:[:k | self removeKey:k ifAbsent:nil].


!

resetSyntaxColorsAllBlackExceptBadIDs
    "resets the colors in the CurrentPreferences to no-color mode,
     except for bad identifiers, which are underwaved."

    self class syntaxColorKeys do:[:k | self removeKey:k ifAbsent:nil].
    self at:#badIdentifierEmphasis put:(Array with:#underwave with:(#underlineColor->Color red)).
    self at:#errorColor            put:Color black.
    self at:#commentColor          put:Color black.
    self at:#constantColor         put:Color black.
    self at:#methodSelectorEmphasis put:#normal.
    self at:#selectorEmphasis       put:#normal.

!

resetSyntaxColorsGreenComments
    "resets the colors in the CurrentPreferences to alternative default values
     (with green comments)"

    self class syntaxColorKeys do:[:k | self removeKey:k ifAbsent:nil].
    self at:#commentColor put:(Color green darkened).

! !

!UserPreferences methodsFor:'default value'!

defaultValue
    "the defaultValue for non-existing keys"

    ^ false
!

errorKeyNotFound:aKey
    "for any non-existing key, false is returned"

    ^ self defaultValue
! !

!UserPreferences class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.61 2001-01-17 17:38:02 cg Exp $'
! !