ResourcePack.st
changeset 8462 e7faff5c7fea
parent 8461 55ca0b1e251b
child 8470 fa52e3d659d7
equal deleted inserted replaced
8461:55ca0b1e251b 8462:e7faff5c7fea
     1 "{ Encoding: utf8 }"
     1 "{ Encoding: utf8 }"
     2 
     2 
     3 "
     3 "
     4  COPYRIGHT (c) 1993 by Claus Gittinger
     4  COPYRIGHT (c) 1993 by Claus Gittinger
     5 	      All Rights Reserved
     5               All Rights Reserved
     6 
     6 
     7  This software is furnished under a license and may be used
     7  This software is furnished under a license and may be used
     8  only in accordance with the terms of that license and with the
     8  only in accordance with the terms of that license and with the
     9  inclusion of the above copyright notice.   This software may not
     9  inclusion of the above copyright notice.   This software may not
    10  be provided or otherwise made available to, or used by, any
    10  be provided or otherwise made available to, or used by, any
    14 "{ Package: 'stx:libview' }"
    14 "{ Package: 'stx:libview' }"
    15 
    15 
    16 "{ NameSpace: Smalltalk }"
    16 "{ NameSpace: Smalltalk }"
    17 
    17 
    18 Dictionary subclass:#ResourcePack
    18 Dictionary subclass:#ResourcePack
    19 	instanceVariableNames:'packsClassName packsFileName fileReadFailed superPack projectPack
    19         instanceVariableNames:'packsClassName packsFileName fileReadFailed superPack projectPack
    20 		usedKeys cache'
    20                 usedKeys cache'
    21 	classVariableNames:'Packs FailedToLoadPacks DebugModifications
    21         classVariableNames:'Packs FailedToLoadPacks DebugModifications
    22 		KeepStatisticsOnUsedKeys'
    22                 KeepStatisticsOnUsedKeys'
    23 	poolDictionaries:''
    23         poolDictionaries:''
    24 	category:'Interface-Internationalization'
    24         category:'Interface-Internationalization'
    25 !
    25 !
    26 
    26 
    27 !ResourcePack class methodsFor:'documentation'!
    27 !ResourcePack class methodsFor:'documentation'!
    28 
    28 
    29 copyright
    29 copyright
    30 "
    30 "
    31  COPYRIGHT (c) 1993 by Claus Gittinger
    31  COPYRIGHT (c) 1993 by Claus Gittinger
    32 	      All Rights Reserved
    32               All Rights Reserved
    33 
    33 
    34  This software is furnished under a license and may be used
    34  This software is furnished under a license and may be used
    35  only in accordance with the terms of that license and with the
    35  only in accordance with the terms of that license and with the
    36  inclusion of the above copyright notice.   This software may not
    36  inclusion of the above copyright notice.   This software may not
    37  be provided or otherwise made available to, or used by, any
    37  be provided or otherwise made available to, or used by, any
   153 examples
   153 examples
   154 "
   154 "
   155     normally, resources are found in files named after their classes sourcefile
   155     normally, resources are found in files named after their classes sourcefile
   156     For example, the FileBrowsers resources are found in 'FBrowser.rs'.
   156     For example, the FileBrowsers resources are found in 'FBrowser.rs'.
   157     For the examples below, we process resources from a constant string;
   157     For the examples below, we process resources from a constant string;
   158 	this is NOT representative.
   158         this is NOT representative.
   159 									[exBegin]
   159                                                                         [exBegin]
   160 	|stream res|
   160         |stream res|
   161 
   161 
   162 	stream := ReadStream on:'
   162         stream := ReadStream on:'
   163 foo  ''the translation for foo''
   163 foo  ''the translation for foo''
   164 #if Language == #de
   164 #if Language == #de
   165 bar  ''die deutsche uebersetzung von bar''
   165 bar  ''die deutsche uebersetzung von bar''
   166 baz  ''baz hat den Wert %1''
   166 baz  ''baz hat den Wert %1''
   167 #endif
   167 #endif
   170 baz  ''%1, c''''est baz''
   170 baz  ''%1, c''''est baz''
   171 #endif
   171 #endif
   172 
   172 
   173 '.
   173 '.
   174 
   174 
   175 	res := ResourcePack new readFromResourceStream:stream in:nil.
   175         res := ResourcePack new readFromResourceStream:stream in:nil.
   176 
   176 
   177 	Transcript showCR:'baz is translated to: ' , (res string:'baz' with:'1234').
   177         Transcript showCR:'baz is translated to: ' , (res string:'baz' with:'1234').
   178 	Transcript showCR:'bar is translated to: ' , (res string:'bar').
   178         Transcript showCR:'bar is translated to: ' , (res string:'bar').
   179 	Transcript showCR:'foo is translated to: ' , (res string:'foo').
   179         Transcript showCR:'foo is translated to: ' , (res string:'foo').
   180 	Transcript showCR:'fooBar is translated to: ' , (res string:'fooBar').
   180         Transcript showCR:'fooBar is translated to: ' , (res string:'fooBar').
   181 									[exEnd]
   181                                                                         [exEnd]
   182     set the Language to french:
   182     set the Language to french:
   183 									[exBegin]
   183                                                                         [exBegin]
   184 	Language := #fr
   184         Language := #fr
   185 									[exEnd]
   185                                                                         [exEnd]
   186     and repeat the above.
   186     and repeat the above.
   187     back to english:
   187     back to english:
   188 									[exBegin]
   188                                                                         [exBegin]
   189 	Language := #en
   189         Language := #en
   190 									[exEnd]
   190                                                                         [exEnd]
   191     back to german:
   191     back to german:
   192 									[exBegin]
   192                                                                         [exBegin]
   193 	Language := #de
   193         Language := #de
   194 									[exEnd]
   194                                                                         [exEnd]
   195 "
   195 "
   196 ! !
   196 ! !
   197 
   197 
   198 !ResourcePack class methodsFor:'initialization'!
   198 !ResourcePack class methodsFor:'initialization'!
   199 
   199 
   208     "
   208     "
   209 !
   209 !
   210 
   210 
   211 initialize
   211 initialize
   212     Packs isNil ifTrue:[
   212     Packs isNil ifTrue:[
   213 	Packs := WeakArray new:100.
   213         Packs := WeakArray new:100.
   214 	FailedToLoadPacks := Set new.
   214         FailedToLoadPacks := Set new.
   215     ].
   215     ].
   216 
   216 
   217     "
   217     "
   218      ResourcePack initialize
   218      ResourcePack initialize
   219     "
   219     "
   334     |fullName pack rsrcDir file|
   334     |fullName pack rsrcDir file|
   335 
   335 
   336     fullName := package , '/resources/',resourceFileName.
   336     fullName := package , '/resources/',resourceFileName.
   337 
   337 
   338     cached ifTrue:[
   338     cached ifTrue:[
   339 	pack := self searchCacheFor:fullName.
   339         pack := self searchCacheFor:fullName.
   340 	pack notNil ifTrue:[^ pack].
   340         pack notNil ifTrue:[^ pack].
   341 	(FailedToLoadPacks includes:fullName) ifTrue:[^ nil].
   341         (FailedToLoadPacks includes:fullName) ifTrue:[^ nil].
   342     ].
   342     ].
   343 
   343 
   344     rsrcDir := Smalltalk projectDirectoryForPackage:package.
   344     rsrcDir := Smalltalk projectDirectoryForPackage:package.
   345     rsrcDir isNil ifTrue:[
   345     rsrcDir isNil ifTrue:[
   346 	file := Smalltalk getResourceFileName:resourceFileName forPackage:package.
   346         file := Smalltalk getResourceFileName:resourceFileName forPackage:package.
   347 	file isNil ifTrue:[
   347         file isNil ifTrue:[
   348 	    FailedToLoadPacks add:fullName.
   348             FailedToLoadPacks add:fullName.
   349 	    ^ nil
   349             ^ nil
   350 	].
   350         ].
   351 	rsrcDir := file asFilename directory.
   351         rsrcDir := file asFilename directory.
   352     ] ifFalse:[
   352     ] ifFalse:[
   353 	rsrcDir := rsrcDir asFilename construct:'resources'.
   353         rsrcDir := rsrcDir asFilename construct:'resources'.
   354 	rsrcDir exists ifFalse:[
   354         rsrcDir exists ifFalse:[
   355 	    FailedToLoadPacks add:fullName.
   355             FailedToLoadPacks add:fullName.
   356 	    ^ nil
   356             ^ nil
   357 	].
   357         ].
   358     ].
   358     ].
   359 
   359 
   360     pack := self fromFile:resourceFileName directory:rsrcDir cached:cached.
   360     pack := self fromFile:resourceFileName directory:rsrcDir cached:cached.
   361     pack packsClassOrFileName:fullName.
   361     pack packsClassOrFileName:fullName.
   362     ^ pack
   362     ^ pack
   409 
   409 
   410 addToCache:aPack
   410 addToCache:aPack
   411     |idx|
   411     |idx|
   412 
   412 
   413     Packs isNil ifTrue:[
   413     Packs isNil ifTrue:[
   414 	self initialize.
   414         self initialize.
   415     ].
   415     ].
   416 
   416 
   417     idx := Packs identityIndexOf:nil.
   417     idx := Packs identityIndexOf:nil.
   418     idx == 0 ifTrue:[
   418     idx == 0 ifTrue:[
   419 	idx := Packs findFirst:[:slot | slot class == SmallInteger].
   419         idx := Packs findFirst:[:slot | slot class == SmallInteger].
   420     ].
   420     ].
   421     idx == 0 ifTrue:[
   421     idx == 0 ifTrue:[
   422 	"
   422         "
   423 	 throw away oldest
   423          throw away oldest
   424 	"
   424         "
   425 	idx := Packs size.
   425         idx := Packs size.
   426 	Packs replaceFrom:1 to:idx-1 with:Packs startingAt:2.
   426         Packs replaceFrom:1 to:idx-1 with:Packs startingAt:2.
   427     ].
   427     ].
   428     aPack at:'__language__' put:(UserPreferences current language,'_',UserPreferences current languageTerritory).
   428     aPack at:'__language__' put:(UserPreferences current language,'_',UserPreferences current languageTerritory).
   429     Packs at:idx put:aPack.
   429     Packs at:idx put:aPack.
   430 
   430 
   431     "Modified: / 18-09-2006 / 19:12:12 / cg"
   431     "Modified: / 18-09-2006 / 19:12:12 / cg"
   433 
   433 
   434 searchCacheFor:aClassOrFileName
   434 searchCacheFor:aClassOrFileName
   435     |sz "{ Class: SmallInteger }" lang|
   435     |sz "{ Class: SmallInteger }" lang|
   436 
   436 
   437     Packs isNil ifTrue:[
   437     Packs isNil ifTrue:[
   438 	self initialize.
   438         self initialize.
   439 	^ nil
   439         ^ nil
   440     ].
   440     ].
   441 
   441 
   442     lang := (UserPreferences current language,'_',UserPreferences current languageTerritory).
   442     lang := (UserPreferences current language,'_',UserPreferences current languageTerritory).
   443 
   443 
   444     sz := Packs size.
   444     sz := Packs size.
   445     1 to:sz do:[:idx |
   445     1 to:sz do:[:idx |
   446 	|aPack|
   446         |aPack|
   447 
   447 
   448 	aPack := Packs at:idx.
   448         aPack := Packs at:idx.
   449 	(aPack notNil and:[aPack class ~~ SmallInteger]) ifTrue:[
   449         (aPack notNil and:[aPack class ~~ SmallInteger]) ifTrue:[
   450 	    (aPack at:'__language__' ifAbsent:nil) = lang ifTrue:[
   450             (aPack at:'__language__' ifAbsent:nil) = lang ifTrue:[
   451 		aClassOrFileName = aPack packsClassOrFileName ifTrue:[
   451                 aClassOrFileName = aPack packsClassOrFileName ifTrue:[
   452 		    "
   452                     "
   453 		     bring to front for LRU
   453                      bring to front for LRU
   454 		    "
   454                     "
   455 		    idx ~~ 1 ifTrue:[
   455                     idx ~~ 1 ifTrue:[
   456 			Packs replaceFrom:2 to:idx with:Packs startingAt:1.
   456                         Packs replaceFrom:2 to:idx with:Packs startingAt:1.
   457 			Packs at:1 put:aPack.
   457                         Packs at:1 put:aPack.
   458 		    ].
   458                     ].
   459 		    ^ aPack
   459                     ^ aPack
   460 		]
   460                 ]
   461 	    ]
   461             ]
   462 	]
   462         ]
   463     ].
   463     ].
   464     ^ nil
   464     ^ nil
   465 
   465 
   466     "
   466     "
   467      ResourcePack searchCacheFor:'TextView'
   467      ResourcePack searchCacheFor:'TextView'
   478     (lineString startsWith:'encoding') ifFalse:[^ nil].
   478     (lineString startsWith:'encoding') ifFalse:[^ nil].
   479 
   479 
   480     rest := lineString copyFrom:9.
   480     rest := lineString copyFrom:9.
   481     rest := rest withoutSeparators.
   481     rest := rest withoutSeparators.
   482     (rest startsWith:'#') ifTrue:[
   482     (rest startsWith:'#') ifTrue:[
   483 	rest := rest copyFrom:2.
   483         rest := rest copyFrom:2.
   484     ].
   484     ].
   485     (rest startsWith:'''') ifTrue:[
   485     (rest startsWith:'''') ifTrue:[
   486 	rest := rest copyFrom:2.
   486         rest := rest copyFrom:2.
   487 	(rest endsWith:'''') ifTrue:[
   487         (rest endsWith:'''') ifTrue:[
   488 	    rest := rest copyButLast:1.
   488             rest := rest copyButLast:1.
   489 	].
   489         ].
   490     ].
   490     ].
   491     encoding := rest asSymbol.
   491     encoding := rest asSymbol.
   492     ^ encoding.
   492     ^ encoding.
   493 !
   493 !
   494 
   494 
   495 processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack
   495 processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack
   496     "process a single valid line (i.e. #ifdef & #include has already been processed)"
   496     "process a single valid line (i.e. #ifdef & #include has already been processed)"
   497 
   497 
   498     self
   498     self
   499 	processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack
   499         processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack
   500 	keepUselessTranslations:false.
   500         keepUselessTranslations:false.
   501 !
   501 !
   502 
   502 
   503 processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack keepUselessTranslations:keepUselessTranslations
   503 processResourceLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError for:aResourcePack keepUselessTranslations:keepUselessTranslations
   504     "process a single valid line (i.e. #ifdef & #include has already been processed)"
   504     "process a single valid line (i.e. #ifdef & #include has already been processed)"
   505 
   505 
   506     |name lineStream idx rest macroName value
   506     |name lineStream idx rest macroName value
   507      conditional hasError decoder oldValue ignoreTranslation indirect|
   507      conditional hasError decoder oldValue ignoreTranslation indirect|
   508 
   508 
   509     "/ Transcript showCR:lineString.
   509     "/ Transcript showCR:lineString.
   510     encodingSymbolOrEncoder notNil ifTrue:[
   510     encodingSymbolOrEncoder notNil ifTrue:[
   511 	encodingSymbolOrEncoder isSymbol ifTrue:[
   511         encodingSymbolOrEncoder isSymbol ifTrue:[
   512 	    decoder := CharacterEncoder encoderFor:encodingSymbolOrEncoder ifAbsent:nil.
   512             decoder := CharacterEncoder encoderFor:encodingSymbolOrEncoder ifAbsent:nil.
   513 	    decoder isNil ifTrue:[ decoder := CharacterEncoder nullEncoderInstance ].
   513             decoder isNil ifTrue:[ decoder := CharacterEncoder nullEncoderInstance ].
   514 	] ifFalse:[
   514         ] ifFalse:[
   515 	    decoder := encodingSymbolOrEncoder
   515             decoder := encodingSymbolOrEncoder
   516 	].
   516         ].
   517     ].
   517     ].
   518 
   518 
   519     decoder notNil ifTrue:[
   519     decoder notNil ifTrue:[
   520 	lineStream := (decoder decodeString:lineString) readStream.
   520         lineStream := (decoder decodeString:lineString) readStream.
   521     ] ifFalse:[
   521     ] ifFalse:[
   522 	lineStream := lineString readStream.
   522         lineStream := lineString readStream.
   523     ].
   523     ].
   524     lineStream signalAtEnd:false.
   524     lineStream signalAtEnd:false.
   525     lineStream skipSeparators.
   525     lineStream skipSeparators.
   526 
   526 
   527     lineStream peek == $# ifTrue:[
   527     lineStream peek == $# ifTrue:[
   528 	name := Array
   528         name := Array
   529 		    readFrom:lineStream
   529                     readFrom:lineStream
   530 		    onError:[
   530                     onError:[
   531 				printError value:('invalid line <' , lineString , '>').
   531                                 printError value:('invalid line <' , lineString , '>').
   532 				nil
   532                                 nil
   533 			    ].
   533                             ].
   534     ] ifFalse:[
   534     ] ifFalse:[
   535 	lineStream peek == $' ifTrue:[
   535         lineStream peek == $' ifTrue:[
   536 	    name := String
   536             name := String
   537 			readSmalltalkStringFrom:lineStream
   537                         readSmalltalkStringFrom:lineStream
   538 			onError:[
   538                         onError:[
   539 				    printError value:('invalid line <' , lineString , '>').
   539                                     printError value:('invalid line <' , lineString , '>').
   540 				    nil
   540                                     nil
   541 				].
   541                                 ].
   542 	] ifFalse:[
   542         ] ifFalse:[
   543 	    name := lineStream upToSeparator.
   543             name := lineStream upToSeparator.
   544 	].
   544         ].
   545     ].
   545     ].
   546 
   546 
   547     name isNil ifTrue:[^ self ].
   547     name isNil ifTrue:[^ self ].
   548 
   548 
   549     ignoreTranslation := false.
   549     ignoreTranslation := false.
   551 
   551 
   552     lineStream skipSeparators.
   552     lineStream skipSeparators.
   553     idx := lineStream position + 1 + 1.
   553     idx := lineStream position + 1 + 1.
   554 
   554 
   555     lineStream peek == $< ifTrue:[
   555     lineStream peek == $< ifTrue:[
   556 	"
   556         "
   557 	 skip <type> if present
   557          skip <type> if present
   558 	"
   558         "
   559 	lineStream skipThrough:$>.
   559         lineStream skipThrough:$>.
   560 	lineStream skipSeparators.
   560         lineStream skipSeparators.
   561 	idx := lineStream position + 2.
   561         idx := lineStream position + 2.
   562     ].
   562     ].
   563 
   563 
   564     conditional := indirect := false.
   564     conditional := indirect := false.
   565     lineStream peek == $? ifTrue:[
   565     lineStream peek == $? ifTrue:[
   566 	conditional := true.
   566         conditional := true.
   567 	lineStream next.
   567         lineStream next.
   568 	lineStream skipSeparators.
   568         lineStream skipSeparators.
   569     ].
   569     ].
   570 
   570 
   571     lineStream peek == $@ ifTrue:[
   571     lineStream peek == $@ ifTrue:[
   572 	indirect := true.
   572         indirect := true.
   573 	lineStream next.
   573         lineStream next.
   574 	lineStream skipSeparators.
   574         lineStream skipSeparators.
   575     ].
   575     ].
   576 
   576 
   577     lineStream peek == $= ifTrue:[
   577     lineStream peek == $= ifTrue:[
   578 	lineStream next.
   578         lineStream next.
   579 
   579 
   580 	macroName := lineStream nextAlphaNumericWord.
   580         macroName := lineStream nextAlphaNumericWord.
   581 	[lineStream peek == $.] whileTrue:[
   581         [lineStream peek == $.] whileTrue:[
   582 	    lineStream next.
   582             lineStream next.
   583 	    lineStream peek notNil ifTrue:[
   583             lineStream peek notNil ifTrue:[
   584 		macroName := macroName , '.' , (lineStream nextAlphaNumericWord)
   584                 macroName := macroName , '.' , (lineStream nextAlphaNumericWord)
   585 	    ]
   585             ]
   586 	].
   586         ].
   587 	rest := lineStream upToEnd.
   587         rest := lineStream upToEnd.
   588 	value := aResourcePack at:macroName ifAbsent:nil.
   588         value := aResourcePack at:macroName ifAbsent:nil.
   589 	(value isNil) ifTrue:[
   589         (value isNil) ifTrue:[
   590 	    hasError := true.
   590             hasError := true.
   591 	    printError value:('bad (nil-valued) macro: ' , macroName).
   591             printError value:('bad (nil-valued) macro: ' , macroName).
   592 	].
   592         ].
   593 "/        value isBlock ifTrue:[
   593 "/        value isBlock ifTrue:[
   594 "/            value := value value
   594 "/            value := value value
   595 "/        ].
   595 "/        ].
   596 	rest isBlank ifFalse:[
   596         rest isBlank ifFalse:[
   597 	    value := Compiler evaluate:('self ' , rest)
   597             value := Compiler evaluate:('self ' , rest)
   598 			      receiver:value
   598                               receiver:value
   599 			      notifying:nil
   599                               notifying:nil
   600 			      compile:false.
   600                               compile:false.
   601 	    (value == #Error) ifTrue:[
   601             (value == #Error) ifTrue:[
   602 		hasError := true.
   602                 hasError := true.
   603 		printError value:('error in: "self ' , rest , '"').
   603                 printError value:('error in: "self ' , rest , '"').
   604 	    ].
   604             ].
   605 	    "/ 'self ' print. rest print. ' -> ' print. value printCR.
   605             "/ 'self ' print. rest print. ' -> ' print. value printCR.
   606 	]
   606         ]
   607     ] ifFalse:[
   607     ] ifFalse:[
   608 	lineStream peek == $' ifTrue:[
   608         lineStream peek == $' ifTrue:[
   609 	    value := String
   609             value := String
   610 			readSmalltalkStringFrom:lineStream
   610                         readSmalltalkStringFrom:lineStream
   611 			onError:[
   611                         onError:[
   612 				    printError value:('invalid line <' , lineString , '>').
   612                                     printError value:('invalid line <' , lineString , '>').
   613 				    nil
   613                                     nil
   614 				].
   614                                 ].
   615 	    "/ ' -> ' print. value printCR.
   615             "/ ' -> ' print. value printCR.
   616 	] ifFalse:[
   616         ] ifFalse:[
   617 	    rest := lineStream upToEnd.
   617             rest := lineStream upToEnd.
   618 	    [
   618             [
   619 		value := Compiler evaluate:rest compile:"true" false.
   619                 value := Compiler evaluate:rest compile:"true" false.
   620 	    ] on:Error do:[
   620             ] on:Error do:[
   621 		printError value:('invalid line <' , rest , '>').
   621                 printError value:('invalid line <' , rest , '>').
   622 		"/ value := rest
   622                 "/ value := rest
   623 	    ].
   623             ].
   624 	    "/ rest print. ' -> ' print. value printCR.
   624             "/ rest print. ' -> ' print. value printCR.
   625 	].
   625         ].
   626 	(value == #Error) ifTrue:[
   626         (value == #Error) ifTrue:[
   627 	    hasError := true.
   627             hasError := true.
   628 	    printError value:('error in: "' , rest , '"').
   628             printError value:('error in: "' , rest , '"').
   629 	] ifFalse:[
   629         ] ifFalse:[
   630 "/            value isString ifTrue:[
   630 "/            value isString ifTrue:[
   631 "/                decoder notNil ifTrue:[
   631 "/                decoder notNil ifTrue:[
   632 "/                    value := decoder decodeString:value
   632 "/                    value := decoder decodeString:value
   633 "/                ]
   633 "/                ]
   634 "/            ]
   634 "/            ]
   635 	]
   635         ]
   636     ].
   636     ].
   637 
   637 
   638     "/ Transcript show:name; show:' -> '; showCR:value.
   638     "/ Transcript show:name; show:' -> '; showCR:value.
   639 
   639 
   640     hasError ifFalse:[
   640     hasError ifFalse:[
   641 	(conditional not
   641         (conditional not
   642 	or:[(aResourcePack includesKey:name) not]) ifTrue:[
   642         or:[(aResourcePack includesKey:name) not]) ifTrue:[
   643 	    name = value ifTrue:[
   643             name = value ifTrue:[
   644 		keepUselessTranslations ifFalse:[
   644                 keepUselessTranslations ifFalse:[
   645 		    printError value:('useless resource: "' , name , '"').
   645                     printError value:('useless resource: "' , name , '"').
   646 		    ignoreTranslation := true
   646                     ignoreTranslation := true
   647 		].
   647                 ].
   648 	    ].
   648             ].
   649 	    ignoreTranslation ifFalse:[
   649             ignoreTranslation ifFalse:[
   650 		oldValue := aResourcePack at:name ifAbsent:nil.
   650                 oldValue := aResourcePack at:name ifAbsent:nil.
   651 		oldValue notNil ifTrue:[
   651                 oldValue notNil ifTrue:[
   652 		    oldValue ~= value ifTrue:[
   652                     oldValue ~= value ifTrue:[
   653 			printError value:('conflicting resource: "' , name , '"').
   653                         printError value:('conflicting resource: "' , name , '"').
   654 			printError value:('oldValue: ' , oldValue printString).
   654                         printError value:('oldValue: ' , oldValue printString).
   655 			printError value:('newValue: ' , value printString).
   655                         printError value:('newValue: ' , value printString).
   656 		    ] ifFalse:[
   656                     ] ifFalse:[
   657 			printError value:('duplicate resource: "' , name , '"').
   657                         printError value:('duplicate resource: "' , name , '"').
   658 		    ].
   658                     ].
   659 		].
   659                 ].
   660 		indirect ifTrue:[
   660                 indirect ifTrue:[
   661 		    value := aResourcePack string:value.
   661                     value := aResourcePack string:value.
   662 		].
   662                 ].
   663 
   663 
   664 		DebugModifications == true ifTrue:[
   664                 DebugModifications == true ifTrue:[
   665 		    "/ for debugging only !! (not all primitive code is ready for immutableStrings)
   665                     "/ for debugging only !! (not all primitive code is ready for immutableStrings)
   666 		    value class == String ifTrue:[
   666                     value class == String ifTrue:[
   667 			value := value asImmutableString.
   667                         value := value asImmutableString.
   668 		    ].
   668                     ].
   669 		].
   669                 ].
   670 
   670 
   671 		aResourcePack at:name put:value.
   671                 aResourcePack at:name put:value.
   672 	    ]
   672             ]
   673 	]
   673         ]
   674     ]
   674     ]
   675 
   675 
   676     "Modified: / 06-02-2014 / 15:33:03 / cg"
   676     "Modified: / 06-02-2014 / 15:33:03 / cg"
   677 !
   677 !
   678 
   678 
   700     "
   700     "
   701 !
   701 !
   702 
   702 
   703 shortenedKeyFor:aKey
   703 shortenedKeyFor:aKey
   704     "if
   704     "if
   705 	  aKey is '(...)', then return '...'
   705           aKey is '(...)', then return '...'
   706 	  if aKey is '[...]', then return '...'
   706           if aKey is '[...]', then return '...'
   707 	  if aKey is '{...}', then return '...'
   707           if aKey is '{...}', then return '...'
   708 	  if aKey starts or ends with any of '\:=.,?!! ', then return aKey without it
   708           if aKey starts or ends with any of '\:=.,?!! ', then return aKey without it
   709 
   709 
   710      This means, that only a single translation is required to provide local translations for
   710      This means, that only a single translation is required to provide local translations for
   711      things like
   711      things like
   712 	'search'
   712         'search'
   713 	'search:'
   713         'search:'
   714 	'search...'
   714         'search...'
   715     "
   715     "
   716 
   716 
   717     |idx idx1 idx2 first last keySize|
   717     |idx idx1 idx2 first last keySize|
   718 
   718 
   719     first := aKey first.
   719     first := aKey first.
   721     keySize := aKey size.
   721     keySize := aKey size.
   722 
   722 
   723     ((first == $( and:[last == $) ])
   723     ((first == $( and:[last == $) ])
   724     or:[ (first == $[ and:[last == $] ])
   724     or:[ (first == $[ and:[last == $] ])
   725     or:[ (first == ${ and:[last == $} ]) ]]) ifTrue:[
   725     or:[ (first == ${ and:[last == $} ]) ]]) ifTrue:[
   726 	^ self shortenedKeyFor:(aKey copyFrom:2 to:keySize-1).
   726         ^ self shortenedKeyFor:(aKey copyFrom:2 to:keySize-1).
   727     ].
   727     ].
   728 
   728 
   729     idx1 := aKey findFirst:[:ch | ch isSeparator not].
   729     idx1 := aKey findFirst:[:ch | ch isSeparator not].
   730     idx2 := aKey findLast:[:ch | ch isSeparator not] ifNone:keySize.
   730     idx2 := aKey findLast:[:ch | ch isSeparator not] ifNone:keySize.
   731     (idx1 > 1 or:[idx2 < keySize]) ifTrue:[
   731     (idx1 > 1 or:[idx2 < keySize]) ifTrue:[
   732 	^ self shortenedKeyFor:(aKey copyFrom:idx1 to:idx2)
   732         ^ self shortenedKeyFor:(aKey copyFrom:idx1 to:idx2)
   733     ].
   733     ].
   734 
   734 
   735     idx1 := aKey findFirst:[:ch | ('*:=.?!!,-><\' includes:ch) not].
   735     idx1 := aKey findFirst:[:ch | ('*:=.?!!,-><\' includes:ch) not].
   736     idx2 := aKey findLast:[:ch | ('*:=.?!!,-><\' includes:ch) not] ifNone:keySize.
   736     idx2 := aKey findLast:[:ch | ('*:=.?!!,-><\' includes:ch) not] ifNone:keySize.
   737     (idx1 > 1 or:[idx2 < keySize]) ifTrue:[
   737     (idx1 > 1 or:[idx2 < keySize]) ifTrue:[
   738 	^ self shortenedKeyFor:(aKey copyFrom:idx1 to:idx2)
   738         ^ self shortenedKeyFor:(aKey copyFrom:idx1 to:idx2)
   739     ].
   739     ].
   740 
   740 
   741     "/ change duplicated &'s to single
   741     "/ change duplicated &'s to single
   742     (idx := aKey indexOf:$&) ~~ 0 ifTrue:[
   742     (idx := aKey indexOf:$&) ~~ 0 ifTrue:[
   743 	(aKey at:idx+1 ifAbsent:nil) ~~ $& ifTrue:[
   743         (aKey at:idx+1 ifAbsent:nil) ~~ $& ifTrue:[
   744 	    ^ self shortenedKeyFor:(aKey copyTo:idx-1),(aKey copyFrom:idx+1).
   744             ^ self shortenedKeyFor:(aKey copyTo:idx-1),(aKey copyFrom:idx+1).
   745 	].
   745         ].
   746     ].
   746     ].
   747     ^ aKey.
   747     ^ aKey.
   748 
   748 
   749     "
   749     "
   750      'abcde' findFirst:[:ch | 'bcd' includes:ch]
   750      'abcde' findFirst:[:ch | 'bcd' includes:ch]
   805         val notNil ifTrue:[
   805         val notNil ifTrue:[
   806             cache at:aKey put:val.
   806             cache at:aKey put:val.
   807             ^ val
   807             ^ val
   808         ].
   808         ].
   809     ].
   809     ].
   810     alreadySearched := Set new.
   810     alreadySearched := IdentitySet new.
   811     projectPack notNil ifTrue:[ alreadySearched add:projectPack ].
   811     projectPack notNil ifTrue:[ alreadySearched add:projectPack ].
   812 
   812 
   813     pack := self superPack.
   813     pack := self superPack.
   814     [ pack notNil ] whileTrue:[
   814     [ pack notNil ] whileTrue:[
   815         val := pack localAt:aKey.
   815         val := pack localAt:aKey.
   999 
   999 
  1000     ^ self at:s ifAbsent:s
  1000     ^ self at:s ifAbsent:s
  1001 
  1001 
  1002     "
  1002     "
  1003      NewLauncher classResources
  1003      NewLauncher classResources
  1004 	string:'LICENCEFILE'
  1004         string:'LICENCEFILE'
  1005     "
  1005     "
  1006 !
  1006 !
  1007 
  1007 
  1008 string:s default:defaultString
  1008 string:s default:defaultString
  1009     "translate (retrieve) a string - if not present, return defaultString"
  1009     "translate (retrieve) a string - if not present, return defaultString"
  1010 
  1010 
  1011     ^ self at:s ifAbsent:defaultString
  1011     ^ self at:s ifAbsent:defaultString
  1012 
  1012 
  1013     "
  1013     "
  1014      NewLauncher classResources
  1014      NewLauncher classResources
  1015 	string:'fooBar' default:'Hello world'
  1015         string:'fooBar' default:'Hello world'
  1016     "
  1016     "
  1017 
  1017 
  1018 !
  1018 !
  1019 
  1019 
  1020 string:s default:defaultString with:arg
  1020 string:s default:defaultString with:arg
  1294 
  1294 
  1295     val := self localAt:aKey.
  1295     val := self localAt:aKey.
  1296     val notNil ifTrue:[^ self].
  1296     val notNil ifTrue:[^ self].
  1297 
  1297 
  1298     (projectPack := self projectPack) notNil ifTrue:[
  1298     (projectPack := self projectPack) notNil ifTrue:[
  1299 	val := projectPack localAt:aKey.
  1299         val := projectPack localAt:aKey.
  1300 	val notNil ifTrue:[^ projectPack].
  1300         val notNil ifTrue:[^ projectPack].
  1301     ].
  1301     ].
  1302     alreadySearched := Set new.
  1302     alreadySearched := Set new.
  1303     projectPack notNil ifTrue:[ alreadySearched add:projectPack ].
  1303     projectPack notNil ifTrue:[ alreadySearched add:projectPack ].
  1304 
  1304 
  1305     pack := self superPack.
  1305     pack := self superPack.
  1306     [ pack notNil ] whileTrue:[
  1306     [ pack notNil ] whileTrue:[
  1307 	val := pack localAt:aKey.
  1307         val := pack localAt:aKey.
  1308 	val notNil ifTrue:[^ pack].
  1308         val notNil ifTrue:[^ pack].
  1309 
  1309 
  1310 	(projectPack := pack projectPack) notNil ifTrue:[
  1310         (projectPack := pack projectPack) notNil ifTrue:[
  1311 	    (alreadySearched includes:projectPack) ifFalse:[
  1311             (alreadySearched includes:projectPack) ifFalse:[
  1312 		val := projectPack localAt:aKey.
  1312                 val := projectPack localAt:aKey.
  1313 		val notNil ifTrue:[^ projectPack].
  1313                 val notNil ifTrue:[^ projectPack].
  1314 		alreadySearched add:projectPack.
  1314                 alreadySearched add:projectPack.
  1315 	    ].
  1315             ].
  1316 	].
  1316         ].
  1317 	pack := pack superPack
  1317         pack := pack superPack
  1318     ].
  1318     ].
  1319 
  1319 
  1320     alreadySearched copy do:[:projectPack |
  1320     alreadySearched copy do:[:projectPack |
  1321 	|p|
  1321         |p|
  1322 
  1322 
  1323 	p := projectPack superPack.
  1323         p := projectPack superPack.
  1324 	[p notNil and:[(alreadySearched includes:p) not]] whileTrue:[
  1324         [p notNil and:[(alreadySearched includes:p) not]] whileTrue:[
  1325 	    val := p localAt:aKey.
  1325             val := p localAt:aKey.
  1326 	    val notNil ifTrue:[^ p].
  1326             val notNil ifTrue:[^ p].
  1327 	    alreadySearched add:p.
  1327             alreadySearched add:p.
  1328 	    p := p superPack.
  1328             p := p superPack.
  1329 	].
  1329         ].
  1330     ].
  1330     ].
  1331 
  1331 
  1332     ^ nil
  1332     ^ nil
  1333 ! !
  1333 ! !
  1334 
  1334 
  1414 
  1414 
  1415 processLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError
  1415 processLine:lineString encoding:encodingSymbolOrEncoder file:fileName printErrorWith:printError
  1416     "process a single valid line (i.e. #ifdef & #include has already been processed)"
  1416     "process a single valid line (i.e. #ifdef & #include has already been processed)"
  1417 
  1417 
  1418     self class
  1418     self class
  1419 	processResourceLine:lineString
  1419         processResourceLine:lineString
  1420 	encoding:encodingSymbolOrEncoder
  1420         encoding:encodingSymbolOrEncoder
  1421 	file:fileName
  1421         file:fileName
  1422 	printErrorWith:printError
  1422         printErrorWith:printError
  1423 	for:self
  1423         for:self
  1424 !
  1424 !
  1425 
  1425 
  1426 readFromFile:fileName directory:dirName
  1426 readFromFile:fileName directory:dirName
  1427     "read definitions from a file in a directory"
  1427     "read definitions from a file in a directory"
  1428 
  1428 
  1430 
  1430 
  1431     fileReadFailed := false.
  1431     fileReadFailed := false.
  1432     "/ need to catch errors here, as the handler might itself need resources.
  1432     "/ need to catch errors here, as the handler might itself need resources.
  1433     "/ (happens when da.rs is not present in libbasic/resources.rs)
  1433     "/ (happens when da.rs is not present in libbasic/resources.rs)
  1434     ExternalStream openErrorSignal handle:[:ex |
  1434     ExternalStream openErrorSignal handle:[:ex |
  1435 	Transcript showCR:'ResourcePack: failed to open file: ',fileName asString,' in ',dirName asString.
  1435         Transcript showCR:'ResourcePack: failed to open file: ',fileName asString,' in ',dirName asString.
  1436 	inStream := nil.
  1436         inStream := nil.
  1437     ] do:[
  1437     ] do:[
  1438 	dirName = 'resources' ifTrue:[
  1438         dirName = 'resources' ifTrue:[
  1439 	    inStream := Smalltalk resourceFileStreamFor:fileName
  1439             inStream := Smalltalk resourceFileStreamFor:fileName
  1440 	] ifFalse:[
  1440         ] ifFalse:[
  1441 	    inStream := Smalltalk systemFileStreamFor:
  1441             inStream := Smalltalk systemFileStreamFor:
  1442 			    (dirName isNil
  1442                             (dirName isNil
  1443 				ifTrue:[fileName]
  1443                                 ifTrue:[fileName]
  1444 				ifFalse:[dirName asFilename construct:fileName]).
  1444                                 ifFalse:[dirName asFilename construct:fileName]).
  1445 	].
  1445         ].
  1446     ].
  1446     ].
  1447 
  1447 
  1448     inStream isNil ifTrue:[
  1448     inStream isNil ifTrue:[
  1449 	"
  1449         "
  1450 	 an empty pack
  1450          an empty pack
  1451 	"
  1451         "
  1452 	^ self nonexistingFileRead
  1452         ^ self nonexistingFileRead
  1453     ].
  1453     ].
  1454 
  1454 
  1455     triedFilename := inStream pathName.
  1455     triedFilename := inStream pathName.
  1456     [
  1456     [
  1457 	ok := self readFromResourceStream:inStream in:(triedFilename asFilename directoryName).
  1457         ok := self readFromResourceStream:inStream in:(triedFilename asFilename directoryName).
  1458     ] ensure:[
  1458     ] ensure:[
  1459 	inStream close.
  1459         inStream close.
  1460     ].
  1460     ].
  1461 
  1461 
  1462     ok ifTrue:[
  1462     ok ifTrue:[
  1463 	packsFileName := triedFilename
  1463         packsFileName := triedFilename
  1464     ] ifFalse:[
  1464     ] ifFalse:[
  1465 	fileReadFailed := true.
  1465         fileReadFailed := true.
  1466 
  1466 
  1467 	('ResourcePack [warning]: "' , triedFilename , '" contains error(s) - data may be incomplete.') errorPrintCR.
  1467         ('ResourcePack [warning]: "' , triedFilename , '" contains error(s) - data may be incomplete.') errorPrintCR.
  1468     ].
  1468     ].
  1469 
  1469 
  1470     "Modified: / 20-08-2011 / 17:10:02 / cg"
  1470     "Modified: / 20-08-2011 / 17:10:02 / cg"
  1471 !
  1471 !
  1472 
  1472