[Pkg] The Trunk: Multilingual-nice.168.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Sep 4 20:20:49 UTC 2013


Nicolas Cellier uploaded a new version of Multilingual to project The Trunk:
http://source.squeak.org/trunk/Multilingual-nice.168.mcz

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

Name: Multilingual-nice.168
Author: nice
Time: 4 September 2013, 10:19:27.305 pm
UUID: f359e589-1b80-460d-a9c1-876436a0e056
Ancestors: Multilingual-tpr.167

1) avoid 'a litral string' asSymbol, #'a literal symbol' is the syntax.
2) Transform this construct into something not less understandable:
    [ doSomeLoop.
	testStopCondition ifTrue: [^something] ] repeat
=>
    [ doSomeLoop.
	testStopCondition ] whileFalse.

	^something

=============== Diff against Multilingual-tpr.167 ===============

Item was changed:
  ----- Method: EFontBDFFontReader>>readFrom:to: (in category 'as yet unclassified') -----
  readFrom: start to: end
  
  	| xTable glyphs ascent descent chars charsNum height form blt lastAscii pointSize ret lastValue encoding bbx strikeWidth minAscii maxAscii maxWidth |
  	form := encoding := bbx := nil.
  	self initialize.
  	self readAttributes.
  	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
+ 	ascent := Integer readFromString: (properties at: #'FONT_ASCENT')  first.
+ 	descent := Integer readFromString: (properties at: #'FONT_DESCENT') first.
+ 	(properties includesKey: #'POINT_SIZE') ifTrue: [
+ 		pointSize := (Integer readFromString: (properties at: #'POINT_SIZE') first) // 10.
- 	ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
- 	descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
- 	(properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [
- 		pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
  	] ifFalse: [
  		pointSize := (ascent + descent) * 72 // 96.
  	].
  		
  	
  	maxWidth := 0.
  	minAscii := 16r200000.
  	strikeWidth := 0.
  	maxAscii := 0.
  
  	charsNum := Integer readFromString: (properties at: #CHARS) first.
  	chars := Set new: charsNum.
  
  	self readCharactersInRangeFrom: start to: end totalNums: charsNum storeInto: chars.
  
  	chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
  	charsNum := chars size. "undefined encodings make this different"
  
  	chars do: [:array | | width |
  		encoding := array at: 2.
  		bbx := array at: 3..
  		width := bbx at: 1.
  		maxWidth := maxWidth max: width.
  		minAscii := minAscii min: encoding.
  		maxAscii := maxAscii max: encoding.
  		strikeWidth := strikeWidth + width.
  	].
  	glyphs := Form extent: strikeWidth at height.
  	blt := BitBlt toForm: glyphs.
  	"xTable := XTableForUnicodeFont new ranges: (Array with: (Array with: start with: end))."
  	xTable := SparseLargeTable new: end + 3 chunkSize: 32 arrayClass: Array base: start + 1 defaultValue: -1.
  	lastAscii := start.	
  	1 to: charsNum do: [:i |
  		form := (chars at: i) first.
  		encoding := (chars at: i) second.
  		bbx := (chars at: i) third.
  		"lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]."
  		lastValue := xTable at: lastAscii + 1 + 1.
  		xTable at: encoding + 1 put: lastValue.
  		blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4)))
  				extent: (bbx at: 1)@(bbx at: 2))
  			from: 0 at 0 in: form.
  		xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1).
  		lastAscii := encoding.
  	].
  
  	xTable zapDefaultOnlyEntries.
  	ret := Array new: 8.
  	ret at: 1 put: xTable.
  	ret at: 2 put: glyphs.
  	ret at: 3 put: minAscii.
  	ret at: 4 put: maxAscii.
  	ret at: 5 put: maxWidth.
  	ret at: 6 put: ascent.
  	ret at: 7 put: descent.
  	ret at: 8 put: pointSize.
  	^ret.
  " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"
  !

Item was changed:
  ----- Method: EFontBDFFontReaderForRanges>>readRanges: (in category 'as yet unclassified') -----
  readRanges: ranges
  
  	| xTable glyphs ascent descent chars charsNum height form blt lastAscii pointSize ret lastValue start end encoding bbx strikeWidth minAscii maxAscii maxWidth |
  	form := encoding := bbx := nil.
  	self initialize.
  	self readAttributes.
  	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
+ 	ascent := Integer readFromString: (properties at: #'FONT_ASCENT') first.
+ 	descent := Integer readFromString: (properties at: #'FONT_DESCENT') first.
+ 	(properties includesKey: #'POINT_SIZE') ifTrue: [
+ 		pointSize := (Integer readFromString: (properties at: #'POINT_SIZE') first) // 10.
- 	ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
- 	descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
- 	(properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [
- 		pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
  	] ifFalse: [
  		pointSize := (ascent + descent) * 72 // 96.
  	].
  
  	maxWidth := 0.
  	minAscii := 16r200000.
  	strikeWidth := 0.
  	maxAscii := 0.
  
  	charsNum := Integer readFromString: (properties at: #CHARS) first.
  	chars := Set new: charsNum.
  
  	self readCharactersInRanges: ranges storeInto: chars.
  
  	chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
  	charsNum := chars size. "undefined encodings make this different"
  
  	chars do: [:array | | width |
  		encoding := array at: 2.
  		bbx := array at: 3..
  		width := bbx at: 1.
  		maxWidth := maxWidth max: width.
  		minAscii := minAscii min: encoding.
  		maxAscii := maxAscii max: encoding.
  		strikeWidth := strikeWidth + width.
  	].
  
  	glyphs := Form extent: strikeWidth at height.
  	blt := BitBlt toForm: glyphs.
  	start := (ranges collect: [:r | r first]) min.
  	end := (ranges collect: [:r | r second]) max + 3.
  
  	xTable := SparseLargeTable new: end chunkSize: 64 arrayClass: Array base: start +1 defaultValue: -1.
  	lastAscii := start.
  	xTable at: lastAscii + 2 put: 0.
  	1 to: charsNum do: [:i |
  		form := (chars at: i) first.
  		encoding := (chars at: i) second.
  		bbx := (chars at: i) third.
  		"lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]."
  		lastValue := xTable at: lastAscii + 1 + 1.
  		xTable at: encoding + 1 put: lastValue.
  		blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4)))
  				extent: (bbx at: 1)@(bbx at: 2))
  			from: 0 at 0 in: form.
  		xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1).
  		lastAscii := encoding.
  	].
  	xTable at: xTable size put: (xTable at: xTable size - 1).
  	xTable zapDefaultOnlyEntries.
  	ret := Array new: 8.
  	ret at: 1 put: xTable.
  	ret at: 2 put: glyphs.
  	ret at: 3 put: minAscii.
  	ret at: 4 put: maxAscii.
  	ret at: 5 put: maxWidth.
  	ret at: 6 put: ascent.
  	ret at: 7 put: descent.
  	ret at: 8 put: pointSize.
  	^ret.
  " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"
  !

Item was changed:
  ----- Method: EFontBDFFontReaderForRanges>>readRanges:overrideWith:otherRanges:additionalOverrideRange: (in category 'as yet unclassified') -----
  readRanges: ranges overrideWith: otherFileName otherRanges: otherRanges additionalOverrideRange: additionalRange
  
  	| xTable glyphs ascent descent chars charsNum height form blt lastAscii pointSize ret lastValue start end encoding bbx strikeWidth minAscii maxAscii maxWidth |
  	form := encoding := bbx := nil.
  	self initialize.
  	self readAttributes.
  	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
+ 	ascent := Integer readFromString: (properties at: #'FONT_ASCENT') first.
+ 	descent := Integer readFromString: (properties at: #'FONT_DESCENT') first.
+ 	(properties includesKey: #'POINT_SIZE') ifTrue: [
+ 		pointSize := (Integer readFromString: (properties at: #'POINT_SIZE') first) // 10.
- 	ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first.
- 	descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first.
- 	(properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [
- 		pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10.
  	] ifFalse: [
  		pointSize := (ascent + descent) * 72 // 96.
  	].
  		
  	
  	maxWidth := 0.
  	minAscii := 16r200000.
  	strikeWidth := 0.
  	maxAscii := 0.
  
  	charsNum := Integer readFromString: (properties at: #CHARS) first.
  	chars := Set new: charsNum.
  
  	self readCharactersInRanges: ranges storeInto: chars.
  	chars := self override: chars with: otherFileName ranges: otherRanges transcodingTable: (UCSTable jisx0208Table) additionalRange: additionalRange.
  
  	chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)].
  	charsNum := chars size. "undefined encodings make this different"
  	
  	chars do: [:array | | width |
  		encoding := array at: 2.
  		bbx := array at: 3..
  		width := bbx at: 1.
  		maxWidth := maxWidth max: width.
  		minAscii := minAscii min: encoding.
  		maxAscii := maxAscii max: encoding.
  		strikeWidth := strikeWidth + width.
  	].
  
  	glyphs := Form extent: strikeWidth at height.
  	blt := BitBlt toForm: glyphs.
  	start := ((ranges collect: [:r | r first]), (additionalRange collect: [:r2 | r2 first])) min.
  	end := ((ranges collect: [:r | r second]), (additionalRange collect: [:r2 | r2 second])) max + 3.
  	"xRange := Array with: (Array with: ((ranges collect: [:r | r first]), (additionalRange collect: [:r2 | r2 first])) min
  						with: (((ranges collect: [:r | r second]), (additionalRange collect: [:r2 | r2 second])) max + 2))."
  	"xTable := XTableForUnicodeFont new
  		ranges: xRange."
  	xTable := SparseLargeTable new: end chunkSize: 64 arrayClass: Array base: start defaultValue: -1.
  	lastAscii := start.
  	xTable at: lastAscii + 2 put: 0.
  	1 to: charsNum do: [:i |
  		form := (chars at: i) first.
  		encoding := (chars at: i) second.
  		bbx := (chars at: i) third.
  		"lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]."
  		lastValue := xTable at: lastAscii + 1 + 1.
  		xTable at: encoding + 1 put: lastValue.
  		blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4)))
  				extent: (bbx at: 1)@(bbx at: 2))
  			from: 0 at 0 in: form.
  		xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1).
  		lastAscii := encoding.
  	].
  	xTable at: xTable size put: (xTable at: xTable size - 1).
  	xTable zapDefaultOnlyEntries.
  	ret := Array new: 8.
  	ret at: 1 put: xTable.
  	ret at: 2 put: glyphs.
  	ret at: 3 put: minAscii.
  	ret at: 4 put: maxAscii.
  	ret at: 5 put: maxWidth.
  	ret at: 6 put: ascent.
  	ret at: 7 put: descent.
  	ret at: 8 put: pointSize.
  	^ret.
  " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"
  !

Item was changed:
  ----- Method: MultiCharacterBlockScanner>>characterBlockAtPoint:index:in: (in category 'scanning') -----
  characterBlockAtPoint: aPoint index: index in: textLine
  	"This method is the Morphic characterBlock finder.  It combines
  	MVC's characterBlockAtPoint:, -ForIndex:, and buildCharcterBlock:in:"
  	| runLength lineStop stopCondition |
  	line := textLine.
  	rightMargin := line rightMargin.
  	lastIndex := line first.
  	self setStopConditions.		"also sets font"
  	characterIndex := index.  " == nil means scanning for point"
  	characterPoint := aPoint.
  	(characterPoint isNil or: [characterPoint y > line bottom])
  		ifTrue: [characterPoint := line bottomRight].
  	(text isEmpty or: [(characterPoint y < line top or: [characterPoint x < line left])
  				or: [characterIndex notNil and: [characterIndex < line first]]])
  		ifTrue:	[^ (CharacterBlock new stringIndex: line first text: text
  					topLeft: line leftMargin at line top extent: 0 @ textStyle lineGrid)
  					textLine: line].
  	destX := leftMargin := line leftMarginForAlignment: alignment.
  	destY := line top.
  	runLength := text runLengthFor: line first.
  	characterIndex
  		ifNotNil:	[lineStop := characterIndex  "scanning for index"]
  		ifNil:	[lineStop := line last  "scanning for point"].
  	runStopIndex := lastIndex + (runLength - 1) min: lineStop.
  	lastCharacterExtent := 0 @ line lineHeight.
  	spaceCount := 0.
  
  	[stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  		in: text string rightX: characterPoint x
  		stopConditions: stopConditions kern: kern.
  	"see setStopConditions for stopping conditions for character block 	operations."
  	self lastCharacterExtentSetX: (specialWidth
  		ifNil: [font widthOf: (text at: lastIndex)]
  		ifNotNil: [specialWidth]).
+ 	self perform: stopCondition] whileFalse.
+ 	
+ 	characterIndex
- 	(self perform: stopCondition) ifTrue:
- 		[characterIndex
  			ifNil: [
  				"Result for characterBlockAtPoint: "
  				(stopCondition ~~ #cr and: [ lastIndex == line last
  					and: [ aPoint x > ((characterPoint x) + (lastCharacterExtent x / 2)) ]])
  						ifTrue: [ "Correct for right half of last character in line"
  							^ (CharacterBlock new stringIndex: lastIndex + 1
  									text: text
  									topLeft: characterPoint + (lastCharacterExtent x @ 0) + (font descentKern @ 0)
  									extent:  0 @ lastCharacterExtent y)
  								textLine: line ].
  					^ (CharacterBlock new stringIndex: lastIndex
  						text: text topLeft: characterPoint + (font descentKern @ 0)
  						extent: lastCharacterExtent - (font baseKern @ 0))
  								textLine: line]
  			ifNotNil: ["Result for characterBlockForIndex: "
  					^ (CharacterBlock new stringIndex: characterIndex
  						text: text topLeft: characterPoint + ((font descentKern) - kern @ 0)
  						extent: lastCharacterExtent)
+ 								textLine: line]!
- 								textLine: line]]] repeat!

