[Pkg] The Trunk: GetText-edc.21.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 29 11:46:00 UTC 2012


Edgar J. De Cleene uploaded a new version of GetText to project The Trunk:
http://source.squeak.org/trunk/GetText-edc.21.mcz

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

Name: GetText-edc.21
Author: edc
Time: 29 March 2012, 8:48:03.631 am
UUID: b6d73dcd-1e45-4ceb-b1ed-98caccac3efa
Ancestors: GetText-edc.18, GetText-edc.20

More cleanup following Nico suggestions.
Can't delete bad versions of trunk...

=============== Diff against GetText-edc.18 ===============

Item was removed:
- ----- Method: GetTextExporter>>export: (in category 'exporting') -----
- export: aLanguage 
- 	language := aLanguage.
- 	[stream := FileStream forceNewFileNamed: self defaultFileName.
- 	stream lineEndConvention: #lf.
- 	stream converter: UTF8TextConverter new.
- 	self exportHeader.
- 	self exportTranslations.
- 	self exportUntranslated]
- 		ensure: [stream close]!

Item was removed:
- ----- Method: GetTextExporter>>exportTranslations (in category 'private-translations') -----
- exportTranslations
- 	| keys size |
- 	keys := language translations keys asArray sort.
- 	size := keys size.
- 	ProgressInitiationException
- 		display: 'Exporting translated phrases as a gettext file.'
- 		during: [:bar | 1
- 				to: size
- 				do: [:index | 
- 					self
- 						exportPhrase: (keys at: index)
- 						translation: (language translations
- 								at: (keys at: index)).
- 					bar value: index / size]]!

Item was removed:
- ----- Method: GetTextExporter>>exportUntranslated (in category 'private-translations') -----
- exportUntranslated
- 	| keys |
- 	keys := language untranslated keys asArray sort.
- 	ProgressInitiationException
- 		display: 'Exporting untranslated phrases as a gettext file.'
- 		at: Sensor cursorPoint
- 		from: 1
- 		to: keys size
- 		during: [:bar | 1
- 				to: keys size
- 				do: [:index | 
- 					self
- 						exportPhrase: (keys at: index)
- 						translation: ''.
- 					bar value: index]]!

Item was removed:
- Object subclass: #GetTextExporter2
- 	instanceVariableNames: 'stream'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'GetText-Editor'!
- 
- !GetTextExporter2 commentStamp: '<historical>' prior: 0!
- Export translations to gettext format divided into categories.
- 
- "Export gettext template files"
- GetTextExporter2 new exportTemplate.
- 
- "Export translation files for current locale"
- GetTextExporter2 new exportTranslator: (InternalTranslator newLocaleID: LocaleID current).
- 
- "Export all gettext template and po files."
- GetTextExporter2 exportAll.
- 
- "To register a class category as a new domain"
- TextDomainManager registerClassCategory: 'Morphic-Books' domain: 'Book'.
- "Remove a class category"
- TextDomainManager unregisterClassCategory: 'Morphic-Books'.!

Item was removed:
- ----- Method: GetTextExporter2 class>>coverageStatus (in category 'utilities') -----
- coverageStatus
- 	"self coverageStatus"
- 	| keys diff |
- 	keys := self keys.
- 	diff := InternalTranslator allKnownPhrases keys difference: keys.
- 	Transcript cr; show: 'Detected keywords by GetTextExporter2: ' , keys size printString.
- 	Transcript cr; show: 'All known phrases in InternalTranslator: ' , InternalTranslator allKnownPhrases size printString.
- 	Transcript cr; show: 'Coverage: ' , (keys size / InternalTranslator allKnownPhrases size * 100.0) printString , '%'.
- 	diff inspect!

Item was removed:
- ----- Method: GetTextExporter2 class>>exportAll (in category 'utilities') -----
- exportAll
- 	"GetTextExporter2 exportAll"
- 	self new exportTemplate.
- 	InternalTranslator availableLanguageLocaleIDs
- 		do: [:each | self new exportTranslator: each translator]!

Item was removed:
- ----- Method: GetTextExporter2 class>>exportTemplate (in category 'utilities') -----
- exportTemplate
- 	"GetTextExporter2 exportTemplate"
- 	self new exportTemplate.!

Item was removed:
- ----- Method: GetTextExporter2 class>>keys (in category 'utilities') -----
- keys
- 	| categories |
- 	categories := Dictionary new.
- 	GetTextExporter2 new appendTranslations: categories.
- 	^ categories values
- 		inject: Set new
- 		into: [:set :next | set addAll: next keys;
- 				 yourself]!

