Squeak 4.6: GetText-mt.37.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

Squeak 4.6: GetText-mt.37.mcz

commits-2
Chris Muller uploaded a new version of GetText to project Squeak 4.6:
http://source.squeak.org/squeak46/GetText-mt.37.mcz

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

Name: GetText-mt.37
Author: mt
Time: 10 May 2015, 1:57:01.667 pm
UUID: 0033c111-0112-dd4f-95ac-0a56cc7a0f68
Ancestors: GetText-nice.36

Skip registering LanguageEditor in world menu for now because it is not functional at the moment.

==================== Snapshot ====================

SystemOrganization addCategory: #'GetText-Editor'!

Object subclass: #GetTextExporter
        instanceVariableNames: 'stream'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'GetText-Editor'!

!GetTextExporter commentStamp: '<historical>' prior: 0!
Export translations to gettext format divided into categories.

"Export gettext template files"
GetTextExporter new exportTemplate.

"Export translation files for current locale"
GetTextExporter new exportTranslator: (InternalTranslator newLocaleID: LocaleID current).

"Export all gettext template and po files."
GetTextExporter exportAll.

!

----- Method: GetTextExporter 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!

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

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

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

----- Method: GetTextExporter 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.

]]!

----- Method: GetTextExporter 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.
        self new exportTranslator: src.
        InternalTranslator removeLocaleID: localeID.
        dst := localeID translator.
        GetTextImporter import: dst allDirectory: FileDirectory default!

----- Method: GetTextExporter 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']!

----- Method: GetTextExporter>>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 := (PackageOrganizer default packageOfMethod: methodReference ifNone: [nil]).
                domainName := domainName isNil ifTrue: [TextDomainManager defaultDomain] ifFalse: [domainName name].
                literals := domains at: domainName ifAbsentPut: [Dictionary new].
                keywords do: [ :literal |
                        references := literals at: literal ifAbsentPut: [OrderedCollection new].
                        references add: methodReference.
                ].
        ].

!

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

----- Method: GetTextExporter>>appendVocabularies: (in category 'private') -----
appendVocabularies: domains
        | literalsForDomain references domainName methodReference |
       
        EToyVocabulary allPhrasesWithContextToTranslate do: [ :r |
                methodReference :=  (MethodReference class: (r second) selector: (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.
                ].
        ].
        !

----- Method: GetTextExporter>>createExtraInformation (in category 'private') -----
createExtraInformation
        | extras |
        extras := OrderedCollection new.
        #(
                'Language name as you''d like it to appear in the Languages menu' 'Language-Name'
                'Directionality of language' 'Language-Direction'
                ) pairsDo: [:first :second |
                        extras add: (Array with: '' with: first with: second).
        ].
        ^ extras!

----- Method: GetTextExporter>>createHeaders (in category 'private-headers') -----
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!

----- Method: GetTextExporter>>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']!

----- Method: GetTextExporter>>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!

----- Method: GetTextExporter>>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 := domain,
                                                (translator
                                                        ifNil: ['.pot']
                                                        ifNotNil: ['.po']).
        dirName := 'po', FileDirectory slash,
                                                                (translator
                                                                                ifNil: ['templates']
                                                                                ifNotNil: [translator localeID posixName]).
        pathName := dirName , FileDirectory slash , fileName.
        (FileDirectory default directoryNamed: dirName) assureExistence.
        ^ pathName!

----- Method: GetTextExporter>>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.
        domainName = TextDomainManager defaultDomain
        ifTrue: [self exportInformation: self createExtraInformation].
        self exportBody: literals translator: translator]
                ensure: [stream close]!

----- Method: GetTextExporter>>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)]!

----- Method: GetTextExporter>>exportHeader (in category 'private-headers') -----
exportHeader
        self exportTag: 'msgid' msg: ''.
        self exportTag: 'msgstr' msg: ''.
        self createHeaders
                do: [:each | self exportHeaderLineKey: each key value: each value].
        stream cr; cr!

----- Method: GetTextExporter>>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!

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

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

----- Method: GetTextExporter>>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!

----- Method: GetTextExporter>>exportRecordHeader: (in category 'private') -----
exportRecordHeader: context
        stream
                nextPutAll: '#: ';
                nextPutAll: context;
                cr.!

----- Method: GetTextExporter>>exportTag:msg: (in category 'private') -----
exportTag: tag msg: aString
        stream nextPutAll: tag.
        stream space.
        aString lineIndicesDo: [:start :endWithoutDelimiters :end |
                | line |
                line := (end = endWithoutDelimiters)
                        ifTrue: [aString copyFrom: start to: endWithoutDelimiters]
                        ifFalse: [(aString at: endWithoutDelimiters + 1) = Character cr
                                ifTrue: [aString copyFrom: start to: endWithoutDelimiters + 1]
                                ifFalse: [(aString copyFrom: start to: endWithoutDelimiters) copyWith: Character cr]].
                stream
                        nextPut: $";
                        nextPutAll: (self formatString: line);
                        nextPut: $";
                        cr].!

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

----- Method: GetTextExporter>>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]!

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

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

----- Method: GetTextExporter>>getTextDomainForPackage: (in category 'as yet unclassified') -----
getTextDomainForPackage: aPackageInfo
        ^TextDomainManager domainForPackage: aPackageInfo!

----- Method: GetTextExporter>>stream (in category 'accessing') -----
stream
        ^ stream!

----- Method: GetTextExporter>>stream: (in category 'accessing') -----
stream: aStream
        stream := aStream!

----- Method: GetTextExporter>>translationFor:in: (in category 'private') -----
translationFor: aKey in: translator
        | translation |
        translator ifNil: [^ ''].
        TextDomainManager allKnownDomains do: [:domain |
                translation := translator translate: aKey inDomain: domain.
                aKey = translation ifFalse: [^translation]
        ].
        ^ aKey!

Object subclass: #GetTextInterchange
        instanceVariableNames: 'language stream'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'GetText-Editor'!

GetTextInterchange subclass: #GetTextImporter
        instanceVariableNames: 'msgId msgStr state'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'GetText-Editor'!

!GetTextImporter commentStamp: 'tak 10/24/2007 11:23' prior: 0!
GetTextImporter load gettext po file into a InternalTranslator.

GetTextImporter new importID: (LocaleID isoString: 'lang-name') fileNamed: 'lang.po'
!

----- Method: GetTextImporter class>>cleanUpUnnecessaryPhrases (in category 'utilities') -----
cleanUpUnnecessaryPhrases
        | keys refuse replaceBlock reader writer char result |
        "GetTextImporter cleanUpUnnecessaryPhrases"
        ""
        "Collect wrong phrases"
        keys := InternalTranslator allKnownPhrases copy keys.
        refuse := Set new.
        "replaceBlock value: 'te\\nst'."
        replaceBlock := [:aString |
                        reader := aString readStream.
                        writer := '' writeStream.
                        [reader atEnd]
                                whileFalse: [char := reader next.
                                        (char = $\
                                                        and: [reader peek = $\])
                                                ifFalse: [writer nextPut: char]].
                        writer contents].
        keys
                do: [:each |
                        result := replaceBlock value: each.
                        (result ~= each
                                        and: [keys includes: result])
                                ifTrue: [refuse add: each].
                        result := GetTextImporter new formatString: each.
                        (result ~= each
                                        and: [keys includes: result])
                                ifTrue: [refuse add: each]].
        ""
        "Remove from translated"
        InternalTranslator cachedTranslations
                do: [:each | refuse
                                do: [:key | each translations
                                                removeKey: key
                                                ifAbsent: []]].
        ""
        "Remove from untranslated"
        refuse
                do: [:key | InternalTranslator allKnownPhrases
                                removeKey: key
                                ifAbsent: []]!

