[etoys-dev] Etoys: System-Richo.12.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 23 09:41:07 EDT 2010


A new version of System was added to project Etoys:
http://source.squeak.org/etoys/System-Richo.12.mcz

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

Name: System-Richo.12
Author: Richo
Time: 13 May 2010, 4:10:15 pm
UUID: 3188de42-860f-5949-9f9a-12f540c657b7
Ancestors: System-Richo.11

* Removed a lot of stuff used for Localization.
* Modified TextDomainManager to use method properties to store the text domain of each method. This happens in a lazy way. It's also posible to preconfigure the method properties of all methods with translations but it takes forever and it ends up with a Space Low warning (see TextDomainManager class>>updateDomainOfAllMethodsWithTranslations)

=============== Diff against System-bf.9 ===============

Item was added:
+ ----- Method: TextDomainManager classSide>>allMethodsWithTranslations (in category 'accessing') -----
+ allMethodsWithTranslations
+ "Look for #translated calls"
+ | methodsWithTranslations |
+ methodsWithTranslations := TranslatedReceiverFinder new stringReceiversWithContext: #translated.
+ methodsWithTranslations := methodsWithTranslations, (TranslatedReceiverFinder new
+ stringReceiversWithContext: #translatedNoop).
+ 
+ methodsWithTranslations := methodsWithTranslations collect: [:each | each key compiledMethod].
+ 
+ "Look for Etoys tiles and vocabularies"
+ methodsWithTranslations := methodsWithTranslations, (EToyVocabulary allPhrasesWithContextToTranslate collect: [:r |
+ 	(MethodReference new setStandardClass: r second methodSymbol: r third) compiledMethod.
+ ]).
+ 
+ ^methodsWithTranslations!

Item was added:
+ ----- Method: TextDomainManager classSide>>domainForPackage: (in category 'accessing') -----
+ domainForPackage: aPackageInfo
+ "Package names and text domains are synonyms now"
+ 	^aPackageInfo name!

Item was changed:
  Object subclass: #TextDomainManager
  	instanceVariableNames: ''
+ 	classVariableNames: 'ClassCategories Classes DefaultDomain DomainInfos LoneClasses Packages'
- 	classVariableNames: 'ClassCategories Classes DefaultDomain DomainInfos LoneClasses'
  	poolDictionaries: ''
  	category: 'System-Localization'!
+ TextDomainManager class
+ 	instanceVariableNames: 'defaultDomain'!
  
  !TextDomainManager commentStamp: 'tk 1/4/2008 16:08' prior: 0!
  I manages mapping from class category to textdomain.
  
  Class variables:
   ClassCategories	IdentityDictionary -- classCategory -> domainName 
   Classes			IdentityDictionary -- class name (a Symbol) -> domainName   (a cache only!!)
   DefaultDomain	String -- the default domain name
   DomainInfos		Dictionary -- domainName -> a TextDomainInfo
   LoneClasses		IdentityDictionary -- class name (a Symbol) -> domainName.  For classes whose entire category are not all in the same domain (BookMorph and QuickGuideMorph)
  
  TextDomainManager registerCategoryPrefix: 'DrGeoII' domain: 'DrGeoII'.
  TextDomainManager unregisterDomain: 'DrGeoII'.
  
  TextDomainManager registerClass: #QuickGuideMorph domain: 'quickguides'.
  TextDomainManager registerClass: #QuickGuideHolderMorph  domain: 'quickguides'.
  !
+ TextDomainManager class
+ 	instanceVariableNames: 'defaultDomain'!

Item was added:
+ ----- Method: TextDomainManager classSide>>domainOfMethod: (in category 'accessing') -----
+ domainOfMethod: aCompiledMethod 
+ 	^ aCompiledMethod
+ 		propertyValueAt: self textDomainProperty
+ 		ifAbsent: [self updateDomainOfMethod: aCompiledMethod] !

Item was added:
+ ----- Method: TextDomainManager classSide>>clearAllDomains (in category 'private') -----
+ clearAllDomains
+ 	SystemNavigation default
+ 		allCompiledMethodDo: [:each | each
+ 				removeProperty: self textDomainProperty
+ 				ifAbsent: []] !

Item was added:
+ ----- Method: TextDomainManager classSide>>updateDomainOfAllMethodsWithTranslations (in category 'private') -----
+ updateDomainOfAllMethodsWithTranslations
+ self allMethodsWithTranslations do: [:each|
+ 	self updateDomainOfMethod: each
+ ]!

Item was changed:
  ----- Method: TextDomainManager classSide>>initialize (in category 'class initialization') -----
  initialize
  	"	TextDomainManager initialize	"
+ 	self defaultDomain: 'Etoys'; clearAllDomains!
- 
- 	ClassCategories _ IdentityDictionary new.
- 	Classes _ IdentityDictionary new.
- 	DomainInfos _ Dictionary new.
- 	self defaultDomain: 'etoys'.
- 	self registerClass: #QuickGuideMorph domain: 'quickguides'.
- 	self registerClass: #QuickGuideHolderMorph  domain: 'quickguides'.
- !

Item was added:
+ ----- Method: TextDomainManager classSide>>textDomainProperty (in category 'private') -----
+ textDomainProperty
+ ^#textDomain!

Item was changed:
  ----- Method: TextDomainManager classSide>>defaultDomain (in category 'accessing') -----
  defaultDomain
+ "I'm not sure we still need a default domain, AFAIK the default domain will only be used when no domain is found. In that case, wouldn't it be better to just look for a translation in all domains?"
+ 	^defaultDomain!
- 	^DefaultDomain!

Item was added:
+ ----- Method: TextDomainManager classSide>>updateDomainOfMethod: (in category 'private') -----
+ updateDomainOfMethod: aCompiledMethod 
+ 	"First it looks for the package of the method reference (using
+ 	the PackageOrganizer: deadly slow). If the method doesn't
+ 	belong to any package it uses the default domain. Finally it
+ 	stores the text domain of the method using a method
+ 	property, this way we gain performance the next time we
+ 	translate the same method because we avoid the use of
+ 	PackageOrganizer. Have I mentioned it is really slow? :)"
+ 	| package |
+ 	package := PackageOrganizer default
+ 				packageOfMethod: aCompiledMethod methodReference
+ 				ifNone: [].
+ 	^ aCompiledMethod
+ 		propertyValueAt: self textDomainProperty
+ 		put: (package isNil
+ 				ifTrue: [TextDomainManager defaultDomain]
+ 				ifFalse: [package name])!