Item was removed:
- ----- Method: GetTextExporter2 class>>listAllHelp (in category 'utilities') -----
- listAllHelp
- 	"self listAllHelp"
- 	| spec specs oCatalog flap flapSelectors allKeys oCatalogHelp flapHelp |
- 	oCatalog := Dictionary new.
- 	Morph withAllSubclasses
- 		do: [:aClass | (aClass class includesSelector: #descriptionForPartsBin)
- 				ifTrue: [spec := aClass descriptionForPartsBin.
- 					oCatalog at: spec formalName put: spec documentation]].
- 	Morph withAllSubclasses
- 		do: [:aClass | (aClass class includesSelector: #supplementaryPartsDescriptions)
- 				ifTrue: [specs := aClass supplementaryPartsDescriptions.
- 					specs
- 						do: [:each | oCatalog at: each formalName put: each documentation]]].
- 	flap := Dictionary new.
- 	flapSelectors := #(#defaultsQuadsDefiningPlugInSuppliesFlap #defaultsQuadsDefiningStackToolsFlap #defaultsQuadsDefiningSuppliesFlap #defaultsQuadsDefiningToolsFlap #defaultsQuadsDefiningWidgetsFlap #defaultsQuadsDefiningScriptingFlap ).
- 	flapSelectors
- 		do: [:selector | 
- 			specs := Flaps perform: selector.
- 			specs
- 				do: [:each | flap at: each third put: each fourth]].
- 	allKeys := oCatalog keys intersection: flap keys.
- 	allKeys asArray sort
- 		do: [:each | 
- 			oCatalogHelp := oCatalog
- 						at: each
- 						ifAbsent: [''].
- 			flapHelp := flap
- 						at: each
- 						ifAbsent: [''].
- 			oCatalogHelp = flapHelp
- 				ifFalse: [Transcript cr; show: 'Name: ' , each.
- 					Transcript cr; show: 'O: ' , oCatalogHelp.
- 					Transcript cr; show: 'F: ' , flapHelp.
- 					Transcript cr.
- 
- ]]!

Item was removed:
- ----- Method: GetTextExporter2 class>>verifyExport (in category 'utilities') -----
- verifyExport
- 	"Same as #verifyMsgID: but it writes / reads .po files actually"
- 	"GetTextExporter2 verifyExport"
- 	"InternalTranslator removeLocaleID: (LocaleID isoString: 'test-US')"
- 	| src dst localeID |
- 	localeID := LocaleID isoString: 'test-US'.
- 	self verifyMsgID: localeID.
- 	src := localeID translator.
- 	GetTextExporter2 new exportTranslator: src.
- 	InternalTranslator removeLocaleID: localeID.
- 	dst := localeID translator.
- 	GetTextImporter import: dst allDirectory: FileDirectory default!

Item was removed:
- ----- Method: GetTextExporter2 class>>verifyMsgID: (in category 'utilities') -----
- verifyMsgID: localeID 
- 	"GetTextExporter2 verifyMsgID: (LocaleID isoString: 'test-US')"
- 	"InternalTranslator removeLocaleID: (LocaleID isoString: 'test-US')"
- 	"Test gettext keyword extract function without file I/O.
- 	A language named <langName> will be made. And
- 	all possible translated words are shown with extra X charactor like
- 	'XwordX' in the language."
- 	| src |
- 	InternalTranslator removeLocaleID: localeID.
- 	src := localeID translator.
- 	self keys
- 		do: [:key | src generics at: key put: 'X' , key , 'X']!

Item was removed:
- ----- Method: GetTextExporter2>>appendStringReceivers:into: (in category 'private') -----
- appendStringReceivers: aSymbol into: domains
- 	| literals references domainName methodReference keywords found |
- 	
- 	found := TranslatedReceiverFinder new stringReceiversWithContext: aSymbol.
- 	found do: [ :assoc |
- 		methodReference := assoc key.
- 		keywords := assoc value.
- 		domainName := self getTextDomainForPackage:
- 			(PackageOrganizer default packageOfMethod: methodReference ifNone: [TextDomainManager defaultDomain]).
- 		literals := domains at: domainName ifAbsentPut: [Dictionary new].
- 		keywords do: [ :literal |
- 			references := literals at: literal ifAbsentPut: [OrderedCollection new].
- 			references add: methodReference.
- 		].
- 	]. 
- !

Item was removed:
- ----- Method: GetTextExporter2>>appendTranslations: (in category 'exporting') -----
- appendTranslations: domains 
- 	self appendStringReceivers: #translated into: domains.
- 	self appendStringReceivers: #translatedNoop into: domains.
- 	self appendVocabularies: domains.
- !

Item was removed:
- ----- Method: GetTextExporter2>>appendVocabularies: (in category 'private') -----
- appendVocabularies: domains
- 	| literalsForDomain references domainName methodReference |
- 	
- 	EToyVocabulary allPhrasesWithContextToTranslate do: [ :r |
- 		methodReference :=  (MethodReference new setStandardClass: (r second) methodSymbol: (r third)).
- 		"domainName := self getTextDomainForPackage: (PackageOrganizer default packageOfMethod: methodReference)".
- 		domainName := 'Etoys-Tiles'.
- 		literalsForDomain := domains at: domainName ifAbsentPut: [Dictionary new].
- 		r fourth do: [ :literal |
- 			references := literalsForDomain at: literal ifAbsentPut: [OrderedCollection new].
- 			references add: methodReference.
- 		].
- 	]. 
- 	!

Item was removed:
- ----- Method: GetTextExporter2>>createExtraInformation (in category 'private') -----
- createExtraInformation
- 	| extras |
- 	extras := OrderedCollection new.
- 	#(
- 		'Language name as you''d like it to appear in the Languages menu' 'Language-Name'
- 		'Scale to apply to font size (2 for twice as large)' 'Font-Scale'
- 		'Directionality of language' 'Language-Direction'
- 		'Use this if you do not want any of the text to be bolded, for legibility' 'Suppress-Bold'
- 		'Font to use on a Windows system' 'Win-Font'
- 		'Font to use on a Mac system' 'Mac-Font'
- 		'Font to use on a Linux system' 'Linux-Font') pairsDo: [:first :second |
- 			extras add: (Array with: '' with: first with: second).
- 	].
- 	^ extras!

Item was removed:
- ----- Method: GetTextExporter2>>createHeaders (in category 'private') -----
- createHeaders
- 	| headers |
- 	headers := OrderedCollection new.
- 	headers add: 'Project-Id-Version' -> 'eToys'.
- 	headers add: 'POT-Creation-Date' -> self currentDateAndTime.
- 	headers add: 'PO-Revision-Date' -> self currentDateAndTime.
- 	headers add: 'Last-Translator' -> ''.
- 	headers add: 'Language-Team' -> ''.
- 	headers add: 'MIME-Version' -> '1.0'.
- 	headers add: 'Content-Type' -> ('text/plain; charset=', stream converter class encodingNames first).
- 	headers add: 'Content-Transfer-Encoding' -> '8bit'.
- 	headers add: 'X-Etoys-SystemVersion' -> (SystemVersion current asString).
- 	^ headers!

Item was removed:
- ----- Method: GetTextExporter2>>currentDateAndTime (in category 'private') -----
- currentDateAndTime
- 	^ String
- 		streamContents: [:aStream | 
- 			aStream nextPutAll: Date today yyyymmdd;
- 				space.
- 			Time now
- 				print24: true
- 				showSeconds: false
- 				on: aStream.
- 			aStream nextPutAll: '-0000']!

Item was removed:
- ----- Method: GetTextExporter2>>dirNameCategory:translator: (in category 'exporting') -----
- dirNameCategory: category translator: translator 
- 	"Answer a file name for the category. Make one if it is not exist yet.
- 	Make template file name if translator is nil"
- 	"self new dirNameCategory: 'Morphic-Scripting Support' translator:
- 	NaturalLanguageTranslator current"
- 	"self new dirNameCategory: 'Morphic-Scripting Support' translator: nil"
- 	| safeCategory fileName dirName pathName |
- 	safeCategory := category copyReplaceAll: ' ' with: ':='.
- 	fileName := translator
- 				ifNil: [safeCategory , '.pot']
- 				ifNotNil: [translator localeID posixName , '.po'].
- 	dirName := (safeCategory findTokens: '-')
- 				inject: 'po'
- 				into: [:aString :next | aString , FileDirectory slash , next].
- 	pathName := dirName , FileDirectory slash , fileName.
- 	(FileDirectory default directoryNamed: dirName) assureExistence.
- 	^ pathName!

Item was removed:
- ----- Method: GetTextExporter2>>dirNameDomain:translator: (in category 'exporting') -----
- dirNameDomain: domain translator: translator 
- 	"Answer a file name for the domain. Make one if it is not exist yet.
- 	Make template file name if translator is nil"
- 	"self new dirNameDomain: 'etoys' translator:
- 	NaturalLanguageTranslator current"
- 	"self new dirNameDomain: 'etoys' translator: nil"
- 	| fileName dirName pathName |
- 	"safeCategory := category copyReplaceAll: ' ' with: ':='."
- 	fileName := translator
- 				ifNil: [domain , '.pot']
- 				ifNotNil: [translator localeID posixName , '.po'].
- 	dirName := 'po', FileDirectory slash, domain.
- 	pathName := dirName , FileDirectory slash , fileName.
- 	(FileDirectory default directoryNamed: dirName) assureExistence.
- 	^ pathName!

Item was removed:
- ----- Method: GetTextExporter2>>export:translator:domain: (in category 'private') -----
- export: literals translator: translator domain: domainName 
- 	| fileName |
- 	"Export a gettext file in a category. literals is a dictionary of keyword -> #(MethodReference...) in the textDomain."
- 	fileName := self dirNameDomain: domainName translator: translator.
- 	[stream := FileStream forceNewFileNamed: fileName.
- 	stream lineEndConvention: #lf.
- 	stream converter: UTF8TextConverter new.
- 	self exportHeader: domainName.
- 	self exportInformation: self createExtraInformation.
- 	self exportBody: literals translator: translator]
- 		ensure: [stream close]!

Item was removed:
- ----- Method: GetTextExporter2>>exportBody:translator: (in category 'file out') -----
- exportBody: literals translator: translator 
- 	"Export a gettext file body. literals is a dictionary of keyword ->
- 	#(MethodReference...) in the textDomain."
- 	"Build {sortKey. comment. msgid } to optimize sorting (getting category is
- 	too slow).
- 	If there are two or more methods for a mgsid, only first method
- 	(alphabetical) is used for sorting."
- 	| sorted msgid sortedMethods category sortKey comment triplets commentUnderLined |
- 	triplets := literals associations
- 				collect: [:assoc | 
- 					msgid := assoc key.
- 					sortedMethods := assoc value asArray sort.
- 					category := (Smalltalk at: sortedMethods first classSymbol) category asString.
- 					sortKey := category , ',' , sortedMethods first printString , ',' , msgid.
- 					comment := (sortedMethods
- 								collect: [:each | each actualClass asString , '>>' , each methodSymbol asString])
- 								inject: category
- 								into: [:result :methodName | result , ',' , methodName].
- 					"Replace white spaces to := because gettext tool might
- 					replace a space to a new line some times, and it makes
- 					difficult to take a diff."
- 					commentUnderLined := comment copyReplaceAll: ' ' with: ':='.
- 					Array
- 						with: sortKey
- 						with: commentUnderLined
- 						with: msgid].
- 	"Sort and output the words"
- 	sorted := triplets
- 				sort: [:a :b | a first <= b first].
- 	sorted
- 		do: [:triplet | 
- 			comment := triplet second.
- 			msgid := triplet third.
- 			self exportRecordHeader: comment.
- 			self
- 				exportPhrase: msgid
- 				translation: (self translationFor: msgid in: translator)]!