----- Method: GetTextImporter class>>import:allDirectory: (in category 'utilities') -----
import: translator allDirectory: aFileDirectory
        "self import: NaturalLanguageTranslator current allDirectory:
        FileDirectory default"
        | fileName targetFile |
        fileName := translator localeID posixName , '.po'.
        (FileDirectory default directoryNamed: 'po')
                withAllSubdirectoriesCollect: [:each | (each fileExists: fileName)
                                ifTrue: [targetFile := each fullNameFor: fileName.
                                        self new import: translator fileNamed: targetFile]]!

----- Method: GetTextImporter class>>importAll (in category 'utilities') -----
importAll
        "GetTextImporter importAll"
        "Import all gettext files on po/. Only registered language is imported"
        InternalTranslator cachedTranslations
                do: [:translator | self import: translator allDirectory: FileDirectory default]!

----- Method: GetTextImporter>>appendId: (in category 'parsing') -----
appendId: aString
        msgId := msgId , aString!

----- Method: GetTextImporter>>appendStr: (in category 'parsing') -----
appendStr: aString
        msgStr := msgStr , aString!

----- Method: GetTextImporter>>formatString: (in category 'private') -----
formatString: aString
"
        self assert: (GetTextImporter new formatString: 'test') = 'test'.
        self assert: (GetTextImporter new formatString: 'te\nst') = ('te', String cr, 'st').
        self assert: (GetTextImporter new formatString: 'te\\nst') = ('te\nst').
        self assert: (GetTextImporter new formatString: 'te\\st') = ('te\st').
        self assert: (GetTextImporter new formatString: 'te\st') = ('te\st').
"
        | reader writer char |
        reader := aString readStream.
        writer := '' writeStream.
        [reader atEnd]
                whileFalse: [char := reader next.
                        (char = $\
                                        and: [reader atEnd not])
                                ifTrue: [char := reader next.
                                        char caseOf: {
                                                [$n] -> [writer nextPut: Character cr].
                                                [$t] -> [writer nextPut: Character tab].
                                                [$"] -> [writer nextPut: $"].
                                                [$\] -> [writer nextPut: $\]}
                                                 otherwise: [writer nextPutAll: {$\. char}]]
                                ifFalse: [writer nextPut: char]].
        ^ writer contents!

----- Method: GetTextImporter>>import: (in category 'importing') -----
import: aLanguage
        ^ self import: aLanguage fileNamed:  aLanguage localeID posixName , '.po'!

----- Method: GetTextImporter>>import:fileNamed: (in category 'importing') -----
import: aLanguage fileNamed: fileName
        self importID: aLanguage localeID fileNamed: fileName!

----- Method: GetTextImporter>>importID:fileNamed: (in category 'importing') -----
importID: localeID fileNamed: fileName
        | currentPlatform |
        language := InternalTranslator newLocaleID: localeID.
        currentPlatform := Locale currentPlatform.
        [Locale
                currentPlatform: (Locale localeID: localeID).
        [stream := FileStream readOnlyFileNamed: fileName.
        stream text.
        self parse]
                ensure: [stream notNil
                                ifTrue: [stream close]]]
                ensure: [Locale currentPlatform: currentPlatform].
        NaturalLanguageTranslator privateStartUp "Actually it is not private no more...".!

----- Method: GetTextImporter>>initialize (in category 'initialize-release') -----
initialize
        msgId := ''.
        msgStr := ''.
        state := nil!

----- Method: GetTextImporter>>parse (in category 'parsing') -----
parse
        | size |
        size := (stream isKindOf: FileStream)
                                ifTrue: [stream size]
                                ifFalse: [1].
        ProgressInitiationException
                display: 'Importing phrases from a gettext file.'
                during: [:bar | [stream atEnd]
                                whileFalse: [| line |
                                        line := stream upTo: Character linefeed.
                                        self
                                                parseLine: ((line endsWith: String cr)
                                                                ifTrue: [line allButLast]
                                                                ifFalse: [line]).
                                        bar value: stream position / size]].
        self storeTranslation!

----- Method: GetTextImporter>>parseLine: (in category 'parsing') -----
parseLine: lineString
        (lineString beginsWith: '"Content-Type:')
                ifTrue: [self setContentType: lineString.
                        ^ self].
        (lineString beginsWith: '#')
                ifTrue: ["do nothing"
                        ^ self].
        lineString = ''
                ifTrue: [^ self storeTranslation].
        (lineString beginsWith: 'msgid')
                ifTrue: [state := #appendId:.
                        self parseMsg: lineString.
                        ^ self].
        (lineString beginsWith: 'msgstr')
                ifTrue: [state := #appendStr:.
                        self parseMsg: lineString.
                        ^ self].
        self parseMsg: lineString!

----- Method: GetTextImporter>>parseMsg: (in category 'parsing') -----
parseMsg: lineString
        | begin end msg |
        begin := lineString indexOf: $".
        end := lineString lastIndexOf: $".
        msg := begin + 1 <= (end - 1)
                                ifTrue: [lineString copyFrom: begin + 1 to: end - 1]
                                ifFalse: [''].
        state
                ifNotNil: [self perform: state with: msg].
        ^ msg!

----- Method: GetTextImporter>>setContentType: (in category 'parsing') -----
setContentType: lineString
        "self new setContentType: 'Content-Type: text/plain; charset=utf-8'"
        | reader charSet |
        reader := lineString readStream.
        reader upTo: $=.
        charSet := reader upTo: $\.
        stream
                converter: (TextConverter newForEncoding: charSet)!

----- Method: GetTextImporter>>storeTranslation (in category 'parsing') -----
storeTranslation
        | key |
        key := self formatString: msgId.
        msgId isEmpty
                ifFalse: [InternalTranslator registerPhrase: key.
                        msgStr isEmpty
                                ifFalse: [language
                                                rawPhrase: key
                                                translation: (self formatString: msgStr)]].
        self initialize!

----- Method: GetTextInterchange>>defaultFileName (in category 'private') -----
defaultFileName
        ^ language localeID posixName , '.po'!

----- Method: GetTextInterchange>>language: (in category 'accessing') -----
language: translator
        language := translator!

----- Method: GetTextInterchange>>stream (in category 'accessing') -----
stream
        ^ stream!

----- Method: GetTextInterchange>>stream: (in category 'accessing') -----
stream: aStream
        stream := aStream!

SystemWindow subclass: #LanguageEditor
        instanceVariableNames: 'translator translations untranslated selectedTranslation selectedTranslations selectedUntranslated translationsList untranslatedList translationText translationsFilter untranslatedFilter newerKeys'
        classVariableNames: 'CheckMethods'
        poolDictionaries: ''
        category: 'GetText-Editor'!

