[squeak-dev] The Trunk: EToys-nice.343.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jun 11 09:09:47 UTC 2019


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

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

Name: EToys-nice.343
Author: nice
Time: 11 June 2019, 11:08:46.028371 am
UUID: 31d65fd7-f312-e74b-b70f-7c2ef66d97b6
Ancestors: EToys-cmm.342

1) Classify Etoys specific font reading methods back to Etoys.
    We can either move all the methods to Multilingual, or none, but not some...

2) Stop sending squeakToIso and isoToSqueak which are no longer needed at least since 2005.

=============== Diff against EToys-cmm.342 ===============

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForSimplifiedChinese (in category '*Etoys-Squeakland-font reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForSimplifiedChinese (in category '*Etoys-Squeakland-as yet unclassified') -----
  additionalRangesForSimplifiedChinese
  
  	| basics |
  	basics := {
  		{16rFF00. 16rFF60}
  }.
  	^ basics
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>override2:with:ranges:transcodingTable:additionalRange: (in category '*Etoys-Squeakland-font reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>override2:with:ranges:transcodingTable:additionalRange: (in category '*Etoys-Squeakland-as yet unclassified') -----
  override2: chars with: otherFileName ranges: pairArray transcodingTable: table additionalRange: additionalRanges
  
  	| other newChars form u j in newArray |
  	other := BDFFontReader readOnlyFileNamed: otherFileName.
  
  	newChars := PluggableSet new.
  	newChars hashBlock: [:elem | (elem at: 2) hash].
  	newChars equalBlock: [:a :b | (a at: 2) = (b at: 2)].
  
  	other readChars do: [:array | 
  		j := array at: 2.
  		u := table at: (((j // 256) - 33 * 94 + ((j \\ 256) - 33)) + 1).
  		u ~= -1 ifTrue: [
  			u hex printString displayAt: 0 at 0.
  			in := false.
  			pairArray do: [:pair |
  				(u between: pair first and: pair second) ifTrue: [
  					in := true
  				]
  			].
  			in ifTrue: [
  				form := array at: 1.
  				form ifNotNil: [
  					newArray := array shallowCopy.
  					newArray at: 2 put: u.
  					newChars add: newArray.
  				].
  			].
  		].
  	].
  
  	newChars addAll: chars.
  	^ newChars.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>rangesForSimplifiedChinese (in category '*Etoys-Squeakland-font reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>rangesForSimplifiedChinese (in category '*Etoys-Squeakland-as yet unclassified') -----
  rangesForSimplifiedChinese
  
  	| basics etc |
  	basics := {
  		Array with: 16rA1 with: 16rFF
  	}.
  	etc := {
  		Array with: 16r100 with: 16r17F. "extended latin"
  		Array with: 16r370 with: 16r3FF. "greek"
  		Array with: 16r400 with: 16r52F. "cyrillic"
  		Array with: 16r2000 with: 16r206F. "general punctuation"
  		Array with: 16r2100 with: 16r214F. "letterlike"
  		Array with: 16r2150 with: 16r218F. "number form"
  		Array with: 16r2190 with: 16r21FF. "arrows"
  		Array with: 16r2200 with: 16r22FF. "math operators"
  		Array with: 16r2300 with: 16r23FF. "misc tech"
  		Array with: 16r2460 with: 16r24FF. "enclosed alnum"
  		Array with: 16r2500 with: 16r257F. "box drawing"
  		Array with: 16r2580 with: 16r259F. "box elem"
  		Array with: 16r25A0 with: 16r25FF. "geometric shapes"
  		Array with: 16r2600 with: 16r26FF. "misc symbols"
  		Array with: 16r3000 with: 16r303F. "cjk symbols"
  		Array with: 16r3040 with: 16r309F. "hiragana"
  		Array with: 16r30A0 with: 16r30FF. "katakana"
  		Array with: 16r3190 with: 16r319F. "kanbun"
  		Array with: 16r31F0 with: 16r31FF. "katakana extension"
  		Array with: 16r3200 with: 16r32FF. "enclosed CJK"
  		Array with: 16r3300 with: 16r33FF. "CJK compatibility"
  		Array with: 16r4E00 with: 16r9FAF. "CJK ideograph"
  		Array with: 16rAC00 with: 16rD7AF. "Hangul Syllables"
  		Array with: 16rF900 with: 16rFAFF. "CJK compatiblity ideograph"
  		Array with: 16rFF00 with: 16rFFEF. "half and full"
  	}.
  
  	^ basics, etc.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>readCharactersInRanges2:storeInto: (in category '*Etoys-Squeakland-font reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>readCharactersInRanges2:storeInto: (in category '*Etoys-Squeakland-as yet unclassified') -----
  readCharactersInRanges2: ranges storeInto: chars
  
  	| array form code rangeStream in |
  	rangeStream := ReadStream on: ranges.
  	[true] whileTrue: [
  		array := self readOneCharacter.
  		array second ifNil: [^ self].
  		code := array at: 2.
  		in := false.
  		ranges do: [:range |
  			(code between: range first and: range last) ifTrue: [
  				in := true.
  			].
  		].
  		in ifTrue: [
  			form := array at: 1.
  			form ifNotNil: [
  				chars add: array.
  			].
  		].
  	].
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>readRangesForSimplifiedChinese:overrideWith:otherRanges:additionalOverrideRange: (in category '*Etoys-Squeakland-font reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>readRangesForSimplifiedChinese:overrideWith:otherRanges:additionalOverrideRange: (in category '*Etoys-Squeakland-as yet unclassified') -----
  readRangesForSimplifiedChinese: ranges overrideWith: otherFileName otherRanges: otherRanges additionalOverrideRange: additionalRange
  
  	| xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx width blt lastAscii pointSize ret lastValue start end |
  	form := encoding := bbx := nil.
  	self initialize.
  	self readAttributes.
  	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
  	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 readCharactersInRanges2: ranges storeInto: chars.
  	chars := self override2: chars with: otherFileName ranges: otherRanges transcodingTable: (UCSTable jisx0208Table) additionalRange: additionalRange.
  
  	chars := chars sorted: [:x :y | (x at: 2) <= (y at: 2)].
  	charsNum := chars size. "undefined encodings make this different"
  	
  	chars do: [:array |
  		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: String>>replaceHtmlCharRefs (in category '*Etoys-internet') -----
  replaceHtmlCharRefs
  
          | pos ampIndex scIndex special specialValue outString outPos newOutPos |
  
          outString := String new: self size.
          outPos := 0.
  
          pos := 1.
          
          [ pos <= self size ] whileTrue: [ 
                  "read up to the next ampersand"
                  ampIndex := self indexOf: $& startingAt: pos ifAbsent: [0].
                  
                  ampIndex = 0 ifTrue: [
                          pos = 1 ifTrue: [ ^self ] ifFalse: [ ampIndex := self size+1 ] ].
  
                  newOutPos := outPos + ampIndex - pos.
                  outString
                          replaceFrom: outPos + 1
                          to: newOutPos
                          with: self
                          startingAt: pos.
                  outPos := newOutPos.
                  pos := ampIndex.
  
                  ampIndex <= self size ifTrue: [
                          "find the $;"
                          scIndex := self indexOf: $; startingAt: ampIndex ifAbsent: [ self size + 1 ].
  
                          special := self copyFrom: ampIndex+1 to: scIndex-1.       
                          specialValue := HtmlEntity valueOfHtmlEntity: special. 
  
                          specialValue
                                  ifNil: [
                                          "not a recognized entity.  wite it back"
  								  scIndex > self size ifTrue: [ scIndex := self size ].
  
                                          newOutPos := outPos + scIndex - ampIndex + 1.
                                          outString
                                                  replaceFrom: outPos+1
                                                  to: newOutPos
                                                  with: self
                                                  startingAt: ampIndex.
                                          outPos := newOutPos.]
                                  ifNotNil: [
                                          outPos := outPos + 1.
+                                         outString at: outPos put: specialValue].
-                                         outString at: outPos put: specialValue isoToSqueak.].
                          
                          pos := scIndex + 1. ]. ].
  
  
          ^outString copyFrom: 1 to: outPos!

Item was changed:
  ----- Method: UTF32CNInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf 
  	| keyValue |
  	keyValue := evtBuf at: 6.
  	keyValue < 256
+ 		ifTrue: [^Character value: keyValue].
- 		ifTrue: [^ (Character value: keyValue) squeakToIso].
  	^ Character leadingChar: SimplifiedChineseEnvironment leadingChar code: keyValue!

Item was changed:
  ----- Method: UTF32GreekInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf 
  	| keyValue |
  	keyValue := evtBuf at: 6.
  	keyValue < 256
+ 		ifTrue: [^Character value: keyValue].
- 		ifTrue: [^ (Character value: keyValue) squeakToIso].
  	^ Character leadingChar: GreekEnvironment leadingChar code: keyValue!

Item was changed:
  ----- Method: UTF32NPInputInterpreter>>nextCharFrom:firstEvt: (in category 'all') -----
  nextCharFrom: sensor firstEvt: evtBuf 
  	| keyValue |
  	keyValue := evtBuf at: 6.
  	keyValue < 256
+ 		ifTrue: [^Character value: keyValue].
- 		ifTrue: [^ (Character value: keyValue) squeakToIso].
  	^ Character leadingChar: NepaleseEnvironment leadingChar code: keyValue!



More information about the Squeak-dev mailing list