Item was removed:
- ----- Method: GetTextExporter2>>exportHeader: (in category 'private') -----
- exportHeader: domainName
- 	| headers |
- 	self exportTag: 'msgid' msg: ''.
- 	self exportTag: 'msgstr' msg: ''.
- 	headers := self createHeaders.
- 	headers add: 'X-Etoys-Domain' -> domainName.
- 	headers do: [:each | self exportHeaderLineKey: each key value: each value].
- 	stream cr; cr!

Item was removed:
- ----- Method: GetTextExporter2>>exportHeaderLineKey:value: (in category 'private') -----
- exportHeaderLineKey: keyString value: valueString 
- 	stream nextPut: $";
- 		 nextPutAll: keyString;
- 		 nextPut: $:;
- 		 space;
- 		 nextPutAll: valueString;
- 		 nextPutAll: '\n';
- 		 nextPut: $";
- 		 cr.!

Item was removed:
- ----- Method: GetTextExporter2>>exportInformation: (in category 'private') -----
- exportInformation: anOrderedCollection
- 	anOrderedCollection do: [:each |
- 		self exportRecordHeader: each second.
- 		self exportPhrase: each third translation: ''].
- 	stream cr.!

Item was removed:
- ----- Method: GetTextExporter2>>exportPhrase:translation: (in category 'private') -----
- exportPhrase: phraseString translation: translationString 
- 	| normalizedTrans tmp transStartsWithCR transEndsWithCR|
- 	phraseString isEmpty
- 		ifTrue: [^ self].
- 	self exportTag: 'msgid' msg: phraseString.
- 	translationString size = 0 ifTrue: [
- 		normalizedTrans := ''
- 	] ifFalse: [
- 		transEndsWithCR := translationString last = (Character cr).
- 		phraseString last = (Character cr) ifTrue: [
- 			transEndsWithCR ifTrue: [
- 				normalizedTrans := translationString
- 			] ifFalse: [
- 				normalizedTrans :=  translationString , String cr
- 			]
- 		] ifFalse: [
- 			transEndsWithCR ifTrue: [
- 				normalizedTrans := translationString allButLast
- 			] ifFalse: [
- 				normalizedTrans := translationString
- 			]
- 		].
- 		transStartsWithCR := normalizedTrans first = (Character cr).
- 		phraseString first = (Character cr) ifTrue: [
- 			transStartsWithCR ifFalse: [
- 				tmp := (Character cr asString) , normalizedTrans.
- 				normalizedTrans := tmp.
- 			]
- 		] ifFalse: [
- 			transStartsWithCR ifTrue: [
- 				normalizedTrans := normalizedTrans allButFirst
- 			]
- 		]
- 	].
- 	self exportTag: 'msgstr' msg: normalizedTrans.
- 	stream cr!

Item was removed:
- ----- Method: GetTextExporter2>>exportRecordHeader: (in category 'private') -----
- exportRecordHeader: context
- 	stream 
- 		nextPutAll: '#: ';
- 		nextPutAll: context;
- 		cr.!

Item was removed:
- ----- Method: GetTextExporter2>>exportTag:msg: (in category 'private') -----
- exportTag: tag msg: aString 
- 	| pos end line |
- 	(aString indexOf: Character cr)
- 			= 0
- 		ifTrue: [self exportTag: tag singleLine: aString]
- 		ifFalse: [self exportTag: tag singleLine: ''.
- 			pos := 1.
- 			end := 0.
- 			[end < aString size]
- 				whileTrue: [end := aString indexOf: Character cr startingAt: pos.
- 					end = 0
- 						ifTrue: [end := aString size].
- 					line := aString copyFrom: pos to: end.
- 					stream nextPut: $";
- 						
- 						nextPutAll: (self formatString: line);
- 						 nextPut: $";
- 						 cr.
- 					pos := end + 1]]!

Item was removed:
- ----- Method: GetTextExporter2>>exportTag:singleLine: (in category 'private') -----
- exportTag: tag singleLine: aString 
- 	stream nextPutAll: tag.
- 	stream space.
- 	stream nextPut: $".
- 	stream
- 		nextPutAll: (self formatString: aString).
- 	stream nextPut: $".
- 	stream cr!

Item was removed:
- ----- Method: GetTextExporter2>>exportTemplate (in category 'exporting') -----
- exportTemplate
- 	"GetTextExporter2 new exportTemplate"
- 	self exportTranslator: nil!

Item was removed:
- ----- Method: GetTextExporter2>>exportTranslator: (in category 'exporting') -----
- exportTranslator: translator 
- 	"Export translation files. the file extention is 'po', or 'pot' if translator is nil "
- 	"GetTextExporter2 new exportTranslator: NaturalLanguageTranslator current "
- 	| domains |
- 	domains := Dictionary new.
- 	self appendTranslations: domains.
- 	domains
- 		keysAndValuesDo: [:domainName :value |
- 			self
- 				export: value
- 				translator: translator
- 				domain: domainName]!

Item was removed:
- ----- Method: GetTextExporter2>>formatReplacements (in category 'private') -----
- formatReplacements
- 	| replacements |
- 	replacements := OrderedCollection new.
- 	replacements add: '\' -> '\\'.
- 	replacements add: String cr -> '\n'.
- 	replacements add: String tab -> '\t'.
- 	replacements add: '"' -> '\"'.
- 	^ replacements!

Item was removed:
- ----- Method: GetTextExporter2>>formatString: (in category 'private') -----
- formatString: aString 
- 	| result |
- 	result := aString.
- 	self formatReplacements
- 		do: [:each | result := result copyReplaceAll: each key with: each value].
- 	^ result!

Item was removed:
- ----- Method: GetTextExporter2>>getTextDomainForPackage: (in category 'as yet unclassified') -----
- getTextDomainForPackage: aPackageInfo 
- 	^TextDomainManager domainForPackage: aPackageInfo!

Item was removed:
- ----- Method: GetTextExporter2>>stream (in category 'accessing') -----
- stream
- 	^ stream!

Item was removed:
- ----- Method: GetTextExporter2>>stream: (in category 'accessing') -----
- stream: aStream
- 	stream := aStream!

Item was removed:
- ----- Method: GetTextExporter2>>translationFor:in: (in category 'private') -----
- translationFor: aKey in: translator
- 	translator ifNil: [^''].
- 	translator translations at: aKey ifPresent: [:s | ^s].
- 	"If we have old camelCase translations, make space-separated words"
- 	translator translations at: aKey toCamelCase ifPresent: [:s | 
- 		(s includes: Character space) ifTrue: [^s].
- 		^s fromCamelCase].
- 	^''!

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

