ResourcePack.st
author claus
Tue, 16 May 1995 19:17:11 +0200
changeset 144 cf645a1ebbb3
parent 135 cf8e46015072
child 145 ac7088b0aee5
permissions -rw-r--r--
.

"
 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'
	 classVariableNames:'Packs'
	 poolDictionaries:''
	 category:'Interface-Support'
!

ResourcePack comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/ResourcePack.st,v 1.15 1995-05-16 17:13:52 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview/ResourcePack.st,v 1.15 1995-05-16 17:13:52 claus Exp $
"
!

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

!ResourcePack class methodsFor:'initialization'!

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

    "ResourcePack initialize"
!

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

    Packs := nil.
    self initialize

    "ResourcePack flushCachedResourcePacks"
! !

!ResourcePack class methodsFor:'private'!

addToCache:aPack
    |idx|

    idx := Packs identityIndexOf:nil.
    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|

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

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

	aPack := Packs at:idx.
	aPack notNil 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 class methodsFor:'instance creation'!

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
!

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

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

!ResourcePack methodsFor:'merging'!

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

!ResourcePack methodsFor:'accessing'!

dependents:aCollection
    dependents := aCollection
!

dependents
    ^ dependents
!

packsClassName
    ^ packsClassName
!

packsClassName:aString
    packsClassName := aString
!

at:aKey
    "translate a string"

    ^ self at:aKey ifAbsent:aKey
!

at:aKey default:default
    "translate a string"

    ^ self at:aKey ifAbsent:default
!

name:aKey
    "translate a string"

    ^ self at:aKey ifAbsent:aKey
!

name:aKey default:default
    "translate a string"

    ^ self at:aKey ifAbsent:default
!

array:anArray
    "translate a collection of strings"

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

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 withArgs:argArray
    "translate and expand args"

    |template|

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

!ResourcePack methodsFor:'file reading'!

readFromFile:fileName directory:dirName
    |inStream|

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

processLine:aLine
    |lineString name stream l rest macroName value|

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

"/                          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).
	    ]
	].
	self at:name put:value.
    ]
!

readFromResourceStream:inStream in:dirName
    |lineString rest value ifLevel skipping l name first str macroName|

    ifLevel := 0.
    skipping := false.
    [inStream atEnd] whileFalse:[
	lineString := inStream nextLine.
	(lineString notNil and:[lineString isEmpty not]) ifTrue:[
	    first := lineString at:1.
	    first == $; 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:[
				(lineString startsWith:'include') ifTrue:[
				    rest := lineString copyFrom:8.
				    value := Compiler evaluate:rest compile:false.
				    self readFromFile:value directory:dirName
				]
			    ]
			]
		    ].
		] ifFalse:[
		    skipping ifFalse:[
			lineString := lineString withoutSeparators.
			name := nil.
			(lineString at:1) == $' ifTrue:[
			    str := ReadStream on:lineString.
			    name := String readFrom:str.
			    l := str position.

"/                          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.
			    (rest startsWith:'=') ifTrue:[
				rest := rest copyFrom:2.
				str := ReadStream on:rest.
				macroName := str nextAlphaNumericWord.
				rest := str 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).
				]
			    ].
			    self at:name put:value.
			]
		    ]
		]
	    ]
	]
    ].
! !

ResourcePack initialize!