ResourcePack.st
changeset 3762 968432b99c48
parent 3701 ccb98616318b
child 3769 4b0f188d7f5c
--- a/ResourcePack.st	Mon Nov 04 21:57:21 2002 +0100
+++ b/ResourcePack.st	Mon Nov 11 10:27:08 2002 +0100
@@ -50,31 +50,31 @@
     where 'className' is built by the usual abbreviation mechanism (see abbrev-files).
 
     Conditional mappings are possible, by including lines as:
-        #if <expression>
-        #endif
+	#if <expression>
+	#endif
     in the resourcefile. Example:
     file 'foo.rs':
-        #if Language == #de
-        'abort' 'Abbruch'
-        #endif
-        #if Language == #fr
-        'abort' 'canceller'
-        #endif
+	#if Language == #de
+	'abort' 'Abbruch'
+	#endif
+	#if Language == #fr
+	'abort' 'canceller'
+	#endif
 
     the corresponding resource-strings are accessed (from methods within the class)
     using:
-        resources string:'abort'
+	resources string:'abort'
 
     returning the mapped string (i.e. 'Abbruch' if the global Language is set
     to #de)..
 
     If no corresponding entry is found in the resources, the key is returned;
     alternatively, use:
-        resources string:'foo' default:'bar'
+	resources string:'foo' default:'bar'
     which returns 'bar', if no resource definition for 'foo' is found.
 
     Translations can also include arguments, such as:
-        resources string:'really delete %1' with:fileName
+	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,
@@ -98,32 +98,32 @@
     (which is better than nothing or empty button labels ;-)
 
     Summary:
-        in subclasses of View and ApplicationModel,
-        instead of writing:
+	in subclasses of View and ApplicationModel,
+	instead of writing:
 
-                ...
-                b := Button label:'press me'
-                ...
+		...
+		b := Button label:'press me'
+		...
 
-        always write:
+	always write:
 
-                ...
-                b := Button label:(resources string:'press me')
-                ...
+		...
+		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:
+	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
+		ResourcePack for:aClassName
 
-        as an example, see how the Date class gets the national names of
-        week & monthnames.
+	as an example, see how the Date class gets the national names of
+	week & monthnames.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
@@ -132,11 +132,11 @@
     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|
+	this is NOT representative.
+									[exBegin]
+	|stream res|
 
-        stream := ReadStream on:'
+	stream := ReadStream on:'
 foo  ''the translation for foo''
 #if Language == #de
 bar  ''die deutsche uebersetzung von bar''
@@ -149,26 +149,26 @@
 
 '.
 
-        res := ResourcePack new readFromResourceStream:stream in:nil.
+	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]
+	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 := #fr
-                                                                        [exEnd]
+									[exBegin]
+	Language := #fr
+									[exEnd]
     and repeat the above.
     back to english:
-                                                                        [exBegin]
-        Language := #en 
-                                                                        [exEnd]
+									[exBegin]
+	Language := #en 
+									[exEnd]
     back to german:
-                                                                        [exBegin]
-        Language := #de 
-                                                                        [exEnd]
+									[exBegin]
+	Language := #de 
+									[exEnd]
 "
 ! !
 
@@ -212,12 +212,12 @@
     and:[(prjDir := prjDir asFilename) exists
     and:[(prjDir := prjDir construct:'resources') exists
     and:[(prjDir construct:baseName) exists]]]) ifTrue:[
-        pack := self fromFile:baseName directory:prjDir pathName.
+	pack := self fromFile:baseName directory:prjDir pathName.
     ] ifFalse:[
-        pack := self fromFile:baseName.
+	pack := self fromFile:baseName.
     ].
     aClass == Object ifFalse:[
-        pack superPack:(self for:(aClass superclass)).
+	pack superPack:(self for:(aClass superclass)).
     ].
     pack packsClassName:nm.
     self addToCache:pack.