Item was removed:
- ----- 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 removed:
- ----- Method: ISOLanguageDefinition class>>extraCountryDefinitions (in category 'private') -----
- extraCountryDefinitions
- 	^{
- 	{'Kids'. 'KIDS'. 'KIDS'.}.
- 	}!

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: ISOLanguageDefinition class>>initialize (in category 'class initialization') -----
- initialize
- 	"ISOLanguageDefinition initialize"
- 
- 	ISO3Table := nil.
- 	ISO2Table := nil!

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: ISOLanguageDefinition class>>iso3166Codes (in category 'private') -----
- iso3166Codes
- "http://www.unicode.org/onlinedat/countries.html"
- 
- ^'­LAND ISLANDS
- AX
- 
- 
- †
- †
- †
- †
- AFGHANISTAN
- AF
- AFG
- 004
- †
- †
- †
- †
- ALBANIA
- AL
- ALB
- 008
- CTRY_ALBANIA
- 355
- †
- †
- ALGERIA
- DZ
- DZA
- 012
- CTRY_ALGERIA
- 213
- verArabic
- 16
- AMERICAN SAMOA
- AS
- ASM
- 016
- †
- †
- †
- †
- ANDORRA
- AD
- AND
- 020
- †
- †
- †
- †
- ANGOLA
- AO
- AGO
- 024
- †
- †
- †
- †
- ANGUILLA
- AI
- AIA
- 660
- †
- †
- †
- †
- ANTARCTICA
- AQ
- ATA
- 010
- †
- †
- †
- †
- ANTIGUA AND BARBUDA
- AG
- ATG
- 028
- †
- †
- †
- †
- ARGENTINA
- AR
- ARG
- 032
- CTRY_ARGENTINA
- 54
- †
- †
- ARMENIA
- AM
- ARM
- 051
- CTRY_ARMENIA
- 374
- verArmenian
- 84
- ARUBA
- AW
- ABW
- 533
- †
- †
- †
- †
- AUSTRALIA
- AU
- AUS
- 036
- CTRY_AUSTRALIA
- 61
- verAustralia
- 15
- AUSTRIA
- AT
- AUT
- 040
- CTRY_AUSTRIA
- 43
- verAustria
- 92
- AZERBAIJAN
- AZ
- AZE
- 031
- CTRY_AZERBAIJAN
- 994
- †
- †
- BAHAMAS
- BS
- BHS
- 044
- †
- †
- †
- †
- BAHRAIN
- BH
- BHR
- 048
- CTRY_BAHRAIN
- 973
- †
- †
- BANGLADESH
- BD
- BGD
- 050
- †
- †
- verBengali
- 60
- BARBADOS
- BB
- BRB
- 052
- †
- †
- †
- †
- BELARUS
- BY
- BLR
- 112
- CTRY_BELARUS
- 375
- †
- †
- BELGIUM
- BE
- BEL
- 056
- CTRY_BELGIUM
- 32
- verFrBelgium, verFlemish
- 98
- BELIZE
- BZ
- BLZ
- 084
- CTRY_BELIZE
- 501
- †
- †
- BENIN
- BJ
- BEN
- 204
- †
- †
- †
- †
- BERMUDA
- BM
- BMU
- 060
- †
- †
- †
- †
- BHUTAN
- BT
- BTN
- 064
- †
- †
- verBhutan
- 83
- BOLIVIA
- BO
- BOL
- 068
- CTRY_BOLIVIA
- 591
- †
- †
- BOSNIA AND HERZEGOVINA
- BA
- BIH
- 070
- †
- †
- †
- †
- BOTSWANA
- BW
- BWA
- 072
- †
- †
- †
- †
- BOUVET ISLAND
- BV
- BVT
- 074
- †
- †
- †
- †
- BRAZIL
- BR
- BRA
- 076
- CTRY_BRAZIL
- 55
- verBrazil
- 71
- BRITISH INDIAN OCEAN TERRITORY
- IO
- IOT
- 086
- †
- †
- †
- †
- BRUNEI DARUSSALAM
- BN
- BRN
- 096
- CTRY_BRUNEI_DARUSSALAM
- 673
- †
- †
- BULGARIA
- BG
- BGR
- 100
- CTRY_BULGARIA
- 359
- verBulgaria†
- 72
- BURKINA FASO
- BF
- BFA
- 854
- †
- †
- †
- †
- BURUNDI
- BI
- BDI
- 108
- †
- †
- †
- †
- CAMBODIA
- KH
- KHM
- 116
- †
- †
- †
- †
- CAMEROON
- CM
- CMR
- 120
- †
- †
- †
- †
- CANADA
- CA
- CAN
- 124
- CTRY_CANADA
- 2
- verFrCanada, verEndCanada
- 82
- CAPE VERDE
- CV
- CPV
- 132
- †
- †
- †
- †
- CAYMAN ISLANDS
- KY
- CYM
- 136
- †
- †
- †
- †
- CENTRAL AFRICAN REPUBLIC
- CF
- CAF
- 140
- †
- †
- †
- †
- CHAD
- TD
- TCD
- 148
- †
- †
- †
- †
- CHILE
- CL
- CHL
- 152
- CTRY_CHILE
- 56
- †
- †
- CHINA
- CN
- CHN
- 156
- CTRY_PRCHINA
- 86
- verChina
- 52
- CHRISTMAS ISLAND
- CX
- CXR
- 162
- †
- †
- †
- †
- COCOS (KEELING) ISLANDS
- CC
- CCK
- 166
- †
- †
- †
- †
- COLOMBIA
- CO
- COL
- 170
- CTRY_COLOMBIA
- 57
- †
- †
- COMOROS
- KM
- COM
- 174
- †
- †
- †
- †
- CONGO
- CG
- COG
- 178
- †
- †
- †
- †
- CONGO, THE DEMOCRATIC REPUBLIC OF THE
- CD
- 
- 
- †
- †
- †
- †
- COOK ISLANDS
- CK
- COK
- 184
- †
- †
- †
- †
- COSTA RICA
- CR
- CRI
- 188
- CTRY_COSTA_RICA
- 506
- †
- †
- COTE D''IVOIRE
- CI
- CIV
- 384
- †
- †
- †
- †
- CROATIA (local name: Hrvatska)
- HR
- HRV
- 191
- CTRY_CROATIA
- 385
- verCroatia, verYugoCroatian
- 68 (c), 25 (y)
- CUBA
- CU
- CUB
- 192
- †
- †
- †
- †
- CYPRUS
- CY
- CYP
- 196
- †
- †
- verCyprus
- 23
- CZECH REPUBLIC
- CZ
- CZE
- 203
- CTRY_CZECH
- 420
- verCzech†
- 56
- DENMARK
- DK
- DNK
- 208
- CTRY_DENMARK
- 45
- verDenmark(da), verFaeroeIsl(fo)
- 9(da), 47(fo)
- DJIBOUTI
- DJ
- DJI
- 262
- †
- †
- †
- †
- DOMINICA
- DM
- DMA
- 212
- †
- †
- †
- †
- DOMINICAN REPUBLIC
- DO
- DOM
- 214
- CTRY_DOMINICAN_REPUBLIC
- 1
- †
- †
- EAST TIMOR
- TL
- TLS
- 626
- †
- †
- †
- †
- ECUADOR
- EC
- ECU
- 218
- CTRY_ECUADOR
- 593
- †
- †
- EGYPT
- EG
- EGY
- 818
- CTRY_EGYPT
- 20
- verArabic
- 16
- EL SALVADOR
- SV
- SLV
- 222
- CTRY_EL_SALVADOR
- 503
- †
- †
- EQUATORIAL GUINEA
- GQ
- GNQ
- 226
- †
- †
- †
- †
- ERITREA
- ER
- ERI
- 232
- †
- †
- †
- †
- ESTONIA
- EE
- EST
- 233
- CTRY_ESTONIA
- 372
- verEstonia
- 44
- ETHIOPIA
- ET
- ETH
- 210
- †
- †
- †
- †
- FALKLAND ISLANDS (MALVINAS)
- FK
- FLK
- 238
- †
- †
- †
- †
- FAROE ISLANDS
- FO
- FRO
- 234
- CTRY_FAEROE_ISLANDS
- 298
- †
- †
- FIJI
- FJ
- FJI
- 242
- †
- †
- †
- †
- FINLAND
- FI
- FIN
- 246
- CTRY_FINLAND
- 358
- verFinland
- 17
- FRANCE
- FR
- FRA
- 250
- CTRY_FRANCE
- 33
- verFrance
- 1
- FRANCE, METROPOLITAN
- FX
- FXX
- 249
- †
- †
- †
- †
- FRENCH GUIANA
- GF
- GUF
- 254
- †
- †
- †
- †
- FRENCH POLYNESIA
- PF
- PYF
- 258
- †
- †
- †
- †
- FRENCH SOUTHERN TERRITORIES
- TF
- ATF
- 260
- †
- †
- †
- †
- GABON
- GA
- GAB
- 266
- †
- †
- †
- †
- GAMBIA
- GM
- GMB
- 270
- †
- †
- †
- †
- GEORGIA
- GE
- GEO
- 268
- CTRY_GEORGIA
- 995
- verGeorgian
- 85
- GERMANY
- DE
- DEU
- 276
- CTRY_GERMANY
- 49
- verGermany
- 3
- GHANA
- GH
- GHA
- 288
- †
- †
- †
- †
- GIBRALTAR
- GI
- GIB
- 292
- †
- †
- †
- †
- GREECE
- GR
- GRC
- 300
- CTRY_GREECE
- 30
- verGreece, verGreecePoly
- 20, 40
- GREENLAND
- GL
- GRL
- 304
- †
- †
- verGreenland
- 107
- GRENADA
- GD
- GRD
- 308
- †
- †
- †
- †
- GUADELOUPE
- GP
- GLP
- 312
- †
- †
- †
- †
- GUAM
- GU
- GUM
- 316
- †
- †
- †
- †
- GUATEMALA
- GT
- GTM
- 320
- CTRY_GUATEMALA
- 502
- †
- †
- GUINEA
- GN
- GIN
- 324
- †
- †
- †
- †
- GUINEA-BISSAU
- GW
- GNB
- 624
- †
- †
- †
- †
- GUYANA
- GY
- GUY
- 328
- †
- †
- †
- †
- HAITI
- HT
- HTI
- 332
- †
- †
- †
- †
- HEARD ISLAND & MCDONALD ISLANDS
- HM
- HMD
- 334
- †
- †
- †
- †
- HONDURAS
- HN
- HND
- 340
- CTRY_HONDURAS
- 504
- †
- †
- HONG KONG
- HK
- HKG
- 344
- CTRY_HONG_KONG
- 852
- †
- †
- HUNGARY
- HU
- HUN
- 348
- CTRY_HUNGARY
- 36
- verHungary
- 43
- ICELAND
- IS
- ISL
- 352
- CTRY_ICELAND
- 354
- verIceland
- 21
- INDIA
- IN
- IND
- 356
- CTRY_INDIA
- 91
- verIndiaHindi(hi)
- 33
- INDONESIA
- ID
- IDN
- 360
- CTRY_INDONESIA
- 62
- †
- †
- IRAN, ISLAMIC REPUBLIC OF
- IR
- IRN
- 364
- CTRY_IRAN
- 981
- verIran
- 48
- IRAQ
- IQ
- IRQ
- 368
- CTRY_IRAQ
- 964
- verArabic
- 16
- IRELAND
- IE
- IRL
- 372
- CTRY_IRELAND
- 353
- verIreland
- 50
- ISRAEL
- IL
- ISR
- 376
- CTRY_ISRAEL
- 972
- verIsrael
- 13
- ITALY
- IT
- ITA
- 380
- CTRY_ITALY
- 39
- verItaly
- 4
- JAMAICA
- JM
- JAM
- 388
- CTRY_JAMAICA
- 1
- †
- †
- JAPAN
- JP
- JPN
- 392
- CTRY_JAPAN
- 81
- verJapan
- 14
- JORDAN
- JO
- JOR
- 400
- CTRY_JORDAN
- 962
- †
- †
- KAZAKHSTAN
- KZ
- KAZ
- 398
- CTRY_KAZAKSTAN
- 7
- †
- †
- KENYA
- KE
- KEN
- 404
- CTRY_KENYA
- 254
- †
- †
- KIRIBATI
- KI
- KIR
- 296
- †
- †
- †
- †
- KOREA, DEMOCRATIC PEOPLE''S REPUBLIC OF
- KP
- PRK
- 408
- †
- †
- verKorea
- 51
- KOREA, REPUBLIC OF
- KR
- KOR
- 410
- CTRY_SOUTH_KOREA
- 82
- verKorea
- †
- KUWAIT
- KW
- KWT
- 414
- CTRY_KUWAIT
- 965
- †
- †
- KYRGYZSTAN
- KG
- KGZ
- 417
- CTRY_KYRGYZSTAN
- 996
- †
- †
- LAO PEOPLE''S DEMOCRATIC REPUBLIC
- LA
- LAO
- 418
- †
- †
- †
- †
- LATVIA
- LV
- LVA
- 428
- CTRY_LATVIA
- 371
- verLatvia
- 45
- LEBANON
- LB
- LBN
- 422
- CTRY_LEBANON
- 961
- †
- †
- LESOTHO
- LS
- LSO
- 426
- †
- †
- †
- †
- LIBERIA
- LR
- LBR
- 430
- †
- †
- †
- †
- LIBYAN ARAB JAMAHIRIYA
- LY
- LBY
- 434
- CTRY_LIBYA
- 218
- verArabic
- 16
- LIECHTENSTEIN
- LI
- LIE
- 438
- CTRY_LIECHTENSTEIN
- 41
- †
- †
- LITHUANIA
- LT
- LTU
- 440
- CTRY_LITHUANIA
- 370
- verLithuania
- 41
- LUXEMBOURG
- LU
- LUX
- 442
- CTRY_LUXEMBOURG
- 352
- verFrBelgiumLux
- 6
- MACAU
- MO
- MAC
- 446
- CTRY_MACAU
- 853
- †
- †
- MACEDONIA, THE FORMER YUGOSLAV REPUBLIC OF
- MK
- MKD
- 807
- CTRY_MACEDONIA
- 389
- verMacedonian
- †
- MADAGASCAR
- MG
- MDG
- 450
- †
- †
- †
- †
- MALAWI
- MW
- MWI
- 454
- †
- †
- †
- †
- MALAYSIA
- MY
- MYS
- 458
- CTRY_MALAYSIA
- 60
- †
- †
- MALDIVES
- MV
- MDV
- 462
- CTRY_MALDIVES
- 960
- †
- †
- MALI
- ML
- MLI
- 466
- †
- †
- †
- †
- MALTA
- MT
- MLT
- 470
- †
- †
- verMalta
- 22
- MARSHALL ISLANDS
- MH
- MHL
- 584
- †
- †
- †
- †
- MARTINIQUE
- MQ
- MTQ
- 474
- †
- †
- †
- †
- MAURITANIA
- MR
- MRT
- 478
- †
- †
- †
- †
- MAURITIUS
- MU
- MUS
- 480
- †
- †
- †
- †
- MAYOTTE
- YT
- MYT
- 175
- †
- †
- †
- †
- MEXICO
- MX
- MEX
- 484
- CTRY_MEXICO
- 52
- †
- †
- MICRONESIA, FEDERATED STATES OF
- FM
- FSM
- 583
- †
- †
- †
- †
- MOLDOVA, REPUBLIC OF
- MD
- MDA
- 498
- †
- †
- †
- †
- MONACO
- MC
- MCO
- 492
- CTRY_MONACO
- 33
- †
- †
- MONGOLIA
- MN
- MNG
- 496
- CTRY_MONGOLIA
- 976
- †
- †
- MONTSERRAT
- MS
- MSR
- 500
- †
- †
- †
- †
- MOROCCO
- MA
- MAR
- 504
- CTRY_MOROCCO
- 212
- verArabic
- 16
- MOZAMBIQUE
- MZ
- MOZ
- 508
- †
- †
- †
- †
- MYANMAR
- MM
- MMR
- 104
- †
- †
- †
- †
- NAMIBIA
- NA
- NAM
- 516
- †
- †
- †
- †
- NAURU
- NR
- NRU
- 520
- †
- †
- †
- †
- NEPAL
- NP
- NPL
- 524
- †
- †
- verNepal
- 106
- NETHERLANDS
- NL
- NLD
- 528
- CTRY_NETHERLANDS
- 31
- verNetherlands
- 5
- NETHERLANDS ANTILLES
- AN
- ANT
- 530
- †
- †
- †
- †
- NEW CALEDONIA
- NC
- NCL
- 540
- †
- †
- †
- †
- NEW ZEALAND
- NZ
- NZL
- 554
- CTRY_NEW_ZEALAND
- 64
- †
- †
- NICARAGUA
- NI
- NIC
- 558
- CTRY_NICARAGUA
- 505
- †
- †
- NIGER
- NE
- NER
- 562
- †
- †
- †
- †
- NIGERIA
- NG
- NGA
- 566
- †
- †
- †
- †
- NIUE
- NU
- NIU
- 570
- †
- †
- †
- †
- NORFOLK ISLAND
- NF
- NFK
- 574
- †
- †
- †
- †
- NORTHERN MARIANA ISLANDS
- MP
- MNP
- 580
- †
- †
- †
- †
- NORWAY
- NO
- NOR
- 578
- CTRY_NORWAY
- 47
- verNorway
- 12
- OMAN
- OM
- OMN
- 512
- CTRY_OMAN
- 968
- †
- †
- PAKISTAN
- PK
- PAK
- 586
- CTRY_PAKISTAN
- 92
- verPakistanUrdu, verPunjabi
- 34 (U), 95 (P)
- PALAU
- PW
- PLW
- 585
- †
- †
- †
- †
- PANAMA
- PA
- PAN
- 591
- CTRY_PANAMA
- 507
- †
- †
- PALESTINIAN TERRITORY, OCCUPIED
- PS
- 
- 
- 
- 
- †
- †
- PAPUA NEW GUINEA
- PG
- PNG
- 598
- †
- †
- †
- †
- PARAGUAY
- PY
- PRY
- 600
- CTRY_PARAGUAY
- 595
- †
- †
- PERU
- PE
- PER
- 604
- CTRY_PERU
- 51
- †
- †
- PHILIPPINES
- PH
- PHL
- 608
- CTRY_PHILIPPINES
- 63
- †
- †
- PITCAIRN
- PN
- PCN
- 612
- †
- †
- †
- †
- POLAND
- PL
- POL
- 616
- CTRY_POLAND
- 48
- verPoland
- 42
- PORTUGAL
- PT
- PRT
- 620
- CTRY_PORTUGAL
- 351
- verPortugal
- 10
- PUERTO RICO
- PR
- PRI
- 630
- CTRY_PUERTO_RICO
- 1
- †
- †
- QATAR
- QA
- QAT
- 634
- CTRY_QATAR
- 974
- †
- †
- REUNION
- RE
- REU
- 638
- †
- †
- †
- †
- ROMANIA
- RO
- ROU*
- 642
- CTRY_ROMANIA
- 40
- verRomania
- 39
- RUSSIAN FEDERATION
- RU
- RUS
- 643
- CTRY_RUSSIA
- 7
- verRussia
- 49
- RWANDA
- RW
- RWA
- 646
- †
- †
- †
- †
- SAINT KITTS AND NEVIS
- KN
- KNA
- 659
- †
- †
- †
- †
- SAINT LUCIA
- LC
- LCA
- 662
- †
- †
- †
- †
- SAINT VINCENT AND THE GRENADINES
- VC
- VCT
- 670
- †
- †
- †
- †
- SAMOA
- WS
- WSM
- 882
- †
- †
- †
- †
- SAN MARINO
- SM
- SMR
- 674
- †
- †
- †
- †
- SAO TOME AND PRINCIPE
- ST
- STP
- 678
- †
- †
- †
- †
- SAUDI ARABIA
- SA
- SAU
- 682
- CTRY_SAUDI_ARABIA
- 966
- verArabic
- 16
- SENEGAL
- SN
- SEN
- 686
- †
- †
- †
- †
- SERBIA AND MONTENEGRO
- CS
- †
- †
- CTRY_SERBIA
- 381
- †
- †
- SEYCHELLES
- SC
- SYC
- 690
- †
- †
- †
- †
- SIERRA LEONE
- SL
- SLE
- 694
- †
- †
- †
- †
- SINGAPORE
- SG
- SGP
- 702
- CTRY_SINGAPORE
- 65
- verSingapore
- 100
- SLOVAKIA (Slovak Republic)
- SK
- SVK
- 703
- CTRY_SLOVAK
- 421
- verSlovak
- 57†
- SLOVENIA
- SI
- SVN
- 705
- CTRY_SLOVENIA
- 386
- verSlovenian
- 66
- SOLOMON ISLANDS
- SB
- SLB
- 90
- †
- †
- †
- †
- SOMALIA
- SO
- SOM
- 706
- †
- †
- †
- †
- SOUTH AFRICA
- ZA
- ZAF
- 710
- CTRY_SOUTH_AFRICA
- 27
- †
- †
- SOUTH GEORGIA AND THE SOUTH SANDWICH ISLANDS
- GS
- 
- 
- 
- 
- †
- †
- SPAIN
- ES
- ESP
- 724
- CTRY_SPAIN
- 34
- verSpain
- 8
- SRI LANKA
- LK
- LKA
- 144
- †
- †
- †
- †
- SAINT HELENA
- SH
- SHN
- 654
- †
- †
- †
- †
- SAINT PIERRE AND MIQUELON
- PM
- SPM
- 666
- †
- †
- †
- †
- SUDAN
- SD
- SDN
- 736
- †
- †
- †
- †
- SURINAME
- SR
- SUR
- 740
- †
- †
- †
- †
- SVALBARD AND JAN MAYEN ISLANDS
- SJ
- SJM
- 744
- †
- †
- †
- †
- SWAZILAND
- SZ
- SWZ
- 748
- †
- †
- †
- †
- SWEDEN
- SE
- SWE
- 752
- CTRY_SWEDEN
- 46
- verSweden
- 7
- SWITZERLAND
- CH
- CHE
- 756
- CTRY_SWITZERLAND
- 41
- verFrSwiss(fr), verGrSwiss(de)
- 18(fr), 19(de)
- SYRIAN ARAB REPUBLIC
- SY
- SYR
- 760
- CTRY_SYRIA
- 963
- †
- †
- TAIWAN, PROVINCE OF CHINA
- TW
- TWN
- 158
- CTRY_TAIWAN
- 886
- verTaiwan
- 53
- TAJIKISTAN
- TJ
- TJK
- 762
- †
- †
- †
- †
- TANZANIA, UNITED REPUBLIC OF
- TZ
- TZA
- 834
- †
- †
- †
- †
- TATARSTAN
- 
- 
- †
- CTRY_TATARSTAN
- 7
- †
- †
- THAILAND
- TH
- THA
- 764
- CTRY_THAILAND
- 66
- verThailand
- 54
- TIMOR-LESTE
- TL
- 
- 
- †
- †
- †
- †
- TOGO
- TG
- TGO
- 768
- †
- †
- †
- †
- TOKELAU
- TK
- TKL
- 772
- †
- †
- †
- †
- TONGA
- TO
- TON
- 776
- †
- †
- verTonga
- 88
- TRINIDAD AND TOBAGO
- TT
- TTO
- 780
- CTRY_TRINIDAD_Y_TOBAGO
- 1
- †
- †
- TUNISIA
- TN
- TUN
- 788
- CTRY_TUNISIA
- 216
- verArabic
- 16
- TURKEY
- TR
- TUR
- 792
- CTRY_TURKEY
- 90
- verTurkey
- 24
- TURKMENISTAN
- TM
- TKM
- 795
- †
- †
- †
- †
- TURKS AND CAICOS ISLANDS
- TC
- TCA
- 796
- †
- †
- †
- †
- TUVALU
- TV
- TUV
- 798
- †
- †
- †
- †
- UGANDA
- UG
- UGA
- 800
- †
- †
- †
- †
- UKRAINE
- UA
- UKR
- 804
- CTRY_UKRAINE
- 380
- verUkraine†
- 62
- UNITED ARAB EMIRATES
- AE
- ARE
- 784
- CTRY_UAE
- 971
- †
- †
- UNITED KINGDOM
- GB
- GBR
- 826
- CTRY_UNITED_KINGDOM
- 44
- verBritain
- 2
- UNITED STATES
- US
- USA
- 840
- CTRY_UNITED_STATES
- 1
- verUS
- 0
- UNITED STATES MINOR OUTLYING ISLANDS
- UM
- UMI
- 581
- †
- †
- †
- †
- URUGUAY
- UY
- URY
- 858
- CTRY_URUGUAY
- 598
- †
- †
- UZBEKISTAN
- UZ
- UZB
- 860
- CTRY_UZBEKISTAN
- 7
- †
- †
- VANUATU
- VU
- VUT
- 548
- †
- †
- †
- †
- VATICAN CITY STATE (HOLY SEE)
- VA
- VAT
- 336
- †
- †
- †
- †
- VENEZUELA
- VE
- VEN
- 862
- CTRY_VENEZUELA
- 58
- †
- †
- VIET NAM
- VN
- VNM
- 704
- CTRY_VIET_NAM
- 84
- verVietnam
- †
- VIRGIN ISLANDS (BRITISH)
- VG
- VGB
- 92
- †
- †
- †
- †
- VIRGIN ISLANDS (U.S.)
- VI
- VIR
- 850
- †
- †
- †
- †
- WALLIS AND FUTUNA ISLANDS
- WF
- WLF
- 876
- †
- †
- †
- †
- WESTERN SAHARA
- EH
- ESH
- 732
- †
- †
- †
- †
- YEMEN
- YE
- YEM
- 887
- CTRY_YEMEN
- 967
- †
- †
- YUGOSLAVIA
- YU
- YUG
- 891
- †
- †
- †
- †
- ZAIRE
- ZR
- ZAR
- 180
- †
- †
- †
- †
- ZAMBIA
- ZM
- ZMB
- 894
- †
- †
- †
- †
- ZIMBABWE
- ZW
- ZWE
- 716
- CTRY_ZIMBABWE
- 263
- †
- †
- '!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: ISOLanguageDefinition>>iso2 (in category 'accessing') -----
- iso2
- 	^iso2 ifNil: [self iso3]!

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

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

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

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

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

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

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

