Re: The Trunk: GetText-edc.18.mcz

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

Re: The Trunk: GetText-edc.18.mcz

Nicolas Cellier
Resent with snipped code...

Le 30 mars 2012 03:24, Nicolas Cellier <[hidden email]> a écrit :
This broke #translatedIfCorresponds at least...

Nicolas

Le 15 mars 2012 22:27, <[hidden email]> a écrit :

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

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

Name: GetText-edc.18
Author: edc
Time: 15 March 2012, 6:29:37.486 pm
UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
Ancestors: GetText-edc.17

'_' s replaced by ':='

=============== Diff against GetText-edc.17 ===============

 
SNIP ...
 
Item was changed:
 ----- Method: String>>translatedIfCorresponds (in category '*gettext') -----
 translatedIfCorresponds
       "answer the receiver translated to the default language only if
+       the receiver begins and ends with an underscore (:=)"
+       ^ (':=*:=' match: self)
-       the receiver begins and ends with an underscore (_)"
-       ^ ('_*_' match: self)
               ifTrue: [(self copyFrom: 2 to: self size - 1) translated]
               ifFalse: [self]!

Item was changed:
 ----- Method: TranslatedReceiverFinder>>stringReceiversWithContext (in category 'accessing') -----
 stringReceiversWithContext
       | mrs results rr cls mn t o |
+       mrs := SystemNavigation default allCallsOn: #translated.
+       results := OrderedCollection new.
-       mrs _ SystemNavigation default allCallsOn: #translated.
-       results _ OrderedCollection new.
       mrs do: [:mr |
+               rr := OrderedCollection new.
+               cls := Smalltalk at: mr classSymbol.
-               rr _ OrderedCollection new.
-               cls _ Smalltalk at: mr classSymbol.
               rr add: cls category.
               rr add: mr classSymbol.
               rr add: mr methodSymbol.
               mr classIsMeta ifTrue: [
+                       mn :=  cls class decompile: mr methodSymbol.
-                       mn _  cls class decompile: mr methodSymbol.
               ] ifFalse: [
+                       mn := cls decompile: mr methodSymbol.
-                       mn _ cls decompile: mr methodSymbol.
               ].
+               o := OrderedCollection new.
+               t := Set new.
-               o _ OrderedCollection new.
-               t _ Set new.
               self searchMessageNode: mn addTo: t.
               t do: [ :te |
                       (te receiver isMemberOf: LiteralNode) ifTrue: [
                           o add: te receiver key.
                       ].
               ].
               o ifNotEmpty: [
                       rr add: o.
                       results add: rr.
               ].
       ].
       ^ results.

 !

Item was changed:
 ----- Method: TranslatedReceiverFinder>>stringReceiversWithContext: (in category 'accessing') -----
 stringReceiversWithContext: aSymbol
       "Find string receivers for a symbol.
       Answer a collection of aMethodReference -> {keyword. keyword...}"
       "self new stringReceiversWithContext: #translated"
       | keywords methodReferences |
+       methodReferences := SystemNavigation default allCallsOn: aSymbol.
-       methodReferences _ SystemNavigation default allCallsOn: aSymbol.
       ^ methodReferences inject: OrderedCollection new into: [:list :next |
               keywords := self findWordsWith: aSymbol in: next.
               keywords
                       ifNotEmpty: [list add: next -> keywords].
               list]
 !






Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Edgar De Cleene
Re: [squeak-dev] The Trunk: GetText-edc.18.mcz


On 3/30/12 7:54 AM, "Nicolas Cellier" <[hidden email]> wrote:

translatedIfCorresponds

Ok, this is fixed reverting to original version of method.
You do this or I do this?

Edgar


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Levente Uzonyi-2
In reply to this post by Nicolas Cellier
On Thu, 15 Mar 2012, [hidden email] wrote:

> Edgar J. De Cleene uploaded a new version of GetText to project The Trunk:
> http://source.squeak.org/trunk/GetText-edc.18.mcz
>
> ==================== Summary ====================
>
> Name: GetText-edc.18
> Author: edc
> Time: 15 March 2012, 6:29:37.486 pm
> UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
> Ancestors: GetText-edc.17
>
> '_' s replaced by ':='

The method you used to replace the assignments is wrong, because it's
just simple search and replace, which ignores the context (e.g. strings
and comments). Please review the changes by hand and fix them.


Levente