@@ -344,27 +344,27 @@
     |val alternativeKey|
 
     aKey notNil ifTrue:[
-        val := super at:aKey ifAbsent:nil.
-        val notNil ifTrue:[^ val].
+	val := super at:aKey ifAbsent:nil.
+	val notNil ifTrue:[^ val].
 
-        "/ try with case-first swapped...
-        (aKey isString 
-        and:[aKey size > 0
-        and:[aKey first isLetter]]) ifTrue:[
-            alternativeKey := aKey first isUppercase 
-                                ifTrue:[aKey asLowercaseFirst]
-                                ifFalse:[aKey asUppercaseFirst].
-            val := super at:alternativeKey ifAbsent:nil.
-            val notNil ifTrue:[
-                aKey first isUppercase 
-                    ifTrue:[^val asUppercaseFirst].
-                ^ val asLowercaseFirst.                
-            ].
-        ].
+	"/ try with case-first swapped...
+	(aKey isString 
+	and:[aKey size > 0
+	and:[aKey first isLetter]]) ifTrue:[
+	    alternativeKey := aKey first isUppercase 
+				ifTrue:[aKey asLowercaseFirst]
+				ifFalse:[aKey asUppercaseFirst].
+	    val := super at:alternativeKey ifAbsent:nil.
+	    val notNil ifTrue:[
+		aKey first isUppercase 
+		    ifTrue:[^val asUppercaseFirst].
+		^ val asLowercaseFirst.                
+	    ].
+	].
 
-        superPack notNil ifTrue:[
-            ^ superPack at:aKey ifAbsent:defaultValue.
-        ].
+	superPack notNil ifTrue:[
+	    ^ superPack at:aKey ifAbsent:defaultValue.
+	].
     ].
     ^ defaultValue value
 
@@ -385,7 +385,7 @@
 
     "
      NewLauncher classResources
-        string:'LICENCEFILE' 
+	string:'LICENCEFILE' 
     "
 !
 
@@ -396,7 +396,7 @@
 
     "
      NewLauncher classResources
-        string:'fooBar' default:'Hello world'  
+	string:'fooBar' default:'Hello world'  
     "
 
 !
@@ -408,7 +408,7 @@
 
     "
      NewLauncher classResources
-        string:'%1 fooBar' default:'Hello %1' with:'foo' 
+	string:'%1 fooBar' default:'Hello %1' with:'foo' 
     "
 
 !
@@ -543,17 +543,17 @@
     lineString := aLine withoutSeparators.
     name := nil.
     (lineString at:1) == $' ifTrue:[
-        stream := ReadStream on:lineString.
-        stream signalAtEnd:false.
-        name := String 
-                    readFrom:stream 
-                    onError:[('ResourcePack [warning]: invalid line <'
-                             ,lineString
-                             ,'> in file:'
-                             , fileName
-                            ) errorPrintCR. nil].
+	stream := ReadStream on:lineString.
+	stream signalAtEnd:false.
+	name := String 
+		    readFrom:stream 
+		    onError:[('ResourcePack [warning]: invalid line <'
+			     ,lineString
+			     ,'> in file:'
+			     , fileName
+			    ) errorPrintCR. nil].
 "/ OLD: l := stream position
-        l := stream position + 1.
+	l := stream position + 1.
 
 "/                          l := lineString indexOf:$' startingAt:2.
 "/                          l ~~ 0 ifTrue:[