Item was removed:
- NaturalLanguageTranslator subclass: #InternalTranslator
- 	instanceVariableNames: 'generics'
- 	classVariableNames: 'AllKnownPhrases CachedTranslations'
- 	poolDictionaries: ''
- 	category: 'GetText-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 removed:
- ----- Method: InternalTranslator class>>allKnownPhrases (in category 'private') -----
- allKnownPhrases
- 	^AllKnownPhrases ifNil: [AllKnownPhrases := Dictionary new: 2051]!

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

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

Item was removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>discardAllTranslations (in category 'class initialization') -----
- discardAllTranslations
- 	AllKnownPhrases := nil.
- 	self resetCaches.!

Item was removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>localeID: (in category 'accessing') -----
- localeID: localeID 
- 	"For backward compatibility, see NaturalLanguageTranslator >> fileOutHeaderOn:."
- 	^ self newLocaleID: localeID!

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

Item was removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>newLocaleID: (in category 'accessing') -----
- newLocaleID: localeID 
- 	^ self cachedTranslations
- 		at: localeID
- 		ifAbsentPut: [self new localeID: localeID]!

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

Item was removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>removeLocaleID: (in category 'accessing') -----
- removeLocaleID: localeID 
- 	"self removeLocaleID: (LocaleID isoString: 'ja-kids')"
- 	self cachedTranslations
- 		removeKey: localeID
- 		ifAbsent: [].
- 	NaturalLanguageTranslator privateStartUp!

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