Item was changed:
  ----- Method: MultiCompositionScanner>>composeLine:fromCharacterIndex:inParagraph: (in category 'scanning') -----
  composeLine: lineIndex fromCharacterIndex: startIndex inParagraph: aParagraph 
  	"Answer an instance of TextLineInterval that represents the next line in the paragraph."
  	| runLength stopCondition |
  	destX := spaceX := leftMargin := aParagraph leftMarginForCompositionForLine: lineIndex.
  	destY := 0.
  	rightMargin := aParagraph rightMarginForComposition.
  	leftMargin >= rightMargin ifTrue: [self error: 'No room between margins to compose'].
  	lastIndex := startIndex.	"scanning sets last index"
  	lineHeight := textStyle lineGrid.  "may be increased by setFont:..."
  	baseline := textStyle baseline.
  	baselineY := destY + baseline.
  	self setStopConditions.	"also sets font"
  	self handleIndentation.
  	runLength := text runLengthFor: startIndex.
  	runStopIndex := (lastIndex := startIndex) + (runLength - 1).
  	line := TextLineInterval
  		start: lastIndex
  		stop: 0
  		internalSpaces: 0
  		paddingWidth: 0.
  	presentationLine := TextLineInterval
  		start: lastIndex
  		stop: 0
  		internalSpaces: 0
  		paddingWidth: 0.
  	numOfComposition := 0.
  	presentation := TextStream on: (Text fromString: (WideString new: text size)).
  	spaceCount := 0.
  	
  	[stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  		in: text string rightX: rightMargin stopConditions: stopConditions
  		kern: kern.
  	"See setStopConditions for stopping conditions for composing."
+ 	self perform: stopCondition] whileFalse.
+ 
+ 	presentationLine
+ 		lineHeight: lineHeight + textStyle leading
+ 		baseline: baseline + textStyle leading.
+ 	^line
+ 		lineHeight: lineHeight + textStyle leading
+ 		baseline: baseline + textStyle leading!
- 	(self perform: stopCondition)
- 		ifTrue: [presentationLine lineHeight: lineHeight + textStyle leading
- 					baseline: baseline + textStyle leading.
- 				^line lineHeight: lineHeight + textStyle leading
- 					baseline: baseline + textStyle leading]] repeat!



More information about the Packages mailing list