[Etoys] Many missing translations in POs

korakurider at yahoo.co.jp korakurider at yahoo.co.jp
Mon Oct 29 11:29:37 EDT 2007


OK, Here are updated patches.

korakurider at yahoo.co.jp:
> Hello.
> After switching translation dictionary from NLT to extracted POs, a 
few 
> words don't have translation because those haven't been exported to 
POs.
> Here are proposed fix (attached). 
> 
> 
> (1) viewer category.
>     for instance "collections" isn't translated.
>     TransCategory-KR will fix this.

    Still some categories ('input' for instance) were missing even with 
the last patch.  TransCategory-KR.2.cs is updated one for the problem.

> 
> (2) symbols
>     For instances, these aren't translated.
>     - true/false on boolean readout
>     - emptyScript on ScriptNameTile of "Scripting" category
>     - all of SymbolListTile
>     
>     Unfortunately #translatedNoop isn't useful for this because 
current 
> exporter implementation omits arrayed symbols.
>     
>     By transNoopAll-KR, all of string receiver of #translatedNoopAll
>     including arrayed symbols will be exported. 
>     (the patch has also test).

        With updated transNoopAll-KR.4.cs receiver symbol of 
        #translatedNoopAll will be conveted to no camel case.
        e.g  
        if code is "aObject method: #camelSymbol translatedNoopAll",
        extracted msgid will be "camel symbol".

>     
>     By transSymbols-KR symbols in Vocabulary will be exported.
>     

    For completeness I attached transSymbols-KR again though the patch 
hasn't updated.
    
    
    And with SymListWOCamel-KR, options and readout of SymbolListTile 
will be no-camel-case and the word will be used for translation key.
    
    
    Note that extraction (and no-camel conversion) of function names 