Item was removed:
- ----- Method: InternalTranslator class>>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 removed:
- ----- Method: InternalTranslator class>>services (in category 'file-services') -----
- services
- 	"Answer potential file services associated with this class"
- 	^ {self serviceMergeLanguageTranslations}!

Item was removed:
- ----- Method: InternalTranslator class>>translationSuffix (in category 'private') -----
- translationSuffix
- 	^'translation'!

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: InternalTranslator>>fileOutOn: (in category 'fileIn/fileOut') -----
- fileOutOn: aStream 
- 	"self current fileOutOn: Transcript. Transcript endEntry"
- 	self fileOutOn: aStream keys: nil withBOM: true.
- !

Item was removed:
- ----- 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 removed:
- ----- Method: InternalTranslator>>generics (in category 'private') -----
- generics
- 	^generics ifNil: [generics := Dictionary new]!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: InternalTranslator>>rawPhrase:translation: (in category 'translation') -----
- rawPhrase: phraseString translation: translationString 
- 	self generics at: phraseString put: translationString asString.
- !

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: InternalTranslator>>translations (in category 'accessing') -----
- translations
- 	^self generics!

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

Item was changed:
  ----- Method: LanguageEditor>>getTextExport (in category 'gui methods') -----
  getTextExport
  	Cursor wait