!LanguageEditor commentStamp: 'dgd 11/16/2003 15:02' prior: 0!
Editor for Babel's languages.

Open it from

        World Menu >> open... >> Language Editor (to open on default language)
        World Menu >> open... >> Language Editor for... (to choose the language)

Or click:

        LanguageEditor openOnDefault.
        LanguageEditor open.

See http://swiki.agro.uba.ar/small_land/191 for documentation
!

----- Method: LanguageEditor class>>checkMethods (in category 'private') -----
checkMethods
        ^CheckMethods ifNil: [CheckMethods := self initCheckMethods]!

----- Method: LanguageEditor class>>ensureVisibilityOfWindow: (in category 'private') -----
ensureVisibilityOfWindow: aWindow
        "private - activate the window"
        | |
        aWindow expand.
        aWindow comeToFront.
        ""
        aWindow
                right: (aWindow right min: World right).
        aWindow
                bottom: (aWindow bottom min: World bottom).
        aWindow
                left: (aWindow left max: World left).
        aWindow
                top: (aWindow top max: World top).
        ""
        aWindow flash; flash!

----- Method: LanguageEditor class>>initCheckMethods (in category 'initialize-release') -----
initCheckMethods
        "LanguageEditor initCheckMethods"

        | registry |
        registry := Dictionary new.
        registry
                at: 'es' put: #checkSpanishPhrase:translation:;
                yourself.
        ^registry!