@@ -561,79 +561,79 @@
 "/                              l := l + 1
 "/                          ]
     ] ifFalse:[
-        l := lineString indexOfSeparatorStartingAt:1.
-        l ~~ 0 ifTrue:[
-            name := lineString copyFrom:1 to:l-1.
-        ]
+	l := lineString indexOfSeparatorStartingAt:1.
+	l ~~ 0 ifTrue:[
+	    name := lineString copyFrom:1 to:l-1.
+	]
     ].
     name notNil ifTrue:[
-        hasError := false.
+	hasError := false.
 
-        rest := (lineString copyFrom:l) withoutSeparators.
-        "
-         skip <type> if present
-        "
-        (rest startsWith:$<) ifTrue:[
-             l := lineString indexOf:$> startingAt:l.
-             rest := (lineString copyFrom:l+1) withoutSeparators.
-        ].
+	rest := (lineString copyFrom:l) withoutSeparators.
+	"
+	 skip <type> if present
+	"
+	(rest startsWith:$<) ifTrue:[
+	     l := lineString indexOf:$> startingAt:l.
+	     rest := (lineString copyFrom:l+1) withoutSeparators.
+	].
 
-        conditional := false.
-        (rest startsWith:$?) ifTrue:[
-            rest := (rest copyFrom:2) withoutSeparators.
-            conditional := true.
-        ].
+	conditional := false.
+	(rest startsWith:$?) ifTrue:[
+	    rest := (rest copyFrom:2) withoutSeparators.
+	    conditional := true.
+	].
 
-        (rest startsWith:$=) ifTrue:[
-            rest := rest copyFrom:2.
-            stream := ReadStream on:rest.
-            macroName := stream nextAlphaNumericWord.
-            [stream peek == $.] whileTrue:[
-                stream next.
-                stream peek notNil ifTrue:[
-                    macroName := macroName , '.' , (stream nextAlphaNumericWord)
-                ]
-            ].
-            rest := stream upToEnd.
-            value := self at:macroName ifAbsent:nil.
-            (value isNil) ifTrue:[
-                hasError := true.
-                ('ResourcePack [warning]: bad (nil-valued) macro: ' , macroName) errorPrintCR.
-                ('ResourcePack [warning]: in line: ' , lineString) errorPrintCR.
-                ('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
-            ].
-            value isBlock ifTrue:[
-                value := value value
-            ].
-            value := Compiler evaluate:('self ' , rest)
-                              receiver:value
-                              notifying:nil
-                              compile:false.
-            (value == #Error) ifTrue:[
-                hasError := true.
-                ('ResourcePack [warning]: error in line: "self ' , rest , '"') errorPrintCR.
-                ('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
-            ]
-        ] ifFalse:[
-            value := Compiler evaluate:rest compile:false.
-            (value == #Error) ifTrue:[
-                hasError := true.
-                ('ResourcePack [warning]: error in line: "' , rest , '"') errorPrintCR.
-                ('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
-            ] ifFalse:[
-                encoding notNil ifTrue:[
-                    value isString ifTrue:[
-                        value := value decodeFrom:encoding
-                    ]
-                ]
-            ]
-        ].
-        hasError ifFalse:[
-            (conditional not
-            or:[(self includesKey:name) not]) ifTrue:[
-                self at:name put:value.
-            ]
-        ]
+	(rest startsWith:$=) ifTrue:[
+	    rest := rest copyFrom:2.
+	    stream := ReadStream on:rest.
+	    macroName := stream nextAlphaNumericWord.
+	    [stream peek == $.] whileTrue:[
+		stream next.
+		stream peek notNil ifTrue:[
+		    macroName := macroName , '.' , (stream nextAlphaNumericWord)
+		]
+	    ].
+	    rest := stream upToEnd.
+	    value := self at:macroName ifAbsent:nil.
+	    (value isNil) ifTrue:[
+		hasError := true.
+		('ResourcePack [warning]: bad (nil-valued) macro: ' , macroName) errorPrintCR.
+		('ResourcePack [warning]: in line: ' , lineString) errorPrintCR.
+		('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
+	    ].
+	    value isBlock ifTrue:[
+		value := value value
+	    ].
+	    value := Compiler evaluate:('self ' , rest)
+			      receiver:value
+			      notifying:nil
+			      compile:false.
+	    (value == #Error) ifTrue:[
+		hasError := true.
+		('ResourcePack [warning]: error in line: "self ' , rest , '"') errorPrintCR.
+		('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
+	    ]
+	] ifFalse:[
+	    value := Compiler evaluate:rest compile:false.
+	    (value == #Error) ifTrue:[
+		hasError := true.
+		('ResourcePack [warning]: error in line: "' , rest , '"') errorPrintCR.
+		('ResourcePack [warning]: in file: ' , fileName) errorPrintCR.
+	    ] ifFalse:[
+		encoding notNil ifTrue:[
+		    value isString ifTrue:[
+			value := value decodeFrom:encoding
+		    ]
+		]
+	    ]
+	].
+	hasError ifFalse:[
+	    (conditional not
+	    or:[(self includesKey:name) not]) ifTrue:[
+		self at:name put:value.
+	    ]
+	]
     ]
 
     "Created: / 30.8.1998 / 12:35:37 / cg"
@@ -647,27 +647,27 @@
 
     fileReadFailed := false.
     dirName = 'resources' ifTrue:[
-        inStream := Smalltalk resourceFileStreamFor:fileName
+	inStream := Smalltalk resourceFileStreamFor:fileName
     ] ifFalse:[
-        inStream := Smalltalk 
-                        systemFileStreamFor:(dirName 
-                                                ifNil:[fileName]
-                                                ifNotNil:[dirName asFilename construct:fileName]).
+	inStream := Smalltalk 
+			systemFileStreamFor:(dirName 
+						ifNil:[fileName]
+						ifNotNil:[dirName asFilename construct:fileName]).
     ].
     inStream isNil ifTrue:[
-        "
-         an empty pack
-        "
-        ^ self nonexistingFileRead
+	"
+	 an empty pack
+	"
+	^ self nonexistingFileRead
     ].
 
     ok := self readFromResourceStream:inStream in:dirName.
     inStream close.
 
     ok ifFalse:[
-        fileReadFailed := true.
+	fileReadFailed := true.
 
-        ('ResourcePack [warning]: ''' , fileName pathName , ''' contains error(s) - data may be incomplete.') errorPrintCR.
+	('ResourcePack [warning]: ''' , inStream pathName , ''' contains error(s) - data may be incomplete.') errorPrintCR.
     ].
 
     "Modified: 10.1.1997 / 18:05:17 / cg"
@@ -688,121 +688,121 @@
     lNo := 0.
 
     errorHandler := [:ex | 
-                        |con|
+			|con|
 
-                        ('ResourcePack [warning]: ''' , ex errorString , '''') errorPrintCR.
-                        ('ResourcePack [info]: file: ' , inStream pathName printString , ' line: ' , lNo printString , ': ''' , lineString , '''') errorPrintCR.
-                        con := ex suspendedContext.
-                        ('ResourcePack [info]: in: ' , con fullPrintString) errorPrintCR.
-                        con := con sender.
-                        ('ResourcePack [info]:   : ' , con fullPrintString) errorPrintCR.
-                        con := con sender.
-                        ('ResourcePack [info]:   : ' , con fullPrintString) errorPrintCR.
-                        value := nil.
-                        ok := false.
-                    ].
+			('ResourcePack [warning]: ''' , ex errorString , '''') errorPrintCR.
+			('ResourcePack [info]: file: ' , inStream pathName printString , ' line: ' , lNo printString , ': ''' , lineString , '''') errorPrintCR.
+			con := ex suspendedContext.
+			('ResourcePack [info]: in: ' , con fullPrintString) errorPrintCR.
+			con := con sender.
+			('ResourcePack [info]:   : ' , con fullPrintString) errorPrintCR.
+			con := con sender.
+			('ResourcePack [info]:   : ' , con fullPrintString) errorPrintCR.
+			value := nil.
+			ok := false.
+		    ].
 
     [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 := 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 size > 0) ifTrue:[
-            first := lineString at:1.
-            "/
-            "/ for your convenience: treat ; AND "/ as comment-line
-            "/
-            ((first == $;) or:[lineString startsWith:'"/']) ifFalse:[
-                first == $# ifTrue:[
-                    "/ a directive
-                    lineString := (lineString copyFrom:2) withoutSpaces.
+	(lineString size > 0) ifTrue:[
+	    first := lineString at:1.
+	    "/
+	    "/ for your convenience: treat ; AND "/ as comment-line
+	    "/
+	    ((first == $;) or:[lineString startsWith:'"/']) ifFalse:[
+		first == $# ifTrue:[
+		    "/ a directive
+		    lineString := (lineString copyFrom:2) withoutSpaces.
 
-                    (lineString startsWith:'if') ifTrue:[
-                        skipping ifFalse:[
-                            rest := lineString copyFrom:3.
-                            ErrorSignal 
-                                handle:errorHandler 
-                                do:[
-                                    value := Compiler evaluate:rest compile:false].
-                            (value == #Error) ifTrue:[
-                                ('ResourcePack [warning]: error in resource:' , lineString) errorPrintCR.
-                            ].
-                            (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:[
-                                        (lineString startsWith:'includeResourcesFor') ifTrue:[
-                                            "/ include those resources ...
-                                            rest := lineString copyFrom:('includeResourcesFor' size + 1).
-                                            value := Compiler evaluate:rest compile:false.
-                                            value isBehavior ifTrue:[
-                                                pack := self class for:value.
-                                                pack notNil ifTrue:[
-                                                    self declareAllFrom:pack.
-                                                ]
-                                            ]
-                                        ] ifFalse:[
-                                            rest := lineString copyFrom:('include' size + 1).
-                                            value := Compiler evaluate:rest compile:false.
-                                            value isString ifFalse:[
-                                                ('ResourcePack [warning]: bad include filename: ' , value printString) errorPrintCR.
-                                                ('ResourcePack [info]: line ' , lNo printString , ': ''' , lineString , '''') infoPrintCR.
-                                            ] ifTrue:[
-                                                self readFromFile:value directory:dirName
-                                            ]
-                                        ]
-                                    ] ifFalse:[
-                                        (lineString startsWith:'encoding') ifTrue:[
-                                            rest := lineString copyFrom:9.
-                                            encoding := rest withoutSeparators asSymbol
-                                        ]
-                                    ]
-                                ]
-                            ]
-                        ]
-                    ].
-                ] ifFalse:[
-                    skipping ifFalse:[
-                        ErrorSignal 
-                            handle:errorHandler 
-                            do:[
-                                (lineString at:1) == $!! ifTrue:[
-                                    "/ evaluate the rest
-                                    Compiler evaluate:(lineString copyFrom:2)
-                                                      receiver:nil
-                                                      notifying:nil
-                                                      compile:false.
-                                ] ifFalse:[
-                                    "/ process as resource
-                                    self 
-                                        processLine:lineString 
-                                        encoding:encoding 
-                                        file:(inStream isFileStream 
-                                                ifTrue:[inStream pathName]
-                                                ifFalse:['---'])
-                                ]]
-                    ]
-                ]
-            ]
-        ]
+		    (lineString startsWith:'if') ifTrue:[
+			skipping ifFalse:[
+			    rest := lineString copyFrom:3.
+			    ErrorSignal 
+				handle:errorHandler 
+				do:[
+				    value := Compiler evaluate:rest compile:false].
+			    (value == #Error) ifTrue:[
+				('ResourcePack [warning]: error in resource:' , lineString) errorPrintCR.
+			    ].
+			    (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:[
+					(lineString startsWith:'includeResourcesFor') ifTrue:[
+					    "/ include those resources ...
+					    rest := lineString copyFrom:('includeResourcesFor' size + 1).
+					    value := Compiler evaluate:rest compile:false.
+					    value isBehavior ifTrue:[
+						pack := self class for:value.
+						pack notNil ifTrue:[
+						    self declareAllFrom:pack.
+						]
+					    ]
+					] ifFalse:[
+					    rest := lineString copyFrom:('include' size + 1).
+					    value := Compiler evaluate:rest compile:false.
+					    value isString ifFalse:[
+						('ResourcePack [warning]: bad include filename: ' , value printString) errorPrintCR.
+						('ResourcePack [info]: line ' , lNo printString , ': ''' , lineString , '''') infoPrintCR.
+					    ] ifTrue:[
+						self readFromFile:value directory:dirName
+					    ]
+					]
+				    ] ifFalse:[
+					(lineString startsWith:'encoding') ifTrue:[
+					    rest := lineString copyFrom:9.
+					    encoding := rest withoutSeparators asSymbol
+					]
+				    ]
+				]
+			    ]
+			]
+		    ].
+		] ifFalse:[
+		    skipping ifFalse:[
+			ErrorSignal 
+			    handle:errorHandler 
+			    do:[
+				(lineString at:1) == $!! ifTrue:[
+				    "/ evaluate the rest
+				    Compiler evaluate:(lineString copyFrom:2)
+						      receiver:nil
+						      notifying:nil
+						      compile:false.
+				] ifFalse:[
+				    "/ process as resource
+				    self 
+					processLine:lineString 
+					encoding:encoding 
+					file:(inStream isFileStream 
+						ifTrue:[inStream pathName]
+						ifFalse:['---'])
+				]]
+		    ]
+		]
+	    ]
+	]
     ].
     ^ ok
 
@@ -813,6 +813,6 @@
 !ResourcePack class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/ResourcePack.st,v 1.72 2002-08-19 16:25:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/ResourcePack.st,v 1.73 2002-11-11 09:27:08 cg Exp $'
 ! !
 ResourcePack initialize!