+ 		showWhile: [GetTextExporter new exportTranslator: self model]!
- 		showWhile: [GetTextExporter2 new exportTranslator: self model]!

Item was changed:
  ----- Method: LanguageEditor>>getTextExportTemplate (in category 'gui methods') -----
  getTextExportTemplate
  	Cursor wait
+ 		showWhile: [GetTextExporter new exportTemplate] !
- 		showWhile: [GetTextExporter2 new exportTemplate] !

Item was removed:
- 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: 'GetText-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 removed:
- ----- Method: Locale class>>addLocalChangedListener: (in category 'notification') -----
- addLocalChangedListener: anObjectOrClass
- 	self localeChangedListeners add: anObjectOrClass!

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

Item was removed:
- ----- 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 removed:
- ----- Method: Locale class>>currentPlatform (in category 'accessing') -----
- currentPlatform
- 	"CurrentPlatform := nil"
- 	CurrentPlatform ifNil: [CurrentPlatform := self determineCurrentLocale].
- 	^CurrentPlatform!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: Locale class>>isoLanguage: (in category 'accessing') -----
- isoLanguage: isoLanguage
- 	^self isoLanguage: isoLanguage isoCountry: nil!

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: Locale class>>localeChangedListeners (in category 'notification') -----
- localeChangedListeners
- 	^LocaleChangeListeners ifNil: [LocaleChangeListeners := OrderedCollection new]!

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

Item was removed:
- ----- 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 removed:
- ----- Method: Locale class>>platformEncodings (in category 'class initialization') -----
- platformEncodings
- 	PlatformEncodings isEmptyOrNil ifTrue: [ self initializePlatformEncodings ].
- 	^PlatformEncodings
- !

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

Item was removed:
- ----- Method: Locale class>>resetKnownLocales (in category 'private') -----
- resetKnownLocales
- 
- 	KnownLocales := nil
- !

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: Locale class>>switchAndInstallFontToID: (in category 'accessing') -----
- switchAndInstallFontToID: localeID 
- 	"Locale switchAndInstallFontToID: (LocaleID isoLanguage: 'de')"
- 	| locale |
- 	locale := Locale localeID: localeID.
- 	locale languageEnvironment isFontAvailable
- 		ifFalse: [(self confirm: 'This language needs additional fonts.
- Do you want to install the fonts?' translated)
- 				ifTrue: [locale languageEnvironment installFont]
- 				ifFalse: [^ self]].
- 	self
- 		switchTo: locale!

Item was removed:
- ----- 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 removed:
- ----- Method: Locale class>>switchTo: (in category 'accessing') -----
- switchTo: locale
- 	self switchTo: locale gently: false.
- !

Item was removed:
- ----- 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 removed:
- ----- Method: Locale class>>switchToID: (in category 'accessing') -----
- switchToID: localeID
- 	"Locale switchToID: (LocaleID isoLanguage: 'de') "
- 
- 	self switchTo: (Locale localeID: localeID)!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: Locale>>fetchISOCountry (in category 'private') -----
- fetchISOCountry
- 	"Locale current fetchISOCountry"
- 	| countryCode |
- 	countryCode := self primCountry
- 				ifNil: [^ nil].
- 	^ countryCode copyUpTo: 0 asCharacter!

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: Locale>>primCurrencySymbol (in category 'system primitives') -----
- primCurrencySymbol
- 	"Returns string with currency symbol"
- 	<primitive: 'primitiveCurrencySymbol' module:'LocalePlugin'>
- 	^'$'!

Item was removed:
- ----- 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 removed:
- ----- Method: Locale>>primDecimalSymbol (in category 'system primitives') -----
- primDecimalSymbol
- 	"Returns string with e.g. '.' or ','"
- 	<primitive:'primitiveDecimalSymbol' module: 'LocalePlugin'>
- 	^'.'!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: Locale>>printOn: (in category 'accessing') -----
- printOn: aStream 
- 	super printOn: aStream.
- 	aStream nextPutAll: '(' , id printString , ')'!

Item was removed:
- Object subclass: #LocaleID
- 	instanceVariableNames: 'isoLanguage isoCountry'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'GetText-Localization'!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: LocaleID class>>posixName: (in category 'instance creation') -----
- posixName: aString 
- 	^ self
- 		isoString: (aString copyReplaceAll: ':=' with: '-')!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 := GetTextTranslator translateWithoutLoading: magicPhrase toLocaleID: self.
- 	^ translatedMagicPhrase = magicPhrase
- 		ifTrue: [self displayLanguage]
- 		ifFalse: [translatedMagicPhrase]!

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

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: LocaleID>>printOn: (in category 'printing') -----
- printOn: stream
- 	"<language>-<country>"
- 	stream nextPutAll: self isoLanguage.
- 	self isoCountry
- 		ifNotNil: [stream nextPut: $-; nextPutAll: self isoCountry]!

Item was removed:
- ----- 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 removed:
- ----- Method: LocaleID>>translator (in category 'accessing') -----
- translator
- 	^ InternalTranslator localeID: self !

Item was removed:
- Object subclass: #NaturalLanguageFormTranslator
- 	instanceVariableNames: 'id generics'
- 	classVariableNames: 'CachedTranslations'
- 	poolDictionaries: ''
- 	category: 'GetText-Localization'!

Item was removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageFormTranslator class>>cachedTranslations (in category 'accessing') -----
- cachedTranslations
- 	"CachedTranslations := nil" 
- 	^CachedTranslations ifNil: [CachedTranslations := Dictionary new]!

Item was removed:
- ----- Method: NaturalLanguageFormTranslator class>>cleanUp (in category 'class initialization') -----
- cleanUp
- 	"Flush caches"
- 
- 	CachedTranslations := nil!

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

Item was removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageFormTranslator class>>isoLanguage:isoCountry: (in category 'accessing') -----
- isoLanguage: isoLanguage isoCountry: isoCountry
- 	^self localeID: (LocaleID  isoLanguage: isoLanguage isoCountry: isoCountry)!

Item was removed:
- ----- 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.
- !

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- Object subclass: #NaturalLanguageTranslator
- 	instanceVariableNames: 'id'
- 	classVariableNames: 'Translators'
- 	poolDictionaries: ''
- 	category: 'GetText-Localization'!
- 
- !NaturalLanguageTranslator commentStamp: '<historical>' prior: 0!
- abstract class of natural language translator.
- Class side manages and holds loaded instances of concrete classes.!

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageTranslator class>>cleanUpCache (in category 'private') -----
- cleanUpCache
- 	"NaturalLanguageTranslator cleanUpCache"
- 
- 	self cachedTranslations keys do: [:key |
- 		key isoLanguage size > 2 ifTrue: [self cachedTranslations removeKey: key]]!

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

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

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>domainRegistered: (in category 'accessing') -----
- domainRegistered: aDomainName
- 	"notify that new TextDomain is registered"
- 	self translators do: [:each | each domainRegistered: aDomainName]!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>initialize (in category 'class initialization') -----
- initialize
- 	Smalltalk addToStartUpList: NaturalLanguageTranslator after: FileDirectory.
- !

Item was removed:
- ----- Method: NaturalLanguageTranslator 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 removed:
- ----- Method: NaturalLanguageTranslator class>>isoLanguage:isoCountry: (in category 'accessing') -----
- isoLanguage: isoLanguage isoCountry: isoCountry
- 	^self localeID: (LocaleID  isoLanguage: isoLanguage isoCountry: isoCountry)!

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>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 := langDir directoryNamed: countryDirName.
- 					(countryDir fileNamesMatching: '*.' , self translationSuffix)
- 						ifNotEmpty: [self loadTranslatorForIsoLanguage: langDirName isoCountry: countryDirName]
- 			]
- 		].
- !

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>loadAvailableLocales (in category 'private loading') -----
- loadAvailableLocales
- 	"This loads the default locale and all external locales"
- 
- 	| defaultID |
- 	defaultID := LocaleID current.
- 	self cachedTranslations at: defaultID ifAbsent: [self localeID: defaultID].
- 	self loadAvailableExternalLocales.!

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>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 localeID: (LocaleID isoLanguage: isoLanguage isoCountry: isoCountry).
- 
- 	self loadExternalTranslationsFor: translator!