----- Method: LanguageEditor class>>initialize (in category 'initialize-release') -----
initialize
        "initialize the receiver"
        "(TheWorldMenu respondsTo: #registerOpenCommand:)
                ifTrue: [
                        TheWorldMenu registerOpenCommand: {'Language Editor' translated. {self. #openOnDefault}}.
                        TheWorldMenu registerOpenCommand: {'Language Editor for...' translated. {self. #open}}]"!

----- Method: LanguageEditor class>>on: (in category 'instance creation') -----
on: localeID
        "answer an instance of the receiver on aLanguage"
        ^ self new
                initializeOn: (InternalTranslator cachedTranslations
                                at: localeID
                                ifAbsent: [self
                                                inform: ('Translator for {1} is not found' translated format: {localeID}). ^nil])!

----- Method: LanguageEditor class>>open (in category 'opening') -----
open
        "open the receiver on any language"
        "
        LanguageEditor open.
        "
        | menu availableLanguages |
        menu := MenuMorph new defaultTarget: self.
        menu addTitle: 'Language Editor for...' translated.
        ""
        availableLanguages := (InternalTranslator availableLanguageLocaleIDs asSortedCollection: [:x :y | x asString <= y asString]).
        availableLanguages ifEmpty:[^self inform:'InternalTranslator not initialized'].
        availableLanguages
                do: [:eachLanguage | ""
                        menu
                                add: eachLanguage name
                                target: self
                                selector: #openOn:
                                argument: eachLanguage].
        ""
        menu popUpInWorld!

----- Method: LanguageEditor class>>openOn: (in category 'instance creation') -----
openOn: aLanguage
        "open an instance on aLanguage"
        | editor |
        World submorphs
                do: [:each | ""
                        ((each isKindOf: LanguageEditor)
                                        and: [each translator == aLanguage])
                                ifTrue: [""
                                        self ensureVisibilityOfWindow: each.
                                        ^ self]].
        ""
         editor := self on: aLanguage.
         editor ifNotNil:[^editor openInWorld]!

----- Method: LanguageEditor class>>openOnDefault (in category 'opening') -----
openOnDefault
        "open the receiver on the default language"
        self openOn: LocaleID current!

----- Method: LanguageEditor class>>unload (in category 'initialize-release') -----
unload
        "the receiver is being unloaded"
        (TheWorldMenu respondsTo: #registerOpenCommand:)
                ifTrue: [""
                        TheWorldMenu unregisterOpenCommand: 'Language Editor'.
                        TheWorldMenu unregisterOpenCommand: 'Language Editor for...'] !

----- Method: LanguageEditor>>addTranslation (in category 'gui methods') -----
addTranslation
        "translate a phrase"
        | phrase |
        phrase := UIManager default
                                request: 'enter the original:' translated
                                initialAnswer: ''.

        (phrase isNil
                        or: [phrase = ''])
                ifTrue: [
                        self beep.
                        ^ self].

        self translatePhrase: phrase!

----- Method: LanguageEditor>>applyTranslations (in category 'gui methods') -----
applyTranslations
        "private - try to apply the translations as much as possible all  
        over the image"
        Project current updateLocaleDependents!

----- Method: LanguageEditor>>asHtml: (in category 'reporting') -----
asHtml: aString
        | stream |
        stream := String new writeStream.

        aString
                do: [:each |
                        each caseOf: {
                                [Character cr] -> [stream nextPutAll: '<br>'].
                                [$&] -> [stream nextPutAll: '&amp;'].
                                [$<] -> [stream nextPutAll: '&lt;'].
                                [$>] -> [stream nextPutAll: '&gt;'].
                                [$*] -> [stream nextPutAll: '&star;'].
                                [$@] -> [stream nextPutAll: '&at;']}
                                 otherwise: [stream nextPut: each]].

        ^ stream contents!

----- Method: LanguageEditor>>browseMethodsWithTranslation (in category 'gui methods') -----
browseMethodsWithTranslation
        | translation |
        self selectedTranslation isZero
                ifTrue: [""
                        self beep.
                        self inform: 'select the translation to look for' translated.
                        ^ self].
        ""
        translation := self translations at: self selectedTranslation.
        self systemNavigation browseMethodsWithLiteral: translation!

----- Method: LanguageEditor>>browseMethodsWithUntranslated (in category 'gui methods') -----
browseMethodsWithUntranslated
        | untrans |
        self selectedUntranslated isZero
                ifTrue: [""
                        self beep.
                        self inform: 'select the untrans phrase to look for' translated.
                        ^ self].
        ""
        untrans := self untranslated at: self selectedUntranslated.
        SystemNavigation default browseMethodsWithLiteral: untrans.
!

----- Method: LanguageEditor>>check (in category 'private') -----
check
        "check the translations and answer a collection with the results"
        | results counter phrasesCount checkMethod |
        results := OrderedCollection new.
        untranslated := self untranslated.
        phrasesCount := self translations size + self untranslated size.
        counter := 0.
        checkMethod := self class checkMethods at: self translator localeID printString ifAbsent: [^results].
       
        self translations
                keysAndValuesDo: [:phrase :translation |
                        | result |
                        result := self perform: checkMethod with: phrase with: translation.
                        (result notNil
                                        and: [result notEmpty])
                                ifTrue: [results add: {phrase. translation. result}].
               
                        counter := counter + 1.
                        (counter isDivisibleBy: 50)
                                ifTrue: [| percent |
                                        percent := counter / phrasesCount * 100 printShowingMaxDecimalPlaces: 2.
                                        Transcript
                                                show: ('- checked {1} phrases of {2} ({3}%)...' translated format: {counter. phrasesCount. percent});
                                                 cr]].

        self untranslated
                do: [:phrase |
                        | result |
                        result := self checkUntranslatedPhrase: phrase.
                        (result notNil
                                        and: [result notEmpty])
                                ifTrue: [results add: {phrase. nil. result}].
               
                        counter := counter + 1.
                        (counter isDivisibleBy: 50)
                                ifTrue: [| percent |
                                        percent := counter / phrasesCount * 100 printShowingMaxDecimalPlaces: 2.
                                        Transcript
                                                show: ('- checked {1} phrases of {2} ({3}%)...' translated format: {counter. phrasesCount. percent});
                                                 cr]].

        ^ results!

----- Method: LanguageEditor>>checkPhrase:translation: (in category 'private') -----
checkPhrase: phraseString translation: translationString
        ^nil!

----- Method: LanguageEditor>>checkSpanishPhrase:translation: (in category 'private') -----
checkSpanishPhrase: phraseString translation: translationString
        "check the translation and aswer a string with a comment or a
        nil meaning no-comments"
        | superResult |
        superResult := self checkPhrase: phraseString translation: translationString.
        superResult isNil
                ifFalse: [^ superResult].
        "For some reason, MCInstaller couldn't read Spanish character. "
        "((translationString includes: $?)
        and: [(translationString includes: $ø) not])
                ifTrue: [^ 'øOlvidÛ el signo de pregunta?'].
        ((translationString includes: $!!)
        and: [(translationString includes: $°) not])
                ifTrue: [^ 'øOlvidÛ el signo de admiraciÛn?'].
        "
        ^ nil
!

----- Method: LanguageEditor>>checkUntranslatedPhrase: (in category 'private') -----
checkUntranslatedPhrase: phraseString
        "check the phrase an aswer a string with a comment or a nil  
        meaning no-comments"

        (self translations includes: phraseString)
                ifTrue: [^ 'possible double-translation' translated].

        ^ nil!

----- Method: LanguageEditor>>codeSelectedTranslation (in category 'gui methods') -----
codeSelectedTranslation
        | keys code |
        keys := selectedTranslations
                                collect: [:key | self translations at: key].
        code := String
                                streamContents: [:aStream | self translator fileOutOn: aStream keys: keys withBOM: false].
        (StringHolder new contents: code)
                openLabel: 'exported codes' translated!

----- Method: LanguageEditor>>codeSelectedTranslationAsMimeString (in category 'gui methods') -----
codeSelectedTranslationAsMimeString
        | keys code cont |
        keys := selectedTranslations
                                collect: [:key | self translations at: key].
        code := String
                                streamContents: [:aStream | self translator fileOutOn: aStream keys: keys withBOM: false].

        cont := String streamContents: [:strm |
                strm nextPutAll: '"UTF8+Gzip+Base64 encoded translation for;'; cr.
                strm nextPutAll: '#('.
                keys do: [:each | strm  nextPutAll: '''', each, ''' '.].
                strm nextPutAll: ')"'; cr; cr.
                strm nextPutAll: 'NaturalLanguageTranslator loadForLocaleIsoString: '.
                strm nextPut: $'.
                strm nextPutAll: translator localeID isoString.
                strm nextPut: $'.
                strm nextPutAll: ' fromGzippedMimeLiteral: '.
                strm nextPut: $'.
                strm nextPutAll: code squeakToUtf8 asByteArray zipped base64Encoded.
                strm nextPutAll: '''.'.
                strm cr.
        ].
       
        (StringHolder new contents: cont)
                openLabel: 'exported codes in UTF8+Gzip+Base64 encoding' translated!

----- Method: LanguageEditor>>createButtonLabel:action:help: (in category 'initialization - toolbar') -----
createButtonLabel: aString action: actionSelector help: helpString
        "create a toolbar for the receiver"
        | button |
        button := SimpleButtonMorph new target: self;
                                 label: aString translated "font: Preferences standardButtonFont";
                                 actionSelector: actionSelector;
                                 setBalloonText: helpString translated;
                                 color: translator defaultBackgroundColor twiceDarker;
                                 borderWidth: 2;
                                 borderColor: #raised.
        ""
        ^ button!

----- Method: LanguageEditor>>createMainToolbar (in category 'initialization - toolbar') -----
createMainToolbar
        "create a toolbar for the receiver"
        | toolbar |
        toolbar := self createRow.
        ""
" toolbar
                addMorphBack: (self
                                createUpdatingButtonWording: #debugWording
                                action: #switchDebug
                                help: 'Switch the debug flag')."
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        ""
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'new'
                                action: #newTranslations
                                help: 'Create translations for new language.').
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'save'
                                action: #saveToFile
                                help: 'Save the translations to a file').
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'load'
                                action: #loadFromFile
                                help: 'Load the translations from a file').
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'merge'
                                action: #mergeFromFile
                                help: 'Merge the current translations with the translations in a file').
        ""
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'apply'
                                action: #applyTranslations
                                help: 'Apply the translations as much as possible.').
        ""
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'check translations'
                                action: #check
                                help: 'Check the translations and report the results.').
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'report'
                                action: #report
                                help: 'Create a report.').
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'gettext'
                                action: #getText
                                help: 'Interface with gettext.').
        ""
        ^ toolbar!

----- Method: LanguageEditor>>createRow (in category 'initialization - toolbar') -----
createRow
        "create a row"
        | row |
        row := AlignmentMorph newRow.
        row layoutInset: 3;
                 wrapCentering: #center;
                 cellPositioning: #leftCenter.
        ""
        ^ row!

----- Method: LanguageEditor>>createStatusbar (in category 'initialization - statusbar') -----
createStatusbar
        "create the statusbar for the receiver"
        | statusbar |
        statusbar := self createRow.
        statusbar addMorph: ((UpdatingStringMorph on: self selector: #status) growable: true;
                         useStringFormat;
                         hResizing: #spaceFill;
                         stepTime: 2000).
        ^ statusbar!

----- Method: LanguageEditor>>createTranslationsToolbar (in category 'initialization - toolbar') -----
createTranslationsToolbar
        "create a toolbar for the receiver"
        | toolbar |
        toolbar := self createRow.
        ""
        toolbar
                addMorphBack: (self
                                createUpdatingButtonWording: #translationsFilterWording
                                action: #filterTranslations
                                help: 'Filter the translations list.').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        ""
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'search'
                                action: #searchTranslation
                                help: 'Search for a translation containing...').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'remove'
                                action: #removeTranslation
                                help: 'Remove the selected translation.  If none is selected, ask for the one to remove.').
        ""
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'where'
                                action: #browseMethodsWithTranslation
                                help: 'Launch a browser on all methods that contain the phrase as a substring of any literal String.').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'r-unused'
                                action: #removeTranslatedButUnusedStrings
                                help: 'Remove all the strings that are not used by the system').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'add '
                                action: #addTranslation
                                help: 'Add a new phrase').

        ^ toolbar!

----- Method: LanguageEditor>>createUntranslatedToolbar (in category 'initialization - toolbar') -----
createUntranslatedToolbar
        "create a toolbar for the receiver"
        | toolbar |
        toolbar := self createRow.
        ""
        toolbar
                addMorphBack: (self
                                createUpdatingButtonWording: #untranslatedFilterWording
                                action: #filterUntranslated
                                help: 'Filter the untranslated list.').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        ""
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'search'
                                action: #searchUntranslated
                                help: 'Search for a untranslated phrase containing...').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'remove'
                                action: #removeUntranslated
                                help: 'Remove the selected untranslated phrease.  If none is selected, ask for the one to remove.').
        ""
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'translate'
                                action: #translate
                                help: 'Translate the selected untranslated phrase or a new phrase').
        ""
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'where'
                                action: #browseMethodsWithUntranslated
                                help: 'Launch a browser on all methods that contain the phrase as a substring of any literal String.').
        toolbar addTransparentSpacerOfSize: 5 @ 0.
        toolbar
                addMorphBack: (self
                                createButtonLabel: 'r-unused'
                                action: #removeUntranslatedButUnusedStrings
                                help: 'Remove all the strings that are not used by the system').
        ^ toolbar!

----- Method: LanguageEditor>>createUpdatingButtonWording:action:help: (in category 'initialization - toolbar') -----
createUpdatingButtonWording: wordingSelector action: actionSelector help: helpString
        "create a toolbar for the receiver"
        | button |
        button := (UpdatingSimpleButtonMorph newWithLabel: '-') target: self;
                                 wordingSelector: wordingSelector;
                                 actionSelector: actionSelector;
                                 setBalloonText: helpString translated;
                                 color: translator defaultBackgroundColor twiceDarker;
                                 borderWidth: 1;
                                 borderColor: #raised; cornerStyle: #square.
        ""
        ^ button!

----- Method: LanguageEditor>>delete (in category 'open/close') -----
delete
        "Remove the receiver as a submorph of its owner"
        self model: nil.
        super delete !

----- Method: LanguageEditor>>deselectAllTranslation (in category 'gui methods') -----
deselectAllTranslation
        selectedTranslations := IdentitySet new.
        self changed: #allSelections!

----- Method: LanguageEditor>>filterTranslations (in category 'gui methods') -----
filterTranslations
        | filter |
        filter := UIManager default
                request: 'filter with
(empty string means no-filtering)' translated
                initialAnswer: self translationsFilter.

        self filterTranslations: filter!

----- Method: LanguageEditor>>filterTranslations: (in category 'gui methods') -----
filterTranslations: aString
| filter |
filter := aString ifNil:[''].
""
        translationsFilter := filter.
        self refreshTranslations.
!

----- Method: LanguageEditor>>filterUntranslated (in category 'gui methods') -----
filterUntranslated
        | filter |
        filter := UIManager default
                request: 'filter with
(empty string means no-filtering)' translated
                initialAnswer: self untranslatedFilter.

        self filterUntranslated: filter!

----- Method: LanguageEditor>>filterUntranslated: (in category 'gui methods') -----
filterUntranslated: aString
        | filter |
        filter := aString
                                ifNil: [''].
        ""
        untranslatedFilter := filter.
        self refreshUntranslated!

----- Method: LanguageEditor>>getText (in category 'gui methods') -----
getText
        | menu |
        menu := MenuMorph new defaultTarget: self.
        ""
        menu
                add: 'gettext template' translated
                target: self
                selector: #getTextExportTemplate.
        menu lastItem setBalloonText: 'exports the translations to gettext separated format.' translated.
        menu
                add: 'gettext export' translated
                target: self
                selector: #getTextExport.
        menu lastItem setBalloonText: 'Exports the translations to GetText format.' translated.

        ""
        menu
                add: 'gettext import' translated
                target: self
                selector: #getTextImport.
        menu lastItem setBalloonText: 'Imports the translations from GetText format.' translated.
        ""
        menu popUpInWorld!

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

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

----- Method: LanguageEditor>>getTextImport (in category 'gui methods') -----
getTextImport
        | menu |
        menu := MenuMorph new defaultTarget: self.
        menu addTitle: 'Choose translation file' translated.
        menu add: 'All *.po files' translated action: #getTextImportAll.
        menu add: 'Choose a file' translated action: #getTextImportAFile.
        menu popUpInWorld!

----- Method: LanguageEditor>>getTextImportAFile (in category 'gui methods') -----
getTextImportAFile
        | result |
        result := (StandardFileMenu new pattern: '*.po';
                               
                                oldFileFrom: (FileDirectory default directoryNamed: 'po')) startUpWithCaption: 'Select a File:' translated.
        result
                ifNil: [^ self].
        self
                withUnboundModelDo: [:trans | Cursor wait
                                showWhile: [GetTextImporter new
                                                import: trans
                                                fileNamed: (result directory fullNameFor: result name)]]!

----- Method: LanguageEditor>>getTextImportAll (in category 'gui methods') -----
getTextImportAll
        self
                withUnboundModelDo: [:trans | Cursor wait
                                showWhile: [GetTextImporter import: trans allDirectory: FileDirectory default]].
        self refreshBoth!

----- Method: LanguageEditor>>identifyUnusedStrings (in category 'stef') -----
identifyUnusedStrings
        "self new identifyUnusedStrings"
        translationsList getList
                do: [:each |
                        Transcript show: each.
                        Transcript show: (Smalltalk
                                        allSelect: [:method | method
                                                        hasLiteralSuchThat: [:lit | lit isString
                                                                        and: [lit includesSubstring: each caseSensitive: true]]]) size printString; cr]!

----- Method: LanguageEditor>>initializeNewerKeys (in category 'initialization') -----
initializeNewerKeys

        newerKeys := Set new.
!

----- Method: LanguageEditor>>initializeOn: (in category 'initialization') -----
initializeOn: aLanguage
        "initialize the receiver on aLanguage"
        ""
        selectedTranslation := 0.
        selectedUntranslated := 0.
        selectedTranslations := IdentitySet new.
        ""
        translator := aLanguage.
        ""
        self model: aLanguage.
        self setLabel: 'Language editor for: ' translated , self translator name.
        ""
        self initializeToolbars.
        self initializePanels.
        self initializeStatusbar.
        self initializeNewerKeys.
!

----- Method: LanguageEditor>>initializePanels (in category 'initialization') -----
initializePanels
        "initialize the receiver's panels"
        translationsList := PluggableListMorphOfMany
                                on: self
                                list: #translations
                                primarySelection: #selectedTranslation
                                changePrimarySelection: #selectedTranslation:
                                listSelection: #selectedTranslationsAt:
                                changeListSelection: #selectedTranslationsAt:put:
                                menu: #translationsMenu:
                                keystroke: #translationsKeystroke:.
        translationsList setBalloonText: 'List of all the translated phrases.' translated.
        ""
        untranslatedList := PluggableListMorph
                                on: self
                                list: #untranslated
                                selected: #selectedUntranslated
                                changeSelected: #selectedUntranslated:
                                menu: #untranslatedMenu:
                                keystroke: #untranslatedKeystroke:.
        untranslatedList setBalloonText: 'List of all the untranslated phrases.' translated.
        ""
        translationText := PluggableTextMorph
                                on: self
                                text: #translation
                                accept: #translation:
                                readSelection: nil
                                menu: nil.
        translationText setBalloonText: 'Translation for the selected phrase in the upper list.' translated.
        ""
        self
                addMorph: translationsList
                frame: (0 @ 0.18 corner: 0.5 @ 0.66).
        self
                addMorph: untranslatedList
                frame: (0.5 @ 0.18 corner: 1 @ 0.93).
        self
                addMorph: translationText
                frame: (0 @ 0.66 corner: 0.5 @ 0.93).
        self hResizing: #shrinkWrap!

----- Method: LanguageEditor>>initializeStatusbar (in category 'initialization - statusbar') -----
initializeStatusbar
        "initialize the receiver's statusbar"
        self
                addMorph: self createStatusbar
                frame: (0 @ 0.93 corner: 1 @ 1)!

----- Method: LanguageEditor>>initializeToolbars (in category 'initialization - toolbar') -----
initializeToolbars
        "initialize the receiver's toolbar"
        self
                addMorph: self createMainToolbar
                frame: (0 @ 0 corner: 1 @ 0.09).
        ""
        self
                addMorph: self createTranslationsToolbar
                frame: (0 @ 0.09 corner: 0.5 @ 0.18).
        self
                addMorph: self createUntranslatedToolbar
                frame: (0.5 @ 0.09 corner: 1 @ 0.18)!

----- Method: LanguageEditor>>loadFromFile (in category 'gui methods') -----
loadFromFile
        | fileName |
        fileName := self selectTranslationFileName.
        fileName isNil
                ifTrue: [""
                        self beep.
                        ^ self].
        ""
        Cursor wait
                showWhile: [
                        self translator loadFromFileNamed: fileName.
                        self refreshBoth]!

----- Method: LanguageEditor>>mergeFromFile (in category 'gui methods') -----
mergeFromFile
        | fileName |
        fileName := self selectTranslationFileName.
        fileName isNil
                ifTrue: [""
                        self beep.
                        ^ self].
        ""
        Cursor wait
                showWhile: [
                        self translator loadFromFileNamed: fileName.
                        self refreshBoth]!

----- Method: LanguageEditor>>newTranslations (in category 'gui methods') -----
newTranslations
        "private - try to apply the translations as much as possible all
        over the image"
        | result newID |
        result := UIManager default request: 'New locale ID string?' translated initialAnswer: Locale current determineLocaleID isoString.
        result isEmpty
                ifTrue: ["Do nothing"
                        ^ self].
        newID := LocaleID isoString: result.
        InternalTranslator
                newLocaleID: (LocaleID isoString: result).
        self class openOn: newID!

----- Method: LanguageEditor>>numberOfTimesStringIsUsed: (in category 'stef') -----
numberOfTimesStringIsUsed: aString

        ^ (self systemNavigation allSelect: [:method | method
                                                        hasLiteralSuchThat: [:lit | lit isString
                                                                        and: [lit includesSubstring: aString caseSensitive: true]]]) size!

----- Method: LanguageEditor>>okToChange (in category 'updating') -----
okToChange
        "Allows a controller to ask this of any model"
        self selectedTranslation isZero
                ifTrue: [^ true].
        ""
        translationText hasUnacceptedEdits
                ifFalse: [^ true].
        ^ (CustomMenu confirm: 'Discard the changes to currently selected translated phrase?' translated)
                and: [""
                        translationText hasUnacceptedEdits: false.
                        true]!

----- Method: LanguageEditor>>perform:orSendTo: (in category 'message handling') -----
perform: selector orSendTo: otherTarget
        "I wish to intercept and handle selector myself"
        ^ self perform: selector!

----- Method: LanguageEditor>>phrase:translation: (in category 'gui methods') -----
phrase: phraseString translation: translationString
        "set the models's translation for phraseString"
        self translator phrase: phraseString translation: translationString.
        self refreshBoth.

        newerKeys add: phraseString.
!

----- Method: LanguageEditor>>phraseToTranslate (in category 'gui methods') -----
phraseToTranslate
        "answer a phrase to translate.  use the selected untranslated phrase or ask for a new one"
        ^ self selectedUntranslated isZero
                ifTrue: [UIManager default
                                multiLineRequest: 'new phrase to translate' translated
                                centerAt: Sensor cursorPoint
                                initialAnswer: ''
                                answerHeight: 200]
                ifFalse: [self untranslated at: self selectedUntranslated]!

----- Method: LanguageEditor>>printHeaderReportOn: (in category 'reporting') -----
printHeaderReportOn: aStream
        "append to aStream a header report of the receiver with swiki  
        format"
        aStream nextPutAll: '!!!!';
               
                nextPutAll: ('Language: {1}' translated format: {self translator localeID isoString});
                 cr.

        aStream nextPutAll: '- ';
               
                nextPutAll: ('{1} translated phrases' translated format: {self translator translations size});
                 cr.

        aStream nextPutAll: '- ';
               
                nextPutAll: ('{1} untranslated phrases' translated format: {self translator untranslated size});
                 cr.

        aStream cr; cr!

----- Method: LanguageEditor>>printReportOn: (in category 'reporting') -----
printReportOn: aStream
        "append to aStream a report of the receiver with swiki format"
        self printHeaderReportOn: aStream.
        self printUntranslatedReportOn: aStream.
        self printTranslationsReportOn: aStream!

----- Method: LanguageEditor>>printTranslationsReportOn: (in category 'reporting') -----
printTranslationsReportOn: aStream
        "append to aStream a report of the receiver's translations"
        | originalPhrases |
        aStream nextPutAll: '!!';
                 nextPutAll: 'translations' translated;
                 cr.

        originalPhrases := self translator translations keys asSortedCollection.

        originalPhrases
                do: [:each |
                        aStream
                                nextPutAll: ('|{1}|{2}|' format: {self asHtml: each. self
                                                        asHtml: (self translator translate: each)});
                                 cr].

        aStream cr; cr!

----- Method: LanguageEditor>>printUntranslatedReportOn: (in category 'reporting') -----
printUntranslatedReportOn: aStream
        "append to aStream a report of the receiver's translations"
        aStream nextPutAll: '!!';
                 nextPutAll: 'not translated' translated;
                 cr.

        self untranslated asSortedCollection
                do: [:each |
                        aStream
                                nextPutAll: ('|{1}|' format: {self asHtml: each});
                                 cr].

        aStream cr; cr!

----- Method: LanguageEditor>>refreshBoth (in category 'updating') -----
refreshBoth
        self refreshUntranslated
!

----- Method: LanguageEditor>>refreshTranslations (in category 'updating') -----
refreshTranslations
        "refresh the translations panel"
        self selectedTranslation: 0.
        translations := nil.
        self changed: #translations.
!

----- Method: LanguageEditor>>refreshUntranslated (in category 'updating') -----
refreshUntranslated
"refresh the untranslated panel"
        self refreshTranslations.
        self selectedUntranslated: 0.
        untranslated := nil.
        self changed: #untranslated.
!

----- Method: LanguageEditor>>removeTranslatedButUnusedStrings (in category 'stef') -----
removeTranslatedButUnusedStrings
        (self confirm: 'Are you sure that you want to remove unused strings?' translated)
                ifFalse: [^ self].
        translationsList getList
                do: [:each |
                        | timesUsed |
                        timesUsed := self numberOfTimesStringIsUsed: each.
                        Transcript show: each.
                        Transcript show: timesUsed printString;
                                 cr.
                        timesUsed isZero
                                ifTrue: [self translator removeTranslationFor: each]]!

----- Method: LanguageEditor>>removeTranslation (in category 'gui methods') -----
removeTranslation
        "remove the selected translation"
        | translation |
        self selectedTranslation isZero
                ifTrue: [""
                        self beep.
                        self inform: 'select the translation to remove' translated.
                        ^ self].
        ""
        translation := self translations at: self selectedTranslation.
""
        (self
                        confirm: ('Removing "{1}".
Are you sure you want to do this?' translated format: {translation}))
                ifFalse: [^ self].
""
        self translator removeTranslationFor: translation.
        self refreshBoth!

----- Method: LanguageEditor>>removeUntranslated (in category 'gui methods') -----
removeUntranslated
        "remove the selected untranslated phrase"
        | untrans |
        self selectedUntranslated isZero
                ifTrue: [""
                        self beep.
                        self inform: 'select the untranslated phrase to remove' translated.
                        ^ self].
        ""
        untrans := self untranslated at: self selectedUntranslated.
        ""
        (self
                        confirm: ('Removing "{1}".
Are you sure you want to do this?' translated format: {untrans}))
                ifFalse: [^ self].
        ""
        self translator removeUntranslated: untrans!

----- Method: LanguageEditor>>removeUntranslatedButUnusedStrings (in category 'stef') -----
removeUntranslatedButUnusedStrings
        (self confirm: 'Are you sure that you want to remove unused strings?' translated)
                ifFalse: [^ self].
        untranslatedList getList
                do: [:each |
                        | timesUsed |
                        timesUsed := self numberOfTimesStringIsUsed: each.
                        Transcript show: each.
                        Transcript show: timesUsed printString;
                                 cr.
                        timesUsed isZero
                                ifTrue: [self translator removeUntranslated: each]].

        self refreshUntranslated.
!

----- Method: LanguageEditor>>report (in category 'gui methods') -----
report
        self reportString openInWorkspaceWithTitle: 'report' translated!

----- Method: LanguageEditor>>reportString (in category 'reporting') -----
reportString
        "answer a string with a report of the receiver"
        | stream |
        stream := String new writeStream.
        self printReportOn: stream.
        ^ stream contents!

----- Method: LanguageEditor>>resetNewerKeys (in category 'gui methods') -----
resetNewerKeys

        self initializeNewerKeys.
!

----- Method: LanguageEditor>>saveToFile (in category 'gui methods') -----
saveToFile
        "save the translator to a file"
        | fileName |
        fileName := UIManager default request: 'file name' translated initialAnswer: translator localeID isoString , '.translation'.
        (fileName isNil
                        or: [fileName isEmpty])
                ifTrue: [
                        self beep.
                        ^ self].

Cursor wait
                showWhile: [
        self translator saveToFileNamed: fileName]!

----- Method: LanguageEditor>>searchTranslation (in category 'gui methods') -----
searchTranslation
        | search |
        search := UIManager default request: 'search for' translated initialAnswer: ''.
        (search isNil
                        or: [search isEmpty])
                ifTrue: [
                        self beep.
                        ^ self].

self searchTranslation: search!

----- Method: LanguageEditor>>searchTranslation: (in category 'gui methods') -----
searchTranslation: aString
        | results index |
        results := self translations
                                select: [:each | ""
                                        ('*' , aString , '*' match: each)
                                                or: ['*' , aString , '*' match: (self translator translate: each)]].
        ""
        results isEmpty
                ifTrue: [""
                        self inform: 'no matches for' translated , ' ''' , aString , ''''.
                        ^ self].
        ""
        results size = 1
                ifTrue: [""
                        self selectTranslationPhrase: results first.
                        ^ self].
        ""
        index := (PopUpMenu
                                labelArray: (results
                                                collect: [:each | ""
                                                        (each copy replaceAll: Character cr with: $\)
                                                                , ' -> '
                                                                , ((self translator translate: each) copy replaceAll: Character cr with: $\)]))
                                startUpWithCaption: 'select the translation...' translated.
        ""
        index isZero
                ifTrue: [""
                        self beep.
                        ^ self].
        ""
        self
                selectTranslationPhrase: (results at: index)!

----- Method: LanguageEditor>>searchUntranslated (in category 'gui methods') -----
searchUntranslated
        | search |
        search := UIManager default request: 'search for' translated initialAnswer: ''.
        (search isNil
                        or: [search isEmpty])
                ifTrue: [
                        self beep.
                        ^ self].

        self searchUntranslated: search!

----- Method: LanguageEditor>>searchUntranslated: (in category 'gui methods') -----
searchUntranslated: aString
        | untranslateds results index |
        untranslateds := self untranslated.
        results := untranslateds
                                select: [:each | '*' , aString , '*' match: each].
        ""
        results isEmpty
                ifTrue: [""
                        self inform: 'no matches for' translated , ' ''' , aString , ''''.
                        ^ self].
        ""
        results size = 1
                ifTrue: [""
                        self selectUntranslatedPhrase: results first.
                        ^ self].
        ""
        index := (PopUpMenu
                                labelArray: (results
                                                collect: [:each | each copy replaceAll: Character cr with: $\]))
                                startUpWithCaption: 'select the untranslated phrase...' translated.
        ""
        index isZero
                ifTrue: [""
                        self beep.
                        ^ self].
        ""
        self
                selectUntranslatedPhrase: (results at: index)!

----- Method: LanguageEditor>>selectAllTranslation (in category 'gui methods') -----
selectAllTranslation
        selectedTranslations := (1 to: self translations size) asIdentitySet.
        self changed: #allSelections!

----- Method: LanguageEditor>>selectNewerKeys (in category 'gui methods') -----
selectNewerKeys

        | index |
        self deselectAllTranslation.
        newerKeys do: [:k |
                index := self translations indexOf: k ifAbsent: [0].
                index > 0 ifTrue: [
                        self selectedTranslationsAt: index put: true
                ].
        ].
!

----- Method: LanguageEditor>>selectTranslationFileName (in category 'gui methods') -----
selectTranslationFileName
        "answer a file with a translation"
        | file |
        file := (StandardFileMenu oldFileMenu: FileDirectory default withPattern: '*.translation')
                                startUpWithCaption: 'Select the file...' translated.
        ^ file isNil
                ifFalse: [file directory fullNameFor: file name]!

----- Method: LanguageEditor>>selectTranslationPhrase: (in category 'gui methods') -----
selectTranslationPhrase: phraseString
        self selectedTranslation: (self translations indexOf: phraseString)!

----- Method: LanguageEditor>>selectUntranslatedPhrase: (in category 'gui methods') -----
selectUntranslatedPhrase: phraseString
        self
                selectedUntranslated: (self untranslated indexOf: phraseString)!

----- Method: LanguageEditor>>selectedTranslation (in category 'accessing') -----
selectedTranslation
        "answer the selectedTranslation"
        ^ selectedTranslation!

----- Method: LanguageEditor>>selectedTranslation: (in category 'accessing') -----
selectedTranslation: anInteger
        "change the receiver's selectedTranslation"
        selectedTranslation := anInteger.
        ""
        self changed: #selectedTranslation.
        self changed: #translation!

----- Method: LanguageEditor>>selectedTranslationsAt: (in category 'accessing') -----
selectedTranslationsAt: index
        ^ selectedTranslations includes: index!

----- Method: LanguageEditor>>selectedTranslationsAt:put: (in category 'accessing') -----
selectedTranslationsAt: index put: value
        value = true
                ifTrue: [selectedTranslations add: index]
                ifFalse: [selectedTranslations
                                remove: index
                                ifAbsent: []]!

----- Method: LanguageEditor>>selectedUntranslated (in category 'accessing') -----
selectedUntranslated
        "answer the selectedUntranslated"
        ^ selectedUntranslated!

----- Method: LanguageEditor>>selectedUntranslated: (in category 'accessing') -----
selectedUntranslated: anInteger
        "change the selectedUntranslated"
        selectedUntranslated := anInteger.
        ""
        self changed: #selectedUntranslated!

----- Method: LanguageEditor>>status (in category 'gui methods') -----
status
        "answer a status string"
        | translationsSize untranslatedSize |
        translationsSize := self translator translations size.
        untranslatedSize := self translator untranslated size.
        ^ '| {1} phrases | {2} translated | {3} untranslated |' translated format: {translationsSize + untranslatedSize. translationsSize. untranslatedSize}!

----- Method: LanguageEditor>>translate (in category 'gui methods') -----
translate
        "translate a phrase"
        | phrase |
        phrase := self phraseToTranslate.
        ""
        (phrase isNil
                        or: [phrase = ''])
                ifTrue: [""
                        self beep.
                        ^ self].
        ""
        self translatePhrase: phrase.
        self refreshBoth!

----- Method: LanguageEditor>>translatePhrase: (in category 'gui methods') -----
translatePhrase: aString
        "translate aString"
        | translation |
        translation := UIManager default
                                multiLineRequest: 'translation for: ' translated , '''' , aString , ''''
                                centerAt: Sensor cursorPoint
                                initialAnswer: aString
                                answerHeight: 200.

        (translation isNil
                        or: [translation = ''])
                ifTrue: [""
                        self beep.
                        ^ self].

        self phrase: aString translation: translation!

----- Method: LanguageEditor>>translation (in category 'accessing') -----
translation
        "answer the translation for the selected phrase"
        self selectedTranslation isZero
                ifTrue: [^ '<select a phrase from the upper list>' translated].
        ""
        ^ self translator
                translate: (self translations at: self selectedTranslation)!

----- Method: LanguageEditor>>translation: (in category 'accessing') -----
translation: aStringOrText
        "change the translation for the selected phrase"
        | phrase |
        self selectedTranslation isZero
                ifTrue: [^ self].
        phrase := self translations at: self selectedTranslation.
        translator
                phrase: phrase
                translation: aStringOrText asString.
        newerKeys add: phrase.
        ^ true!

----- Method: LanguageEditor>>translations (in category 'accessing') -----
translations
        "answet the translator's translations"
        | allTranslations filterString |
        translations ifNotNil: [^translations].
        allTranslations := self translator translations keys.
        ""
        filterString := self translationsFilter.
        ""
        filterString isEmpty
                ifFalse: [allTranslations := allTranslations
                                                select: [:each | ""
                                                        ('*' , filterString , '*' match: each)
                                                                or: ['*' , filterString , '*'
                                                                                match: (self translator translate: each)]]].
""
        ^ translations := allTranslations asSortedCollection asArray!

----- Method: LanguageEditor>>translationsFilter (in category 'accessing') -----
translationsFilter
^translationsFilter ifNil:['']!

----- Method: LanguageEditor>>translationsFilterWording (in category 'gui methods') -----
translationsFilterWording
        ^ (self translationsFilter isEmpty
                ifTrue: ['filter' translated]
                ifFalse: ['filtering: {1}' translated format:{self translationsFilter}]) !

----- Method: LanguageEditor>>translationsKeystroke: (in category 'gui methods') -----
translationsKeystroke: aChar
        "Respond to a Command key in the translations list."
        aChar == $x
                ifTrue: [^ self removeTranslation].
        aChar == $E
                ifTrue: [^ self browseMethodsWithTranslation]!

----- Method: LanguageEditor>>translationsMenu: (in category 'gui methods') -----
translationsMenu: aMenu
        ^ aMenu add: 'remove (x)' translated action: #removeTranslation;
                 add: 'where (E)' translated action: #browseMethodsWithTranslation;
                 add: 'select all' translated action: #selectAllTranslation;
                 add: 'deselect all' translated action: #deselectAllTranslation;
                 add: 'select changed keys' translated action: #selectNewerKeys;
                 add: 'export selection' translated action: #codeSelectedTranslation;
                 add: 'export selection in do-it form' translated action: #codeSelectedTranslationAsMimeString;
                 add: 'reset changed keys' translated action: #resetNewerKeys;
                 yourself!

----- Method: LanguageEditor>>translator (in category 'private') -----
translator
        ^translator!

----- Method: LanguageEditor>>untranslated (in category 'accessing') -----
untranslated
        "answer the translator's untranslated phrases"
       

        | all filterString |
        untranslated ifNotNil: [^ untranslated].
        all := self translator untranslated.
        ""
        filterString := self untranslatedFilter.
        ""
        filterString isEmpty
                ifFalse: [all := all
                                                select: [:each | ""
                                                        ('*' , filterString , '*' match: each)
                                                                or: ['*' , filterString , '*'
                                                                                match: (self translator translate: each)]]].
        ""
        ^ untranslated := all asSortedCollection asArray!

----- Method: LanguageEditor>>untranslatedFilter (in category 'accessing') -----
untranslatedFilter
        ^ untranslatedFilter
                ifNil: ['']!

----- Method: LanguageEditor>>untranslatedFilterWording (in category 'gui methods') -----
untranslatedFilterWording
        ^ self untranslatedFilter isEmpty
                ifTrue: ['filter' translated]
                ifFalse: ['filtering: {1}' translated format: {self untranslatedFilter}]!

----- Method: LanguageEditor>>untranslatedKeystroke: (in category 'gui methods') -----
untranslatedKeystroke: aChar
        "Respond to a Command key in the translations list."
        aChar == $t
                ifTrue: [^ self translate].
        aChar == $E
                ifTrue: [^ self browseMethodsWithUntranslated]!

----- Method: LanguageEditor>>untranslatedMenu: (in category 'gui methods') -----
untranslatedMenu: aMenu
        ^ aMenu add: 'remove' translated action: #removeUntranslated;
                 add: 'translate (t)' translated action: #translate;
                 add: 'where (E)' translated action: #browseMethodsWithUntranslated;
                 yourself!

----- Method: LanguageEditor>>update: (in category 'updating') -----
update: aSymbol
        "Receive a change notice from an object of whom the receiver  
        is a dependent."
        super update: aSymbol.
        ""
        aSymbol == #untranslated
                ifTrue: [self refreshUntranslated].
        aSymbol == #translations
                ifTrue: [self refreshTranslations]!

----- Method: LanguageEditor>>withUnboundModelDo: (in category 'private') -----
withUnboundModelDo: aBlock
        "Private - Evaluate aBlock with the receiver temporary  
        unbound from the model.  
         
        Useful to perform a batch of modifications to the model  
        without updating the view."
        | formerModel |
        formerModel := self model.
        self model: nil.
        [aBlock value: formerModel]
                ensure: [self model: formerModel]!