Item was changed:
  ----- Method: TextDomainManager classSide>>allKnownDomains (in category 'accessing') -----
  allKnownDomains
+ "Every package has it's own text domain now so it's not necessary to keep a registry of all domains, we can simply return all the packages in the image.
+ PROBLEM: If a package doesn't contain translations, it won't have a mo file but the GetTextTranslator will try to load it anyway. This happens when we switch languages. So far I tested it briefly and it seems to work..."
+ ^PackageOrganizer default packageNames!
- 	| domains |
- 	domains _ Set new.
- 	domains addAll: ClassCategories values.
- 	domains add: self defaultDomain.
- 	^domains
- !

Item was changed:
  ----- Method: TextDomainManager classSide>>defaultDomain: (in category 'accessing') -----
  defaultDomain: aDomainName
+ 	defaultDomain := aDomainName!
- 	DefaultDomain _ aDomainName!

Item was removed:
- ----- Method: TextDomainManager classSide>>unregisterDomain: (in category 'accessing') -----
- unregisterDomain: domainName
- 	DomainInfos removeKey: domainName.
- 	self refresh.
- 	NaturalLanguageTranslator domainUnregistered: domainName.
- !

Item was removed:
- ----- Method: TextDomainInfo>>categories (in category 'accessing') -----
- categories
- 	^categories!

Item was removed:
- ----- Method: TextDomainInfo>>category:matches: (in category 'private') -----
- category: categoryName matches: prefix
- 	^ categoryName notNil and: [categoryName = prefix or: [categoryName beginsWith: prefix, '-']]!

Item was removed:
- ----- Method: TextDomainManager classSide>>registerCategoryPrefix:domain: (in category 'accessing') -----
- registerCategoryPrefix: aString domain: aDomainName
- 	| domInfo |
- 	domInfo _ self domainInfoFor: aDomainName.
- 	domInfo categoryPrefixes add: aString.
- 	self refresh.!