Item was removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>localeID: (in category 'accessing') -----
- localeID: localeID 
- 	^ self cachedTranslations
- 		at: localeID
- 		ifAbsentPut: [self new localeID: localeID]!

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>mergeTranslationFileNamed: (in category 'file-services') -----
- mergeTranslationFileNamed: fileFullNameString 
- 	"merge the translation in the file named fileFullNameString"
- 
- 	FileStream readOnlyFileNamed: fileFullNameString do: [:stream |
- 		| localeID translator |
- 		localeID := LocaleID isoString: stream localName sansPeriodSuffix.
- 		translator := self localeID: localeID.
- 		translator loadFromStream: stream].
- 	LanguageEnvironment resetKnownEnvironments.
- 
- !

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

Item was removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>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 removed:
- ----- Method: NaturalLanguageTranslator class>>removeLocaleID: (in category 'accessing') -----
- removeLocaleID: localeID 
- 	"self removeLocaleID: (LocaleID isoString: 'ja-kids')"
- 	^ self translators
- 		removeKey: localeID
- 		ifAbsent: []!

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageTranslator class>>translationSuffix (in category 'private') -----
- translationSuffix
- 	^'translation'!

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

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>checkPhrase:translation: (in category 'translation') -----
- checkPhrase: phrase translation: translation!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>displayLanguage (in category 'accessing') -----
- displayLanguage
- 	^ id displayLanguage!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>displayName (in category 'accessing') -----
- displayName
- 	^ id displayName!

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageTranslator>>fileOutHeader (in category 'fileIn/fileOut') -----
- fileOutHeader
- 	^ '''Translation dictionary'''!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>fileOutHeaderOn: (in category 'fileIn/fileOut') -----
- fileOutHeaderOn: aStream 
- 	aStream nextChunkPut: self fileOutHeader;
- 		 cr.
- 	aStream timeStamp; cr.
- 	aStream nextPut: $!!.
- 	aStream nextChunkPut: '(' , self class name , ' localeID: ' , id storeString , ')'.
- 	aStream cr!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>fileOutOn: (in category 'fileIn/fileOut') -----
- fileOutOn: aStream 
- 	"self current fileOutOn: Transcript. Transcript endEntry"
- 	self fileOutHeaderOn: aStream.
- 	self fileOutOn: aStream keys: nil!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>fileOutOn:keys: (in category 'fileIn/fileOut') -----
- fileOutOn: aStream keys: keys 
- 	"self current fileOutOn: Transcript. Transcript endEntry"
- 	(keys
- 		ifNil: [generics keys asArray sort])
- 		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 removed:
- ----- Method: NaturalLanguageTranslator>>generics (in category 'private') -----
- generics
- 	^generics ifNil: [generics := Dictionary new]!

Item was removed:
- ----- 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 removed:
- ----- Method: NaturalLanguageTranslator>>isoCountry (in category 'accessing') -----
- isoCountry
- 	^self localeID isoCountry!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>isoLanguage (in category 'accessing') -----
- isoLanguage
- 	^self localeID isoLanguage!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>loadFromFileNamed: (in category 'private store-retrieve') -----
- loadFromFileNamed: fileNameString 
- 	"Load translations from an external file"
- 
- 	FileStream readOnlyFileNamed: fileNameString do: [ :file |
- 		self loadFromStream: file ].
- 	self changed: #translations.
- 	self changed: #untranslated.
- !

Item was removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>localeID (in category 'accessing') -----
- localeID
- 	^id!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>phrase:translation: (in category 'translation') -----
- phrase: phraseString translation: translationString 
- 	self generics at: phraseString put: translationString asString.
- 	self changed: #translations.
- 	self changed: #untranslated.!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>rawPhrase:translation: (in category 'translation') -----
- rawPhrase: phraseString translation: translationString 
- 	self generics at: phraseString put: translationString asString.
- !

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

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

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>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 removed:
- ----- Method: NaturalLanguageTranslator>>scanFrom: (in category 'fileIn/fileOut') -----
- scanFrom: aStream 
- 	"Read a definition of dictionary.  
- 	Make sure current locale corresponds my locale id"
- 	| newTranslations currentPlatform |
- 	newTranslations := Dictionary new.
- 	currentPlatform := Locale currentPlatform.
- 	[ | aString assoc |
- 	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 removed:
- ----- Method: NaturalLanguageTranslator>>setCurrent (in category 'language switching') -----
- setCurrent
- 	"notify locale of the translator become current"
- !

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>translate:in: (in category 'translation') -----
- translate: aString in: aContext!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>translationFor: (in category 'translation') -----
- translationFor: aString
- 	^self translate: aString!

Item was removed:
- ----- Method: NaturalLanguageTranslator>>translations (in category 'accessing') -----
- translations
- 	^self generics!

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

Item was removed:
- ----- Method: NaturalLanguageTranslator>>writeAsMimeString (in category 'fileIn/fileOut') -----
- writeAsMimeString
- 
- 	| fileName fileStream tmpStream s2 gzs |
- 	tmpStream := MultiByteBinaryOrTextStream on: ''.
- 	tmpStream converter: UTF8TextConverter new.
- 	self fileOutOn: tmpStream.
- 	s2 := RWBinaryOrTextStream on: ''.
- 	gzs := GZipWriteStream on: s2.
- 	tmpStream reset.
- 	gzs nextPutAll: (tmpStream binary contentsOfEntireFile asString) contents.
- 	gzs close.
- 	s2 reset.
- 
- 	fileName := id isoString, '.translation.gz.mime'.
- 	fileStream := FileStream newFileNamed: fileName.
- 	fileStream nextPutAll: (Base64MimeConverter mimeEncode: s2) contents.
- 	fileStream close.
- !



More information about the Packages mailing list