>
> =============== Diff against GetText-edc.17 ===============
>
> Item was changed:
>  ----- 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].
> - literals _ domains at: domainName ifAbsentPut: [Dictionary new].
>   keywords do: [ :literal |
> + references := literals at: literal ifAbsentPut: [OrderedCollection new].
> - references _ literals at: literal ifAbsentPut: [OrderedCollection new].
>   references add: methodReference.
>   ].
>   ].
>
>  !
>
> Item was changed:
>  ----- Method: GetTextExporter>>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 _ self getTextDomainForPackage: (PackageOrganizer default packageOfMethod: methodReference)".
>   domainName := 'Etoys-Tiles'.
> + literalsForDomain := domains at: domainName ifAbsentPut: [Dictionary new].
> - literalsForDomain _ domains at: domainName ifAbsentPut: [Dictionary new].
>   r fourth do: [ :literal |
> + references := literalsForDomain at: literal ifAbsentPut: [OrderedCollection new].
> - references _ literalsForDomain at: literal ifAbsentPut: [OrderedCollection new].
>   references add: methodReference.
>   ].
>   ].
>   !
>
> Item was changed:
>  ----- 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: ':='.
> - 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 changed:
>  ----- 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: ':='."
> - "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!
>
> Item was changed:
>  ----- 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 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: ':='.
> - 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 changed:
>  ----- 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 := ''
> - normalizedTrans _ ''
>   ] ifFalse: [
> + transEndsWithCR := translationString last = (Character cr).
> - transEndsWithCR _ translationString last = (Character cr).
>   phraseString last = (Character cr) ifTrue: [
>   transEndsWithCR ifTrue: [
> + normalizedTrans := translationString
> - normalizedTrans _ translationString
>   ] ifFalse: [
> + normalizedTrans :=  translationString , String cr
> - normalizedTrans _  translationString , String cr
>   ]
>   ] ifFalse: [
>   transEndsWithCR ifTrue: [
> + normalizedTrans := translationString allButLast
> - normalizedTrans _ translationString allButLast
>   ] ifFalse: [
> + normalizedTrans := translationString
> - normalizedTrans _ translationString
>   ]
>   ].
> + transStartsWithCR := normalizedTrans first = (Character cr).
> - transStartsWithCR _ normalizedTrans first = (Character cr).
>   phraseString first = (Character cr) ifTrue: [
>   transStartsWithCR ifFalse: [
> + tmp := (Character cr asString) , normalizedTrans.
> + normalizedTrans := tmp.
> - tmp _ (Character cr asString) , normalizedTrans.
> - normalizedTrans _ tmp.
>   ]
>   ] ifFalse: [
>   transStartsWithCR ifTrue: [
> + normalizedTrans := normalizedTrans allButFirst
> - normalizedTrans _ normalizedTrans allButFirst
>   ]
>   ]
>   ].
>   self exportTag: 'msgstr' msg: normalizedTrans.
>   stream cr!
>
> Item was changed:
>  ----- 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:
> - domainName _ self getTextDomainForPackage:
>   (PackageOrganizer default packageOfMethod: methodReference ifNone: [TextDomainManager defaultDomain]).
> + literals := domains at: domainName ifAbsentPut: [Dictionary new].
> - literals _ domains at: domainName ifAbsentPut: [Dictionary new].
>   keywords do: [ :literal |
> + references := literals at: literal ifAbsentPut: [OrderedCollection new].
> - references _ literals at: literal ifAbsentPut: [OrderedCollection new].
>   references add: methodReference.
>   ].
>   ].
>  !
>
> Item was changed:
>  ----- 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 _ self getTextDomainForPackage: (PackageOrganizer default packageOfMethod: methodReference)".
>   domainName := 'Etoys-Tiles'.
> + literalsForDomain := domains at: domainName ifAbsentPut: [Dictionary new].
> - literalsForDomain _ domains at: domainName ifAbsentPut: [Dictionary new].
>   r fourth do: [ :literal |
> + references := literalsForDomain at: literal ifAbsentPut: [OrderedCollection new].
> - references _ literalsForDomain at: literal ifAbsentPut: [OrderedCollection new].
>   references add: methodReference.
>   ].
>   ].
>   !
>
> Item was changed:
>  ----- 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: ':='.
> - 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 changed:
>  ----- 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: ':='."
> - "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 changed:
>  ----- 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 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: ':='.
> - 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 changed:
>  ----- 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 := ''
> - normalizedTrans _ ''
>   ] ifFalse: [
> + transEndsWithCR := translationString last = (Character cr).
> - transEndsWithCR _ translationString last = (Character cr).
>   phraseString last = (Character cr) ifTrue: [
>   transEndsWithCR ifTrue: [
> + normalizedTrans := translationString
> - normalizedTrans _ translationString
>   ] ifFalse: [
> + normalizedTrans :=  translationString , String cr
> - normalizedTrans _  translationString , String cr
>   ]
>   ] ifFalse: [
>   transEndsWithCR ifTrue: [
> + normalizedTrans := translationString allButLast
> - normalizedTrans _ translationString allButLast
>   ] ifFalse: [
> + normalizedTrans := translationString
> - normalizedTrans _ translationString
>   ]
>   ].
> + transStartsWithCR := normalizedTrans first = (Character cr).
> - transStartsWithCR _ normalizedTrans first = (Character cr).
>   phraseString first = (Character cr) ifTrue: [
>   transStartsWithCR ifFalse: [
> + tmp := (Character cr asString) , normalizedTrans.
> + normalizedTrans := tmp.
> - tmp _ (Character cr asString) , normalizedTrans.
> - normalizedTrans _ tmp.
>   ]
>   ] ifFalse: [
>   transStartsWithCR ifTrue: [
> + normalizedTrans := normalizedTrans allButFirst
> - normalizedTrans _ normalizedTrans allButFirst
>   ]
>   ]
>   ].
>   self exportTag: 'msgstr' msg: normalizedTrans.
>   stream cr!
>
> Item was changed:
>  ----- Method: GetTextInterchange>>language: (in category 'accessing') -----
>  language: translator
> + language := translator!
> - language _ translator!
>
> Item was changed:
>  ----- Method: GetTextInterchange>>stream: (in category 'accessing') -----
>  stream: aStream
> + stream := aStream!
> - stream _ aStream!
>
> Item was changed:
>  ----- Method: GetTextTranslator class>>defaultLocaleDirs (in category 'translation data layout') -----
>  defaultLocaleDirs
>   | dirs |
> + dirs := OrderedCollection new.
> - dirs _ OrderedCollection new.
>   UserDefaultLocaleDirs ifNotNil: [dirs addAll: UserDefaultLocaleDirs].
>   dirs addAll: self systemDefaultLocaleDirs.
>   ^dirs
>  !
>
> Item was changed:
>  ----- Method: GetTextTranslator class>>findMOForLocaleID:domain: (in category 'private') -----
>  findMOForLocaleID: id domain: aDomainName
>   | sepa langSubDir path |
> + sepa := FileDirectory slash.
> + langSubDir := self langDirNameForLocaleID: id.
> - sepa _ FileDirectory slash.
> - langSubDir _ self langDirNameForLocaleID: id.
>   (self localeDirsForDomain: aDomainName)
>   do: [:each |
> + path := each , sepa , langSubDir, sepa , (self moNameForDomain: aDomainName).
> - path _ each , sepa , langSubDir, sepa , (self moNameForDomain: aDomainName).
>   [(FileDirectory default fileExists: path)
>   ifTrue: [^path]] on: InvalidDirectoryError do: [:e | ^nil]].
>   ^nil.!
>
> Item was changed:
>  ----- Method: GetTextTranslator class>>initialize (in category 'class initialization') -----
>  initialize
> + SystemDefaultLocaleDirs := OrderedCollection new.
> + UserDefaultLocaleDirs := OrderedCollection new.
> + LocaleDirsForDomain := Dictionary new.!
> - SystemDefaultLocaleDirs _ OrderedCollection new.
> - UserDefaultLocaleDirs _ OrderedCollection new.
> - LocaleDirsForDomain _ Dictionary new.!
>
> Item was changed:
>  ----- Method: GetTextTranslator class>>localeDirsForDomain (in category 'private') -----
>  localeDirsForDomain
> + ^LocaleDirsForDomain ifNil: [LocaleDirsForDomain := Dictionary new]!
> - ^LocaleDirsForDomain ifNil: [LocaleDirsForDomain _ Dictionary new]!
>
> Item was changed:
>  ----- Method: GetTextTranslator class>>localeDirsForDomain: (in category 'translation data layout') -----
>  localeDirsForDomain: aDomainName
>   "returns collection of locale directories for text domain.
>   This includes user defined one for the domain, user defaults and system defaults"
>   | dirs dir |
> + dirs := OrderedCollection new.
> + dir := self localeDirForDomain: aDomainName.
> - dirs _ OrderedCollection new.
> - dir _ self localeDirForDomain: aDomainName.
>   dir ifNotNil: [dirs add: dir].
>   dirs addAll:  self defaultLocaleDirs.
>   ^dirs!
>
> Item was changed:
>  ----- Method: GetTextTranslator>>initialize (in category 'initialize-release') -----
>  initialize
> + moFiles := Dictionary new.!
> - moFiles _ Dictionary new.!
>
> Item was changed:
>  ----- Method: GetTextTranslator>>isDomainLoaded: (in category 'accessing') -----
>  isDomainLoaded: aDomainName
>   | mo |
> + mo := moFiles at: aDomainName ifAbsent: [nil].
> - mo _ moFiles at: aDomainName ifAbsent: [nil].
>   ^mo isNil not.
>  !
>
> Item was changed:
>  ----- Method: GetTextTranslator>>loadMOFileForDomain: (in category 'private') -----
>  loadMOFileForDomain: aDomainName
>   | moName |
> + moName := self class findMOForLocaleID: self localeID
> - moName _ self class findMOForLocaleID: self localeID
>   domain: aDomainName.
>   moName notNil
>   ifTrue: [^MOFile new load: moName
>   localeID: self localeID]
>   ifFalse: [^nil]
>  !
>
> Item was changed:
>  ----- Method: GetTextTranslator>>reloadMOFiles (in category 'accessing') -----
>  reloadMOFiles
> + moFiles := Dictionary new.
> - moFiles _ Dictionary new.
>   self loadMOFiles.!
>
> Item was changed:
>  ----- Method: GetTextTranslator>>translate:inDomain: (in category 'translation') -----
>  translate: aString inDomain: aDomainName
>   | mo |
> + mo := self moFileForDomain: aDomainName.
> - mo _ self moFileForDomain: aDomainName.
>   ^mo isNil
>   ifTrue: [aString]
>   ifFalse: [mo translationFor: aString]
>  !
>
> Item was changed:
>  ----- Method: ISOLanguageDefinition class>>iso3166Codes (in category 'private') -----
> (excessive size, no diff calculated)
>
> Item was changed:
>  ----- 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?'].
> - and: [(translationString includes: $?) not])
> - ifTrue: [^ '?Olvid? el signo de pregunta?'].
>   ((translationString includes: $!!)
> + and: [(translationString includes: $?) not])
> + ifTrue: [^ '?Olvid? el signo de admiraci?n?'].
> - and: [(translationString includes: $?) not])
> - ifTrue: [^ '?Olvid? el signo de admiraci?n?'].
>   "
>   ^ nil
>  !
>
> Item was changed:
>  ----- Method: LanguageEditor>>codeSelectedTranslationAsMimeString (in category 'gui methods') -----
>  codeSelectedTranslationAsMimeString
>   | keys code tmpStream s2 gzs cont |
>   keys := selectedTranslations
>   collect: [:key | self translations at: key].
>   code := String
>   streamContents: [:aStream | self translator fileOutOn: aStream keys: keys withBOM: false].
>
> + tmpStream := MultiByteBinaryOrTextStream on: ''.
> - tmpStream _ MultiByteBinaryOrTextStream on: ''.
>   tmpStream converter: UTF8TextConverter new.
>   tmpStream nextPutAll: code.
> + s2 := RWBinaryOrTextStream on: ''.
> - s2 _ RWBinaryOrTextStream on: ''.
>   gzs := GZipWriteStream on: s2.
>   tmpStream reset.
>   gzs nextPutAll: (tmpStream binary contentsOfEntireFile asString) contents.
>   gzs close.
>   s2 reset.
>
> + cont := String streamContents: [:strm |
> - cont _ String streamContents: [:strm |
>   strm nextPutAll: '"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: (Base64MimeConverter mimeEncode: s2) contents.
>   strm nextPutAll: '''.'.
>   strm cr.
>   ].
>
>   (StringHolder new contents: cont)
>   openLabel: 'exported codes in Gzip+Base64 encoding' translated!
>
> Item was changed:
>  ----- Method: LanguageEditor>>filterTranslations: (in category 'gui methods') -----
>  filterTranslations: aString
>  | filter |
>  filter := aString ifNil:[''].
>  ""
> + translationsFilter := filter.
> - translationsFilter _ filter.
>   self refreshTranslations.
>  !
>
> Item was changed:
>  ----- Method: LanguageEditor>>initializeNewerKeys (in category 'initialization') -----
>  initializeNewerKeys
>
> + newerKeys := Set new.
> - newerKeys _ Set new.
>  !
>
> Item was changed:
>  ----- Method: LanguageEditor>>selectNewerKeys (in category 'gui methods') -----
>  selectNewerKeys
>
>   | index |
>   self deselectAllTranslation.
>   newerKeys do: [:k |
> + index := self translations indexOf: k ifAbsent: [0].
> - index _ self translations indexOf: k ifAbsent: [0].
>   index > 0 ifTrue: [
>   self selectedTranslationsAt: index put: true
>   ].
>   ].
>  !
>
> Item was changed:
>  ----- 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.
> - phrase _ self translations at: self selectedTranslation.
>   translator
>   phrase: phrase
>   translation: aStringOrText asString.
>   newerKeys add: phrase.
>   ^ true!
>
> Item was changed:
>  ----- 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!
> - ^ translations _ allTranslations asSortedCollection asArray!
>
> Item was changed:
>  ----- 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!
> - ^ untranslated _ all asSortedCollection asArray!
>
> Item was changed:
>  ----- Method: Locale class>>localeChangedListeners (in category 'notification') -----
>  localeChangedListeners
> + ^LocaleChangeListeners ifNil: [LocaleChangeListeners := OrderedCollection new]!
> - ^LocaleChangeListeners ifNil: [LocaleChangeListeners _ OrderedCollection new]!
>
> Item was changed:
>  ----- Method: Locale class>>migrateSystem (in category 'private') -----
>  migrateSystem
>   "Locale migrateSystem"
>   "Do all the necessary operations to switch to the new Locale environment."
>
> + LocaleChangeListeners := nil.
> - LocaleChangeListeners _ nil.
>   self
>   addLocalChangedListener: HandMorph;
>   addLocalChangedListener: Clipboard;
>   addLocalChangedListener: Vocabulary;
>   addLocalChangedListener: PartsBin;
>   addLocalChangedListener: Project;
>   addLocalChangedListener: PaintBoxMorph;
>   yourself!
>
> Item was changed:
>  ----- 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.
> - ifFalse: [Previous _ Current.
>   CurrentPlatform := Current := Locale localeID: availableID.
>   NaturalLanguageTranslator localeChanged.
>   gentlyFlag ifTrue: [self localeChangedGently] ifFalse: [self localeChanged]]!
>
> Item was changed:
>  ----- Method: LocaleID class>>posixName: (in category 'instance creation') -----
>  posixName: aString
>   ^ self
> + isoString: (aString copyReplaceAll: ':=' with: '-')!
> - isoString: (aString copyReplaceAll: '_' with: '-')!
>
> Item was changed:
>  ----- 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]!
> - ifNotNil: [self isoLanguage , '_' , self isoCountry]!
>
> Item was changed:
>  ----- Method: MOFile>>fileName: (in category 'public') -----
>  fileName: path
> + fileName := path!
> - fileName _ path!
>
> Item was changed:
>  ----- Method: MOFile>>hashPjw: (in category 'experimental') -----
>  hashPjw: aString
>   "So called `hashpjw' function by P.J. Weinberger
>     [see Aho/Sethi/Ullman, COMPILERS: Principles, Techniques and Tools,
>     1986, 1987 Bell Telephone Laboratories, Inc.] "
>   | stringSize hash g |
> + stringSize := aString size.
> + hash := 0.
> - stringSize _ aString size.
> - hash _ 0.
>   1 to: stringSize do: [:pos |
> + hash := hash bitShift: 4.
> + hash := hash + ((aString at: pos) asInteger).
> + g := hash bitAnd: 16rF0000000.
> - hash _ hash bitShift: 4.
> - hash _ hash + ((aString at: pos) asInteger).
> - g _ hash bitAnd: 16rF0000000.
>   g = 0 ifFalse: [
> + hash := hash  bitXor: (g bitShift: -24).
> + hash := hash bitXor: g.
> - hash _ hash  bitXor: (g bitShift: -24).
> - hash _ hash bitXor: g.
>   ]
>   ].
>   ^hash.
>  !
>
> Item was changed:
>  ----- Method: MOFile>>load1:localeID: (in category 'experimental') -----
>  load1: aFileName localeID: id
>   "CASE1:
>   all of strings are loaded.
>   translation strings are converted to Squeak format on load time.
>   original-string/index pairs are registerd to Dictionary on load time.
>   hash search can't be used"
>   | strm originalTable translatedTable |
> + localeID := id.
> - localeID _ id.
>   strm_ FileStream readOnlyFileNamed: aFileName.
> + fileName := aFileName.
> - fileName _ aFileName.
>   [
>   self loadHeader: strm.
> + originalTable := self loadStringPointers: strm
> - originalTable _ self loadStringPointers: strm
>   offset: originalTableOffset.
>
> + originalStrings := self loadStrings: strm
> - originalStrings _ self loadStrings: strm
>   pointers: originalTable.
>
> + translatedTable := self loadStringPointers: strm
> - translatedTable _ self loadStringPointers: strm
>   offset: translatedTableOffset.
>
> + translatedStrings := self loadStrings: strm
> - translatedStrings _ self loadStrings: strm
>   pointers: translatedTable
>   encoding: 'utf8'
>   languageEnvironment: (Locale localeID: localeID) languageEnvironment .
>
> + translations := Dictionary new.
> - translations _ Dictionary new.
>   1 to: nStrings do: [:index |
>   | key |
> + key := originalStrings at: index.
> - key _ originalStrings at: index.
>   translations at: key put: index.
>   ].
> + originalTable := nil.
> - originalTable _ nil.
>   ] ensure: [strm close].!
>
> Item was changed:
>  ----- Method: MOFile>>load4:localeID: (in category 'experimental') -----
>  load4: aFileName localeID: id
>   "CASE4:
>   all of strings are loaded.
>   loading and conversion of translation strings to Squeak format is executed on initialization time.
>   only hash search can be used"
>   | strm originalTable translatedTable |
> + localeID := id.
> - localeID _ id.
>   strm_ FileStream readOnlyFileNamed: aFileName.
> + fileName := aFileName.
> - fileName _ aFileName.
>   [
>   self loadHeader: strm.
>   self loadHashTable: strm.
> + originalTable := self loadStringPointers: strm
> - originalTable _ self loadStringPointers: strm
>   offset: originalTableOffset.
>
> + originalStrings := self loadStrings: strm
> - originalStrings _ self loadStrings: strm
>   pointers: originalTable.
>
> + translatedTable := self loadStringPointers: strm
> - translatedTable _ self loadStringPointers: strm
>   offset: translatedTableOffset.
>
> + translatedStrings := self loadStrings: strm
> - translatedStrings _ self loadStrings: strm
>   pointers: translatedTable
>   encoding: 'utf-8'
>   languageEnvironment: (Locale localeID: localeID) languageEnvironment .
>   ] ensure: [strm close].!
>
> Item was changed:
>  ----- Method: MOFile>>load:localeID: (in category 'public') -----
>  load: aFileName localeID: id
>   "all of original/translated strings are loaded.
>   but conversion of translation string (in utf-8 bytestring) to Squeak format will be defered.
>   original-string/index pairs are registerd to Dictionary on load time.
>   hash search can't be used"
>   | strm originalTable translatedTable |
> + localeID := id.
> - localeID _ id.
>   strm_ FileStream readOnlyFileNamed: aFileName.
> + fileName := aFileName.
> - fileName _ aFileName.
>   [
>   self loadHeader: strm.
> + originalTable := self loadStringPointers: strm
> - originalTable _ self loadStringPointers: strm
>   offset: originalTableOffset.
>
> + originalStrings := self loadStrings: strm
> - originalStrings _ self loadStrings: strm
>   pointers: originalTable.
>
> + translatedTable := self loadStringPointers: strm
> - translatedTable _ self loadStringPointers: strm
>   offset: translatedTableOffset.
>
> + translatedStrings := self loadStrings: strm
> - translatedStrings _ self loadStrings: strm
>   pointers: translatedTable.
>
> + translations := Dictionary new: nStrings * 2.  "make too enough room to avoid #grow"
> - translations _ Dictionary new: nStrings * 2.  "make too enough room to avoid #grow"
>   1 to: nStrings do: [:index |
>   | key |
> + key := originalStrings at: index.
> - key _ originalStrings at: index.
>   translations at: key put: index.
>   ].
> + originalStrings := nil.
> - originalStrings _ nil.
>   ] ensure: [strm close].!
>
> Item was changed:
>  ----- Method: MOFile>>loadHashTable: (in category 'experimental') -----
>  loadHashTable: strm
>   | entry |
> + hashTable := IntegerArray  ofSize: hashTableSize.
> - hashTable _ IntegerArray  ofSize: hashTableSize.
>   strm binary.
>   strm position: hashTableOffset.
>   1 to: hashTableSize do: [:index |
> + entry := self nextInt32From: strm.
> - entry _ self nextInt32From: strm.
>   hashTable at:  index put: entry.
>   ]!
>
> Item was changed:
>  ----- Method: MOFile>>loadHeader: (in category 'private') -----
>  loadHeader: strm
>   strm binary.
> + magic :=  strm uint32.
> - magic _  strm uint32.
>   magic = 16rDE120495
> + ifTrue: [isLittleEndian := true]
> - ifTrue: [isLittleEndian _ true]
>   ifFalse: [
>   magic = 16r950412DE
> + ifTrue: [isLittleEndian := false]
> - ifTrue: [isLittleEndian _ false]
>   ifFalse: [ self error: 'invalid MO']
>   ].
> + revision := self nextInt32From: strm.
> + nStrings := self nextInt32From: strm.
> + originalTableOffset := self nextInt32From: strm.
> + translatedTableOffset := self nextInt32From: strm.
> + hashTableSize := self nextInt32From: strm.
> + hashTableOffset := self nextInt32From: strm.
> - revision _ self nextInt32From: strm.
> - nStrings _ self nextInt32From: strm.
> - originalTableOffset _ self nextInt32From: strm.
> - translatedTableOffset _ self nextInt32From: strm.
> - hashTableSize _ self nextInt32From: strm.
> - hashTableOffset _ self nextInt32From: strm.
>  !
>
> Item was changed:
>  ----- Method: MOFile>>loadString:pointer:length: (in category 'private') -----
>  loadString: strm pointer: top  length: len
>   | str |
> + str := ByteString new: len.
> - str _ ByteString new: len.
>   strm position:  top.
>   strm nextInto: str.
>   ^str replaceAll: Lf with: Cr.
>  !
>
> Item was changed:
>  ----- Method: MOFile>>loadStringPointers:offset: (in category 'private') -----
>  loadStringPointers: strm offset: tableOffset
>   "returns tupple {arrayOfOffsetToString  arrayOfLengthOfString}"
>   | offsetTable lenTable len offset tupple |
> + offsetTable := IntegerArray new: nStrings.
> + lenTable := IntegerArray new: nStrings.
> - offsetTable _ IntegerArray new: nStrings.
> - lenTable _ IntegerArray new: nStrings.
>   strm binary.
>   strm position: tableOffset.
>   1 to: nStrings do: [:index |
> + len := self nextInt32From: strm.
> + offset := self nextInt32From: strm.
> - len _ self nextInt32From: strm.
> - offset _ self nextInt32From: strm.
>   offsetTable at: index put: offset.
>   lenTable at: index put: len.
>   ].
> + tupple := Array new: 2.
> - tupple _ Array new: 2.
>   tupple at: 1 put: offsetTable.
>   tupple at: 2 put:  lenTable.
>   ^tupple
>  !
>
> Item was changed:
>  ----- Method: MOFile>>loadStrings:pointers:encoding:languageEnvironment: (in category 'private') -----
>  loadStrings: strm pointers: tupple encoding: encodingName languageEnvironment: env
>   | strings rawStr str offsetTable lenTable |
> + offsetTable :=  tupple first.
> + lenTable := tupple second.
> + strings := Array new: nStrings.
> - offsetTable _  tupple first.
> - lenTable _ tupple second.
> - strings _ Array new: nStrings.
>   1 to: nStrings do: [:index |
> + rawStr := self loadString: strm
> - rawStr _ self loadString: strm
>   pointer:  (offsetTable at: index)
>   length: (lenTable at: index).
> + str := encodingName isNil ifTrue: [rawStr]
> - str _ encodingName isNil ifTrue: [rawStr]
>   ifFalse: [ encodingName = 'utf8'
>   ifTrue: [rawStr utf8ToSqueak applyLanguageInfomation: env]
>   ifFalse: [self error: 'this encoding isn''t supported']
>   ].
>   strings at: index put: str.
>   ].
>   ^strings.!
>
> Item was changed:
>  ----- Method: MOFile>>searchByDictionary: (in category 'public') -----
>  searchByDictionary: aString
>   | index |
> + index := translations at: aString ifAbsent: [^nil].
> - index _ translations at: aString ifAbsent: [^nil].
>   ^self translatedString: index
>
>  !
>
> Item was changed:
>  ----- Method: MOFile>>searchByHash: (in category 'experimental') -----
>  searchByHash: aString
>   | hashValue nstr index incr key |
> + hashValue :=  self hashPjw: aString.
> + incr := 1 + (hashValue \\ (hashTableSize -2)).
> + index := (hashValue \\ hashTableSize) .
> + [ nstr := (hashTable at: index +1 ).
> - hashValue _  self hashPjw: aString.
> - incr _ 1 + (hashValue \\ (hashTableSize -2)).
> - index _ (hashValue \\ hashTableSize) .
> - [ nstr _ (hashTable at: index +1 ).
>   nstr = 0 ifTrue: [^nil].
> + key := self originalString: nstr.
> - key _ self originalString: nstr.
>   key = aString ifTrue: [^self translatedString: nstr].
>   index >= (hashTableSize - incr)
> + ifTrue: [index := index - (hashTableSize - incr)  ]
> + ifFalse:[index := index + incr].
> - ifTrue: [index _ index - (hashTableSize - incr)  ]
> - ifFalse:[index _ index + incr].
>   ] doWhileTrue: true.!
>
> Item was changed:
>  ----- Method: MOFile>>translateByHash: (in category 'experimental') -----
>  translateByHash: aString
>   | trans |
> + trans := self searchByHash: aString.
> - trans _ self searchByHash: aString.
>   trans isNil ifTrue: [^aString]
>   ifFalse: [^trans].
>  !
>
> Item was changed:
>  ----- Method: MOFile>>translatedString: (in category 'private') -----
>  translatedString: index
>   "KNOWN PROBLEM: conversion is executed everytimes this method called"
>   | str |
> + str := translatedStrings at: index.
> - str _ translatedStrings at: index.
>
>   ^str utf8ToSqueak applyLanguageInfomation: (Locale localeID: localeID) languageEnvironment.
>  !
>
> Item was changed:
>  ----- 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).
> - 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 changed:
>  ----- Method: NaturalLanguageFormTranslator>>saveFormsOn: (in category 'i/o') -----
>  saveFormsOn: aStream
>
>   | rr |
> + rr := ReferenceStream on: aStream.
> - rr _ ReferenceStream on: aStream.
>   rr nextPut: {id isoString. generics}.
>   rr close.
>  !
>
> Item was changed:
>  ----- 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 _ self availableForLocaleID: localeID.
>   (translator isDomainLoaded: aDomainName) ifFalse: [
>   (InternalTranslator availableLanguageLocaleIDs includes: localeID)
> + ifTrue:  [translator := InternalTranslator localeID: localeID].
> - ifTrue:  [translator _ InternalTranslator localeID: localeID].
>   ].
>   ^translator translate: aString inDomain: aDomainName!
>
> Item was changed:
>  ----- Method: String>>translatedIfCorresponds (in category '*gettext') -----
>  translatedIfCorresponds
>   "answer the receiver translated to the default language only if
> + the receiver begins and ends with an underscore (:=)"
> + ^ (':=*:=' match: self)
> - the receiver begins and ends with an underscore (_)"
> - ^ ('_*_' match: self)
>   ifTrue: [(self copyFrom: 2 to: self size - 1) translated]
>   ifFalse: [self]!
>
> Item was changed:
>  ----- Method: TranslatedReceiverFinder>>stringReceiversWithContext (in category 'accessing') -----
>  stringReceiversWithContext
>   | mrs results rr cls mn t o |
> + mrs := SystemNavigation default allCallsOn: #translated.
> + results := OrderedCollection new.
> - mrs _ SystemNavigation default allCallsOn: #translated.
> - results _ OrderedCollection new.
>   mrs do: [:mr |
> + rr := OrderedCollection new.
> + cls := Smalltalk at: mr classSymbol.
> - rr _ OrderedCollection new.
> - cls _ Smalltalk at: mr classSymbol.
>   rr add: cls category.
>   rr add: mr classSymbol.
>   rr add: mr methodSymbol.
>   mr classIsMeta ifTrue: [
> + mn :=  cls class decompile: mr methodSymbol.
> - mn _  cls class decompile: mr methodSymbol.
>   ] ifFalse: [
> + mn := cls decompile: mr methodSymbol.
> - mn _ cls decompile: mr methodSymbol.
>   ].
> + o := OrderedCollection new.
> + t := Set new.
> - o _ OrderedCollection new.
> - t _ Set new.
>   self searchMessageNode: mn addTo: t.
>   t do: [ :te |
>   (te receiver isMemberOf: LiteralNode) ifTrue: [
>      o add: te receiver key.
>   ].
>   ].
>   o ifNotEmpty: [
>   rr add: o.
>   results add: rr.
>   ].
>   ].
>   ^ results.
>
>  !
>
> Item was changed:
>  ----- Method: TranslatedReceiverFinder>>stringReceiversWithContext: (in category 'accessing') -----
>  stringReceiversWithContext: aSymbol
>   "Find string receivers for a symbol.
>   Answer a collection of aMethodReference -> {keyword. keyword...}"
>   "self new stringReceiversWithContext: #translated"
>   | keywords methodReferences |
> + methodReferences := SystemNavigation default allCallsOn: aSymbol.
> - methodReferences _ SystemNavigation default allCallsOn: aSymbol.
>   ^ methodReferences inject: OrderedCollection new into: [:list :next |
>   keywords := self findWordsWith: aSymbol in: next.
>   keywords
>   ifNotEmpty: [list add: next -> keywords].
>   list]
>  !
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Levente Uzonyi-2
In reply to this post by Edgar De Cleene
On Fri, 30 Mar 2012, Edgar J. De Cleene wrote:

>
>
>
> On 3/30/12 7:54 AM, "Nicolas Cellier" <[hidden email]> wrote:
>
>                         translatedIfCorresponds
>
>
> Ok, this is fixed reverting to original version of method.
> You do this or I do this?

The rule for the Trunk is "You break it, you fix it.". See
http://squeakboard.wordpress.com/2009/07/02/a-new-community-development-model/ 

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

David T. Lewis
In reply to this post by Levente Uzonyi-2
On Fri, Mar 30, 2012 at 01:11:59PM +0200, Levente Uzonyi wrote:

> On Thu, 15 Mar 2012, [hidden email] wrote:
>
> >Edgar J. De Cleene uploaded a new version of GetText to project The Trunk:
> >http://source.squeak.org/trunk/GetText-edc.18.mcz
> >
> >==================== Summary ====================
> >
> >Name: GetText-edc.18
> >Author: edc
> >Time: 15 March 2012, 6:29:37.486 pm
> >UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
> >Ancestors: GetText-edc.17
> >
> >'_' s replaced by ':='
>
> The method you used to replace the assignments is wrong, because it's
> just simple search and replace, which ignores the context (e.g. strings
> and comments). Please review the changes by hand and fix them.

I have found that Bert's FixUnderscores package works well for updating
the assignment characters in a package. FixUnderscores will do most of
the changes, but the updates must still be checked by hand as in a case
like this one.

FixUnderscores is on SqueakMap.

Dave
 

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Edgar De Cleene



On 3/30/12 9:09 AM, "David T. Lewis" <[hidden email]> wrote:

> I have found that Bert's FixUnderscores package works well for updating
> the assignment characters in a package. FixUnderscores will do most of
> the changes, but the updates must still be checked by hand as in a case
> like this one.
>
> FixUnderscores is on SqueakMap.
>
> Dave


Very thanks, I use this next time

Also run all test before and after for sure do not break new things.
My fault.

We should be able to delete wrong .mcz from trunk.

Edgar



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Levente Uzonyi-2
In reply to this post by David T. Lewis
On Fri, 30 Mar 2012, David T. Lewis wrote:

> On Fri, Mar 30, 2012 at 01:11:59PM +0200, Levente Uzonyi wrote:
>> On Thu, 15 Mar 2012, [hidden email] wrote:
>>
>>> Edgar J. De Cleene uploaded a new version of GetText to project The Trunk:
>>> http://source.squeak.org/trunk/GetText-edc.18.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: GetText-edc.18
>>> Author: edc
>>> Time: 15 March 2012, 6:29:37.486 pm
>>> UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
>>> Ancestors: GetText-edc.17
>>>
>>> '_' s replaced by ':='
>>
>> The method you used to replace the assignments is wrong, because it's
>> just simple search and replace, which ignores the context (e.g. strings
>> and comments). Please review the changes by hand and fix them.
>
> I have found that Bert's FixUnderscores package works well for updating
> the assignment characters in a package. FixUnderscores will do most of
> the changes, but the updates must still be checked by hand as in a case
> like this one.
>
> FixUnderscores is on SqueakMap.

There's FixUnderscores2 which is even better, because it uses the compiler
to find assignments and do the replacement properly. But I think the best
solution is to add a utility to the Trunk itself (I wrote one using
Eliot's parse node visitor), so it will be straightforward to find the
right tool.
Manual review is still necessary, because sometimes the comments contain
code with assignments.


Levente

>
> Dave
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: GetText-edc.18.mcz

Levente Uzonyi-2
In reply to this post by Edgar De Cleene
On Fri, 30 Mar 2012, Edgar J. De Cleene wrote:

>
>
>
> On 3/30/12 9:09 AM, "David T. Lewis" <[hidden email]> wrote:
>
>> I have found that Bert's FixUnderscores package works well for updating
>> the assignment characters in a package. FixUnderscores will do most of
>> the changes, but the updates must still be checked by hand as in a case
>> like this one.
>>
>> FixUnderscores is on SqueakMap.
>>
>> Dave
>
>
> Very thanks, I use this next time
>
> Also run all test before and after for sure do not break new things.
> My fault.
>
> We should be able to delete wrong .mcz from trunk.
It's possible, but it's a bad idea, because it breaks the Trunk. Let me
quote the rules (or guidelines) here:

"Rules of Engagement

If you have used Monticello in projects with more than two developers in
the past you already know the drill. If not, here are some useful
guidelines:

* Merge often. In particular when you pick up work and right before you
intend to commit.

* Exercise caution. This is a running system and breaking it needlessly is
generally frowned upon.

* Restrain yourself. Getting developer access doesn’t mean you are free to
put in every pet extension you always wanted to have without discussion.

* If in doubt, ask. This is the corollary to the restrain yourself rule.
You’re not under pressure to ship a product, so you have the time to send
a note saying “hey, I’m planning to fix this old issue and it may have
some side effect here or there. Anyone having a problem with that?”

>>> I’ll add a Squeak-dev exception here: Any response from any
non-developer can be entirely ignored in this context.

* You break it, you fix it. If you change something you are generally
expected to take care of the consequences, though there are some
exceptions. If in doubt, ask

* Do good and talk about it. When you’re done with whatever it is you’ve
been working on let people know about it. It can be as short as a note to
Squeak-dev saying “hey, some of you might care that I’ve fixed the long
standing bug with xyz. Update and enjoy”

* Unit Testing. Unit tests are an essential part of maintaining the
reliability of our releases. New units tests are always welcome. Keep in
mind that a unit test should take as little time to run as possible.
Maintaining the reliability of Squeak is always easier when the tests are
all green: if you break something the appearance of a new failure or error
is immediately obvious and the cause is more easily found. To that end
fixes for failures or errors are extremely valuable and please avoid
submitting changes that cause new failures or errors."


Levente

>
> Edgar
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

FixUnderscores (was: The Trunk: GetText-edc.18.mcz)

David T. Lewis
In reply to this post by Levente Uzonyi-2
On Fri, Mar 30, 2012 at 02:39:49PM +0200, Levente Uzonyi wrote:

> On Fri, 30 Mar 2012, David T. Lewis wrote:
>
> >On Fri, Mar 30, 2012 at 01:11:59PM +0200, Levente Uzonyi wrote:
> >>On Thu, 15 Mar 2012, [hidden email] wrote:
> >>
> >>>Edgar J. De Cleene uploaded a new version of GetText to project The
> >>>Trunk:
> >>>http://source.squeak.org/trunk/GetText-edc.18.mcz
> >>>
> >>>==================== Summary ====================
> >>>
> >>>Name: GetText-edc.18
> >>>Author: edc
> >>>Time: 15 March 2012, 6:29:37.486 pm
> >>>UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
> >>>Ancestors: GetText-edc.17
> >>>
> >>>'_' s replaced by ':='
> >>
> >>The method you used to replace the assignments is wrong, because it's
> >>just simple search and replace, which ignores the context (e.g. strings
> >>and comments). Please review the changes by hand and fix them.
> >
> >I have found that Bert's FixUnderscores package works well for updating
> >the assignment characters in a package. FixUnderscores will do most of
> >the changes, but the updates must still be checked by hand as in a case
> >like this one.
> >
> >FixUnderscores is on SqueakMap.
>
> There's FixUnderscores2 which is even better, because it uses the compiler
> to find assignments and do the replacement properly. But I think the best
> solution is to add a utility to the Trunk itself (I wrote one using
> Eliot's parse node visitor), so it will be straightforward to find the
> right tool.
> Manual review is still necessary, because sometimes the comments contain
> code with assignments.

Levente,

That sounds like a good idea to me. If you have the utility available,
please add it to the inbox or trunk. It would be good to have it readily
available, and it will help in reconciling Etoys with trunk.

Dave


Reply | Threaded
Open this post in threaded view
|

Re: FixUnderscores (was: The Trunk: GetText-edc.18.mcz)

Chris Muller-3
I'm not familiar with FixUnderscores2, but the original FixUnderscores
would preserve the accounting information on changed methods.  This is
important -- at least to me -- so I hope the new one does that too.

Replacing based on assignment nodes:  wouldn't that skip the ones that
were embedded in comment strings (e.g., doIt examples, etc.)?  When
the original FixUnderscores would find an underscore in the source
code that occurred in a literal or comment, it would display it in a
methods browser so it could be manually fixed.  Usually there are none
of very few.  It's hard to imagine a "better" solution than that..


On Fri, Mar 30, 2012 at 5:41 PM, David T. Lewis <[hidden email]> wrote:

> On Fri, Mar 30, 2012 at 02:39:49PM +0200, Levente Uzonyi wrote:
>> On Fri, 30 Mar 2012, David T. Lewis wrote:
>>
>> >On Fri, Mar 30, 2012 at 01:11:59PM +0200, Levente Uzonyi wrote:
>> >>On Thu, 15 Mar 2012, [hidden email] wrote:
>> >>
>> >>>Edgar J. De Cleene uploaded a new version of GetText to project The
>> >>>Trunk:
>> >>>http://source.squeak.org/trunk/GetText-edc.18.mcz
>> >>>
>> >>>==================== Summary ====================
>> >>>
>> >>>Name: GetText-edc.18
>> >>>Author: edc
>> >>>Time: 15 March 2012, 6:29:37.486 pm
>> >>>UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
>> >>>Ancestors: GetText-edc.17
>> >>>
>> >>>'_' s replaced by ':='
>> >>
>> >>The method you used to replace the assignments is wrong, because it's
>> >>just simple search and replace, which ignores the context (e.g. strings
>> >>and comments). Please review the changes by hand and fix them.
>> >
>> >I have found that Bert's FixUnderscores package works well for updating
>> >the assignment characters in a package. FixUnderscores will do most of
>> >the changes, but the updates must still be checked by hand as in a case
>> >like this one.
>> >
>> >FixUnderscores is on SqueakMap.
>>
>> There's FixUnderscores2 which is even better, because it uses the compiler
>> to find assignments and do the replacement properly. But I think the best
>> solution is to add a utility to the Trunk itself (I wrote one using
>> Eliot's parse node visitor), so it will be straightforward to find the
>> right tool.
>> Manual review is still necessary, because sometimes the comments contain
>> code with assignments.
>
> Levente,
>
> That sounds like a good idea to me. If you have the utility available,
> please add it to the inbox or trunk. It would be good to have it readily
> available, and it will help in reconciling Etoys with trunk.
>
> Dave
>
>

Reply | Threaded
Open this post in threaded view
|

Re: FixUnderscores (was: The Trunk: GetText-edc.18.mcz)

David T. Lewis
On Sat, Mar 31, 2012 at 11:26:37AM -0500, Chris Muller wrote:
> I'm not familiar with FixUnderscores2, but the original FixUnderscores
> would preserve the accounting information on changed methods.  This is
> important -- at least to me -- so I hope the new one does that too.

+1

Dave


Reply | Threaded
Open this post in threaded view
|

Re: FixUnderscores (was: The Trunk: GetText-edc.18.mcz)

Levente Uzonyi-2
In reply to this post by Chris Muller-3
On Sat, 31 Mar 2012, Chris Muller wrote:

> I'm not familiar with FixUnderscores2, but the original FixUnderscores
> would preserve the accounting information on changed methods.  This is
> important -- at least to me -- so I hope the new one does that too.

Of course.

>
> Replacing based on assignment nodes:  wouldn't that skip the ones that
> were embedded in comment strings (e.g., doIt examples, etc.)?  When

It skips those as expected.

> the original FixUnderscores would find an underscore in the source
> code that occurred in a literal or comment, it would display it in a
> methods browser so it could be manually fixed.  Usually there are none
> of very few.  It's hard to imagine a "better" solution than that..

I think FixUnderscores2 does the same, but I'm about to add a minimal
implementation to the Trunk with the same features.


Levente

>
>
> On Fri, Mar 30, 2012 at 5:41 PM, David T. Lewis <[hidden email]> wrote:
>> On Fri, Mar 30, 2012 at 02:39:49PM +0200, Levente Uzonyi wrote:
>>> On Fri, 30 Mar 2012, David T. Lewis wrote:
>>>
>>>> On Fri, Mar 30, 2012 at 01:11:59PM +0200, Levente Uzonyi wrote:
>>>>> On Thu, 15 Mar 2012, [hidden email] wrote:
>>>>>
>>>>>> Edgar J. De Cleene uploaded a new version of GetText to project The
>>>>>> Trunk:
>>>>>> http://source.squeak.org/trunk/GetText-edc.18.mcz
>>>>>>
>>>>>> ==================== Summary ====================
>>>>>>
>>>>>> Name: GetText-edc.18
>>>>>> Author: edc
>>>>>> Time: 15 March 2012, 6:29:37.486 pm
>>>>>> UUID: 43d88f85-6e87-41fb-8dd1-883feaf3d297
>>>>>> Ancestors: GetText-edc.17
>>>>>>
>>>>>> '_' s replaced by ':='
>>>>>
>>>>> The method you used to replace the assignments is wrong, because it's
>>>>> just simple search and replace, which ignores the context (e.g. strings
>>>>> and comments). Please review the changes by hand and fix them.
>>>>
>>>> I have found that Bert's FixUnderscores package works well for updating
>>>> the assignment characters in a package. FixUnderscores will do most of
>>>> the changes, but the updates must still be checked by hand as in a case
>>>> like this one.
>>>>
>>>> FixUnderscores is on SqueakMap.
>>>
>>> There's FixUnderscores2 which is even better, because it uses the compiler
>>> to find assignments and do the replacement properly. But I think the best
>>> solution is to add a utility to the Trunk itself (I wrote one using
>>> Eliot's parse node visitor), so it will be straightforward to find the
>>> right tool.
>>> Manual review is still necessary, because sometimes the comments contain
>>> code with assignments.
>>
>> Levente,
>>
>> That sounds like a good idea to me. If you have the utility available,
>> please add it to the inbox or trunk. It would be good to have it readily
>> available, and it will help in reconciling Etoys with trunk.
>>
>> Dave
>>
>>
>
>