discussed recently hasn't implemented yet, because of time constraint 
for me (and I can't in near future).
    But I think translations have been much improved...

/Korakurider
-------------- next part --------------
'From etoys2.2 of 22 September 2007 [latest update: #1731] on 29 October 2007 at 11:56:16 pm'!
"Change Set:		TransCategory-KR
Date:			28 October 2007
Author:			Korakurider

To make sure all of viewer category symbols are exported to POs/POT and translated"!


!EToyVocabulary class methodsFor: 'as yet unclassified' stamp: 'KR 10/29/2007 23:54'!
allPhrasesWithContextToTranslate
	| etoyVocab results literals additions |

	results := OrderedCollection new.
	etoyVocab := Vocabulary eToyVocabulary.
	etoyVocab initialize.		"just to make sure that it's unfiltered."
	self morphClassesDeclaringViewerAdditions do: [:cl |
		(cl class includesSelector: #additionsToViewerCategories)
			ifTrue: [
				literals := OrderedCollection new.
				cl additionsToViewerCategories do: [:group | 
					literals add: group first.
					group second do: [:tuple |
						literals add: (ScriptingSystem wordingForOperator: (tuple at: 2)).  "wording"
						literals add: (tuple at: 3).  "help string"]].
				literals ifNotEmpty: [
					results add: {cl category. cl. #additionsToViewerCategories. literals}]].

		cl class selectors do: [:aSelector | ((aSelector beginsWith: 'additionsToViewerCategory')
								and: [(aSelector at: 26 ifAbsent: []) ~= $:])
			ifTrue: [
				literals := OrderedCollection new.
				additions := (cl perform: aSelector).
				literals add: additions first.
				additions second do: [:tuple |
					literals add: (ScriptingSystem wordingForOperator: (tuple at: 2)).  "wording"
					literals add: (tuple at: 3).  "help string"].
				literals ifNotEmpty: [
					results add: {cl category. cl. aSelector. literals}]]]].
	^results.! !

-------------- next part --------------
'From etoys2.2 of 22 September 2007 [latest update: #1731] on 29 October 2007 at 11:46:27 pm'!
"Change Set:		transNoopAll-KR
Date:			29 October 2007
Author:			Korakurider

GetTextExporter2 extracts receivers of #translatedNoopAll including arrayed symbols.
Note that symbol with CamelCase will be converted as no camel case.
e.g.   if code is like    aObject method: #camelSymbol  translatedNoopAll,
	extracted msgid=""camel symbol"".

see LanguageEditorTest>>testFindTranslatedWords.
"!


!Object methodsFor: 'translating' stamp: 'KR 10/28/2007 15:30'!
literalStringsAndSymbolsDo: aBlock 
	"Assuming the receiver receiver is a literal, evaluate aBlock with all Strings (including Symbols) within it."
	^ self! !

!Object methodsFor: 'translating' stamp: 'KR 10/28/2007 15:28'!
translatedNoopAll
	"This is correspondence gettext_noop() in gettext.  
	the receiver including arrayed symbols will be extracted into POs and translated" ! !


!Array methodsFor: 'translating' stamp: 'KR 10/28/2007 15:31'!
literalStringsAndSymbolsDo: aBlock 
	"Assuming the receiver receiver is a literal, evaluate aBlock with all Strings (including Symbols) within it."
	self do: [:each | each literalStringsAndSymbolsDo: aBlock]! !

!Array methodsFor: 'translating' stamp: 'KR 10/28/2007 15:28'!
translatedNoopAll
	"This is correspondence gettext_noop() in gettext.  
	the receiver including arrayed symbols will be extracted into POs and translated" 
	^ self! !


!GetTextExporter2 methodsFor: 'exporting' stamp: 'KR 10/28/2007 21:36'!
appendTranslations: domains 
	self appendStringReceivers: #translated into: domains includingSymbols: false.
	self appendStringReceivers: #translatedNoop into: domains includingSymbols: false.
	self appendStringReceivers: #translatedNoopAll into: domains includingSymbols:  true.
	self appendVocabularies: domains.
! !

!GetTextExporter2 methodsFor: 'private' stamp: 'KR 10/28/2007 21:35'!
appendStringReceivers: aSymbol into: domains includingSymbols: bool
	| literals references domainName methodReference keywords found |
	
	found := TranslatedReceiverFinder new stringReceiversWithContext: aSymbol includingSymbols: bool.
	found do: [ :assoc |
		methodReference := assoc key.
		keywords := assoc value.
		domainName _ self getTextDomainForClassCategory:
			(Smalltalk at: methodReference classSymbol) category.
		literals _ domains at: domainName ifAbsentPut: [Dictionary new].
		keywords do: [ :literal |
			references _ literals at: literal ifAbsentPut: [OrderedCollection new].
			references add: methodReference.
		].
	]. 
! !


!LanguageEditorTest methodsFor: 'testing' stamp: 'KR 10/29/2007 23:45'!
testFindTranslatedWords
	"self debug: #testFindTranslatedWords"
	| message words |
	message := MethodReference new setStandardClass: self class methodSymbol: #translatedFinderExample.
	words := TranslatedReceiverFinder new findWordsWith: #findme in: message includingSymbols: false.
	self		assert: (words includes: 'normal').
	self		assert: (words includes: 'inside in an array').
	self		assert: (words includes: 'nested array').
	self		assert: (words includes: 'nested array again').
	self		 assert: (words includes: 'shouldBeIgnored') not.
	self 		assert: (words includes: 'should be ignored') not.
	"Maybe you don't need a symbol"
	self		assert: (words includes: 'symbol') not.
	self		assert: (words includes: 'allSymbol') not.
	self		assert: (words includes: 'all symbol') not.
	self		assert: (words includes: 'allSymbolAgain') not.
	self		assert: (words includes: 'all symbol again') not.

	"Test another findring method to including symbols"
	words := TranslatedReceiverFinder new findWordsWith: #findme in: message includingSymbols: true.
	self		assert: (words includes: 'normal').
	self		assert: (words includes: 'inside in an array').
	self		assert: (words includes: 'nested array').
	self		assert: (words includes: 'nested array again').
	self 		assert: (words includes: 'shouldBeIgnored') not.
	self 		assert: (words includes: 'should be ignored').
	self		assert: (words includes: 'symbol').
	self		assert: (words includes: 'allSymbol') not.
	self		assert: (words includes: 'all symbol').
	self		assert: (words includes: 'allSymbolAgain') not.
	self		assert: (words includes: 'all symbol again').
! !


!String methodsFor: 'translating' stamp: 'KR 10/28/2007 15:32'!
literalStringsAndSymbolsDo: aBlock 
	"Assuming the receiver receiver is a literal, evaluate aBlock with all Strings (including Symbols) within it."
	aBlock value: self! !

!String methodsFor: 'translating' stamp: 'KR 10/28/2007 15:28'!
translatedNoopAll
	"This is correspondence gettext_noop() in gettext.  
	the receiver including arrayed symbols will be extracted into POs and translated" 
	^ self! !


!Symbol methodsFor: 'translating' stamp: 'KR 10/28/2007 15:34'!
literalStringsAndSymbolsDo: aBlock 
	"Assuming the receiver receiver is a literal, evaluate aBlock with all Strings (including Symbols) within it."
	aBlock value: self! !


!TranslatedReceiverFinder methodsFor: 'accessing' stamp: 'KR 10/29/2007 23:41'!
findWordsWith: aSymbol in: aMethodReference includingSymbols: bool
	"Find words for translation with the symbol in a method. See
	LanguageEditorTest >>testFindTranslatedWords"
	"| message | 
	message := MethodReference new setStandardClass: Morph class
	methodSymbol: #supplementaryPartsDescriptions.
	self new findWordsWIth: #translatedNoop in: message"
	| messages keywords aParseNode |
	aParseNode := aMethodReference decompile.
	"Find from string literal"
	messages := Set new.
	self
		search: aSymbol
		messageNode: aParseNode
		addTo: messages.
	keywords := OrderedCollection new.
	messages
		select: [:aMessageNode | aMessageNode receiver isMemberOf: LiteralNode]
		thenDo: [:aMessageNode | 
			bool ifTrue: [ aMessageNode receiver key 
							literalStringsAndSymbolsDo: [:literal | 
								literal isSymbol 
										ifTrue: [keywords add: literal fromCamelCase]  "#CamelCase will be flattered"
										ifFalse: [keywords add: literal].
							]
				]
				ifFalse: [aMessageNode receiver key literalStringsDo: [:literal | keywords add: literal]].
		].
	"Find from array literal"
	self
		arraySearch: aSymbol
		messageNode: aParseNode
		addTo: keywords.

	^keywords! !

!TranslatedReceiverFinder methodsFor: 'accessing' stamp: 'KR 10/28/2007 21:34'!
stringReceiversWithContext: aSymbol includingSymbols: bool
	"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 inject: OrderedCollection new into: [:list :next |
		keywords := self findWordsWith: aSymbol in: next includingSymbols: bool.
		keywords
			ifNotEmpty: [list add: next -> keywords].
		list]
! !

-------------- next part --------------
'From etoys2.2 of 22 September 2007 [latest update: #1730] on 28 October 2007 at 11:52:15 pm'!
"Change Set:		transSymbols-KR
Date:			28 October 2007
Author:			Korakurider

to make sure that all of symbols  in vocabulary will be exported to POs and will be translated"!


!StandardScriptingSystem methodsFor: 'utilities' stamp: 'KR 10/28/2007 23:45'!
arithmeticalOperatorsAndHelpStrings
	"Answer an array consisting of lists of the standard arithmetical operator tiles and of the corresponding balloon help for them"

	^ #((+ - * / // \\ max: min:)
	 	('add' 'subtract' 'multiply' 'divide' 'divide & truncate' 'remainder when divided by' 'larger value' 'smaller value' )) translatedNoop! !

!StandardScriptingSystem methodsFor: 'utilities' stamp: 'KR 10/28/2007 23:44'!
numericComparitorsAndHelpStrings
	"Answer an array whose first element is the list of comparitors, and whose second element is a list of the corresponding help strings"

	^ #((< <= = ~= > >= isDivisibleBy:)
	 	('less than' 'less than or equal' 'equal' 'not equal' 'greater than' 'greater than or equal' 'divisible by' )) translatedNoop! !

!StandardScriptingSystem methodsFor: 'utilities' stamp: 'KR 10/28/2007 23:49'!
tableOfNumericFunctions
	"Answer an array of <external function name> <actual function to call> <help string> triplets."

"		English on tile			selector				English balloon help"
	^ #(
		(abs 					abs						'absolute value')
		(arcTan				arcTan				'angle, in radians, whose tangent is the argument')
		(cos					cos						'trigonometric cosine, argument in radians')
		(cubed					cubed					'the argument times itself, times itself again')
		(cubeRoot				cubeRoot				'cube root of the argument')
		(degreeArcTan		degreeArcTan		'angle, in degrees, whose tangent is the argument')
		(degreeCos				degreeCos				'trigonometric cosine, argument in degrees')
		(degreeSin				degreeSin				'trignometric sine, argument in degrees')
		(degreeTan			degreeTan				'trigonometric tangent, argument in degrees')

		(degreesToRadians	degreesToRadians	'the number of degrees equivalent to the argument which is assumed to be expressed in radians')
		(exp					exp					'exponential (e to the power of the argument)')
		(factorial				factorial				'the product of all the whole numbers between 1 and the argument')
		(ln						safeLn					'natural logarithm')
		(log						safeLog				'logarithm, base 10')
		(negativeOf 			negated				'the negative of the argument')
		(radiansToDegrees	radiansToDegrees	'the number of radians equivalent to the argument, which is expressed in degrees.')
		(random				random				'a randomly chosen integer between 1 and the argument')
		(rounded				rounded				'the integer closest to the argument.')
		(sin						sin						'trigonometric sine, argument in radians')
		(squared				squared				'the argument multiplied by itself')
		(squareRoot			safeSquareRoot		'square root of the argument')
		(tan					tan						'trigonometric tangent, argument in radians')) translatedNoop


"
		(raisedto 		raisedTo:		'raised to the power')   
"! !


!TileMorph methodsFor: 'accessing' stamp: 'KR 10/28/2007 23:47'!
options
	"Answer the options of the tile for an arrow"
	(type == #literal
			and: [literal isKindOf: Boolean])
		ifTrue: [^ {{true. false}. #('true' 'false' ) translatedNoopAll}].
	operatorOrExpression
		ifNil: [^ nil].
	(ScriptingSystem arithmeticalOperatorsAndHelpStrings first includes: operatorOrExpression)
		ifTrue: [^ ScriptingSystem arithmeticalOperatorsAndHelpStrings].
	(ScriptingSystem numericComparitorsAndHelpStrings first includes: operatorOrExpression)
		ifTrue: [self receiverType = #Number
				ifTrue: [^ ScriptingSystem numericComparitorsAndHelpStrings]
				ifFalse: [^ #(#(#= #~=) #('equal' 'not equal')) translatedNoop ]].
	^ nil! !


!VideoMorph class methodsFor: 'misc' stamp: 'KR 10/28/2007 21:53'!
resolutions
	"answer a collection of valid resolutions"
	^ #(#original #'256 colors' #'256 grays' #'4 grays' #'black and white' ) translatedNoopAll! !


!Vocabulary methodsFor: 'translation' stamp: 'KR 10/28/2007 23:16'!
translatedWordingFor: aSymbol
	"If I have a translated wording for aSymbol, return it, else return aSymbol.  Caveat: at present, this mechanism is only germane for *assignment-operator wordings*"

	#(: Incr: Decr: Mult:) with: #('' 'increase by' 'decrease by' 'multiply by') translatedNoop do:
		[:a :b | aSymbol = a ifTrue: [^ b translated]].

	^ aSymbol translated! !


!ScriptNameType methodsFor: 'tiles' stamp: 'KR 10/28/2007 22:55'!
defaultArgumentTile
	"Answer a tile to represent the type"

	| aTile  |
	aTile _ ScriptNameTile new dataType: self vocabularyName.
	aTile addArrows.
	aTile setLiteral: #emptyScript translatedNoopAll.
	^ aTile! !


!Vocabulary class methodsFor: 'class initialization' stamp: 'KR 10/28/2007 21:52'!
initializeStandardVocabularies
	"Initialize a few standard vocabularies and place them in the AllStandardVocabularies list."

	AllStandardVocabularies _ nil.

	self addStandardVocabulary: EToyVocabulary new.
	self addStandardVocabulary: EToyVectorVocabulary new.

	self addStandardVocabulary: self newPublicVocabulary.
	self addStandardVocabulary: FullVocabulary new.

	self addStandardVocabulary: self newQuadVocabulary.

	self addStandardVocabulary: ColorType new.
	self addStandardVocabulary: BooleanType new.
	self addStandardVocabulary: GraphicType new.
	self addStandardVocabulary: PlayerType new.
	self addStandardVocabulary: SoundType new.
	self addStandardVocabulary: StringType new.
	self addStandardVocabulary: MenuType new.
	self addStandardVocabulary: UnknownType new.
	self addStandardVocabulary: ScriptNameType new.
	self addStandardVocabulary: PointType new.

	self addStandardVocabulary: (SymbolListType new symbols: #(simple raised inset complexFramed complexRaised complexInset complexAltFramed complexAltRaised complexAltInset) translatedNoopAll ; vocabularyName: #BorderStyle; yourself).
	self addStandardVocabulary: (SymbolListType new symbols: #(lines arrows arrowheads dots) translatedNoopAll ; vocabularyName: #TrailStyle; yourself).
	self addStandardVocabulary: (SymbolListType new symbols: #(leftToRight rightToLeft topToBottom bottomToTop) translatedNoopAll ; vocabularyName: #ListDirection; yourself).

	self addStandardVocabulary: (SymbolListType new symbols: #(topLeft bottomRight center justified) translatedNoopAll ; vocabularyName: #ListCentering; yourself).

	self addStandardVocabulary: (SymbolListType new symbols: #(buttonDown whilePressed buttonUp) translatedNoopAll ; vocabularyName: #ButtonPhase; yourself).

	self addStandardVocabulary: (SymbolListType new symbols: #(rotate #'do not rotate' #'flip left right' #'flip up down') translatedNoopAll; vocabularyName: #RotationStyle; yourself).

	self addStandardVocabulary: (SymbolListType new symbols: #(rigid spaceFill shrinkWrap) translatedNoopAll; vocabularyName: #Resizing; yourself).

	self addStandardVocabulary: self newSystemVocabulary.  "A custom vocabulary for Smalltalk -- still under development)"

	self numberVocabulary.  		"creates and adds it"
	self wonderlandVocabulary.  	"creates and adds it"
	self vocabularyForClass: Time.   "creates and adds it"

	self addStandardVocabulary: (KedamaPatchType new vocabularyName: #Patch; yourself).
	self addStandardVocabulary: (SymbolListType new symbols: #(wrap stick bouncing) translatedNoopAll; vocabularyName: #EdgeMode; yourself).
	self addStandardVocabulary: (SymbolListType new symbols: #(logScale linear color) translatedNoopAll; vocabularyName: #PatchDisplayMode; yourself).

	"Vocabulary initialize"! !

-------------- next part --------------
'From etoys2.2 of 22 September 2007 [latest update: #1731] on 30 October 2007 at 12:21:40 am'!
"Change Set:		SymListWOCamel-KR
Date:			30 October 2007
Author:			Korakurider

SymbolListTile show options and readout as no camel case. 
The no-camel words will be used for translation key.
"!


!UpdatingStringMorph methodsFor: 'target access' stamp: 'KR 10/29/2007 19:06'!
acceptValueFromTarget: v
	"Accept a value from the target"

	lastValue _ v.
	self format == #string ifTrue: [^ v asString].
	self format == #symbol ifTrue: [^ v asString fromCamelCase translated].
	(format == #default and: [v isNumber]) ifTrue:
		[^ self stringForNumericValue: v].
	^ v printString translated! !


!Vocabulary methodsFor: 'translation' stamp: 'KR 10/29/2007 19:01'!
translatedWordingFor: aSymbol
	"If I have a translated wording for aSymbol, return it, else return aSymbol.  Caveat: at present, this mechanism is only germane for *assignment-operator wordings*"

	#(: Incr: Decr: Mult:) with: #('' 'increase by' 'decrease by' 'multiply by') do:
		[:a :b | aSymbol = a ifTrue: [^ b translated]].

	^ aSymbol fromCamelCase translated! !



More information about the etoys-dev mailing list