ViewStyle.st
author Claus Gittinger <cg@exept.de>
Thu, 24 Jun 1999 14:47:57 +0200
changeset 2775 319d0a97eeac
parent 2347 c276691fdd72
child 3048 df43567e46cd
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      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.
"

ResourcePack subclass:#ViewStyle
	instanceVariableNames:'name is3D viewGrey'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

!ViewStyle class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      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
"
    instances of this class keep all view-style specific information.
    The current viewStyle is kept in Views-classvariable called 'StyleSheet'
    and is instantiated with 'View defaultStyle:aStyleSymbol', which reads
    a stylesheet from a file '<aStyleSymbol>.style' (usually in the 'resources'
    directory.

    [see also:]
	View
	( Configuration & Customization :html: custom/TOP.html#VIEWSTYLE )

    [author:]
	Claus Gittinger
"
! !

!ViewStyle class methodsFor:'instance creation'!

fromFile:aFileName
    "get the preferences definitions from a file"

    |prefs failed nm|

    prefs := self new.
    (aFileName endsWith:'.style') ifTrue:[
	nm := aFileName copyWithoutLast:6
    ] ifFalse:[
	nm := aFileName
    ].
    prefs at:#name put:nm. 

    failed := (prefs readFromFile:aFileName directory:'resources') isNil.
    prefs at:#fileReadFailed put:failed. 
    ^ prefs

    "
     ViewStyle fromFile:'motif.style'
     ViewStyle fromFile:'normal.style'
     ViewStyle fromFile:'iris.style'
    "
! !

!ViewStyle methodsFor:'accessing'!

at:aKey
    |sCls val|

    sCls := thisContext sender receiver.
    sCls isBehavior ifFalse:[sCls := sCls class].
    (sCls isSubclassOf:SimpleView) ifTrue:[
	val := self at:(sCls name , '.' , aKey) default:nil.
	val notNil ifTrue:[^ val].
    ].
    ^ self at:aKey default:nil

    "Modified: 10.9.1995 / 10:59:38 / claus"
!

at:aKey default:default
    "translate a string; if not present, return default.
     Here, two keys are tried, iff the key is of the form 'foo.bar',
     'fooBar' is also tried.
     This has been added for a smooth migration towards names with a form of
     'classname.itemKey' in the stylesheets."

    |v i k2|

    (self includesKey:aKey) ifTrue:[
	^ (super at:aKey ifAbsent:default) value
    ].
    (i := aKey indexOf:$.) ~~ 0 ifTrue:[
	k2 := (aKey copyTo:i-1) , (aKey copyFrom:i+1) asUppercaseFirst.
	(self includesKey:k2) ifTrue:[^ super at:k2 ifAbsent:default].
    ].
    ^ default value

    "Created: / 14.10.1997 / 00:21:15 / cg"
    "Modified: / 15.9.1998 / 21:47:13 / cg"
!

colorAt:aKey
    "retrieve a color resource - also aquire a device color
     to avoid repeated color allocations later"

    ^ self deviceResourceAt:aKey default:nil 
!

colorAt:aKey default:default
    "retrieve a color resource - also aquire a device color
     to avoid repeated color allocations later"

    ^ self deviceResourceAt:aKey default:default
!

deviceResourceAt:aKey default:default
    "retrieve a resource - also aquire a device version
     for the default display, to avoid repeated allocations later"

    |aResource deviceResource device|

    device := Display.
    aResource := self at:aKey default:default.
    aResource isNil ifTrue:[
	aResource := default
    ].
    aResource notNil ifTrue:[
	device notNil ifTrue:[
	    deviceResource := aResource onDevice:device.
	]
    ].
    deviceResource notNil ifTrue:[
	^ deviceResource
    ].
    ^ aResource

    "Modified: / 5.9.1998 / 20:25:19 / cg"
!

doesNotUnderstand:aMessage
    ^ self at:(aMessage selector) default:nil
!

fontAt:aKey
    "retrieve a font resource - also aquire a device font
     to avoid repeated font allocations later"

    ^ self deviceResourceAt:aKey default:nil 
!

fontAt:aKey default:default
    "retrieve a font resource - also aquire a device font
     to avoid repeated font allocations later"

    ^ self deviceResourceAt:aKey default:default
!

is3D
    is3D isNil ifTrue:[
	is3D := self at:#is3D default:false.
    ].
    ^ is3D
!

name
    name isNil ifTrue:[
	name := self at:#name default:'noname'.
    ].
    ^ name
!

viewGrey
    viewGrey isNil ifTrue:[
        viewGrey := self at:#viewGrey default:nil.
    ].
    ^ viewGrey
! !

!ViewStyle methodsFor:'error handling'!

nonexistingFileRead
    "here, a non-existing stylesheet is treated as an error"

    fileReadFailed := true.
    ^ self

    "Created: 6.9.1997 / 11:40:16 / cg"
! !

!ViewStyle class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/ViewStyle.st,v 1.17 1999-06-24 12:47:57 cg Exp $'
! !