[etoys-dev] Etoys: System-bf.16.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 24 08:04:17 EDT 2010


Bert Freudenberg uploaded a new version of System to project Etoys:
http://source.squeak.org/etoys/System-bf.16.mcz

==================== Summary ====================

Name: System-bf.16
Author: bf
Time: 24 May 2010, 2:03:24 pm
UUID: edbb42e2-522c-4212-8118-49c8e67eb5ee
Ancestors: System-Richo.15

- move essential classes back from GetText package to System-Localization

=============== Diff against System-Richo.15 ===============

Item was added:
+ ----- Method: InternalTranslator>>translate:inDomain: (in category 'translation') -----
+ translate: aString inDomain: aDomainName 
+ 	| translator |
+ 	^ self generics
+ 		at: aString
+ 		ifAbsent: [self localeID hasParent
+ 				ifTrue: [translator := self class cachedTranslations
+ 								at: self localeID parent
+ 								ifAbsent: [^ aString].
+ 					translator translate: aString inDomain: aDomainName]
+ 				ifFalse: [aString]]!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>localeID: (in category 'initialize-release') -----
+ localeID: anID
+ 	id := anID!

Item was added:
+ ----- Method: Locale class>>switchAndInstallFontToID:gently: (in category 'accessing') -----
+ switchAndInstallFontToID: localeID gently: gentlyFlag
+ 
+ 	| locale result env envFound ret fontInImage menu |
+ 	"Assumption: Rainbow => can try Pango"
+ 	"Logic:
+ 		- in Sugar, we don't bother asking any questions, and we don't bother automatically loading fonts.
+ 			in Sugar, and if the font is available, use the font. 
+ 			in Sugar, and if the font is not in the image, try to enable Pango.
+ 			- if the previous step fails, notify the user that you cannot switch to the language.
+ 		- not in Rainbow, 
+ 			- if the font is in the image, use the font.
+ 			- if the font is not in the image,
+ 				- ask to choose:
+ 					- load font
+ 					- try to enable pango, if pango is available
+ 					- or cancel.
+ 			- if the previous step fails, notify the user that you cannot switch to the language.
+ 	Details:
+ 		- how to check non-pango font is available:
+ 			- if the language environment for the locale doesn't exist, the font is not available.
+ 			- if font loading fails, it is not available.
+ 		- how to check if the language environment doesn't exist:
+ 			- if the locales languageEnvironment is Latin1 but the locale isn't it is not available.
+ 	"	
+ 	locale := Locale localeID: localeID.
+ 	env := locale languageEnvironment.
+ 	result := true.
+ 	envFound := (Latin1Environment supportedLanguages includes: locale isoLanguage) or: [(env isMemberOf: Latin1Environment) not].
+ 	fontInImage := envFound and: [env isFontAvailable].
+ 	SugarLauncher isRunningInSugar ifTrue: [
+ 		fontInImage ifFalse: [
+ 			"font is not available in the image.  Even don't ask for font installation."
+ 			Cursor wait showWhile: [
+ 				Preferences setPreference: #usePangoRenderer toValue: true.
+ 				TextMorph usePango: true]].
+ 	] ifFalse: [
+ 		fontInImage ifFalse: [
+ 			menu := MenuMorph new.
+ 			menu defaultTarget: menu.
+ 			envFound ifTrue: [menu add: 'load font' translated selector: #modalSelection: argument: #loadFont].
+ 			RomePluginCanvas pangoIsAvailable ifTrue: [menu add:  'enable Pango' translated selector: #modalSelection: argument: #enablePango].
+ 			menu add:  'cancel' translated selector: #modalSelection: argument: #cancel.
+ 			menu addTitle: 'This language needs additional fonts.
+ Do you want to install the fonts?' translated.
+ 			ret := menu invokeModal.
+ 			ret = #loadFont ifTrue: [result := env installFont. result ifTrue: [StrikeFont setupDefaultFallbackTextStyle]].
+ 			ret = #enablePango ifTrue: [
+ 				(result := RomePluginCanvas pangoIsAvailable) ifTrue: [
+ 					Cursor wait showWhile: [
+ 						Preferences setPreference: #usePangoRenderer toValue: true.
+ 						TextMorph usePango: true]]].
+ 			(ret ~~ #loadFont and: [ret ~~ #enablePango]) ifTrue: [result := false]]].
+ 
+ 	result ifFalse: [self inform: 'Cannot load additional fonts' translated] ifTrue: [self switchTo: locale gently: gentlyFlag].
+ !

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>privateStartUp (in category 'class initialization') -----
+ privateStartUp
+ 	self resetCaches.
+ 	GetTextTranslator privateStartUp.
+ 	InternalTranslator privateStartUp.
+ 	self localeChanged.!

Item was added:
+ ----- Method: InternalTranslator>>rawPhrase:translation: (in category 'translation') -----
+ rawPhrase: phraseString translation: translationString 
+ 	self generics at: phraseString put: translationString asString.
+ !

Item was added:
+ Object subclass: #Locale
+ 	instanceVariableNames: 'id shortDate longDate time decimalSymbol digitGrouping currencySymbol currencyNotation measurement offsetLocalToUTC offsetVMToUTC dstActive'
+ 	classVariableNames: 'Current CurrentPlatform KnownLocales LanguageSymbols LocaleChangeListeners PlatformEncodings Previous'
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!
+ 
+ !Locale commentStamp: '<historical>' prior: 0!
+ Main comment stating the purpose of this class and relevant relationship to other classes.
+ 
+ 
+ 
+ 	http://www.w3.org/WAI/ER/IG/ert/iso639.htm
+ 	http://www.oasis-open.org/cover/iso639a.html
+ 	See also
+ 	http://oss.software.ibm.com/cvs/icu/~checkout~/icuhtml/design/language_code_issues.html
+ 	http://www.w3.org/Protocols/rfc2616/rfc2616-sec3.html#sec3.10
+ 	
+ ISO 3166
+ http://mitglied.lycos.de/buran/knowhow/codes/locales/
+ !

Item was added:
+ Object subclass: #LocaleID
+ 	instanceVariableNames: 'isoLanguage isoCountry'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!

Item was added:
+ ----- Method: Locale>>primLanguage (in category 'system primitives') -----
+ primLanguage
+ 	"returns string with language tag according to ISO 639"
+ 	<primitive:'primitiveLanguage' module: 'LocalePlugin'>
+ 	^'en'
+ 
+ !

Item was added:
+ ----- Method: Locale>>iconForNativeLanguage (in category 'accessing') -----
+ iconForNativeLanguage
+ 
+ 	^ (NaturalLanguageFormTranslator localeID: self localeID) translate: 'LanguageNameInNativeLanguage'.
+ !

Item was added:
+ ----- Method: Locale class>>localeChangedGently (in category 'notification') -----
+ localeChangedGently
+ 
+ 	#(#ParagraphEditor #BitEditor #FormEditor #StandardSystemController )
+ 		do: [:key | Smalltalk
+ 				at: key
+ 				ifPresent: [:class | class initialize]].
+ 	PartsBin localeChangedGently.
+ 	Project localeChangedGently.
+ 	PaintBoxMorph localeChangedGently.
+ 	ColorPickerMorph localeChangedGently.
+ 	Preferences localeChangedGently.
+ !

Item was added:
+ ----- Method: Locale>>isoLocale (in category 'accessing') -----
+ isoLocale
+ 	"<language>-<country>"
+ 	^self isoCountry
+ 		ifNil: [self isoLanguage]
+ 		ifNotNil: [self isoLanguage , '-' , self isoCountry]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>localeID (in category 'accessing') -----
+ localeID
+ 	^id!

Item was added:
+ ----- Method: Locale>>primCurrencyNotation (in category 'system primitives') -----
+ primCurrencyNotation
+ 	"Returns boolean if symbol is pre- (true) or post-fix (false)"
+ 	<primitive: 'primitiveCurrencyNotation' module: 'LocalePlugin'>
+ 	^true!

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso3Alternate: (in category 'initialize') -----
+ iso3Alternate: aString
+ 	iso3Alternate := aString ifEmpty: [nil] ifNotEmpty: [aString]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>generics (in category 'accessing') -----
+ generics
+ 	^generics ifNil: [generics := Dictionary new]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>cachedTranslations (in category 'accessing') -----
+ cachedTranslations
+ 	"CachedTranslations := nil" 
+ 	^CachedTranslations ifNil: [CachedTranslations := Dictionary new]!

Item was added:
+ ----- Method: Locale>>isoCountry (in category 'accessing') -----
+ isoCountry
+ 	^self localeID isoCountry!

Item was added:
(excessive method size, no diff calculated)

Item was added:
+ ----- Method: Locale>>determineLocale (in category 'accessing') -----
+ determineLocale
+ 	self localeID: self determineLocaleID!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>isDomainLoaded: (in category 'accessing') -----
+ isDomainLoaded: aDomainName
+ 	"ask if translation dictionary for the domain has been loaded and available now for use"
+ 	self subclassResponsibility.!

Item was added:
+ ----- Method: LocaleID>>displayLanguage (in category 'accessing') -----
+ displayLanguage
+ 	| language |
+ 	language := (ISOLanguageDefinition iso2LanguageTable
+ 				at: self isoLanguage
+ 				ifAbsent: [^ self isoLanguage]) language.
+ 	^ self isoCountry
+ 		ifNil: [language]
+ 		ifNotNil: [language , ' (' , self displayCountry , ')']!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>availableLanguageLocaleIDs (in category 'accessing') -----
+ availableLanguageLocaleIDs
+ 	"Return the locale ids for the currently available languages.  
+ 	Meaning those which either internally or externally have  
+ 	translations available."
+ 	"NaturalLanguageTranslator availableLanguageLocaleIDs"
+ 	^ self translators values collect:[:each | each localeID]!

Item was added:
+ ----- Method: Locale class>>startUp: (in category 'system startUp') -----
+ startUp: resuming
+ 	| newID |
+ 	resuming ifFalse: [^self].
+ 	(Preferences valueOfFlag: #useLocale)
+ 		ifTrue: [
+ 			DateAndTime localTimeZone: (TimeZone
+ 				offset:  (Duration minutes: Locale current offsetLocalToUTC)
+ 				name: 'Local Time'
+ 				abbreviation: 'LT').
+ 			newID := self current determineLocaleID.
+ 			newID ~= LocaleID current
+ 				ifTrue: [self switchAndInstallFontToID: newID gently: true]]!

Item was added:
+ ----- Method: LocaleID class>>posixName: (in category 'instance creation') -----
+ posixName: aString 
+ 	^ self
+ 		isoString: (aString copyReplaceAll: '_' with: '-')!

Item was added:
+ ----- Method: LocaleID>>hash (in category 'comparing') -----
+ hash
+ 	^self isoLanguage hash bitXor: self isoCountry hash!

Item was added:
+ ----- Method: InternalTranslator>>removeUntranslated: (in category 'translation') -----
+ removeUntranslated: untranslated
+ 
+ 	self class allKnownPhrases removeKey: untranslated ifAbsent: [].
+ !

Item was added:
+ ----- Method: ISOLanguageDefinition class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"ISOLanguageDefinition initialize"
+ 
+ 	ISO3Table := nil.
+ 	ISO2Table := nil!

Item was added:
+ ----- Method: Locale>>primShortDateFormat (in category 'system primitives') -----
+ primShortDateFormat
+ 	"Returns the short date format
+ 	d day, m month, y year,
+ 	double symbol is null padded, single not padded (m=6, mm=06)
+ 	dddd weekday
+ 	mmmm month name"
+ 	<primitive:'primitiveShortDateFormat' module: 'LocalePlugin'>
+ 	^'m/d/yy'!

Item was added:
+ NaturalLanguageTranslator subclass: #InternalTranslator
+ 	instanceVariableNames: 'generics'
+ 	classVariableNames: 'AllKnownPhrases CachedTranslations'
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!
+ 
+ !InternalTranslator commentStamp: 'tak 10/19/2007 11:12' prior: 0!
+ An InternalTranslator is used a translation dictionary in a image.
+ You can use it without any external translation file.
+ 
+ Structure:
+  generics		Dictionary -- msgid -> msgstr
+ !

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>saveFormsOn: (in category 'i/o') -----
+ saveFormsOn: aStream
+ 
+ 	| rr |
+ 	rr _ ReferenceStream on: aStream.
+ 	rr nextPut: {id isoString. generics}.
+ 	rr close.
+ !

Item was added:
+ ----- Method: Locale class>>switchTo: (in category 'accessing') -----
+ switchTo: locale
+ 	self switchTo: locale gently: false.
+ !

Item was added:
+ ----- Method: Locale class>>switchTo:gently: (in category 'accessing') -----
+ switchTo: locale gently: gentlyFlag
+ 	"Locale switchTo: (Locale isoLanguage: 'de')"
+ 	| availableID |
+ 	availableID := (NaturalLanguageTranslator availableForLocaleID: locale localeID) localeID.
+ 	Current localeID = availableID
+ 		ifFalse: [Previous _ Current.
+ 				CurrentPlatform := Current := Locale localeID: availableID.
+ 				NaturalLanguageTranslator localeChanged.
+ 				gentlyFlag ifTrue: [self localeChangedGently] ifFalse: [self localeChanged]]!

Item was added:
+ ----- Method: Locale>>primMeasurement (in category 'system primitives') -----
+ primMeasurement
+ 	"Returns boolean denoting metric(true) or imperial(false)."
+ 	<primitive:'primitiveMeasurementMetric' module: 'LocalePlugin'>
+ 	^true
+ !

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>availableForLocaleID: (in category 'accessing') -----
+ availableForLocaleID: localeID 
+ 	"Answer available locale ID.
+ 	If translator is not found for correct locale ID, then isoLanguage is
+ 	attempted for the key."
+ 	^ self translators
+ 		at: localeID
+ 		ifAbsent: [localeID hasParent
+ 				ifTrue: [self translators
+ 						at: localeID parent
+ 						ifAbsent: [self default]]
+ 				ifFalse: [self default]]!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>initialize (in category 'class initialization') -----
+ initialize
+ 	Smalltalk addToStartUpList: NaturalLanguageTranslator after: FileDirectory.
+ !

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>translate:toLocaleID:inDomain: (in category 'translation') -----
+ translate: aString toLocaleID: localeID inDomain: aDomainName
+ 	^ (self availableForLocaleID: localeID)
+ 		translate: aString inDomain: aDomainName!

Item was added:
+ ----- Method: Locale class>>localeChanged (in category 'notification') -----
+ localeChanged
+ 
+ 	#(#ParagraphEditor #BitEditor #FormEditor #StandardSystemController )
+ 		do: [:key | Smalltalk
+ 				at: key
+ 				ifPresent: [:class | class initialize]].
+ 	PartsBin localeChanged.
+ 	Project localeChanged.
+ 	PaintBoxMorph localeChanged.
+ 	ColorPickerMorph localeChanged.
+ 	Preferences localeChanged!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>default (in category 'accessing') -----
+ default
+ 	"Answer translator for backstop"
+ 	"self default translate: 'test'"
+ 	^ self new
+ 		localeID: (LocaleID isoLanguage: 'en')!

Item was added:
+ ----- Method: InternalTranslator classSide>>privateStartUp (in category 'class initialization') -----
+ privateStartUp
+ 	self loadAvailableExternalLocales.
+ 	self mergeLegacyTranslators.
+ !

Item was added:
+ ----- Method: Locale class>>isoLanguage:isoCountry: (in category 'accessing') -----
+ isoLanguage: isoLanguage isoCountry: isoCountry
+ 	^self localeID: (LocaleID  isoLanguage: isoLanguage isoCountry: isoCountry)!

Item was added:
+ ----- Method: LocaleID>>posixName (in category 'printing') -----
+ posixName
+ 	"(LocaleID isoString: 'es-MX') posixName"
+ 	"(LocaleID isoString: 'es') posixName"
+ 	"language[_territory]"
+ 	^ self isoCountry
+ 		ifNil: [self isoLanguage]
+ 		ifNotNil: [self isoLanguage , '_' , self isoCountry]!

Item was added:
+ ----- Method: InternalTranslator classSide>>translationSuffix (in category 'private') -----
+ translationSuffix
+ 	^'translation'!

Item was added:
+ ----- Method: Locale class>>initKnownLocales (in category 'private') -----
+ initKnownLocales
+ 	| locales |
+ 	locales := Dictionary new.
+ 
+ 	"Init the locales for which we have translations"
+ 	InternalTranslator availableLanguageLocaleIDs do: [:id |
+ 		locales at: id put: (Locale new localeID: id)].
+ 	^locales!

Item was added:
+ ----- Method: Locale>>fetchISOCountry (in category 'private') -----
+ fetchISOCountry
+ 	"Locale current fetchISOCountry"
+ 	| countryCode |
+ 	countryCode := self primCountry
+ 				ifNil: [^ nil].
+ 	^ countryCode copyUpTo: 0 asCharacter!

Item was added:
+ ----- Method: Locale>>primDST (in category 'system primitives') -----
+ primDST
+ 	"Returns boolean if DST  (daylight saving time) is active or not"
+ 	<primitive:'primitiveDaylightSavings' module: 'LocalePlugin'>
+ 	^false!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>translate: (in category 'translation') -----
+ translate: aString
+ 	^self translate: aString 
+ 		inDomain: TextDomainManager defaultDomain!

Item was added:
+ ----- Method: Locale class>>currentPlatform: (in category 'accessing') -----
+ currentPlatform: locale
+ 	CurrentPlatform := locale.
+ 	LanguageEnvironment startUp.
+ !

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso2LanguageDefinition: (in category 'accessing') -----
+ iso2LanguageDefinition: aString
+ 	^self iso2LanguageTable at: aString!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>translate:toLocaleID: (in category 'translation') -----
+ translate: aString toLocaleID: localeID
+ 	"translate for default domain"
+ 	^ (self availableForLocaleID: localeID)
+ 		translate: aString!

Item was added:
+ ----- Method: LocaleID>>translator (in category 'accessing') -----
+ translator
+ 	^ InternalTranslator localeID: self !

Item was changed:
  SystemOrganization addCategory: #'System-Applications'!
  SystemOrganization addCategory: #'System-Change Notification'!
  SystemOrganization addCategory: #'System-Changes'!
  SystemOrganization addCategory: #'System-Clipboard-Extended'!
  SystemOrganization addCategory: #'System-Compiler'!
  SystemOrganization addCategory: #'System-Digital Signatures'!
  SystemOrganization addCategory: #'System-Download'!
  SystemOrganization addCategory: #'System-Environments'!
  SystemOrganization addCategory: #'System-Exceptions Kernel'!
  SystemOrganization addCategory: #'System-FilePackage'!
  SystemOrganization addCategory: #'System-FileRegistry'!
  SystemOrganization addCategory: #'System-Finalization'!
+ SystemOrganization addCategory: #'System-Localization'!
  SystemOrganization addCategory: #'System-Object Events'!
  SystemOrganization addCategory: #'System-Object Storage'!
  SystemOrganization addCategory: #'System-Pools'!
  SystemOrganization addCategory: #'System-Preferences'!
  SystemOrganization addCategory: #'System-Serial Port'!
  SystemOrganization addCategory: #'System-Support'!
  SystemOrganization addCategory: #'System-Tools'!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>translateWithoutLoading:toLocaleID: (in category 'translation') -----
+ translateWithoutLoading: aString toLocaleID: localeID
+ 	"translate for default domain"
+ 	^self translateWithoutLoading: aString toLocaleID: localeID inDomain: TextDomainManager defaultDomain.
+ !

Item was added:
+ ----- Method: Locale>>fetchISO2Language (in category 'private') -----
+ fetchISO2Language
+ 	"Locale current fetchISO2Language"
+ 	| lang isoLang |
+ 	lang := self primLanguage.
+ 	lang ifNil: [^nil].
+ 	lang := lang copyUpTo: 0 asCharacter.
+ 	lang size == 2
+ 		ifTrue: [^lang].
+ 	isoLang := ISOLanguageDefinition iso3LanguageDefinition: lang.
+ 	^isoLang
+ 		ifNil: [nil]
+ 		ifNotNil: [isoLang iso2]!

Item was added:
+ ----- Method: InternalTranslator>>isDomainLoaded: (in category 'accessing') -----
+ isDomainLoaded: aDomainName
+ 	^true
+ !

Item was added:
+ ----- Method: InternalTranslator>>phrase:translation: (in category 'translation') -----
+ phrase: phraseString translation: translationString 
+ 	self generics at: phraseString put: translationString asString.
+ 	self changed: #translations.
+ 	self changed: #untranslated.!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>initISO3LanguageTable (in category 'private') -----
+ initISO3LanguageTable
+ 	"ISOLanguageDefinition initIso3LanguageTable"
+ 
+ 	| table |
+ 	table := ISOLanguageDefinition readISOLanguagesFrom: ISOLanguageDefinition isoLanguages readStream.
+ 	table addAll: self extraISO3Definitions.
+ 	^table!

Item was added:
+ ----- Method: InternalTranslator>>fileOutOn:keys:withBOM: (in category 'fileIn/fileOut') -----
+ fileOutOn: aStream keys: keys withBOM: bomFlag
+ 	"self current fileOutOn: Transcript. Transcript endEntry"
+ 	self fileOutHeaderOn: aStream withBOM: bomFlag.
+ 	(keys
+ 		ifNil: [generics keys asSortedCollection])
+ 		do: [:key | self
+ 				nextChunkPut: (generics associationAt: key)
+ 				on: aStream].
+ 	keys
+ 		ifNil: [self untranslated
+ 				do: [:each | self nextChunkPut: each -> '' on: aStream]].
+ 	aStream nextPut: $!!;
+ 		 cr!

Item was added:
+ ----- Method: InternalTranslator classSide>>availableLanguageLocaleIDs (in category 'accessing') -----
+ availableLanguageLocaleIDs
+ 	"Return locale ids for the internal translation dictionary."
+ 	"InternalTranslator availableLanguageLocaleIDs"
+ 	^ self cachedTranslations values collect:[:each | each localeID]!

Item was added:
+ ----- Method: Locale class>>localeID: (in category 'accessing') -----
+ localeID: id
+ 	^self knownLocales at: id ifAbsentPut: [Locale new localeID: id]!

Item was added:
+ ----- Method: LocaleID>>isoCountry (in category 'accessing') -----
+ isoCountry
+ 	^isoCountry!

Item was added:
+ ----- Method: InternalTranslator classSide>>directoryForLanguage:country:create: (in category 'private loading') -----
+ directoryForLanguage: isoLanguage country: isoCountry create: createDir
+ 	"Try to locate the <prefs>/locale/<language>{/<country>} folder.
+ 	If createDir is set, create the path down to country or language, depending on wether it's specified..
+ 	Return the directory for country or language depending on specification.
+ 	If neither exists, nil"
+ 
+ 	"NaturalLanguageTranslator directoryForLanguage: 'es' country: nil create: true"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'de' country: 'DE' create: true"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'en' country: 'US' create: false"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'en' country: nil create: true"
+ 
+ 	"If this fails, there is nothing we can do about it here"
+ 	| localeDir  countryDir languageDir |
+ 	localeDir := self localeDirCreate: createDir.
+ 	localeDir ifNil: [^nil].
+ 
+ 	isoCountry ifNil: [
+ 		languageDir := localeDir directoryNamed: isoLanguage.
+ 		createDir
+ 			ifTrue: [languageDir assureExistence].
+ 		^languageDir exists
+ 			ifTrue: [languageDir]
+ 			ifFalse: [nil]].
+ 
+ 	countryDir := languageDir directoryNamed: isoCountry.
+ 	createDir
+ 		ifTrue: [countryDir assureExistence].
+ 
+ 	^countryDir exists
+ 		ifTrue: [countryDir]
+ 		ifFalse: [nil]!

Item was added:
+ ----- Method: Locale class>>previous (in category 'accessing') -----
+ previous
+ 
+ 	^ Previous
+ !

Item was added:
+ ----- Method: ISOLanguageDefinition class>>readISOLanguagesFrom: (in category 'private') -----
+ readISOLanguagesFrom: stream
+ 	"ISOLanguageDefinition readISOLanguagesFrom: ISOLanguageDefinition isoLanguages readStream "
+ 	| languages language code3 index line |
+ 	languages := Dictionary new.
+ 	[stream atEnd
+ 		or: [(line := stream nextLine readStream) atEnd]]
+ 		whileFalse: [
+ 			language := ISOLanguageDefinition new.
+ 			code3 := line upTo: Character tab.
+ 			(index := code3 indexOf: $/) > 0
+ 				ifTrue: [
+ 					language iso3: (code3 copyFrom: 1 to: index-1).
+ 					language iso3Alternate: (code3 copyFrom: index+1 to: code3 size)]
+ 				ifFalse: [language iso3: code3].
+ 			language
+ 				iso2: (line upTo: Character tab);
+ 				language: line upToEnd.
+ 			languages at: language iso3 put: language].
+ 	^languages!

Item was added:
+ ----- Method: Locale>>determineLocaleID (in category 'accessing') -----
+ determineLocaleID
+ 	"Locale current determineLocaleID"
+ 	| isoLang isoCountry |
+ 	isoLang := self fetchISO2Language
+ 				ifNil: [^ self localeID].
+ 	isoCountry := self fetchISOCountry
+ 				ifNil: [^ LocaleID isoLanguage: isoLang].
+ 	^ LocaleID isoLanguage: isoLang isoCountry: isoCountry!

Item was added:
+ ----- Method: InternalTranslator>>translations (in category 'accessing') -----
+ translations
+ 	^self generics!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>startUp: (in category 'class initialization') -----
+ startUp: resuming 
+ 	resuming
+ 		ifFalse: [^ self].
+ 	self privateStartUp.!

Item was added:
+ ----- Method: InternalTranslator>>loadFromStream: (in category 'private store-retrieve') -----
+ loadFromStream: stream 
+ 	"Load translations from an external file"
+ 	| header isFileIn |
+ 	header := '''Translation dictionary'''.
+ 	isFileIn := (stream next: header size)
+ 				= header.
+ 	stream reset.
+ 	isFileIn
+ 		ifTrue: [stream fileInAnnouncing: 'Loading ' translated, stream localName]
+ 		ifFalse: [self loadFromRefStream: stream]!

Item was added:
+ ----- Method: InternalTranslator>>loadFromRefStream: (in category 'private store-retrieve') -----
+ loadFromRefStream: stream 
+ 	"Load translations from an external file"
+ 	| loadedArray refStream |
+ 	refStream := ReferenceStream on: stream.
+ 	[loadedArray := refStream next]
+ 		ensure: [refStream close].
+ 	self processExternalObject: loadedArray !

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso3Alternate (in category 'accessing') -----
+ iso3Alternate
+ 	^iso3Alternate ifNil: ['']!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>removeLocaleID: (in category 'accessing') -----
+ removeLocaleID: localeID 
+ 	"self removeLocaleID: (LocaleID isoString: 'ja-kids')"
+ 	^ self translators
+ 		removeKey: localeID
+ 		ifAbsent: []!

Item was added:
+ ----- Method: Locale class>>knownLocales (in category 'private') -----
+ knownLocales
+ 	"KnownLocales := nil"
+ 	^KnownLocales ifNil: [KnownLocales := self initKnownLocales]!

Item was added:
+ Object subclass: #ISOLanguageDefinition
+ 	instanceVariableNames: 'iso3 iso2 iso3Alternate language'
+ 	classVariableNames: 'ISO2Countries ISO2Table ISO3Countries ISO3Table'
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!

Item was added:
+ ----- Method: Locale>>localeID (in category 'accessing') -----
+ localeID
+ 	^id!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>domainRegistered: (in category 'accessing') -----
+ domainRegistered: aDomainName
+ 	"notify that new TextDomain is registered"
+ 	self translators do: [:each | each domainRegistered: aDomainName]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>isoLanguage: (in category 'accessing') -----
+ isoLanguage: isoLanguage
+ 	"Return the generic language translator as there is no information about the country code"
+ 
+ 	^self isoLanguage: isoLanguage isoCountry: nil!

Item was added:
+ ----- Method: Locale>>isoLanguage (in category 'accessing') -----
+ isoLanguage
+ 	^self localeID isoLanguage!

Item was added:
+ ----- Method: ISOLanguageDefinition>>language (in category 'accessing') -----
+ language
+ 	^language!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>localeChanged (in category 'accessing') -----
+ localeChanged
+ 	"notify some project starts to use this locale.
+ 	 this facility may use the event to load translation data dynamically" 
+ 	self current setCurrent
+ !

Item was added:
+ ----- Method: LocaleID class>>isoLanguage:isoCountry: (in category 'instance creation') -----
+ isoLanguage: langString isoCountry: countryStringOrNil
+ 	^self new isoLanguage: langString isoCountry: countryStringOrNil!

Item was added:
+ ----- Method: Locale>>primTimeFormat (in category 'system primitives') -----
+ primTimeFormat
+ 	"Returns string time format
+ 	Format is made up of 
+ 	h hour (h 12, H 24), m minute, s seconds, x (am/pm String)
+ 	double symbol is null padded, single not padded (h=6, hh=06)"
+ 	<primitive:'primitiveTimeFormat' module: 'LocalePlugin'>
+ 	^'h:mmx'!

Item was added:
+ ----- Method: InternalTranslator>>fileOutHeader (in category 'fileIn/fileOut') -----
+ fileOutHeader
+ 	^ '''Translation dictionary'''!

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso2 (in category 'accessing') -----
+ iso2
+ 	^iso2 ifNil: [self iso3]!

Item was added:
+ ----- Method: InternalTranslator classSide>>registerPhrase: (in category 'private') -----
+ registerPhrase: phrase
+ 	"Using a Dictionary so we can lookup existing string instead of creating needless copies when loading a translation."
+ 	self allKnownPhrases at: phrase put: phrase!

Item was added:
+ ----- Method: Locale>>offsetLocalToUTC (in category 'accessing') -----
+ offsetLocalToUTC
+ 	^self primTimezone!

Item was added:
+ ----- Method: InternalTranslator>>nextChunkPut:on: (in category 'fileIn/fileOut') -----
+ nextChunkPut: anObject on: aStream 
+ 	| i remainder terminator |
+ 	terminator := $!!.
+ 	remainder := anObject storeString.
+ 	[(i := remainder indexOf: terminator) = 0]
+ 		whileFalse: [aStream
+ 				nextPutAll: (remainder copyFrom: 1 to: i).
+ 			aStream nextPut: terminator.
+ 			"double imbedded terminators"
+ 			remainder := remainder copyFrom: i + 1 to: remainder size].
+ 	aStream nextPutAll: remainder.
+ 	aStream nextPut: terminator; cr.!

Item was added:
+ ----- Method: Locale>>primCountry (in category 'system primitives') -----
+ primCountry
+ 	"Returns string with country tag according to ISO 639"
+ 	<primitive: 'primitiveCountry' module: 'LocalePlugin'>
+ 	^'US'!

Item was added:
+ Object subclass: #NaturalLanguageTranslator
+ 	instanceVariableNames: 'id'
+ 	classVariableNames: 'Translators'
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!
+ 
+ !NaturalLanguageTranslator commentStamp: '<historical>' prior: 0!
+ abstract class of natural language translator.
+ Class side manages and holds loaded instances of concrete classes.!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>domainUnregistered: (in category 'accessing') -----
+ domainUnregistered: aDomainName
+ 	"notify that new TextDomain is unregistered.  Concrete subclass can responds to this event if needed"!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>initISOCountries (in category 'private') -----
+ initISOCountries
+ 	"ISOLanguageDefinition initISOCountries"
+ 	| iso3166Table |
+ 	iso3166Table := ISOLanguageDefinition buildIso3166CodesTables.
+ 	ISO2Countries := Dictionary new.
+ 	ISO3Countries := Dictionary new.
+ 	iso3166Table do: [:entry | 
+ 		ISO2Countries at: (entry at: 2) put: (entry at: 1).
+ 		ISO3Countries at: (entry at: 3) put: (entry at: 1)].
+ 	self extraCountryDefinitions do: [:entry | 
+ 		ISO2Countries at: (entry at: 2) put: (entry at: 1).
+ 		ISO3Countries at: (entry at: 3) put: (entry at: 1)]!

Item was added:
+ ----- Method: LocaleID>>= (in category 'comparing') -----
+ = anotherObject
+ 	self class == anotherObject class
+ 		ifFalse: [^false].
+ 	^self isoLanguage = anotherObject isoLanguage
+ 		and: [self isoCountry = anotherObject isoCountry]!

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso2: (in category 'initialize') -----
+ iso2: aString
+ 	iso2 := aString ifEmpty: [nil] ifNotEmpty: [aString]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>name:form: (in category 'accessing') -----
+ name: formName form: translatedForm 
+ 	self generics at: formName put: translatedForm.
+ !

Item was added:
+ ----- Method: Locale class>>determineCurrentLocale (in category 'private') -----
+ determineCurrentLocale
+ 	"For now just return the default locale.
+ 	A smarter way would be to determine the current platforms default locale."
+ 	"Locale determineCurrentLocale"
+ 
+ 	^self new determineLocale!

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso3 (in category 'accessing') -----
+ iso3
+ 	^iso3 ifNil: ['']!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>localeID: (in category 'accessing') -----
+ localeID: anID
+ 	id := anID!

Item was added:
+ ----- Method: LocaleID class>>isoString: (in category 'instance creation') -----
+ isoString: isoString
+ 	"Parse the isoString (<language>-<country>) into its components and return the matching LocaleID"
+ 	"LocaleID isoString: 'en' "
+ 	"LocaleID isoString: 'en-us' "
+ 
+ 	| parts language country |
+ 	parts := isoString findTokens: #($- ).
+ 	language := parts first.
+ 	parts size > 1
+ 		ifTrue: [country := parts second].
+ 	^self isoLanguage: language isoCountry: country!

Item was added:
+ ----- Method: InternalTranslator>>fileOutHeaderOn:withBOM: (in category 'user interface') -----
+ fileOutHeaderOn: aStream withBOM: bomFlag
+ 	bomFlag ifTrue: [
+ 		aStream binary.
+ 		UTF8TextConverter writeBOMOn: aStream.
+ 		aStream text.
+ 	].
+ 	aStream nextChunkPut: self fileOutHeader;
+ 		 cr.
+ 	aStream timeStamp; cr.
+ 	aStream nextPut: $!!.
+ 	aStream nextChunkPut: '(' , self class name , ' localeID: ' , id storeString , ')'.
+ 	aStream cr!

Item was added:
+ ----- Method: LocaleID>>parent (in category 'accessing') -----
+ parent
+ 	^self class isoLanguage: self isoLanguage!

Item was added:
+ ----- Method: Locale class>>initializePlatformEncodings (in category 'class initialization') -----
+ initializePlatformEncodings
+ 	"Locale initializePlatformEncodings"
+ 
+ 	| platform |
+ 	PlatformEncodings isNil ifTrue: [ PlatformEncodings := Dictionary new ].
+ 
+ 	platform := PlatformEncodings at: 'default' ifAbsentPut: Dictionary new.
+ 	platform
+ 		at: 'default' put: 'iso8859-1';
+ 		at: 'Win32 CE' put: 'utf-8';
+ 		yourself.
+ 
+ 	platform := PlatformEncodings at: 'ja' ifAbsentPut: Dictionary new.
+ 	platform
+ 		at: 'default' put: 'shift-jis';
+ 		at: 'unix' put: 'euc-jp';
+ 		at: 'Win32 CE' put: 'utf-8';
+ 		yourself.
+ 
+ 	platform := PlatformEncodings at: 'ko' ifAbsentPut: Dictionary new.
+ 	platform
+ 		at: 'default' put: 'euc-kr';
+ 		at: 'Win32 CE' put: 'utf-8';
+ 		yourself.
+ 
+ 	platform := PlatformEncodings at: 'zh' ifAbsentPut: Dictionary new.
+ 	platform
+ 		at: 'default' put: 'gb2312';
+ 		at: 'unix' put: 'euc-cn';
+ 		at: 'Win32 CE' put: 'utf-8';
+ 		yourself.
+ !

Item was added:
+ ----- Method: InternalTranslator>>fileOutHeaderOn: (in category 'user interface') -----
+ fileOutHeaderOn: aStream 
+ 	aStream binary.
+ 	UTF8TextConverter writeBOMOn: aStream.
+ 	aStream text.
+ 	aStream nextChunkPut: self fileOutHeader;
+ 		 cr.
+ 	aStream timeStamp; cr.
+ 	aStream nextPut: $!!.
+ 	aStream nextChunkPut: '(' , self class name , ' localeID: ' , id storeString , ')'.
+ 	aStream cr!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso2LanguageTable (in category 'private') -----
+ iso2LanguageTable
+ 	"ISOLanguageDefinition iso2LanguageTable"
+ 
+ 	ISO2Table ifNotNil: [^ISO2Table].
+ 	ISO2Table := Dictionary new: self iso3LanguageTable basicSize.
+ 	self iso3LanguageTable do: [:entry |
+ 		ISO2Table at: entry iso2 put: entry].
+ 	^ISO2Table!

Item was added:
+ ----- Method: LocaleID class>>previous (in category 'accessing') -----
+ previous
+ 	^Locale previous localeID!

Item was added:
+ ----- Method: InternalTranslator classSide>>removeLocaleID: (in category 'accessing') -----
+ removeLocaleID: localeID 
+ 	"self removeLocaleID: (LocaleID isoString: 'ja-kids')"
+ 	self cachedTranslations
+ 		removeKey: localeID
+ 		ifAbsent: [].
+ 	NaturalLanguageTranslator privateStartUp!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso3Countries (in category 'private') -----
+ iso3Countries
+ 	"ISOLanguageDefinition iso3Countries"
+ 	"ISO2Countries := nil. ISO3Countries := nil"
+ 
+ 	ISO3Countries ifNil: [self initISOCountries].
+ 	^ISO3Countries!

Item was added:
+ ----- Method: Locale class>>localeChangedListeners (in category 'notification') -----
+ localeChangedListeners
+ 	^LocaleChangeListeners ifNil: [LocaleChangeListeners _ OrderedCollection new]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>bitmapForJapanese (in category 'as yet unclassified') -----
+ bitmapForJapanese
+ 
+ 	^ (Form
+ 	extent: 54 at 17
+ 	depth: 16
+ 	fromArray: #( 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65536 0 1 65537 65537 65537 65537 0 0 0 0 1 0 0 0 0 65537 65537 1 65537 65537 65536 1 0 0 0 1 0 0 1 0 0 0 1 0 0 0 0 1 0 0 0 0 0 0 0 1 0 0 0 65536 0 0 65536 0 0 1 0 0 0 1 0 0 0 0 1 0 0 0 1 65537 65537 65536 1 0 0 0 1 0 0 65536 0 0 1 0 0 0 1 0 1 65537 65537 65537 65537 65537 65537 0 0 0 1 65537 65537 0 0 1 0 1 0 0 0 1 0 0 0 1 0 0 0 0 65537 65536 0 0 0 65537 65537 0 65536 1 0 0 0 65536 1 0 0 0 1 65537 65537 65537 65537 0 0 0 1 1 1 0 0 0 0 0 0 65536 1 0 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 0 1 1 1 0 0 0 65537 65537 65537 65537 65537 65537 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 0 65536 1 0 65536 0 0 0 0 0 0 0 0 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 1 0 1 0 1 0 0 65537 65537 1 65537 65537 65536 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 65536 65537 65537 65537 65536 65536 0 65536 1 1 0 0 65536 0 0 65536 0 65536 0 0 1 0 0 0 1 0 1 0 0 1 0 0 1 0 65536 1 1 0 0 65536 0 1 0 0 65536 0 0 1 65537 65537 65537 65537 0 0 0 0 1 0 0 0 0 65537 65537 1 65537 65537 65536 0 1 0 0 1 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0 0 0 0 0 0 0 0 65536 0 0 0 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 0 0)
+ 	offset: 0 at 0)!

Item was added:
+ ----- Method: InternalTranslator classSide>>allKnownPhrases (in category 'private') -----
+ allKnownPhrases
+ 	^AllKnownPhrases ifNil: [AllKnownPhrases := Dictionary new: 2051]!

Item was added:
+ ----- Method: Locale>>primVMOffsetToUTC (in category 'system primitives') -----
+ primVMOffsetToUTC
+ 	"Returns the offset in minutes between the VM and UTC.
+ 	If the VM does not support UTC times, this is 0.
+ 	Also gives us backward compatibility with old VMs as the primitive will fail and we then can return 0."
+ 	<primitive:'primitiveVMOffsetToUTC' module: 'LocalePlugin'>
+ 	^0!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso2Countries (in category 'private') -----
+ iso2Countries
+ 	"ISOLanguageDefinition iso2Countries"
+ 	"ISO2Countries := nil. ISO3Countries := nil"
+ 
+ 	ISO2Countries ifNil: [self initISOCountries].
+ 	^ISO2Countries!

Item was added:
+ ----- Method: Locale class>>current (in category 'accessing') -----
+ current
+ 	"Current := nil"
+ 	Current ifNil: [
+ 		Current := self determineCurrentLocale.
+ 		"Transcript show: 'Current locale: ' , Current localeID asString; cr"].
+ 	^Current!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>localeID (in category 'accessing') -----
+ localeID
+ 	^id!

Item was added:
+ ----- Method: Locale>>primTimezone (in category 'system primitives') -----
+ primTimezone
+ 	"The offset from UTC in minutes, with positive offsets being towards the east.
+ 	(San Francisco is in UTC -07*60 and Paris is in UTC +02*60 when daylight savings is in effect)."
+ 	<primitive:'primitiveTimezoneOffset' module: 'LocalePlugin'>
+ 	^0!

Item was added:
+ ----- Method: Locale>>printOn: (in category 'accessing') -----
+ printOn: aStream 
+ 	super printOn: aStream.
+ 	aStream nextPutAll: '(' , id printString , ')'!

Item was added:
+ ----- Method: InternalTranslator>>processExternalObject: (in category 'private store-retrieve') -----
+ processExternalObject: anArray 
+ 	"pivate - process the external object"
+ 
+ 	"new format -> {translations. untranslated}"
+ 
+ 	anArray second do: [:each | self class registerPhrase: each].
+ 
+ 	self mergeTranslations: anArray first!

Item was added:
+ ----- Method: InternalTranslator>>fileOutOn: (in category 'fileIn/fileOut') -----
+ fileOutOn: aStream 
+ 	"self current fileOutOn: Transcript. Transcript endEntry"
+ 	self fileOutOn: aStream keys: nil withBOM: true.
+ !

Item was added:
+ ----- Method: Locale class>>languageSymbol: (in category 'accessing') -----
+ languageSymbol: languageSymbol
+ 	"Locale languageSymbol: #Deutsch"
+ 
+ 	^self isoLanguage: (LanguageSymbols at: languageSymbol)!

Item was added:
+ ----- Method: Locale>>languageEnvironment (in category 'accessing') -----
+ languageEnvironment
+ 	^LanguageEnvironment localeID: self localeID!

Item was added:
+ ----- Method: Locale class>>defaultEncodingName: (in category 'platform specific') -----
+ defaultEncodingName: languageSymbol 
+ 	| encodings platformName osVersion |
+ 	platformName := SmalltalkImage current platformName.
+ 	osVersion := SmalltalkImage current getSystemAttribute: 1002.
+ 	encodings := self platformEncodings at: languageSymbol
+ 				ifAbsent: [self platformEncodings at: #default].
+ 	encodings at: platformName ifPresent: [:encoding | ^encoding].
+ 	encodings at: platformName , ' ' , osVersion
+ 		ifPresent: [:encoding | ^encoding].
+ 	^encodings at: #default!

Item was added:
+ ----- Method: LocaleID>>isoLanguage (in category 'accessing') -----
+ isoLanguage
+ 	^isoLanguage!

Item was added:
+ ----- Method: InternalTranslator classSide>>loadForLocaleIsoString:fromGzippedMimeLiteral: (in category 'file-services') -----
+ loadForLocaleIsoString: localeString fromGzippedMimeLiteral: mimeString 
+ 	"merge the translation from the mime literal."
+ 	| stream localeID translator gs rbStream s currentPlatform |
+ 	s := Base64MimeConverter mimeDecodeToBytes: mimeString readStream.
+ 	s reset.
+ 	gs := GZipReadStream on: s.
+ 	rbStream := MultiByteBinaryOrTextStream with: gs contents asString.
+ 	rbStream converter: UTF8TextConverter new.
+ 	rbStream reset.
+ 	localeID := LocaleID isoString: localeString.
+ 	currentPlatform := Locale currentPlatform.
+ 	[Locale
+ 		currentPlatform: (Locale localeID: localeID).
+ 	stream := ReadStream on: rbStream contents]
+ 		ensure: [Locale currentPlatform: currentPlatform].
+ 	translator := self localeID: localeID.
+ 	translator loadFromStream: stream.
+ 	LanguageEnvironment resetKnownEnvironments!

Item was added:
+ ----- Method: InternalTranslator classSide>>registeredPhraseFor: (in category 'private') -----
+ registeredPhraseFor: phrase
+ 	"Using a Dictionary so we can lookup existing string instead of creating needless copies when loading a translation."
+ 	^self allKnownPhrases at: phrase ifAbsentPut: [phrase]!

Item was added:
+ ----- Method: InternalTranslator classSide>>fileReaderServicesForFile:suffix: (in category 'file-services') -----
+ fileReaderServicesForFile: fullName suffix: suffix 
+ 	"Answer the file services associated with given file"
+ 	^ (suffix = self translationSuffix) | (suffix = '*')
+ 		ifTrue: [{self serviceMergeLanguageTranslations}]
+ 		ifFalse: [#()]!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>translateWithoutLoading:toLocaleID:inDomain: (in category 'translation') -----
+ translateWithoutLoading: aString toLocaleID: localeID inDomain: aDomainName
+ 	"try to translate with small footprint:
+ 		if GetTextTranslator hasn't loaded MO, try to use InternalTranslator.
+ 		if InternalTranslator isn't available, then actually load MO and use it"
+ 	| translator |
+ 	translator _ self availableForLocaleID: localeID.
+ 	(translator isDomainLoaded: aDomainName) ifFalse: [
+ 		(InternalTranslator availableLanguageLocaleIDs includes: localeID)
+ 			ifTrue:  [translator _ InternalTranslator localeID: localeID].
+ 	].
+ 	^translator translate: aString inDomain: aDomainName!

Item was added:
+ ----- Method: InternalTranslator>>mergeTranslations: (in category 'private store-retrieve') -----
+ mergeTranslations: newTranslations
+ 	"Merge a new set of translations into the exiting table.
+ 	Overwrites existing entries."
+ 
+ 	newTranslations keysAndValuesDo: [:key :value |
+ 		self rawPhrase: (self class registeredPhraseFor: key) translation: value].
+ 	self changed: #translations.
+ 	self changed: #untranslated.!

Item was added:
+ ----- Method: Locale class>>defaultInputInterpreter (in category 'platform specific') -----
+ defaultInputInterpreter
+ 	| platformName osVersion |
+ 	platformName := SmalltalkImage current platformName.
+ 	osVersion := SmalltalkImage current getSystemAttribute: 1002.
+ 	(platformName = 'Win32' and: [osVersion = 'CE']) 
+ 		ifTrue: [^NoInputInterpreter new].
+ 	platformName = 'Win32' ifTrue: [^MacRomanInputInterpreter new].
+ 	^NoInputInterpreter new!

Item was added:
+ ----- Method: Locale class>>stringForLanguageNameIs: (in category 'accessing') -----
+ stringForLanguageNameIs: localeID 
+ 	"Answer a string for a menu determining whether the given  
+ 	symbol is the project's natural language"
+ 	^ (self current localeID = localeID
+ 		ifTrue: ['<yes>']
+ 		ifFalse: ['<no>'])
+ 		, localeID displayName!

Item was added:
+ ----- Method: Locale class>>addLocalChangedListener: (in category 'notification') -----
+ addLocalChangedListener: anObjectOrClass
+ 	self localeChangedListeners add: anObjectOrClass!

Item was added:
+ ----- Method: InternalTranslator classSide>>serviceMergeLanguageTranslations (in category 'file-services') -----
+ serviceMergeLanguageTranslations
+ 	"Answer a service for merging of translation files"
+ 	^ SimpleServiceEntry
+ 		provider: self
+ 		label: 'merge the translation file' translatedNoop
+ 		selector: #mergeTranslationFileNamed:
+ 		description: 'merge the translation file into the language named like the file' translatedNoop
+ 		buttonLabel: 'merge' translatedNoop!

Item was added:
+ ----- Method: LocaleID>>isoString (in category 'accessing') -----
+ isoString
+ 	^self asString!

Item was added:
+ ----- Method: InternalTranslator classSide>>localeID: (in category 'accessing') -----
+ localeID: localeID 
+ 	"For backward compatibility, see NaturalLanguageTranslator >> fileOutHeaderOn:."
+ 	^ self newLocaleID: localeID!

Item was added:
+ ----- Method: ISOLanguageDefinition>>language: (in category 'initialize') -----
+ language: aString
+ 	language := aString!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>isoLanguages (in category 'private') -----
+ isoLanguages
+ 	"ISO 639: 3-letter codes"
+ 	^'aar	aa	Afar
+ abk	ab	Abkhazian
+ ace		Achinese
+ ach		Acoli
+ ada		Adangme
+ ady		Adyghe; Adygei
+ afa		Afro-Asiatic languages
+ afh		Afrihili
+ afr	af	Afrikaans
+ ain		Ainu
+ aka	ak	Akan
+ akk		Akkadian
+ alb/sqi	sq	Albanian
+ ale		Aleut
+ alg		Algonquian languages
+ alt		Southern Altai
+ amh	am	Amharic
+ ang		English, Old (ca.450-1100)
+ anp		Angika
+ apa		Apache languages
+ ara	ar	Arabic
+ arc		Official Aramaic (700-300 BCE); Imperial Aramaic (700-300 BCE)
+ arg	an	Aragonese
+ arm/hye	hy	Armenian
+ arn		Mapudungun; Mapuche
+ arp		Arapaho
+ art		Artificial languages
+ arw		Arawak
+ asm	as	Assamese
+ ast		Asturian; Bable; Leonese; Asturleonese
+ ath		Athapascan languages
+ aus		Australian languages
+ ava	av	Avaric
+ ave	ae	Avestan
+ awa		Awadhi
+ aym	ay	Aymara
+ aze	az	Azerbaijani
+ bad		Banda languages
+ bai		Bamileke languages
+ bak	ba	Bashkir
+ bal		Baluchi
+ bam	bm	Bambara
+ ban		Balinese
+ baq/eus	eu	Basque
+ bas		Basa
+ bat		Baltic languages
+ bej		Beja; Bedawiyet
+ bel	be	Belarusian
+ bem		Bemba
+ ben	bn	Bengali
+ ber		Berber languages)
+ bho		Bhojpuri
+ bih	bh	Bihari
+ bik		Bikol
+ bin		Bini; Edo
+ bis	bi	Bislama
+ bla		Siksika
+ bnt		Bantu languages
+ bos	bs	Bosnian
+ bra		Braj
+ bre	br	Breton
+ btk		Batak languages
+ bua		Buriat
+ bug		Buginese
+ bul	bg	Bulgarian
+ bur/mya	my	Burmese
+ byn		Blin; Bilin
+ cad		Caddo
+ cai		Central American Indian languages
+ car		Galibi Carib
+ cat	ca	Catalan; Valencian
+ cau		Caucasian languages
+ ceb		Cebuano
+ cel		Celtic languages
+ cha	ch	Chamorro
+ chb		Chibcha
+ che	ce	Chechen
+ chg		Chagatai
+ chi/zho	zh	Chinese
+ chk		Chuukese
+ chm		Mari
+ chn		Chinook jargon
+ cho		Choctaw
+ chp		Chipewyan; Dene Suline
+ chr		Cherokee
+ chu	cu	Church Slavic; Old Slavonic; Church Slavonic; Old Bulgarian; Old Church Slavonic
+ chv	cv	Chuvash
+ chy		Cheyenne
+ cmc		Chamic languages
+ cop		Coptic
+ cor	kw	Cornish
+ cos	co	Corsican
+ cpe		Creoles and pidgins, English based
+ cpf		Creoles and pidgins, French-based
+ cpp		Creoles and pidgins, Portuguese-based
+ cre	cr	Cree
+ crh		Crimean Tatar; Crimean Turkish
+ crp		Creoles and pidgins
+ csb		Kashubian
+ cus		Cushitic languages
+ cze/ces	cs	Czech
+ dak		Dakota
+ dan	da	Danish
+ dar		Dargwa
+ day		Land Dayak languages
+ del		Delaware
+ den		Slave (Athapascan)
+ dgr		Dogrib
+ din		Dinka
+ div	dv	Divehi; Dhivehi; Maldivian
+ doi		Dogri
+ dra		Dravidian languages
+ dsb		Lower Sorbian
+ dua		Duala
+ dum		Dutch, Middle (ca.1050-1350)
+ dut/nld	nl	Dutch; Flemish
+ dyu		Dyula
+ dzo	dz	Dzongkha
+ efi		Efik
+ egy		Egyptian (Ancient)
+ eka		Ekajuk
+ elx		Elamite
+ eng	en	English
+ enm		English, Middle (1100-1500)
+ epo	eo	Esperanto
+ est	et	Estonian
+ ewe	ee	Ewe
+ ewo		Ewondo
+ fan		Fang
+ fao	fo	Faroese
+ fat		Fanti
+ fij	fj	Fijian
+ fil		Filipino; Pilipino
+ fin	fi	Finnish
+ fiu		Finno-Ugrian languages)
+ fon		Fon
+ fre/fra	fr	French
+ frm		French, Middle (ca.1400-1600)
+ fro		French, Old (842-ca.1400)
+ frr		Northern Frisian
+ frs		Eastern Frisian
+ fry	fy	Western Frisian
+ ful	ff	Fulah
+ fur		Friulian
+ gaa		Ga
+ gay		Gayo
+ gba		Gbaya
+ gem		Germanic languages
+ geo/kat	ka	Georgian
+ ger/deu	de	German
+ gez		Geez
+ gil		Gilbertese
+ gla	gd	Gaelic; Scottish Gaelic
+ gle	ga	Irish
+ glg	gl	Galician
+ glv	gv	Manx
+ gmh		German, Middle High (ca.1050-1500)
+ goh		German, Old High (ca.750-1050)
+ gon		Gondi
+ gor		Gorontalo
+ got		Gothic
+ grb		Grebo
+ grc		Greek, Ancient (to 1453)
+ gre/ell	el	Greek, Modern (1453-)
+ grn	gn	Guarani
+ gsw		Swiss German; Alemannic; Alsatian
+ guj	gu	Gujarati
+ gwi		Gwich''in
+ hai		Haida
+ hat	ht	Haitian; Haitian Creole
+ hau	ha	Hausa
+ haw		Hawaiian
+ heb	he	Hebrew
+ her	hz	Herero
+ hil		Hiligaynon
+ him		Himachali
+ hin	hi	Hindi
+ hit		Hittite
+ hmn		Hmong
+ hmo	ho	Hiri Motu
+ hrv	hr	Croatian
+ hsb		Upper Sorbian
+ hun	hu	Hungarian
+ hup		Hupa
+ iba		Iban
+ ibo	ig	Igbo
+ ice/isl	is	Icelandic
+ ido	io	Ido
+ iii	ii	Sichuan Yi; Nuosu
+ ijo		Ijo languages
+ iku	iu	Inuktitut
+ ile	ie	Interlingue; Occidental
+ ilo		Iloko
+ ina	ia	Interlingua (International Auxiliary Language Association)
+ inc		Indic languages
+ ind	id	Indonesian
+ ine		Indo-European languages
+ inh		Ingush
+ ipk	ik	Inupiaq
+ ira		Iranian languages
+ iro		Iroquoian languages
+ ita	it	Italian
+ jav	jv	Javanese
+ jbo		Lojban
+ jpn	ja	Japanese
+ jpr		Judeo-Persian
+ jrb		Judeo-Arabic
+ kaa		Kara-Kalpak
+ kab		Kabyle
+ kac		Kachin; Jingpho
+ kal	kl	Kalaallisut; Greenlandic
+ kam		Kamba
+ kan	kn	Kannada
+ kar		Karen languages
+ kas	ks	Kashmiri
+ kau	kr	Kanuri
+ kaw		Kawi
+ kaz	kk	Kazakh
+ kbd		Kabardian
+ kha		Khasi
+ khi		Khoisan languages
+ khm	km	Central Khmer
+ kho		Khotanese; Sakan
+ kik	ki	Kikuyu; Gikuyu
+ kin	rw	Kinyarwanda
+ kir	ky	Kirghiz; Kyrgyz
+ kmb		Kimbundu
+ kok		Konkani
+ kom	kv	Komi
+ kon	kg	Kongo
+ kor	ko	Korean
+ kos		Kosraean
+ kpe		Kpelle
+ krc		Karachay-Balkar
+ krl		Karelian
+ kro		Kru languages
+ kru		Kurukh
+ kua	kj	Kuanyama; Kwanyama
+ kum		Kumyk
+ kur	ku	Kurdish
+ kut		Kutenai
+ lad		Ladino
+ lah		Lahnda
+ lam		Lamba
+ lao	lo	Lao
+ lat	la	Latin
+ lav	lv	Latvian
+ lez		Lezghian
+ lim	li	Limburgan; Limburger; Limburgish
+ lin	ln	Lingala
+ lit	lt	Lithuanian
+ lol		Mongo
+ loz		Lozi
+ ltz	lb	Luxembourgish; Letzeburgesch
+ lua		Luba-Lulua
+ lub	lu	Luba-Katanga
+ lug	lg	Ganda
+ lui		Luiseno
+ lun		Lunda
+ luo		Luo (Kenya and Tanzania)
+ lus		Lushai
+ mac/mkd	mk	Macedonian
+ mad		Madurese
+ mag		Magahi
+ mah	mh	Marshallese
+ mai		Maithili
+ mak		Makasar
+ mal	ml	Malayalam
+ man		Mandingo
+ mao/mri	mi	Maori
+ map		Austronesian languages
+ mar	mr	Marathi
+ mas		Masai
+ may/msa	ms	Malay
+ mdf		Moksha
+ mdr		Mandar
+ men		Mende
+ mga		Irish, Middle (900-1200)
+ mic		Mi''kmaq; Micmac
+ min		Minangkabau
+ mis		Uncoded languages
+ mkh		Mon-Khmer languages
+ mlg	mg	Malagasy
+ mlt	mt	Maltese
+ mnc		Manchu
+ mni		Manipuri
+ mno		Manobo languages
+ moh		Mohawk
+ mon	mn	Mongolian
+ mos		Mossi
+ mul		Multiple languages
+ mun		Munda languages
+ mus		Creek
+ mwl		Mirandese
+ mwr		Marwari
+ myn		Mayan languages
+ myv		Erzya
+ nah		Nahuatl languages
+ nai		North American Indian languages
+ nap		Neapolitan
+ nau	na	Nauru
+ nav	nv	Navajo; Navaho
+ nbl	nr	Ndebele, South; South Ndebele
+ nde	nd	Ndebele, North; North Ndebele
+ ndo	ng	Ndonga
+ nds		Low German; Low Saxon; German, Low; Saxon, Low
+ nep	ne	Nepali
+ new		Nepal Bhasa; Newari
+ nia		Nias
+ nic		Niger-Kordofanian languages
+ niu		Niuean
+ nno	nn	Norwegian Nynorsk; Nynorsk, Norwegian
+ nob	nb	Bokmal, Norwegian; Norwegian Bokmal
+ nog		Nogai
+ non		Norse, Old
+ nor	no	Norwegian
+ nqo		N''Ko
+ nso		Pedi; Sepedi; Northern Sotho
+ nub		Nubian languages
+ nwc		Classical Newari; Old Newari; Classical Nepal Bhasa
+ nya	ny	Chichewa; Chewa; Nyanja
+ nym		Nyamwezi
+ nyn		Nyankole
+ nyo		Nyoro
+ nzi		Nzima
+ oci	oc	Occitan (post 1500)
+ oji	oj	Ojibwa
+ ori	or	Oriya
+ orm	om	Oromo
+ osa		Osage
+ oss	os	Ossetian; Ossetic
+ ota		Turkish, Ottoman (1500-1928)
+ oto		Otomian languages
+ paa		Papuan languages
+ pag		Pangasinan
+ pal		Pahlavi
+ pam		Pampanga; Kapampangan
+ pan	pa	Panjabi; Punjabi
+ pap		Papiamento
+ pau		Palauan
+ peo		Persian, Old (ca.600-400 B.C.)
+ per/fas	fa	Persian
+ phi		Philippine languages)
+ phn		Phoenician
+ pli	pi	Pali
+ pol	pl	Polish
+ pon		Pohnpeian
+ por	pt	Portuguese
+ pra		Prakrit languages
+ pro		Provencal, Old (to 1500);Occitan, Old (to 1500)
+ pus	ps	Pushto; Pashto
+ qaa-qtz		Reserved for local use
+ que	qu	Quechua
+ raj		Rajasthani
+ rap		Rapanui
+ rar		Rarotongan; Cook Islands Maori
+ roa		Romance languages
+ roh	rm	Romansh
+ rom		Romany
+ rum/ron	ro	Romanian; Moldavian; Moldovan
+ run	rn	Rundi
+ rup		Aromanian; Arumanian; Macedo-Romanian
+ rus	ru	Russian
+ sad		Sandawe
+ sag	sg	Sango
+ sah		Yakut
+ sai		South American Indian languages
+ sal		Salishan languages
+ sam		Samaritan Aramaic
+ san	sa	Sanskrit
+ sas		Sasak
+ sat		Santali
+ scn		Sicilian
+ sco		Scots
+ sel		Selkup
+ sem		Semitic languages
+ sga		Irish, Old (to 900)
+ sgn		Sign Languages
+ shn		Shan
+ sid		Sidamo
+ sin	si	Sinhala; Sinhalese
+ sio		Siouan languages
+ sit		Sino-Tibetan languages
+ sla		Slavic languages
+ slo/slk	sk	Slovak
+ slv	sl	Slovenian
+ sma		Southern Sami
+ sme	se	Northern Sami
+ smi		Sami languages
+ smj		Lule Sami
+ smn		Inari Sami
+ smo	sm	Samoan
+ sms		Skolt Sami
+ sna	sn	Shona
+ snd	sd	Sindhi
+ snk		Soninke
+ sog		Sogdian
+ som	so	Somali
+ son		Songhai languages
+ sot	st	Sotho, Southern
+ spa	es	Spanish; Castilian
+ srd	sc	Sardinian
+ srn		Sranan Tongo
+ srp	sr	Serbian
+ srr		Serer
+ ssa		Nilo-Saharan languages
+ ssw	ss	Swati
+ suk		Sukuma
+ sun	su	Sundanese
+ sus		Susu
+ sux		Sumerian
+ swa	sw	Swahili
+ swe	sv	Swedish
+ syc		Classical Syriac
+ syr		Syriac
+ tah	ty	Tahitian
+ tai		Tai languages
+ tam	ta	Tamil
+ tat	tt	Tatar
+ tel	te	Telugu
+ tem		Timne
+ ter		Tereno
+ tet		Tetum
+ tgk	tg	Tajik
+ tgl	tl	Tagalog
+ tha	th	Thai
+ tib/bod	bo	Tibetan
+ tig		Tigre
+ tir	ti	Tigrinya
+ tiv		Tiv
+ tkl		Tokelau
+ tlh		Klingon; tlhIngan-Hol
+ tli		Tlingit
+ tmh		Tamashek
+ tog		Tonga (Nyasa)
+ ton	to	Tonga (Tonga Islands)
+ tpi		Tok Pisin
+ tsi		Tsimshian
+ tsn	tn	Tswana
+ tso	ts	Tsonga
+ tuk	tk	Turkmen
+ tum		Tumbuka
+ tup		Tupi languages
+ tur	tr	Turkish
+ tut		Altaic languages
+ tvl		Tuvalu
+ twi	tw	Twi
+ tyv		Tuvinian
+ udm		Udmurt
+ uga		Ugaritic
+ uig	ug	Uighur; Uyghur
+ ukr	uk	Ukrainian
+ umb		Umbundu
+ und		Undetermined
+ urd	ur	Urdu
+ uzb	uz	Uzbek
+ vai		Vai
+ ven	ve	Venda
+ vie	vi	Vietnamese
+ vol	vo	Volapuk
+ vot		Votic
+ wak		Wakashan languages
+ wal		Wolaitta; Wolaytta
+ war		Waray
+ was		Washo
+ wel/cym	cy	Welsh
+ wen		Sorbian languages
+ wln	wa	Walloon
+ wol	wo	Wolof
+ xal		Kalmyk; Oirat
+ xho	xh	Xhosa
+ yao		Yao
+ yap		Yapese
+ yid	yi	Yiddish
+ yor	yo	Yoruba
+ ypk		Yupik languages
+ zap		Zapotec
+ zbl		Blissymbols; Blissymbolics; Bliss
+ zen		Zenaga
+ zha	za	Zhuang; Chuang
+ znd		Zande languages
+ zul	zu	Zulu
+ zun		Zuni
+ zxx		No linguistic content; Not applicable
+ zza		Zaza; Dimili; Dimli; Kirdki; Kirmanjki; Zazaki'!

Item was added:
+ ----- Method: Locale class>>isoLanguage: (in category 'accessing') -----
+ isoLanguage: isoLanguage
+ 	^self isoLanguage: isoLanguage isoCountry: nil!

Item was added:
+ ----- Method: InternalTranslator classSide>>localeDirCreate: (in category 'private loading') -----
+ localeDirCreate: createDir
+ 	"Try to locate the <prefs>/locale/ folder.
+ 	If createDir is set, try to create the path.
+ 	If it doesn't exist, return nil"
+ 
+ 	"If this fails, there is nothing we can do about it here"
+ 	| prefDir  localeDir |
+ 	(createDir not
+ 			and: [ExternalSettings preferenceDirectory isNil])
+ 		ifTrue: [^ nil].
+ 
+ 	prefDir := ExternalSettings assuredPreferenceDirectory.
+ 	prefDir exists
+ 		ifFalse: [^nil].
+ 
+ 
+ 	localeDir := prefDir directoryNamed: 'locale'.
+ 	createDir
+ 		ifTrue: [localeDir assureExistence].
+ 	^localeDir exists
+ 		ifTrue: [localeDir]
+ 		ifFalse: [nil]!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>resetCaches (in category 'class initialization') -----
+ resetCaches
+ 	Translators := nil.!

Item was added:
+ ----- Method: Locale>>primDigitGrouping (in category 'system primitives') -----
+ primDigitGrouping
+ 	"Returns string with e.g. '.' or ',' (thousands etc)"
+ 	<primitive:'primitiveDigitGroupingSymbol' module: 'LocalePlugin'>
+ 	^','!

Item was added:
+ ----- Method: Locale>>primLongDateFormat (in category 'system primitives') -----
+ primLongDateFormat
+ 	"Returns the long date format
+ 	d day, m month, y year,
+ 	double symbol is null padded, single not padded (m=6, mm=06)
+ 	dddd weekday
+ 	mmmm month name"
+ 	<primitive:'primitiveLongDateFormat' module: 'LocalePlugin'>
+ 	^'dddd, mmmm d, yyyy'!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>initializeJapaneseBitmap (in category 'as yet unclassified') -----
+ initializeJapaneseBitmap
+ 
+ 	(self localeID: (LocaleID isoString: 'ja')) name: 'LanguageNameInNativeLanguage' form: self bitmapForJapanese.
+ !

Item was added:
+ ----- Method: InternalTranslator>>loadFromFileNamed: (in category 'private store-retrieve') -----
+ loadFromFileNamed: fileNameString 
+ 	"Load translations from an external file"
+ 
+ 	| stream |
+ 	[stream := FileStream readOnlyFileNamed: fileNameString.
+ 	self loadFromStream: stream]
+ 		ensure: [stream close].
+ 	self changed: #translations.
+ 	self changed: #untranslated.
+ !

Item was added:
+ ----- Method: Locale class>>platformEncodings (in category 'class initialization') -----
+ platformEncodings
+ 	PlatformEncodings isEmptyOrNil ifTrue: [ self initializePlatformEncodings ].
+ 	^PlatformEncodings
+ !

Item was added:
+ ----- Method: NaturalLanguageFormTranslator>>translate: (in category 'utilities') -----
+ translate: aString
+ 
+ 	^ (self generics
+ 		at: aString ifAbsent: [nil]) deepCopy.
+ 
+ 	"Do you like to write 'form ifNotNil: [form deepCopy]'?"
+ !

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso3LanguageDefinition: (in category 'accessing') -----
+ iso3LanguageDefinition: aString
+ 	^self iso3LanguageTable at: aString!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>extraCountryDefinitions (in category 'private') -----
+ extraCountryDefinitions
+ 	^{
+ 	{'Kids'. 'KIDS'. 'KIDS'.}.
+ 	}!

Item was added:
+ ----- Method: InternalTranslator classSide>>services (in category 'file-services') -----
+ services
+ 	"Answer potential file services associated with this class"
+ 	^ {self serviceMergeLanguageTranslations}!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>atRandom (in category 'accessing') -----
+ atRandom
+ 
+ 	self subclassResponsibility.
+ !

Item was added:
+ ----- Method: Locale class>>clipboadInterpreter (in category 'accessing') -----
+ clipboadInterpreter
+ 	^NoConversionClipboardInterpreter new!

Item was added:
+ ----- Method: LocaleID>>displayCountry (in category 'accessing') -----
+ displayCountry
+ 	^(ISOLanguageDefinition iso2Countries at: self isoCountry asUppercase ifAbsent: [ self isoCountry ]) !

Item was added:
+ ----- Method: InternalTranslator>>generics (in category 'private') -----
+ generics
+ 	^generics ifNil: [generics := Dictionary new]!

Item was added:
+ ----- Method: InternalTranslator classSide>>cachedTranslations (in category 'private') -----
+ cachedTranslations
+ 	"CachedTranslations := nil" 
+ 	^CachedTranslations ifNil: [CachedTranslations := Dictionary new]!

Item was added:
+ ----- Method: LocaleID class>>current (in category 'accessing') -----
+ current
+ 	^Locale current localeID!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>current (in category 'accessing') -----
+ current
+ 	^ self availableForLocaleID: LocaleID current!

Item was added:
+ ----- Method: Locale class>>currentPlatform (in category 'accessing') -----
+ currentPlatform
+ 	"CurrentPlatform := nil"
+ 	CurrentPlatform ifNil: [CurrentPlatform := self determineCurrentLocale].
+ 	^CurrentPlatform!

Item was added:
+ ----- Method: InternalTranslator>>removeTranslationFor: (in category 'translation') -----
+ removeTranslationFor: phraseString
+ 	self generics removeKey: phraseString ifAbsent: [].
+ 	self changed: #translations.
+ 	self changed: #untranslated.!

Item was added:
+ ----- Method: InternalTranslator classSide>>loadExternalTranslationsFor: (in category 'private loading') -----
+ loadExternalTranslationsFor: translator
+ 	"Try to load translations from external external files.
+ 	The files are located in the <prefs>/locale/<language>{/<country>} folder.
+ 	There can be more than one file for each location, so applications can install their own partial translation tables. All files in the specific folder are loaded."
+ 
+ 	| translationDir |
+ 	translationDir := self directoryForLocaleID: translator localeID create: false.
+ 	translationDir ifNil: [ ^nil ]. 
+ 	(translationDir fileNamesMatching: '*.' , self translationSuffix)
+ 		do: [:fileName | translator loadFromFileNamed: (translationDir fullNameFor: fileName)]!

Item was added:
+ ----- Method: Locale>>localeID: (in category 'accessing') -----
+ localeID: anID
+ 	id := anID!

Item was added:
+ ----- Method: Locale>>primCurrencySymbol (in category 'system primitives') -----
+ primCurrencySymbol
+ 	"Returns string with currency symbol"
+ 	<primitive: 'primitiveCurrencySymbol' module:'LocalePlugin'>
+ 	^'$'!

Item was added:
+ ----- Method: InternalTranslator>>scanFrom: (in category 'fileIn/fileOut') -----
+ scanFrom: aStream 
+ 	"Read a definition of dictionary.  
+ 	Make sure current locale corresponds my locale id"
+ 	| aString newTranslations assoc currentPlatform |
+ 	newTranslations := Dictionary new.
+ 	currentPlatform := Locale currentPlatform.
+ 	[Locale
+ 		currentPlatform: (Locale localeID: id).
+ 	[aString := aStream nextChunk withSqueakLineEndings.
+ 	aString size > 0]
+ 		whileTrue: [assoc := Compiler evaluate: aString.
+ 			assoc value = ''
+ 				ifTrue: [self class registerPhrase: assoc key]
+ 				ifFalse: [newTranslations add: assoc]]]
+ 		ensure: [Locale currentPlatform: currentPlatform].
+ 	self mergeTranslations: newTranslations!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	aStream nextPutAll: self class name; nextPut: $(; print: self localeID; nextPut: $)!

Item was added:
+ ----- Method: LocaleID>>printOn: (in category 'printing') -----
+ printOn: stream
+ 	"<language>-<country>"
+ 	stream nextPutAll: self isoLanguage.
+ 	self isoCountry
+ 		ifNotNil: [stream nextPut: $-; nextPutAll: self isoCountry]!

Item was added:
+ ----- Method: Locale class>>isoLocale: (in category 'accessing') -----
+ isoLocale: aString
+ 	!

Item was added:
+ ----- Method: ISOLanguageDefinition>>iso3: (in category 'initialize') -----
+ iso3: aString
+ 	iso3 := aString ifEmpty: [nil] ifNotEmpty: [aString]!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>setCurrent (in category 'language switching') -----
+ setCurrent
+ 	"notify locale of the translator become current"
+ !

Item was added:
+ ----- Method: InternalTranslator classSide>>newLocaleID: (in category 'accessing') -----
+ newLocaleID: localeID 
+ 	^ self cachedTranslations
+ 		at: localeID
+ 		ifAbsentPut: [self new localeID: localeID]!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>extraISO3Definitions (in category 'private') -----
+ extraISO3Definitions
+ 
+ 	^self readISOLanguagesFrom: 'jpk		Japanese (Kids)
+ ' readStream!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>translate:inDomain: (in category 'translation') -----
+ translate: aString inDomain: aDomainName
+ 	^ aString!

Item was added:
+ Object subclass: #NaturalLanguageFormTranslator
+ 	instanceVariableNames: 'id generics'
+ 	classVariableNames: 'CachedTranslations'
+ 	poolDictionaries: ''
+ 	category: 'System-Localization'!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>translators (in category 'accessing') -----
+ translators
+ 	^ Translators ifNil: [Translators := Dictionary new]	!

Item was added:
+ ----- Method: Locale class>>currentPlatform:during: (in category 'accessing') -----
+ currentPlatform: locale during: aBlock 
+ 	"Alter current language platform during a block"
+ 	| backupPlatform |
+ 	backupPlatform := self currentPlatform.
+ 	[self currentPlatform: locale.
+ 	aBlock value]
+ 		ensure: [self currentPlatform: backupPlatform]!

Item was added:
+ ----- Method: InternalTranslator classSide>>mergeTranslationFileNamed: (in category 'file-services') -----
+ mergeTranslationFileNamed: fileFullNameString 
+ 	"merge the translation in the file named fileFullNameString"
+ 
+ 	| stream localeID translator |
+ 	stream := FileStream readOnlyFileNamed: fileFullNameString.
+ 	[localeID := LocaleID isoString: stream localName sansPeriodSuffix.
+ 	translator := self localeID: localeID.
+ 	translator loadFromStream: stream]
+ 		ensure: [stream close].
+ 	LanguageEnvironment resetKnownEnvironments.
+ 
+ !

Item was added:
+ ----- Method: InternalTranslator>>saveToFileNamed: (in category 'private store-retrieve') -----
+ saveToFileNamed: fileNameString 
+ 	"save the receiver's translations to a file named fileNameString"
+ 	| stream |
+ 	"Set true if you need to save as binary"
+ 	false
+ 		ifTrue: [stream := ReferenceStream fileNamed: fileNameString.
+ 			stream nextPut: {self translations. self untranslated}.
+ 			stream close.
+ 			^ self].
+ 	stream := FileStream fileNamed: fileNameString.
+ 	[self fileOutOn: stream]
+ 		ensure: [stream close]!

Item was added:
+ ----- Method: InternalTranslator classSide>>mergeLegacyTranslators (in category 'accessing') -----
+ mergeLegacyTranslators
+ 	self availableLanguageLocaleIDs
+ 		do: [:localeID | (NaturalLanguageTranslator translators includesKey: localeID)
+ 				ifFalse: [NaturalLanguageTranslator translators
+ 						at: localeID
+ 						put: (self newLocaleID: localeID)]]!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>buildIso3166CodesTables (in category 'private') -----
+ buildIso3166CodesTables
+ 	"ISOLanguageDefinition buildIso3166CodesTables"
+ 	| rawdata stream country isoa2 isoa3 unNumeric macName macCode windowsName windowsCode empty table |
+ 	rawdata := self iso3166Codes.
+ 	table := OrderedCollection new: 200. 
+ 	stream := rawdata readStream.
+ 	empty := 160 asCharacter asString.
+ 	[stream atEnd] whileFalse: 
+ 		[country := stream nextLine.
+ 		isoa2 := stream nextLine.
+ 		isoa3 := stream nextLine.
+ 		unNumeric := stream nextLine.
+ 		windowsName := stream nextLine.
+ 		windowsName = empty ifTrue: [windowsName := nil].
+ 		windowsCode := stream nextLine. 
+ 		windowsCode = empty ifTrue: [windowsCode := nil].
+ 		macName := stream nextLine.
+ 		macName = empty ifTrue: [macName := nil].
+ 		macCode := stream nextLine.
+ 		macCode = empty ifTrue: [macCode := nil].
+ 		table add: { country.  isoa2. isoa3.  unNumeric. windowsName.  windowsCode.  macName. macCode. }].
+ 	^table!

Item was added:
+ ----- Method: InternalTranslator>>untranslated (in category 'accessing') -----
+ untranslated
+ 	| translations |
+ 	translations := self translations.
+ 	^self class allKnownPhrases reject: [:each | translations includesKey: each]!

Item was added:
+ ----- Method: InternalTranslator classSide>>resetCaches (in category 'class initialization') -----
+ resetCaches
+ 	CachedTranslations := nil.
+ !

Item was added:
+ ----- Method: Locale class>>switchToID: (in category 'accessing') -----
+ switchToID: localeID
+ 	"Locale switchToID: (LocaleID isoLanguage: 'de') "
+ 
+ 	self switchTo: (Locale localeID: localeID)!

Item was added:
+ ----- Method: LocaleID>>displayName (in category 'accessing') -----
+ displayName
+ 	"Answer a proper name to represent the receiver in GUI. 
+ 	 
+ 	The wording is provided by translations of the magic value 
+ 	'<language display name>'. 
+ 	 
+ 	'English' -> 'English'  
+ 	'German' -> 'Deutsch'  
+ 	"
+ 	| magicPhrase translatedMagicPhrase |
+ 	magicPhrase := '<language display name>'.
+ 	translatedMagicPhrase := NaturalLanguageTranslator translateWithoutLoading: magicPhrase toLocaleID: self.
+ 	^ translatedMagicPhrase = magicPhrase
+ 		ifTrue: [self displayLanguage]
+ 		ifFalse: [translatedMagicPhrase]!

Item was added:
+ ----- Method: NaturalLanguageTranslator>>domainRegistered: (in category 'accessing') -----
+ domainRegistered: aDomainName
+ 	"notify that new TextDomain is registered.  Concrete subclass can responds to this event if needed"!

Item was added:
+ ----- Method: InternalTranslator>>rawRemoveUntranslated: (in category 'translation') -----
+ rawRemoveUntranslated: untranslated
+ 
+ 	self class allKnownPhrases removeKey: untranslated ifAbsent: [].
+ 	self changed: #untranslated.!

Item was added:
+ ----- Method: LocaleID class>>isoLanguage: (in category 'instance creation') -----
+ isoLanguage: langString
+ 	^self isoLanguage: langString isoCountry: nil!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>isoLanguage:isoCountry: (in category 'accessing') -----
+ isoLanguage: isoLanguage isoCountry: isoCountry
+ 	^self localeID: (LocaleID  isoLanguage: isoLanguage isoCountry: isoCountry)!

Item was added:
+ ----- Method: Locale>>primDecimalSymbol (in category 'system primitives') -----
+ primDecimalSymbol
+ 	"Returns string with e.g. '.' or ','"
+ 	<primitive:'primitiveDecimalSymbol' module: 'LocalePlugin'>
+ 	^'.'!

Item was added:
+ ----- Method: LocaleID>>isoLanguage:isoCountry: (in category 'initialize') -----
+ isoLanguage: langString isoCountry: countryStringOrNil
+ 	isoLanguage := langString.
+ 	isoCountry := countryStringOrNil!

Item was added:
+ ----- Method: InternalTranslator classSide>>discardAllTranslations (in category 'class initialization') -----
+ discardAllTranslations
+ 	AllKnownPhrases := nil.
+ 	self resetCaches.!

Item was added:
+ ----- Method: InternalTranslator>>atRandom (in category 'accessing') -----
+ atRandom
+ 
+ 	^ generics atRandom value.
+ !

Item was added:
+ ----- Method: InternalTranslator>>checkPhrase:translation: (in category 'translation') -----
+ checkPhrase: phrase translation: translation!

Item was added:
+ ----- Method: InternalTranslator>>defaultBackgroundColor (in category 'user interface') -----
+ defaultBackgroundColor
+ 	"answer the receiver's defaultBackgroundColor for views"
+ 	^ Color cyan!

Item was added:
+ ----- Method: LocaleID>>storeOn: (in category 'printing') -----
+ storeOn: aStream 
+ 	aStream nextPut: $(.
+ 	aStream nextPutAll: self class name.
+ 	aStream nextPutAll: ' isoString: '.
+ 	aStream nextPutAll: '''' , self printString , ''''.
+ 	aStream nextPut: $).
+ !

Item was added:
+ ----- Method: InternalTranslator classSide>>loadTranslatorForIsoLanguage:isoCountry: (in category 'private loading') -----
+ loadTranslatorForIsoLanguage: isoLanguage isoCountry: isoCountry 
+ 	"private - load the translations from <prefs>/locale/ directory  
+ 	the procedure is to assure the existence of a translator for the  
+ 	given language/country and then load the external translations for this translator"
+ 
+ 	| translator |
+ 	translator := self newLocaleID: (LocaleID isoLanguage: isoLanguage isoCountry: isoCountry).
+ 
+ 	self loadExternalTranslationsFor: translator!

Item was added:
+ ----- Method: InternalTranslator classSide>>directoryForLocaleID:create: (in category 'private loading') -----
+ directoryForLocaleID: localeID create: createDir
+ 	"Try to locate the <prefs>/locale/<language>{/<country>} folder.
+ 	If createDir is set, create the path down to country or language, depending on locale.
+ 	Return the directory for country or language depending on locale.
+ 	If neither exists, nil"
+ 
+ 	"NaturalLanguageTranslator directoryForLanguage: 'de' country: nil readOnly: true"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'de' country: 'DE' readOnly: true"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'en' country: 'US' readOnly: false"
+ 	"NaturalLanguageTranslator directoryForLanguage: 'en' country: nil readOnly: true"
+ 
+ 	^self directoryForLanguage: localeID isoLanguage country: localeID isoCountry create: createDir!

Item was added:
+ ----- Method: LocaleID>>hasParent (in category 'testing') -----
+ hasParent
+ 	^self isoCountry notNil!

Item was added:
+ ----- Method: InternalTranslator classSide>>loadAvailableExternalLocales (in category 'private loading') -----
+ loadAvailableExternalLocales
+ 	"private - register locales IDs based on the content of the <prefs>/locale/ directory"
+ 	| localeDir |
+ 	localeDir := self localeDirCreate: false.
+ 	localeDir ifNil: [^ #()].
+ 
+ 	localeDir directoryNames
+ 		do: [:langDirName | 
+ 			| langDir | 
+ 			langDir := localeDir directoryNamed: langDirName.
+ 
+ 			(langDir fileNamesMatching: '*.' , self translationSuffix)
+ 				ifNotEmpty: [self loadTranslatorForIsoLanguage: langDirName isoCountry: nil].
+ 
+ 			langDir directoryNames
+ 				do: [:countryDirName | 
+ 					| countryDir | 
+ 					countryDir := langDirName directoryNamed: countryDirName.
+ 					(countryDir fileNamesMatching: '*.' , self translationSuffix)
+ 						ifNotEmpty: [self loadTranslatorForIsoLanguage: langDirName isoCountry: countryDirName]
+ 			]
+ 		].
+ !

Item was added:
+ ----- Method: Locale class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Locale initialize"
+ 
+ 	Smalltalk addToStartUpList: Locale.
+ 	Preferences addPreference: #useLocale
+ 		categories: #('general') default: false 
+ 		balloonHelp: 'Use the system locale to set the system language etc at startup'.!

Item was added:
+ ----- Method: ISOLanguageDefinition class>>iso3LanguageTable (in category 'private') -----
+ iso3LanguageTable
+ 	"ISOLanguageDefinition iso3LanguageTable"
+ 
+ 	^ISO3Table ifNil: [ISO3Table := self initISO3LanguageTable]!

Item was added:
+ ----- Method: Locale class>>migrateSystem (in category 'private') -----
+ migrateSystem
+ 	"Locale migrateSystem"
+ 	"Do all the necessary operations to switch to the new Locale environment."
+ 
+ 	LocaleChangeListeners _ nil.
+ 	self
+ 		addLocalChangedListener: HandMorph;
+ 		addLocalChangedListener: Clipboard;
+ 		addLocalChangedListener: Vocabulary;
+ 		addLocalChangedListener: PartsBin;
+ 		addLocalChangedListener: Project;
+ 		addLocalChangedListener: PaintBoxMorph;
+ 		yourself!

Item was added:
+ ----- Method: NaturalLanguageTranslator class>>domainUnregistered: (in category 'accessing') -----
+ domainUnregistered: aDomainName
+ 	"notify that new TextDomain is unregistered"
+ 	self translators do: [:each | each domainUnregistered: aDomainName]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>localeID: (in category 'accessing') -----
+ localeID: localeID 
+ 	^ self cachedTranslations
+ 		at: localeID
+ 		ifAbsentPut: [self new localeID: localeID]!

Item was added:
+ ----- Method: NaturalLanguageFormTranslator class>>loadFormsFrom: (in category 'i/o') -----
+ loadFormsFrom: aStream
+ 
+ 	| rr pair inst |
+ 	rr _ ReferenceStream on: aStream.
+ 	pair _ rr next.
+ 	inst _ self localeID: (LocaleID isoString: pair first).
+ 	pair second associationsDo: [:assoc |
+ 		inst name: assoc key form: assoc value.
+ 	].
+ 	^ inst.
+ !



More information about the etoys-dev mailing list