ResourcePack.st
author Claus Gittinger <cg@exept.de>
Fri, 18 Oct 1996 14:36:43 +0200
changeset 1078 f7b6f15899ab
parent 1042 ddb262303ccd
child 1173 86a212598655
permissions -rw-r--r--
changed WeakArray to set emptied slots to zero instead of nil. This allows easier finding of reclaimed slots (and is also ST-80 compatible). Change needs in-depth testing ...

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

Dictionary subclass:#ResourcePack
	instanceVariableNames:'elements dependents packsClassName fileReadFailed'
	classVariableNames:'Packs'
	poolDictionaries:''
	category:'Interface-Support'
!

!ResourcePack  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
"
    to allow easy customization of smalltalk code (i.e. internationalization)
    (replaces the obsolete Resource class).
    ResourcePacks are class specific, meaning that every subclass of View
    and ApplicationModel has an instance of ResourcePack (called resources) 
    which is created when the first instance of the view is created.

    The resourcePack consists of a mapping from strings to values, which are
    then used in labels, buttons, menus etc.
    The resourcePack initializes itself from a file found in 'resources/<className>.rs',
    where 'className' is built by the usual abbreviation mechanism (see abbrev-files).
    Conditional mappings are possible, by including lines as:
        #if <expression>
        #endif
    in the resourcefile. Example:
    file 'foo.rs':
        #if Language == #german
        'abort' 'Abbruch'
        #endif
        #if Language == #french
        'abort' 'canceller'
        #endif

    the corresponding resource-strings are accessed (from methods within the class)
    using:

        resource string:'abort'

    returning the mapped string (i.e. 'Abbruch' if the global Language is set
    to #german)..

    If no corresponding entry is found in the resources, the key is returned.
    Translations can also include arguments, such as:
        resources string:'really delete %1' with:fileName

    This scheme has the advantage, that you can write your programs using your
    native language strings. Later, when new languages are to be supported,
    simply create a resource file for the class and add translations for
    all those strings. (find the keys by looking at users of resource or senders
    of 'string:*'.

    More languages can be added later without any change in the code,
    recompilation or the like. 
    Even by people without access to the source code i.e. which only have the 
    applications binary.

    Also, unsupported languages' strings are simply left unchanged - if you
    write your application in (say) english, and only plan to use it in english,
    no additional work is required (i.e you dont need a resource file then).
    Strings for unknown languages will come in english 
    (which is better than nothing or empty button labels ;-)

    Summary:
        in subclasses of View and ApplicationModel,
        instead of writing:

                ...
                b := Button label:'press me'
                ...

        always write:

                ...
                b := Button label:(resources string:'press me')
                ...

        if your class is not a subclass of one of the above, AND you need
        resource translations, you wont inherit the resources variable
        (which is automatically initialized).
        In this case, you have to ask the ResourcePack class explicitely for
        a corresponding package:

                ResourcePack for:aClassName

        as an example, see how the Date class gets the national names of
        week & monthnames.

    [author:]
        Claus Gittinger
"
!

examples
"
    normally, resources are found in files named after their classes sourcefile
    For example, the FileBrowsers resources are found in 'FBrowser.rs'.
    For the examples below, we process resources from a constant string;
        this is NOT representative.
                                                                        [exBegin]
        |stream res|

        stream := ReadStream on:'
foo  ''the translation for foo''
#if Language == #german
bar  ''die deutsche uebersetzung von bar''
baz  ''baz hat den Wert %1''
#endif
#if Language == #french
bar  ''bar en francaise''
baz  ''%1, c''''est baz''
#endif

'.

        res := ResourcePack new readFromResourceStream:stream in:nil.

        Transcript showCR:'baz is translated to: ' , (res string:'baz' with:'1234').
        Transcript showCR:'bar is translated to: ' , (res string:'bar').
        Transcript showCR:'foo is translated to: ' , (res string:'foo').
        Transcript showCR:'fooBar is translated to: ' , (res string:'fooBar').
                                                                        [exEnd]
    set the Language to french:
                                                                        [exBegin]
        Language := #french
                                                                        [exEnd]
    and repeat the above.
    back to english:
                                                                        [exBegin]
        Language := #english 
                                                                        [exEnd]
    back to german:
                                                                        [exBegin]
        Language := #german 
                                                                        [exEnd]
"
! !

!ResourcePack  class methodsFor:'initialization'!

flushCachedResourcePacks
    "forget all cached resources - needed after a style change"

    Packs := nil.
    self initialize

    "ResourcePack flushCachedResourcePacks"
!

initialize
    Packs isNil ifTrue:[
	Packs := WeakArray new:30
    ].

    "ResourcePack initialize"
! !

!ResourcePack  class methodsFor:'instance creation'!

for:aClass
    "get the full resource definitions for aClass (i.e. with super packs).
     Also leave the resulting pack in the cache for faster access next time."

    |nm pack superPack|

    nm := aClass name.
    pack := self searchCacheFor:nm.
    pack notNil ifTrue:[^ pack].

    pack := self fromFile:(Smalltalk fileNameForClass:nm) , '.rs'.
    aClass == Object ifFalse:[
	superPack := self for:(aClass superclass).
	pack := pack merge:superPack
    ].
    pack packsClassName:nm.
    self addToCache:pack.
    ^ pack

    "
     ResourcePack for:TextView
     ResourcePack for:CodeView
     ResourcePack for:Workspace 
     Workspace classResources
    "
!

fromFile:aFileName
    "get the resource definitions from a file in the default directory.
     Uncached low-level entry."

    ^ self fromFile:aFileName directory:'resources'

    "
     ResourcePack fromFile:'SBrowser.rs'
     ResourcePack fromFile:'FBrowser.rs'
     ResourcePack fromFile:'Smalltalk.rs'
    "
!

fromFile:aFileName directory:dirName
    "get the resource definitions from a file in a directory.
     Uncached low-level entry."

    |newPack|

    newPack := self new.
    newPack readFromFile:aFileName directory:dirName.
    ^ newPack
! !

!ResourcePack  class methodsFor:'private'!

addToCache:aPack
    |idx|

    idx := Packs identityIndexOf:nil.
    idx == 0 ifTrue:[
	idx := Packs identityIndexOf:0
    ].
    idx == 0 ifTrue:[
	"
	 throw away oldest
	"
	idx := Packs size.
	Packs replaceFrom:1 to:idx-1 with:Packs startingAt:2.
    ].
    Packs at:idx put:aPack
!

searchCacheFor:aClassname
    |sz "{ Class: SmallInteger }" |

    Packs isNil ifTrue:[
	self initialize.
	^ nil
    ].

    sz := Packs size.
    1 to:sz do:[:idx |
	|aPack|

	aPack := Packs at:idx.
	(aPack notNil 
	and:[aPack ~~ 0]) ifTrue:[
	    aClassname = aPack packsClassName ifTrue:[
		"
		 bring to end for LRU
		"
		Packs replaceFrom:idx to:sz-1 with:Packs startingAt:idx+1.
		Packs at:sz put:aPack.
		^ aPack
	    ]
	]
    ].
    ^ nil

    "
     ResourcePack searchCacheFor:'TextView' 
    "
! !

!ResourcePack methodsFor:'accessing'!

array:anArray
    "translate a collection of strings"

    ^ anArray collect:[:r | self at:r default:r]
!

at:aKey
    "translate a string"

    ^ self at:aKey ifAbsent:aKey
!

at:aKey default:default
    "translate a string"

    ^ self at:aKey ifAbsent:default
!

dependents
    ^ dependents
!

dependents:aCollection
    dependents := aCollection
!

name:aKey
    "translate a string"

    ^ self at:aKey ifAbsent:aKey
!

name:aKey default:default
    "translate a string"

    ^ self at:aKey ifAbsent:default
!

packsClassName
    ^ packsClassName
!

packsClassName:aString
    packsClassName := aString
!

string:s
    "translate a string"

    ^ self at:s ifAbsent:s
!

string:s with:arg
    "translate and expand arg"

    ^ self string:s withArgs:(Array with:arg)
!

string:s with:arg1 with:arg2
    "translate and expand args"

    ^ self string:s withArgs:(Array with:arg1 with:arg2)
!

string:s with:arg1 with:arg2 with:arg3
    "translate and expand args"

    ^ self string:s withArgs:(Array with:arg1 with:arg2 with:arg3)

    "Created: 9.12.1995 / 19:08:50 / cg"
!

string:s with:arg1 with:arg2 with:arg3 with:arg4
    "translate and expand args"

    ^ self string:s withArgs:(Array with:arg1 with:arg2 with:arg3 with:arg4)

    "Created: 9.9.1996 / 18:52:14 / cg"
!

string:s withArgs:argArray
    "translate and expand args"

    |template|

    template := self at:s ifAbsent:[s].
    ^ template expandPlaceholdersWith:argArray
! !

!ResourcePack methodsFor:'file reading'!

fileReadFailed
    ^ fileReadFailed ~~ false

    "Created: 14.5.1996 / 10:19:26 / cg"
    "Modified: 14.5.1996 / 12:00:59 / cg"
!

processLine:aLine encoding:encoding
    "process a single valid line (i.e. #ifdef & #include has already been processed)"

    |lineString name stream l rest macroName value|

    lineString := aLine withoutSeparators.
    name := nil.
    (lineString at:1) == $' ifTrue:[
        stream := ReadStream on:lineString.
        name := String 
                    readFrom:stream 
                    onError:[('RESOURCEPACK: invalid line <',lineString,'>') errorPrintNL. nil].
"/ OLD: l := stream position
        l := stream position + 1.

"/                          l := lineString indexOf:$' startingAt:2.
"/                          l ~~ 0 ifTrue:[
"/                              name := (lineString copyFrom:2 to:l-1).
"/                              l := l + 1
"/                          ]
    ] ifFalse:[
        l := lineString indexOfSeparatorStartingAt:1.
        l ~~ 0 ifTrue:[
            name := lineString copyFrom:1 to:l-1.
        ]
    ].
    name notNil ifTrue:[
        rest := (lineString copyFrom:l) withoutSeparators.
        "
         skip <type> if present
        "
        (rest startsWith:$<) ifTrue:[
             l := lineString indexOf:$> startingAt:l.
             rest := (lineString copyFrom:l+1) withoutSeparators.
        ].
        (rest startsWith:$=) ifTrue:[
            rest := rest copyFrom:2.
            stream := ReadStream on:rest.
            macroName := stream nextAlphaNumericWord.
            rest := stream upToEnd.
            value := self at:macroName.
            value := Compiler evaluate:('self ' , rest)
                              receiver:value
                              notifying:nil
                              compile:false.
        ] ifFalse:[
            value := Compiler evaluate:rest compile:false.
            (value == #Error) ifTrue:[
                Transcript show:('error in resource:' , name).
            ] ifFalse:[
                encoding notNil ifTrue:[
                    value isString ifTrue:[
                        value := value decodeFrom:encoding
                    ]
                ]
            ]
        ].
        self at:name put:value.
    ]

    "Created: 26.2.1996 / 19:17:07 / cg"
    "Modified: 26.2.1996 / 19:18:07 / cg"
!

readFromFile:fileName directory:dirName
    "read definitions from a file in a directory"

    |inStream ok|

    fileReadFailed := false.
    dirName = 'resources' ifTrue:[
        inStream := Smalltalk resourceFileStreamFor:fileName
    ] ifFalse:[
        inStream := Smalltalk systemFileStreamFor:(dirName , '/' , fileName).
    ].
    inStream isNil ifTrue:[
        "
         an empty pack
        "
        ^ nil
    ].
    ok := self readFromResourceStream:inStream in:dirName.
    inStream close.

    ok ifFalse:[
        fileReadFailed := true.

        ('RESOURCEPACK: ''' , fileName , ''' contains error(s) - data may be incomplete.') errorPrintNL.
    ].

    "Modified: 14.5.1996 / 11:57:22 / cg"
!

readFromResourceStream:inStream in:dirName
    "read definitions from a stream. THe dirName argument is required to
     specify where #include files are searched for.
     Return true, if the style sheet could be read without errors, false otherwise."

    |lineString l lNo rest value ifLevel skipping first ok encoding|

    encoding := nil.

    ok := true.
    ifLevel := 0.
    skipping := false.
    lNo := 0.
    [inStream atEnd] whileFalse:[
        lineString := inStream nextLine. lNo := lNo + 1.
        [lineString notNil and:[lineString endsWith:$\]] whileTrue:[
            lineString := lineString copyWithoutLast:1.
            l := inStream nextLine. lNo := lNo + 1.
            l notNil ifTrue:[
                lineString := lineString , l.
            ].
        ].

        (lineString notNil and:[lineString isEmpty not]) ifTrue:[
            first := lineString at:1.
            "/
            "/ for your convenience: treat ; AND "/ as comment-line
            "/
            ((first == $;) or:[lineString startsWith:'"/']) ifFalse:[
                first == $# ifTrue:[
                    lineString := (lineString copyFrom:2) withoutSpaces.

                    (lineString startsWith:'if') ifTrue:[
                        skipping ifFalse:[
                            rest := lineString copyFrom:3.
                            value := Compiler evaluate:rest compile:false.
                            (value == #Error) ifTrue:[
                                Transcript show:('error in resource:' , lineString).
                            ].
                            (value == false) ifTrue:[
                                skipping := true
                            ]
                        ].
                        ifLevel := ifLevel + 1
                    ] ifFalse:[
                        (lineString startsWith:'endif') ifTrue:[
                            ifLevel := ifLevel - 1.
                            ifLevel == 0 ifTrue:[
                                skipping := false
                            ]
                        ] ifFalse:[
                            (lineString startsWith:'else') ifTrue:[
                                skipping := skipping not
                            ] ifFalse:[
                                skipping ifFalse:[
                                    (lineString startsWith:'include') ifTrue:[
                                        rest := lineString copyFrom:8.
                                        value := Compiler evaluate:rest compile:false.
                                        self readFromFile:value directory:dirName
                                    ] ifFalse:[
                                        (lineString startsWith:'encoding') ifTrue:[
                                            rest := lineString copyFrom:9.
                                            encoding := Compiler evaluate:rest compile:false.
                                        ]
                                    ]
                                ]
                            ]
                        ]
                    ].
                ] ifFalse:[
                    skipping ifFalse:[
                        ErrorSignal handle:[:ex |
                            ('RESOURCEPACK: error: ''' , ex errorString , '''') errorPrintNL.
                            ('RESOURCEPACK: line ' , lNo printString , ': ''' , lineString , '''') errorPrintNL.
                            ok := false.
                        ] do:[
                            self processLine:lineString encoding:encoding
                        ]
                    ]
                ]
            ]
        ]
    ].
    ^ ok

    "Modified: 31.8.1995 / 02:33:45 / claus"
    "Modified: 26.2.1996 / 19:22:36 / cg"
! !

!ResourcePack methodsFor:'merging'!

merge:anotherPack
    anotherPack keysAndValuesDo:[:key :value |
	(self includesKey:key) ifFalse:[
	    self at:key put:value
	]
    ]
! !

!ResourcePack  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/ResourcePack.st,v 1.37 1996-10-18 12:36:43 cg Exp $'
! !
ResourcePack initialize!