Item was removed:
- ----- Method: TextDomainManager classSide>>registerClass:domain: (in category 'accessing') -----
- registerClass: className domain: aDomainName
- 
- 	LoneClasses ifNil: [LoneClasses _ IdentityDictionary new].
- 	LoneClasses at: className put: aDomainName.
- 	self refresh.	"moves it to Classes"
- !

Item was removed:
- ----- Method: TextDomainManager classSide>>refresh (in category 'private') -----
- refresh
- 	ClassCategories _ IdentityDictionary new.
- 	Classes _ IdentityDictionary new.
- 	DomainInfos keysAndValuesDo: [:domainName :domainInfo |
- 		domainInfo matchedSystemCategories do: [:cat |
- 			ClassCategories at: cat ifPresent: [self error: 'category ', (cat asString) , '  belongs to multiple domains'].
- 			ClassCategories at: cat put: domainName.
- 			(SystemOrganization listAtCategoryNamed: cat ) do: [ :cls |
- 				Classes at: cls put: domainName.
- 			]
- 		]
- 	].
- 	Classes addAll: LoneClasses.!

Item was removed:
- ----- Method: TextDomainManager classSide>>domainInfoFor: (in category 'private') -----
- domainInfoFor: domainName
- 	^DomainInfos at: domainName ifAbsentPut: [ self registerDomain: domainName]!

Item was removed:
- ----- Method: TextDomainManager classSide>>domainInfos (in category 'private') -----
- domainInfos
- 	^DomainInfos!

Item was removed:
- ----- Method: TextDomainManager classSide>>domainForClassCategory: (in category 'accessing') -----
- domainForClassCategory: aCategorySymbol
- 	^ClassCategories at: aCategorySymbol ifAbsent: [self defaultDomain]!

Item was removed:
- ----- Method: TextDomainManager classSide>>registerClassCategory:domain: (in category 'accessing') -----
- registerClassCategory: categorySymbol domain: aDomainName
- 	| domInfo |
- 	domInfo _ self domainInfoFor: aDomainName.
- 	domInfo categories add: categorySymbol.
- 	self refresh.
- !

Item was removed:
- ----- Method: TextDomainManager classSide>>domainForClass: (in category 'accessing') -----
- domainForClass: aClass
- 	^Classes at: aClass theNonMetaClass name ifAbsent: [self defaultDomain]!

Item was removed:
- Object subclass: #TextDomainInfo
- 	instanceVariableNames: 'categoryPrefixes categories'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'System-Localization'!
- 
- !TextDomainInfo commentStamp: '<historical>' prior: 0!
- I hold criteria for deciding wheter a systemCategory belongs to domain. 
- - categoryPrefixes is collection of prefix of class category.
- - categories is for specifying fine grained criterion.
- !

Item was removed:
- ----- Method: TextDomainInfo>>initialize (in category 'initialize-release') -----
- initialize
- 	categoryPrefixes _ Set new.
- 	categories _ IdentitySet new.
- !

Item was removed:
- ----- Method: TextDomainManager classSide>>registerDomain: (in category 'accessing') -----
- registerDomain: domainName
- 	| domInfo |
- 	domInfo _ TextDomainInfo new.
- 	DomainInfos at: domainName put: domInfo.
- 	NaturalLanguageTranslator domainRegistered: domainName.
- 	^domInfo!

Item was removed:
- ----- Method: TextDomainInfo>>categoryPrefixes (in category 'accessing') -----
- categoryPrefixes
- 	^categoryPrefixes!

Item was removed:
- ----- Method: TextDomainInfo>>includesCategory: (in category 'accessing') -----
- includesCategory: categorySymbol
- 	(categories includes: categorySymbol) ifTrue: [^true].
- 	categoryPrefixes do: [:each |
- 		(self category: categorySymbol matches: each) ifTrue: [^true]
- 	].
- 
- 	^false.!

Item was removed:
- ----- Method: TextDomainInfo>>matchedSystemCategories (in category 'accessing') -----
- matchedSystemCategories
- 	^SystemOrganization categories 
- 		select: [:cat | self includesCategory: cat]!



More information about the etoys-dev mailing list