[squeak-dev] The Trunk: Multilingual-pre.242.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 6 19:22:29 UTC 2018


Patrick Rein uploaded a new version of Multilingual to project The Trunk:
http://source.squeak.org/trunk/Multilingual-pre.242.mcz

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

Name: Multilingual-pre.242
Author: pre
Time: 6 December 2018, 8:22:23.246566 pm
UUID: 9725107c-37e5-7648-b92a-69cd64ef2a9f
Ancestors: Multilingual-pre.241

In the spirit of a more approachable Squeak this commit classifies all unclassified methods in Multilingual and re-categorizes some misplaced methods. There are also two tiny refactorings in this commit.

=============== Diff against Multilingual-pre.241 ===============

Item was changed:
+ ----- Method: CP1250ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: CP1250ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	| result converter |
  	result := WriteStream on: (String new: aString size).
  	converter := CP1250TextConverter new.
  	aString do: [:each |
  		result nextPut: (converter toSqueak: each macToSqueak) asCharacter.
  	].
  	^ result contents.
  !

Item was changed:
+ ----- Method: CP1250ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: CP1250ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  
  	| result converter |
  	aString isAsciiString ifTrue: [^ aString asOctetString]. "optimization"
  
  	result := WriteStream on: (String new: aString size).
  	converter := CP1250TextConverter new.
  	aString do: [:each |
  		| r |
  		r := converter fromSqueak: each.
  		r charCode < 255 ifTrue: [
  		result nextPut: r squeakToMac]].
  	^ result contents.
  !

Item was changed:
+ ----- Method: CP1250InputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: CP1250InputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := CP1250TextConverter new.
  !

Item was changed:
+ ----- Method: CP1250InputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: CP1250InputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	"Input from the Czech keyboard under Windows doesn't correspond to cp-1250 or iso-8859-2 encoding!!"
  
  	| keyValue |
  
  	keyValue := evtBuf third.
  	^ converter toSqueak: keyValue asCharacter macToSqueak.
  
  !

Item was changed:
+ ----- Method: ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	self subclassResponsibility.
  !

Item was changed:
+ ----- Method: ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  
  	self subclassResponsibility.
  !

Item was changed:
+ ----- Method: EFontBDFFontReader>>readCharactersInRangeFrom:to:totalNums:storeInto: (in category 'reading') -----
- ----- Method: EFontBDFFontReader>>readCharactersInRangeFrom:to:totalNums:storeInto: (in category 'as yet unclassified') -----
  readCharactersInRangeFrom: start to: stop totalNums: upToNum storeInto: chars
  
  	| array form code |
  	1 to: upToNum do: [:i |
  		array := self readOneCharacter.
  		code := array at: 2.
  		code > stop ifTrue: [^ self].
  		(code between: start and: stop) ifTrue: [
  			form := array at: 1.
  			form ifNotNil: [
  				chars add: array.
  			].
  		].
  	].
  !

Item was changed:
+ ----- Method: EFontBDFFontReader>>readFrom:to: (in category 'reading') -----
- ----- 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.
  	] 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 sorted: [: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 class>>rangesForGreek (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges class>>rangesForGreek (in category 'as yet unclassified') -----
  rangesForGreek
  
  	^ {
  		Array with: 16r1 with: 16rFF.
  		Array with: 16r370 with: 16r3FF.
  		Array with: 16r1F00 with: 16r1FFF.
  		Array with: 16r2000 with: 16r206F.
  		Array with: 16r20A0 with: 16r20AF
  	}.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges class>>rangesForLatin2 (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges class>>rangesForLatin2 (in category 'as yet unclassified') -----
  rangesForLatin2
  
  	^ {
  		Array with: 0 with: 16r17F.
  		Array with: 16r2B0 with: 16r2FF.
  		Array with: 16r2000 with: 16r206F.
  		Array with: 16r2122 with: 16r2122.
  		Array with: 16rFFFF with: 16rFFFF. "sentinel"
  	}.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForJapanese (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForJapanese (in category 'as yet unclassified') -----
  additionalRangesForJapanese
  
  	| basics |
  	basics := {
  		Array with: 16r5C with: 16rFF3C.
  		Array with: 16r3013 with: 16rFFFD.
  	}.
  	^ basics
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForKorean (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>additionalRangesForKorean (in category 'as yet unclassified') -----
  additionalRangesForKorean
  
  	| basics |
  	basics := {
  		Array with: 16rA1 with: 16rFFE6C.
  		Array with: 16r3000 with: 16rFFFD.
  	}.
  	^ basics
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>override:with:ranges:transcodingTable:additionalRange: (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>override:with:ranges:transcodingTable:additionalRange: (in category 'as yet unclassified') -----
  override: chars with: otherFileName ranges: pairArray transcodingTable: table additionalRange: additionalRange
  
  	| other rangeStream newChars currentRange |
  	other := BDFFontReader openFileNamed: otherFileName.
  
  	rangeStream := ReadStream on: pairArray.
  	currentRange := rangeStream next.
  
  	newChars := PluggableSet new.
  	newChars hashBlock: [:elem | (elem at: 2) hash].
  	newChars equalBlock: [:a :b | (a at: 2) = (b at: 2)].
  
  	other readChars do: [:array | | code u j form | 
  		code := array at: 2.
  		"code printStringHex printString displayAt: 0 at 0."
  		code > currentRange last ifTrue: [
  			[rangeStream atEnd not and: [currentRange := rangeStream next. currentRange last < code]] whileTrue.
  			rangeStream atEnd ifTrue: [
  				newChars addAll: chars.
  				^ newChars.
  			].
  		].
  		(code between: currentRange first and: currentRange last) ifTrue: [
  			form := array at: 1.
  			form ifNotNil: [
  				j := array at: 2.
  				u := table at: (((j // 256) - 33 * 94 + ((j \\ 256) - 33)) + 1).
  				u ~= -1 ifTrue: [
  					array at: 2 put: u.
  					newChars add: array.
  					additionalRange do: [:e | | newArray |
  						e first = (array at: 2) ifTrue: [
  							newArray := array shallowCopy.
  							newArray at: 2 put: e second.
  							newChars add: newArray
  						].
  					]
  				].
  			].
  		].
  	].
  
  	self error: 'should not reach here'.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>rangesForGreek (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>rangesForGreek (in category 'as yet unclassified') -----
  rangesForGreek
  
+ 	^ self class rangesForGreek
- 	^ {
- 		Array with: 16r1 with: 16rFF.
- 		Array with: 16r370 with: 16r3FF.
- 		Array with: 16r1F00 with: 16r1FFF.
- 		Array with: 16r2000 with: 16r206F.
- 		Array with: 16r20A0 with: 16r20AF
- 	}.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>rangesForJapanese (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>rangesForJapanese (in category 'as yet unclassified') -----
  rangesForJapanese
  
  	| basics etc |
  	basics := {
  		Array with: 16r5C with: 16r5C.
  		Array with: 16rA2 with: 16rA3.
  		Array with: 16rA7 with: 16rA8.
  		Array with: 16rAC with: 16rAC.
  		Array with: 16rB0 with: 16rB1.
  		Array with: 16rB4 with: 16rB4.
  		Array with: 16rB6 with: 16rB6.
  		Array with: 16rD7 with: 16rD7.
  		Array with: 16rF7 with: 16rF7
  	}.
  	etc := {
  		Array with: 16r370 with: 16r3FF. "greek"
  		Array with: 16r400 with: 16r52F. "cyrillic"
  		Array with: 16r1D00 with: 16r1D7F. "phonetic"
  		Array with: 16r1E00 with: 16r1EFF. "latin extended additional"
  		Array with: 16r2000 with: 16r206F. "general punctuation"
  		Array with: 16r20A0 with: 16r20CF. "currency symbols"
  		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: 16r2700 with: 16r27BF. "dingbats"
  		Array with: 16r27C0 with: 16r27EF. "misc math A"
  		Array with: 16r27F0 with: 16r27FF. "supplimental arrow A"
  		Array with: 16r2900 with: 16r297F. "supplimental arrow B"
  		Array with: 16r2980 with: 16r29FF. "misc math B"
  		Array with: 16r2A00 with: 16r2AFF. "supplimental math op"
  		Array with: 16r2900 with: 16r297F. "supplimental arrow B"
  		Array with: 16r2E80 with: 16r2EFF. "cjk radicals suppliment"
  		Array with: 16r2F00 with: 16r2FDF. "kangxi radicals"
  		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: 16r3400 with: 16r4DBF. "CJK unified extension A"
  		Array with: 16r4E00 with: 16r9FAF. "CJK ideograph"
  		Array with: 16rF900 with: 16rFAFF. "CJK compatiblity ideograph"
  		Array with: 16rFE30 with: 16rFE4F. "CJK compatiblity forms"
  		Array with: 16rFF00 with: 16rFFEF. "half and full"
  		Array with: 16rFFFF with: 16rFFFF. "sentinel"
  	}.
  
  	^ basics, etc.
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>rangesForKorean (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>rangesForKorean (in category 'as yet unclassified') -----
  rangesForKorean
  
  	| 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>>rangesForLatin2 (in category 'ranges') -----
- ----- Method: EFontBDFFontReaderForRanges>>rangesForLatin2 (in category 'as yet unclassified') -----
  rangesForLatin2
  
  	^ {
  		Array with: 0 with: 16r17F.
  		Array with: 16r2B0 with: 16r2FF.
  		Array with: 16r2000 with: 16r206F.
  		Array with: 16r2122 with: 16r2122.
  		Array with: 16rFFFF with: 16rFFFF. "sentinel"
  	}.
  !

Item was added:
+ ----- Method: EFontBDFFontReaderForRanges>>readCharactersInRanges2:storeInto: (in category 'reading') -----
+ 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>>readCharactersInRanges:storeInto: (in category 'reading') -----
- ----- Method: EFontBDFFontReaderForRanges>>readCharactersInRanges:storeInto: (in category 'as yet unclassified') -----
  readCharactersInRanges: ranges storeInto: chars
  
  	| array form code rangeStream currentRange |
  	rangeStream := ReadStream on: ranges.
  	currentRange := rangeStream next.
  	[
  		array := self readOneCharacter.
  		array second ifNil: [^ self].
  		code := array at: 2.
  		code > currentRange last ifTrue: [
  			[rangeStream atEnd not and: [currentRange := rangeStream next. currentRange last < code]] whileTrue.
  			rangeStream atEnd ifTrue: [^ self].
  		].
  		(code between: currentRange first and: currentRange last) ifTrue: [
  			form := array at: 1.
  			form ifNotNil: [
  				chars add: array.
  			].
  		].
  	] repeat
  !

Item was changed:
+ ----- Method: EFontBDFFontReaderForRanges>>readRanges: (in category 'reading') -----
- ----- 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.
  	] 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 sorted: [: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 'reading') -----
- ----- 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.
  	] 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 sorted: [: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 added:
+ ----- Method: EFontBDFFontReaderForRanges>>readRangesForSimplifiedChinese:overrideWith:otherRanges:additionalOverrideRange: (in category 'reading') -----
+ 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: ISO88592ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: ISO88592ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString convertFromWithConverter: ISO88592TextConverter new.
  !

Item was changed:
+ ----- Method: ISO88592ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: ISO88592ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  
  	| result converter |
  
  	aString isAsciiString ifTrue: [^ aString asOctetString]. "optimization"
  
  	result := WriteStream on: (String new: aString size).
  	converter := ISO88592TextConverter new.
  	aString do: [:each | | r |
  		r := converter fromSqueak: each.].
  	^ result contents.
  !

Item was changed:
+ ----- Method: ISO88592InputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: ISO88592InputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := ISO88592TextConverter new.
  !

Item was changed:
+ ----- Method: ISO88592InputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: ISO88592InputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| keyValue |
  	keyValue := evtBuf third.
  	^ converter toSqueak: keyValue asCharacter.
  !

Item was changed:
+ ----- Method: InvalidUTF8>>isResumable (in category 'priv handling') -----
- ----- Method: InvalidUTF8>>isResumable (in category 'private') -----
  isResumable
  	^true!

Item was changed:
+ ----- Method: InvalidUTF8>>messageText (in category 'printing') -----
- ----- Method: InvalidUTF8>>messageText (in category 'private') -----
  messageText
  	"Return a textual description of the exception."
  	^messageText ifNil: [string
  		ifNil: ['Invalid UTF8']
  		ifNotNil: ['Invalid utf8: ', string]]!

Item was changed:
+ ----- Method: KeyboardInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: KeyboardInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
- 
- 
  	self subclassResponsibility.
  
  !

Item was changed:
+ ----- Method: KoreanEnvironment class>>clipboardInterpreterClass (in category 'subclass responsibilities') -----
- ----- Method: KoreanEnvironment class>>clipboardInterpreterClass (in category 'as yet unclassified') -----
  clipboardInterpreterClass
  	| platformName osVersion |
  	platformName := Smalltalk platformName.
  	osVersion := Smalltalk osVersion.
  	(platformName = 'Win32' and: [osVersion = 'CE']) 
  		ifTrue: [^NoConversionClipboardInterpreter].
  	platformName = 'Win32' ifTrue: [^WinKSX1001ClipboardInterpreter].
  	platformName = 'Mac OS' 
  		ifTrue: 
  			[('10*' match: osVersion) 
  				ifTrue: [^NoConversionClipboardInterpreter]
  				ifFalse: [^WinKSX1001ClipboardInterpreter]].
  	platformName = 'unix' 
  		ifTrue: 
  			[(ShiftJISTextConverter encodingNames includes: X11Encoding getEncoding) 
  				ifTrue: [^WinKSX1001ClipboardInterpreter]
  				ifFalse: [^NoConversionClipboardInterpreter]].
  	^NoConversionClipboardInterpreter!

Item was changed:
+ ----- Method: KoreanEnvironment class>>defaultEncodingName (in category 'public query') -----
- ----- Method: KoreanEnvironment class>>defaultEncodingName (in category 'as yet unclassified') -----
  defaultEncodingName
  	| platformName osVersion |
  	platformName := Smalltalk platformName.
  	osVersion := Smalltalk osVersion.
  	(platformName = 'Win32' and: [osVersion = 'CE']) ifTrue: [^'utf-8' copy].
  	(#('Win32' 'Mac OS' 'ZaurusOS') includes: platformName) 
  		ifTrue: [^'euc-kr' copy].
  	(#('unix') includes: platformName) ifTrue: [^'euc-kr' copy].
  	^'mac-roman'!

Item was changed:
+ ----- Method: KoreanEnvironment class>>inputInterpreterClass (in category 'subclass responsibilities') -----
- ----- Method: KoreanEnvironment class>>inputInterpreterClass (in category 'as yet unclassified') -----
  inputInterpreterClass
  	| platformName osVersion encoding |
  	platformName := Smalltalk platformName.
  	osVersion := Smalltalk osVersion.
  	(platformName = 'Win32' and: [osVersion = 'CE']) 
  		ifTrue: [^MacRomanInputInterpreter].
  	platformName = 'Win32' ifTrue: [^WinKSX1001InputInterpreter].
  	platformName = 'Mac OS' 
  		ifTrue: 
  			[('10*' match: osVersion) 
  				ifTrue: [^MacUnicodeInputInterpreter]
  				ifFalse: [^WinKSX1001InputInterpreter]].
  	platformName = 'unix' 
  		ifTrue: 
  			[encoding := X11Encoding encoding.
  			(EUCJPTextConverter encodingNames includes: encoding) 
  				ifTrue: [^MacRomanInputInterpreter].
  			(UTF8TextConverter encodingNames includes: encoding) 
  				ifTrue: [^MacRomanInputInterpreter].
  			(ShiftJISTextConverter encodingNames includes: encoding) 
  				ifTrue: [^MacRomanInputInterpreter]].
  	^MacRomanInputInterpreter!

Item was changed:
+ ----- Method: KoreanEnvironment class>>traditionalCharsetClass (in category 'language methods') -----
- ----- Method: KoreanEnvironment class>>traditionalCharsetClass (in category 'as yet unclassified') -----
  traditionalCharsetClass
  
  	^ KSX1001.
  !

Item was changed:
+ ----- Method: MacRomanClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: MacRomanClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString macToSqueak.
  !

Item was changed:
+ ----- Method: MacRomanClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: MacRomanClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  
  	| result |
  	aString isOctetString ifTrue: [^ aString asOctetString squeakToMac].
  
  	result := WriteStream on: (String new: aString size).
  	aString do: [:each | each asciiValue < 256 ifTrue: [result nextPut: each squeakToMac]].
  	^ result contents.
  !

Item was changed:
+ ----- Method: MacRomanInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: MacRomanInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| keyValue |
  	keyValue := evtBuf third.
  	^ keyValue asCharacter macToSqueak.
  !

Item was changed:
+ ----- Method: MacShiftJISClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: MacShiftJISClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  	^ aString convertFromWithConverter: ShiftJISTextConverter new!

Item was changed:
+ ----- Method: MacShiftJISClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: MacShiftJISClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: text
  
  	| string |
  	"self halt."
  	string := text asString.
  	string isAsciiString ifTrue: [^ string asOctetString].
  	string isOctetString ifTrue: [^ string "hmm"].
  	^ string convertToWithConverter: ShiftJISTextConverter new .
  !

Item was changed:
+ ----- Method: MacShiftJISInputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: MacShiftJISInputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := ShiftJISTextConverter new.
  !

Item was changed:
+ ----- Method: MacShiftJISInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: MacShiftJISInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstChar secondChar peekEvent keyValue type stream multiChar |
  	keyValue := evtBuf third.
  	evtBuf fourth = EventKeyChar ifTrue: [type := #keystroke].
  	peekEvent := sensor peekEvent.
  	(peekEvent notNil and: [peekEvent fourth = EventKeyDown]) ifTrue: [
  		sensor nextEvent.
  		peekEvent := sensor peekEvent].
  
  	(type == #keystroke
  	and: [peekEvent notNil 
  	and: [peekEvent first = EventTypeKeyboard
  	and: [peekEvent fourth = EventKeyChar]]]) ifTrue: [
  		firstChar := keyValue asCharacter.
  		secondChar := (peekEvent third) asCharacter.
  		stream := ReadStream on: (String with: firstChar with: secondChar).
  		multiChar := converter nextFromStream: stream.
  		multiChar isOctetCharacter ifFalse: [sensor nextEvent].
  		^ multiChar].
  
  	^ keyValue asCharacter!

Item was changed:
+ ----- Method: MultiByteBinaryOrTextStream>>fileInObjectAndCodeForProject (in category 'fileIn/Out') -----
- ----- Method: MultiByteBinaryOrTextStream>>fileInObjectAndCodeForProject (in category 'as yet unclassified') -----
  fileInObjectAndCodeForProject
  	"This file may contain:
  1) a fileIn of code  
  2) just an object in SmartReferenceStream format 
  3) both code and an object.
  	File it in and return the object.  Note that self must be a FileStream or RWBinaryOrTextStream.  Maybe ReadWriteStream incorporate RWBinaryOrTextStream?"
  	| refStream object |
  	self text.
  	self peek asciiValue = 4
  		ifTrue: [  "pure object file"
  			self binary.
  			refStream := SmartRefStream on: self.
  			object := refStream nextAndClose]
  		ifFalse: [  "objects mixed with a fileIn"
  			self fileInProject.  "reads code and objects, then closes the file"
  			self binary.
  			object := SmartRefStream scannedObject].	"set by side effect of one of the chunks"
  	SmartRefStream scannedObject: nil.  "clear scannedObject"
  	^ object!

Item was changed:
+ ----- Method: MultiByteBinaryOrTextStream>>fileInProject (in category 'fileIn/Out') -----
- ----- Method: MultiByteBinaryOrTextStream>>fileInProject (in category 'as yet unclassified') -----
  fileInProject
  
  	self setConverterForCodeForProject.
  	super fileIn.
  !

Item was changed:
+ ----- Method: MultiByteBinaryOrTextStream>>setConverterForCodeForProject (in category 'private') -----
- ----- Method: MultiByteBinaryOrTextStream>>setConverterForCodeForProject (in category 'as yet unclassified') -----
  setConverterForCodeForProject
  
  	self converter: UTF8TextConverter new.
  !

Item was changed:
+ ----- Method: MultiByteFileStream class>>guessDefaultLineEndConvention (in category 'system startup') -----
- ----- Method: MultiByteFileStream class>>guessDefaultLineEndConvention (in category 'class initialization') -----
  guessDefaultLineEndConvention
  	"Lets try to guess the line end convention from what we know about the
  	path name delimiter from FileDirectory."
  	FileDirectory pathNameDelimiter = $:
  		ifTrue: [^ self defaultToCR].
  	FileDirectory pathNameDelimiter = $/
  		ifTrue: [((Smalltalk osVersion)
  					beginsWith: 'darwin')
  				ifTrue: [^ self defaultToCR]
  				ifFalse: [^ self defaultToLF]].
  	FileDirectory pathNameDelimiter = $\
  		ifTrue: [^ self defaultToCRLF].
  	"in case we don't know"
  	^ self defaultToCR!

Item was changed:
+ ----- Method: MultiByteFileStream class>>newForStdio (in category 'stdio') -----
- ----- Method: MultiByteFileStream class>>newForStdio (in category 'as yet unclassified') -----
  newForStdio
  	"Use crlf as line end convention on windows, lf on all other platforms. Also make sure that the converter is initialized."
  	
  	| lineEndConvention |
  	lineEndConvention := self lineEndDefault.
  	lineEndConvention == #crlf ifFalse: [
  		lineEndConvention := #lf ].
  	^self new
  		lineEndConvention: lineEndConvention;
  		initializeConverter;
  		yourself!

Item was changed:
+ ----- Method: MultiByteFileStream class>>startUp: (in category 'system startup') -----
- ----- Method: MultiByteFileStream class>>startUp: (in category 'class initialization') -----
  startUp: resuming
  
  	resuming ifTrue: [ self guessDefaultLineEndConvention ]
  !

Item was changed:
+ ----- Method: NoConversionClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: NoConversionClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString.
  !

Item was changed:
+ ----- Method: NoConversionClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: NoConversionClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  
  	| result |
  	aString isOctetString ifTrue: [^ aString asOctetString].
  
  	result := WriteStream on: (String new: aString size).
  	aString do: [:each | each value < 256 ifTrue: [result nextPut: each]].
  	^ result contents.
  !

Item was changed:
+ ----- Method: NoConverterFound class>>signalFor: (in category 'exceptionInstantiator') -----
- ----- Method: NoConverterFound class>>signalFor: (in category 'as yet unclassified') -----
  signalFor: encodingName
  
  	self new
  		encoding: encodingName;
  		signal!

Item was changed:
+ ----- Method: NoInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: NoInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  
  
  	| keyValue |
  
  	keyValue := evtBuf third.
  
  	^ keyValue asCharacter.
  
  !

Item was changed:
+ ----- Method: RussianEnvironment class>>clipboardInterpreterClass (in category 'subclass responsibilities') -----
- ----- Method: RussianEnvironment class>>clipboardInterpreterClass (in category 'as yet unclassified') -----
  clipboardInterpreterClass
  
  	^ UTF8ClipboardInterpreter.
  !

Item was changed:
+ ----- Method: RussianEnvironment class>>fileNameConverterClass (in category 'subclass responsibilities') -----
- ----- Method: RussianEnvironment class>>fileNameConverterClass (in category 'as yet unclassified') -----
  fileNameConverterClass
  
  	^UTF8TextConverter.
  !

Item was changed:
+ ----- Method: RussianEnvironment class>>inputInterpreterClass (in category 'subclass responsibilities') -----
- ----- Method: RussianEnvironment class>>inputInterpreterClass (in category 'as yet unclassified') -----
  inputInterpreterClass
  	| platformName  |
  	platformName := Smalltalk platformName.
  	platformName = 'Win32'
  		ifTrue: [^UTF32RussianInputInterpreter].
  	platformName = 'Mac OS'
  		ifTrue: [^ (('10*' match: Smalltalk osVersion)
  					and: [(Smalltalk getSystemAttribute: 3) isNil])
  				ifTrue: [MacUnicodeInputInterpreter]
  				ifFalse: [MacRomanInputInterpreter]].
  	platformName = 'unix'
  		ifTrue: [^ UTF32RussianInputInterpreter].
  	^ MacRomanInputInterpreter!

Item was changed:
+ ----- Method: RussianEnvironment class>>supportedLanguages (in category 'subclass responsibilities') -----
- ----- Method: RussianEnvironment class>>supportedLanguages (in category 'as yet unclassified') -----
  supportedLanguages
  	"Return the languages that this class supports. 
  	Any translations for those languages will use this class as their environment."
  	
  	^#('ru' )!

Item was changed:
+ ----- Method: RussianEnvironment class>>systemConverterClass (in category 'subclass responsibilities') -----
- ----- Method: RussianEnvironment class>>systemConverterClass (in category 'as yet unclassified') -----
  systemConverterClass
  
  	^ UTF8TextConverter!

Item was changed:
+ ----- Method: StrikeFontFixer>>characterFormAt:at: (in category 'accessing') -----
- ----- Method: StrikeFontFixer>>characterFormAt:at: (in category 'as yet unclassified') -----
  characterFormAt: aCharacter at: aPoint
  
  	| f |
  	f := charForms at: aCharacter asciiValue + 1.
  	(f magnifyBy: 3) displayAt: aPoint.
  	^ f.
  !

Item was changed:
+ ----- Method: StrikeFontFixer>>displayOn:at:magnifyBy: (in category 'displaying') -----
- ----- Method: StrikeFontFixer>>displayOn:at:magnifyBy: (in category 'as yet unclassified') -----
  displayOn: aDisplayObject at: aPoint magnifyBy: aNumber
  
  	| form hStep vStep bb source nextPoint |
  	hStep := (strikeFont maxWidth * aNumber * 1.2) asInteger.
  	vStep := (strikeFont height * aNumber *  1.2) asInteger.
  	
  	form := Form extent: (hStep * 16)@(vStep * 16).
  	bb := BitBlt toForm: form.
  	0 to: 15 do: [:i |
  		1 to: 16 do: [:j |
  			source := ((charForms at: (i * 16 + j)) magnifyBy: aNumber).
  			nextPoint := (hStep * (j - 1)@(vStep * i)).
  			bb copy: ((nextPoint+((hStep at vStep - source extent) // 2)) extent: source extent)
  				from: 0 at 0 in: source fillColor: Color black rule: Form over.
  		].
  	].
  	form displayOn: aDisplayObject at: aPoint.
  !

Item was changed:
+ ----- Method: StrikeFontFixer>>font: (in category 'accessing') -----
- ----- Method: StrikeFontFixer>>font: (in category 'as yet unclassified') -----
  font: aStrikeFont
  
  	strikeFont := aStrikeFont.
  	self forms.
  !

Item was changed:
+ ----- Method: StrikeFontFixer>>forms (in category 'accessing') -----
- ----- Method: StrikeFontFixer>>forms (in category 'as yet unclassified') -----
  forms
  
  	1 to: 256 do: [:i |
  		charForms at: i put: (strikeFont characterFormAt: (Character value: (i - 1)))
  	].
  !

Item was changed:
+ ----- Method: StrikeFontFixer>>mappingTable (in category 'accessing') -----
- ----- Method: StrikeFontFixer>>mappingTable (in category 'as yet unclassified') -----
  mappingTable
  
  	^ MappingTable.
  !

Item was changed:
+ ----- Method: StrikeFontFixer>>storeEditedGlyphsOn: (in category 'printing') -----
- ----- Method: StrikeFontFixer>>storeEditedGlyphsOn: (in category 'as yet unclassified') -----
  storeEditedGlyphsOn: aStream
  	NoFontTable do: [:i |
  		| n |
  		n := strikeFont name.
  		(n beginsWith: 'NewYork') ifTrue: [n := 'NewYork'].
  		aStream nextPutAll: '((StrikeFont familyName: ''', n, ''' size: ',
  			strikeFont height asString, ')'.
  		aStream nextPutAll: ' characterFormAt: '.
  		aStream nextPutAll: '(Character value: ', i asString, ')'.
  		aStream nextPutAll: ' put: '.
  		(strikeFont characterFormAt: (Character value: i)) storeOn: aStream base: 2.
  		aStream nextPutAll: ')!!'.
  		aStream nextPut: Character cr.
  		aStream nextPut: Character cr.
  	].!

Item was changed:
+ ----- Method: StrikeFontSet class>>createExternalFontFileForLatin2: (in category 'fileIn/Out') -----
- ----- Method: StrikeFontSet class>>createExternalFontFileForLatin2: (in category 'as yet unclassified') -----
  createExternalFontFileForLatin2: fileName
  "
  	StrikeFontSet createExternalFontFileForLatin2: 'latin2.out'.
  "
  
  	| file array f installDirectory |
  	file := FileStream newFileNamed: fileName.
  	installDirectory := Smalltalk at: #M17nInstallDirectory ifAbsent: [].
  	installDirectory := installDirectory
  		ifNil: [String new]
  		ifNotNil: [installDirectory , FileDirectory pathNameDelimiter asString].
  	array := Array
  				with: (StrikeFont newFromEFontBDFFile: installDirectory , 'b10.bdf' name: 'LatinTwo9' ranges: EFontBDFFontReaderForRanges rangesForLatin2)
  				with: (StrikeFont newFromEFontBDFFile: installDirectory , 'b12.bdf' name: 'LatinTwo10' ranges: EFontBDFFontReaderForRanges rangesForLatin2)
  				with: (StrikeFont newFromEFontBDFFile: installDirectory , 'b14.bdf' name: 'LatinTwo12' ranges: EFontBDFFontReaderForRanges rangesForLatin2)
  				with: (StrikeFont newFromEFontBDFFile: installDirectory , 'b16.bdf' name: 'LatingTwo14' ranges: EFontBDFFontReaderForRanges rangesForLatin2)
  				with: (StrikeFont newFromEFontBDFFile: installDirectory , 'b24.bdf' name: 'LatinTwo20' ranges: EFontBDFFontReaderForRanges rangesForLatin2).
  	TextConstants at: #forceFontWriting put: true.
  	f := ReferenceStream on: file.
  	f nextPut: array.
  	file close.
  	TextConstants removeKey: #forceFontWriting.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>createExternalFontFileForUnicodeJapanese: (in category 'fileIn/Out') -----
- ----- Method: StrikeFontSet class>>createExternalFontFileForUnicodeJapanese: (in category 'as yet unclassified') -----
  createExternalFontFileForUnicodeJapanese: fileName
  "
  	StrikeFontSet createExternalFontFileForUnicodeJapanese: 'uJapaneseFont.out'.
  "
  
  	| file array f installDirectory |
  	file := FileStream newFileNamed: fileName.
  	installDirectory := Smalltalk at: #M17nInstallDirectory ifAbsent: [].
  	installDirectory := installDirectory
  		ifNil: [String new]
  		ifNotNil: [installDirectory , FileDirectory pathNameDelimiter asString].
  	array := Array
  				with: (StrikeFont newForJapaneseFromEFontBDFFile: installDirectory , 'b12.bdf' name: 'Japanese10' overrideWith: 'shnmk12.bdf')
  				with: ((StrikeFont newForJapaneseFromEFontBDFFile: installDirectory , 'b14.bdf' name: 'Japanese12' overrideWith: 'shnmk14.bdf') "fixAscent: 14 andDescent: 1 head: 1")
  				with: ((StrikeFont newForJapaneseFromEFontBDFFile: 'b16.bdf' name: 'Japanese14' overrideWith: 'shnmk16.bdf') "fixAscent: 16 andDescent: 4 head: 4")
  				with: (StrikeFont newForJapaneseFromEFontBDFFile: installDirectory , 'b24.bdf' name: 'Japanese18' overrideWith: 'kanji24.bdf').
  	TextConstants at: #forceFontWriting put: true.
  	f := ReferenceStream on: file.
  	f nextPut: array.
  	file close.
  	TextConstants removeKey: #forceFontWriting.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>createExternalFontFileForUnicodeKorean: (in category 'fileIn/Out') -----
- ----- Method: StrikeFontSet class>>createExternalFontFileForUnicodeKorean: (in category 'as yet unclassified') -----
  createExternalFontFileForUnicodeKorean: fileName
  "
  	Smalltalk garbageCollect.
  	StrikeFontSet createExternalFontFileForUnicodeKorean: 'uKoreanFont.out'.
  "
  
  	| file array f installDirectory |
  	file := FileStream newFileNamed: fileName.
  	installDirectory := Smalltalk at: #M17nInstallDirectory ifAbsent: [].
  	installDirectory := installDirectory
  		ifNil: [String new]
  		ifNotNil: [installDirectory , FileDirectory pathNameDelimiter asString].
  	array := Array
  				with: (StrikeFont newForKoreanFromEFontBDFFile: installDirectory , 'b12.bdf' name: 'Japanese10' overrideWith: 'shnmk12.bdf')
  				with: ((StrikeFont newForKoreanFromEFontBDFFile: installDirectory , 'b14.bdf' name: 'Japanese12' overrideWith: 'shnmk14.bdf') "fixAscent: 14 andDescent: 1 head: 1")
  				with: ((StrikeFont newForKoreanFromEFontBDFFile: installDirectory , 'b16.bdf' name: 'Japanese14' overrideWith: 'hanglg16.bdf') fixAscent: 16 andDescent: 4 head: 4)
  				with: (StrikeFont newForKoreanFromEFontBDFFile: installDirectory , 'b24.bdf' name: 'Japanese18' overrideWith: 'hanglm24.bdf').
  	TextConstants at: #forceFontWriting put: true.
  	f := ReferenceStream on: file.
  	f nextPut: array.
  	file close.
  	TextConstants removeKey: #forceFontWriting.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>decodedFromRemoteCanvas: (in category 'instance creation') -----
- ----- Method: StrikeFontSet class>>decodedFromRemoteCanvas: (in category 'as yet unclassified') -----
  decodedFromRemoteCanvas: aString
  
  	| array |
  	array := aString findTokens: #($ ).
  	^ self familyName: (array at: 1) size: (array at: 2) asNumber emphasized: (array at: 3) asNumber.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>duplicateArrayElementsForLeadingCharShift (in category 'system maintenance') -----
- ----- Method: StrikeFontSet class>>duplicateArrayElementsForLeadingCharShift (in category 'as yet unclassified') -----
  duplicateArrayElementsForLeadingCharShift
  "
  	self duplicateArrayElementsForLeadingCharShift
  "
  	self allInstances do: [:s |
  		| array font |
  		s emphasis = 0 ifTrue: [
  			array := s fontArray.
  			2 to: (4 min: array size) do: [:i |
  				font := array at: i.
  				s addNewFont: font at: ((i - 1) << 2) + 1.
  			].
  		] ifFalse: [
  			s reset
  		].
  	].
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>familyName:size: (in category 'instance creation') -----
- ----- Method: StrikeFontSet class>>familyName:size: (in category 'as yet unclassified') -----
  familyName: aName size: aSize
  	"Answer a font (or the default font if the name is unknown) in the specified size."
  
  	| collection |
  	collection :=  self allInstances select: [:inst | (inst name beginsWith: aName) and: [inst emphasis = 0]].
  	collection isEmpty ifTrue: [
  		(aName = 'DefaultMultiStyle') ifTrue: [
  			collection := (TextConstants at: #DefaultMultiStyle) fontArray.
  		] ifFalse: [
  			^ TextStyle defaultFont
  		]
  	].
  	collection sort: [:a :b | a pointSize <= b pointSize].
  	collection do: [:s | (s pointSize >= aSize) ifTrue: [^ s]].
  	^ TextStyle defaultFont.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>familyName:size:emphasized: (in category 'instance creation') -----
- ----- Method: StrikeFontSet class>>familyName:size:emphasized: (in category 'as yet unclassified') -----
  familyName: aName size: aSize emphasized: emphasisCode
  	"Create the font with this emphasis"
  
  	^ (self familyName: aName size: aSize) emphasized: emphasisCode
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>findMaximumLessThan:in: (in category 'utilities') -----
- ----- Method: StrikeFontSet class>>findMaximumLessThan:in: (in category 'as yet unclassified') -----
  findMaximumLessThan: f in: array
  
  	array size to: 1 by: -1 do: [:i |
  		f height >= (array at: i) height ifTrue: [^ array at: i].
  	].
  	^ array first.
  !

Item was changed:
+ ----- Method: StrikeFontSet class>>newFontArray: (in category 'instance creation') -----
- ----- Method: StrikeFontSet class>>newFontArray: (in category 'as yet unclassified') -----
  newFontArray: anArray
   
  	^super new initializeWithFontArray: anArray
  !

Item was changed:
+ ----- Method: StrikeFontSet>>ascent (in category 'accessing') -----
- ----- Method: StrikeFontSet>>ascent (in category 'as yet unclassified') -----
  ascent
  
  	^ fontArray first ascent.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>ascentKern (in category 'accessing') -----
- ----- Method: StrikeFontSet>>ascentKern (in category 'as yet unclassified') -----
  ascentKern
  
  	^ fontArray first ascentKern.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>baseKern (in category 'accessing') -----
- ----- Method: StrikeFontSet>>baseKern (in category 'as yet unclassified') -----
  baseKern
  
  	^ fontArray first baseKern.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>bonk:with:at: (in category 'private') -----
- ----- Method: StrikeFontSet>>bonk:with:at: (in category 'as yet unclassified') -----
  bonk: glyphForm with: bonkForm at: j
  	"Bonking means to run through the glyphs clearing out black pixels
  	between characters to prevent them from straying into an adjacent
  	character as a result of, eg, bolding or italicizing"
  	"Uses the bonkForm to erase at every character boundary in glyphs."
  
  	| bb offset font x |
  	font := (fontArray at: j).
  	offset := bonkForm offset x.
  	bb := BitBlt toForm: glyphForm.
  	bb sourceForm: bonkForm; sourceRect: bonkForm boundingBox;
  		combinationRule: Form erase; destY: 0.
  	x := font xTable.
  	(x isMemberOf: SparseLargeTable) ifTrue: [
  		x base to: x size-1 do: [:i | bb destX: (x at: i) + offset; copyBits].
  	] ifFalse: [
  		1 to: x size-1 do: [:i | bb destX: (x at: i) + offset; copyBits].
  	].
  !

Item was changed:
+ ----- Method: StrikeFontSet>>depth (in category 'accessing') -----
- ----- Method: StrikeFontSet>>depth (in category 'as yet unclassified') -----
  depth
  
  	^ self glyphs depth!

Item was changed:
+ ----- Method: StrikeFontSet>>derivativeFonts (in category 'accessing') -----
- ----- Method: StrikeFontSet>>derivativeFonts (in category 'as yet unclassified') -----
  derivativeFonts
  	^derivativeFonts copyWithout: nil!

Item was changed:
+ ----- Method: StrikeFontSet>>descent (in category 'accessing') -----
- ----- Method: StrikeFontSet>>descent (in category 'as yet unclassified') -----
  descent
  
  	^ fontArray first descent.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>descentKern (in category 'accessing') -----
- ----- Method: StrikeFontSet>>descentKern (in category 'as yet unclassified') -----
  descentKern
  
  	^ fontArray first descentKern.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>displayLine:at: (in category 'displaying') -----
- ----- Method: StrikeFontSet>>displayLine:at: (in category 'as yet unclassified') -----
  displayLine: aString at: aPoint 
  	"Display the characters in aString, starting at position aPoint."
  
  	self characters: (1 to: aString size)
  		in: aString
  		displayAt: aPoint
  		clippedBy: Display boundingBox
  		rule: Form over
  		fillColor: nil
  		kernDelta: 0
  		on: (BitBlt toForm: Display).
  !

Item was changed:
+ ----- Method: StrikeFontSet>>emphasis (in category 'accessing') -----
- ----- Method: StrikeFontSet>>emphasis (in category 'as yet unclassified') -----
  emphasis
  	"Answer the integer code for synthetic bold, italic, underline, and 
  	strike-out."
  
  	^ emphasis.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>emphasis: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>emphasis: (in category 'as yet unclassified') -----
  emphasis: code 
  	"Set the integer code for synthetic bold, itallic, underline, and strike-out, 
  	where bold=1, italic=2, underlined=4, and struck out=8."
  
  	emphasis := code.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>emphasized: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>emphasized: (in category 'as yet unclassified') -----
  emphasized: code 
  
  	"Answer a copy of the receiver with emphasis set to include code."
  	| derivative addedEmphasis base safeCode |
  	code = 0 ifTrue: [^ self].
  	(derivativeFonts == nil or: [derivativeFonts size = 0]) ifTrue: [^ self].
  	derivative := derivativeFonts at: (safeCode := code min: derivativeFonts size).
  	derivative == nil ifFalse: [^ derivative].  "Already have this style"
  
  	"Dont have it -- derive from another with one with less emphasis"
  	addedEmphasis := 1 bitShift: safeCode highBit - 1.
  	base := self emphasized: safeCode - addedEmphasis.  "Order is Bold, Ital, Under, Narrow"
  	addedEmphasis = 1 ifTrue:   "Compute synthetic bold version of the font"
  		[derivative := (base copy name: base name , 'B') makeBoldGlyphs].
  	addedEmphasis = 2 ifTrue:   "Compute synthetic italic version of the font"
  		[ derivative := (base copy name: base name , 'I') makeItalicGlyphs].
  	addedEmphasis = 4 ifTrue:   "Compute underlined version of the font"
  		[derivative := (base copy name: base name , 'U') makeUnderlinedGlyphs].
  	addedEmphasis = 8 ifTrue:   "Compute narrow version of the font"
  		[derivative := (base copy name: base name , 'N') makeCondensedGlyphs].
  	addedEmphasis = 16 ifTrue:   "Compute struck-out version of the font"
  		[derivative := (base copy name: base name , 'X') makeStruckOutGlyphs].
  	derivative emphasis: safeCode.
  	derivativeFonts at: safeCode put: derivative.
  	^ derivative
  !

Item was changed:
+ ----- Method: StrikeFontSet>>familyName (in category 'accessing') -----
- ----- Method: StrikeFontSet>>familyName (in category 'as yet unclassified') -----
  familyName
  
  	^ fontArray first familyName.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>familySizeFace (in category 'accessing') -----
- ----- Method: StrikeFontSet>>familySizeFace (in category 'as yet unclassified') -----
  familySizeFace
  
  	^ Array
  		with: fontArray first name
  		with: self height
  		with: fontArray first emphasis
  !

Item was changed:
+ ----- Method: StrikeFontSet>>fontArray: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>fontArray: (in category 'as yet unclassified') -----
  fontArray: anArray
  
  	fontArray := anArray.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>fontNameWithPointSize (in category 'accessing') -----
- ----- Method: StrikeFontSet>>fontNameWithPointSize (in category 'as yet unclassified') -----
  fontNameWithPointSize
  
  	^ fontArray first fontNameWithPointSize.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>glyphs (in category 'accessing') -----
- ----- Method: StrikeFontSet>>glyphs (in category 'as yet unclassified') -----
  glyphs
  
  	^ fontArray first glyphs
  !

Item was changed:
+ ----- Method: StrikeFontSet>>glyphsEncoding: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>glyphsEncoding: (in category 'as yet unclassified') -----
  glyphsEncoding: anInteger
  
  	^ (fontArray at: (anInteger+1)) glyphs.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>height (in category 'accessing') -----
- ----- Method: StrikeFontSet>>height (in category 'as yet unclassified') -----
  height
  
  	^ fontArray first height.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>initializeWithFontArray: (in category 'initialize-release') -----
- ----- Method: StrikeFontSet>>initializeWithFontArray: (in category 'as yet unclassified') -----
  initializeWithFontArray: anArray 
  	"Initialize with given font array, the ascent of primary font is modified 
  	if another font has higher size"
  	| primaryFont maxHeight newFont |
  	fontArray := anArray.
  	primaryFont := anArray first.
  	emphasis := 0.
  	name := primaryFont name.
  	maxHeight := anArray
  				inject: 0
  				into: [:theHeight :font | (font notNil
  							and: [theHeight < font height])
  						ifTrue: [font height]
  						ifFalse: [theHeight]].
  	primaryFont height < maxHeight
  		ifTrue: [newFont := primaryFont copy
  						fixAscent: primaryFont ascent + (maxHeight - primaryFont height)
  						andDescent: primaryFont descent
  						head: 0.
  			fontArray at: 1 put: newFont].
  	self reset!

Item was changed:
+ ----- Method: StrikeFontSet>>installOn: (in category 'displaying') -----
- ----- Method: StrikeFontSet>>installOn: (in category 'as yet unclassified') -----
  installOn: aDisplayContext
  
  	^ aDisplayContext installStrikeFont: self.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>installOn:foregroundColor:backgroundColor: (in category 'displaying') -----
- ----- Method: StrikeFontSet>>installOn:foregroundColor:backgroundColor: (in category 'as yet unclassified') -----
  installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor 
  
  	^ aDisplayContext
  		installStrikeFont: self
  		foregroundColor: foregroundColor
  		backgroundColor: backgroundColor.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>lineGrid (in category 'accessing') -----
- ----- Method: StrikeFontSet>>lineGrid (in category 'as yet unclassified') -----
  lineGrid
  
  	| f |
  	f := fontArray first.
  	^ f ascent + f descent.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>maxEncoding (in category 'accessing') -----
- ----- Method: StrikeFontSet>>maxEncoding (in category 'as yet unclassified') -----
  maxEncoding
  
  	^ fontArray size.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>maxWidth (in category 'accessing') -----
- ----- Method: StrikeFontSet>>maxWidth (in category 'as yet unclassified') -----
  maxWidth
  
  	^ (fontArray at: 1) maxWidth.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>name (in category 'testing') -----
- ----- Method: StrikeFontSet>>name (in category 'as yet unclassified') -----
  name
  
  	^ name
  !

Item was changed:
+ ----- Method: StrikeFontSet>>name: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>name: (in category 'as yet unclassified') -----
  name: aString
  
  	name := aString
  !

Item was changed:
+ ----- Method: StrikeFontSet>>objectForDataStream: (in category 'objects from disk') -----
- ----- Method: StrikeFontSet>>objectForDataStream: (in category 'as yet unclassified') -----
  objectForDataStream: refStrm
  	| dp |
  	"I am about to be written on an object file.  Write a reference to a known Font in the other system instead.  "
  
  	"A path to me"
  	(TextConstants at: #forceFontWriting ifAbsent: [false]) ifTrue: [^ self].
  		"special case for saving the default fonts on the disk.  See collectionFromFileNamed:"
  
  	dp := DiskProxy global: #StrikeFontSet selector: #familyName:size:emphasized:
  			args: (Array with: self familyName with: self pointSize
  					with: self emphasis).
  	refStrm replace: self with: dp.
  	^ dp.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>pointSize (in category 'accessing') -----
- ----- Method: StrikeFontSet>>pointSize (in category 'as yet unclassified') -----
  pointSize
  
  	^ fontArray first pointSize.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>reset (in category 'emphasis') -----
- ----- Method: StrikeFontSet>>reset (in category 'as yet unclassified') -----
  reset
  	"Reset the cache of derivative emphasized fonts"
  
  	derivativeFonts := Array new: 32.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>subscript (in category 'accessing') -----
- ----- Method: StrikeFontSet>>subscript (in category 'as yet unclassified') -----
  subscript
  
  	^ fontArray first subscript
  !

Item was changed:
+ ----- Method: StrikeFontSet>>superscript (in category 'accessing') -----
- ----- Method: StrikeFontSet>>superscript (in category 'as yet unclassified') -----
  superscript
  
  	^ fontArray first superscript
  !

Item was changed:
+ ----- Method: StrikeFontSet>>widthOfString: (in category 'measuring') -----
- ----- Method: StrikeFontSet>>widthOfString: (in category 'as yet unclassified') -----
  widthOfString: aString
  
  	aString ifNil:[^0].
  	"Optimizing"
  	(aString isByteString) ifTrue: [
  		^ self fontArray first widthOfString: aString from: 1 to: aString size].
  	^ self widthOfString: aString from: 1 to: aString size.
  "
  	TextStyle default defaultFont widthOfString: 'zort' 21
  "
  !

Item was changed:
+ ----- Method: StrikeFontSet>>xTable (in category 'accessing') -----
- ----- Method: StrikeFontSet>>xTable (in category 'as yet unclassified') -----
  xTable
  	"Answer an Array of the left x-coordinate of characters in glyphs."
  
  	^ fontArray first xTable.
  !

Item was changed:
+ ----- Method: StrikeFontSet>>xTableEncoding: (in category 'accessing') -----
- ----- Method: StrikeFontSet>>xTableEncoding: (in category 'as yet unclassified') -----
  xTableEncoding: anInteger
  	"Answer an Array of the left x-coordinate of characters in glyphs."
  
  	^(fontArray at: anInteger + 1) xTable.
  !

Item was changed:
+ ----- Method: SymbolInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: SymbolInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| keyValue |
  	keyValue := evtBuf third.
  	evtBuf fifth > 1 ifTrue: [^ keyValue asCharacter macToSqueak].
  	^ (self symbolKeyValueToUnicode: keyValue) asCharacter.
  !

Item was changed:
+ ----- Method: SymbolInputInterpreter>>symbolKeyValueToUnicode: (in category 'private') -----
- ----- Method: SymbolInputInterpreter>>symbolKeyValueToUnicode: (in category 'as yet unclassified') -----
  symbolKeyValueToUnicode: keyValue
  
  	keyValue = 127 ifTrue: [^ 127].
  	keyValue < 32 ifTrue: [^ keyValue].
  	keyValue > 255 ifTrue: [^ 0].
  	^ #(0 0 0 0 0 0 0 0 0 61472 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 61472 61473 61474 61475 61476 61477 61478 61479 61480 61481 61482 61483 61484 61485 61486 61487 61488 61489 61490 61491 61492 61493 61494 61495 61496 61497 61498 61499 61500 61501 61502 61503 61504 61505 61506 61507 61508 61509 61510 61511 61512 61513 61514 61515 61516 61517 61518 61519 61520 61521 61522 61523 61524 61525 61526 61527 61528 61529 61530 61531 61532 61533 61534 61535 61536 61537 61538 61539 61540 61541 61542 61543 61544 61545 61546 61547 61548 61549 61550 61551 61552 61553 61554 61555 61556 61557 61558 61559 61560 61561 61562 61563 61564 61565 61566 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 61601 61602 61603 61604 61605 61606 61607 61608 61609 61610 61611 61612 61613 61614 61615 61616 61617 61618 61619 61620 61621 61622 61623 61624 61625 61626 61627 61628 61629 61630 61631 61632 61633 61634 61635 61636 61637 61638 61639 61640 61641 61642 61643 61644 61645 61646 61647 616
 48 61649 61650 61651 61652 61653 61654 61655 61656 61657 61658 61659 61660 61661 61662 61663 61664 61665 61666 61667 61668 61669 61670 61671 61672 61673 61674 61675 61676 61677 61678 61679 0 61681 61682 61683 61684 61685 61686 61687 61688 61689 61690 61691 61692 61693 61694 0) at: keyValue + 1.
  !

Item was changed:
  ----- Method: TextConverter class>>allEncodingNames (in category 'utilities') -----
  allEncodingNames
  	"TextConverter allEncodingNames"
  	| encodingNames |
  	encodingNames := Set new.
  	self allSubclasses
  		do: [:each | 
  			| names | 
  			names := each encodingNames.
  			names notEmpty
  				ifTrue: [encodingNames add: names first asSymbol]].
  	^encodingNames!

Item was changed:
+ ----- Method: UTF32InputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: UTF32InputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf 
  	"Fall back on MacRoman if char is 0"
  	^(evtBuf at: 6) > 0
  		ifTrue: [(evtBuf at: 6) asCharacter]
  		ifFalse: [(evtBuf at: 3) asCharacter macToSqueak].
  !

Item was changed:
+ ----- Method: UTF32JPInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: UTF32JPInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf 
  	| keyValue mark |
  	keyValue := evtBuf at: 6.
  	keyValue = 0 ifTrue: [keyValue := evtBuf at: 3].
  	mark := self japaneseSpecialMark: keyValue.
  	mark notNil
  		ifTrue: [^ mark].
  	keyValue < 256
  		ifTrue: [^ (Character value: keyValue) squeakToIso].
  	^ Character leadingChar: JapaneseEnvironment leadingChar code: keyValue!

Item was changed:
+ ----- Method: UTF8ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: UTF8ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  	^aString utf8ToSqueak!

Item was changed:
+ ----- Method: UTF8ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: UTF8ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: aString
  	^aString squeakToUtf8
  !

Item was changed:
+ ----- Method: UTF8TextConverter class>>initializeLatin1MapAndEncodings (in category 'class initialization') -----
- ----- Method: UTF8TextConverter class>>initializeLatin1MapAndEncodings (in category 'as yet unclassified') -----
  initializeLatin1MapAndEncodings
  	"Initialize the latin1Map and latin1Encodings. These variables ensure that conversions from latin1 ByteString is reasonably fast."
  	
  	latin1Map := (0 to: 255) collect: [ :each | each bitShift: -7 ] as: ByteArray.
  	latin1Encodings := (0 to: 255) collect: [ :each |
  		each <= 127
  			ifTrue: [ nil ]
  			ifFalse: [
  				{ 192 bitOr: (each bitShift: -6). (each bitAnd: 63) bitOr: 128 } asByteArray asString ] ]!

Item was changed:
+ ----- Method: UndefinedConversion class>>signalFor:toEncoding: (in category 'exceptionInstantiator') -----
- ----- Method: UndefinedConversion class>>signalFor:toEncoding: (in category 'as yet unclassified') -----
  signalFor: characterValue toEncoding: anEncoding
  
  	self new
  		unicodeValue: characterValue;
  		targetEncoding: anEncoding;
  		signal!

Item was changed:
+ ----- Method: UnicodeInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: UnicodeInputInterpreter>>nextCharFrom:firstEvt: (in category 'converting') -----
  nextCharFrom: sensor firstEvt: evtBuf
  	"Compose Unicode character sequences"
  	| peekEvent keyValue composed |
  	"Only try this if the first event is composable and is a character event"
  	((Unicode isComposable: (keyValue := evtBuf sixth)) 
  		and:[evtBuf fourth = EventKeyChar]) ifTrue:[
  			"If we have a pending keyDown in the queue, skip that to get to the keystroke"
  			peekEvent := sensor peekEvent.
  			(peekEvent notNil and: [peekEvent fourth = EventKeyDown]) ifTrue: [
  				"skipEvent := "sensor nextEvent.
  				peekEvent := sensor peekEvent].
  			"If we have another character event in the queue, compose it"
  			(peekEvent notNil 
  				and: [peekEvent first = EventTypeKeyboard 
  				and:[peekEvent fourth = EventKeyChar]]) ifTrue:[
  					composed := Unicode compose: keyValue with: peekEvent sixth.
  					composed ifNotNil:[
  						sensor nextEvent.
  						^composed]]].
  	"XXXX: Fixme. We should put the skipped event back if we haven't consumed it."
  	^keyValue asCharacter!

Item was changed:
+ ----- Method: UnixEUCJPInputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: UnixEUCJPInputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := EUCJPTextConverter new.
  !

Item was changed:
+ ----- Method: UnixEUCJPInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: UnixEUCJPInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstChar secondChar peekEvent keyValue type stream multiChar |
  	keyValue := evtBuf third.
  	evtBuf fourth = EventKeyChar ifTrue: [type := #keystroke].
  	peekEvent := sensor peekEvent.
  	(peekEvent notNil and: [peekEvent fourth = EventKeyDown]) ifTrue: [
  		sensor nextEvent.
  		peekEvent := sensor peekEvent].
  
  	(type == #keystroke
  	and: [peekEvent notNil 
  	and: [peekEvent first = EventTypeKeyboard
  	and: [peekEvent fourth = EventKeyChar]]]) ifTrue: [
  		firstChar := keyValue asCharacter.
  		secondChar := (peekEvent third) asCharacter.
  		stream := ReadStream on: (String with: firstChar with: secondChar).
  		multiChar := converter nextFromStream: stream.
  		multiChar isOctetCharacter ifFalse: [sensor nextEvent].
  		^ multiChar].
  
  	^ keyValue asCharacter!

Item was changed:
+ ----- Method: UnixJPClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: UnixJPClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  	^ aString convertFromSystemString!

Item was changed:
+ ----- Method: UnixJPClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: UnixJPClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: text
  
  	| string |
  	"self halt."
  	string := text asString.
  	string isAsciiString ifTrue: [^ string asOctetString].
  	string isOctetString ifTrue: [^ string "hmm"].
  	^ string convertToSystemString .
  !

Item was changed:
+ ----- Method: UnixUTF8JPInputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: UnixUTF8JPInputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := UTF8TextConverter new.!

Item was changed:
+ ----- Method: UnixUTF8JPInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: UnixUTF8JPInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstChar aCollection bytes peekEvent keyValue type stream multiChar |
  	keyValue := evtBuf third.
  	evtBuf fourth = EventKeyChar ifTrue: [type := #keystroke].
  	peekEvent := sensor peekEvent.
  	(peekEvent notNil and: [peekEvent fourth = EventKeyDown]) ifTrue: [
  		sensor nextEvent.
  		peekEvent := sensor peekEvent].
  
  	(type == #keystroke
  	and: [peekEvent notNil 
  	and: [peekEvent first = EventTypeKeyboard
  	and: [peekEvent fourth = EventKeyChar]]]) ifTrue: [
  		firstChar := keyValue asCharacter.
  		aCollection := OrderedCollection new.
  		aCollection add: firstChar.
  		bytes := (keyValue <= 127)
  			ifTrue: [ 0 ]
  			ifFalse: [ (keyValue bitAnd: 16rE0) = 192
  				ifTrue: [ 1 ]
  				ifFalse: [ (keyValue bitAnd: 16rF0) = 224
  					ifTrue: [ 2 ]
  					ifFalse: [ 3 ]
  				]
  			].
  		bytes timesRepeat: [ aCollection add: sensor nextEvent third asCharacter ].
  		"aCollection do: [ :each | Transcript show: (each asciiValue hex , ' ')].
  		Transcript show: Character cr."
  		stream := ReadStream on: (String withAll: aCollection).
  		multiChar := converter nextFromStream: stream.
  		multiChar isOctetCharacter ifFalse: [ sensor nextEvent ].
  		^ multiChar].
  
  	^ keyValue asCharacter!

Item was changed:
+ ----- Method: WinCPTextConverter class>>initializeDecodeTable (in category 'class initialization') -----
- ----- Method: WinCPTextConverter class>>initializeDecodeTable (in category 'as yet unclassified') -----
  initializeDecodeTable
  	decodeTable := (0 to: 255) asArray!

Item was changed:
+ ----- Method: WinGB2312ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinGB2312ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString squeakToMac convertFromSystemString.
  !

Item was changed:
+ ----- Method: WinGB2312ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinGB2312ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: text
  
  	| string |
  	"self halt."
  	string := text asString.
  	string isAsciiString ifTrue: [^ string asOctetString].
  	string isOctetString ifTrue: [^ string "hmm"].
  	^ string convertToSystemString squeakToMac.
  !

Item was changed:
+ ----- Method: WinGB2312InputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: WinGB2312InputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := CNGBTextConverter new.
  !

Item was changed:
+ ----- Method: WinGB2312InputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: WinGB2312InputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstCharacter secondCharacter peekEvent char1Value keyValue pressType type stream multiCharacter |
  	keyValue := evtBuf third.
  	pressType := evtBuf fourth.
  	pressType = EventKeyDown ifTrue: [type := #keyDown].
  	pressType = EventKeyUp ifTrue: [type := #keyUp].
  	pressType = EventKeyChar ifTrue: [type := #keystroke].
  
  	char1Value := (Character value: keyValue) macToSqueak asciiValue.
  	((char1Value > 127 and: [char1Value < 160])
  		or: [char1Value > 223 and: [char1Value < 253]]) ifFalse: [
  			^ keyValue asCharacter.
  		].
  
  	peekEvent := sensor peekEvent.
  	"peekEvent printString displayAt: 0 at 0."
  	(peekEvent notNil and: [(peekEvent at: 4) = EventKeyDown])
  		ifTrue: [sensor nextEvent.
  			peekEvent := sensor peekEvent].
  	(type = #keystroke
  			and: [peekEvent notNil
  					and: [(peekEvent at: 1)
  								= EventTypeKeyboard
  							and: [(peekEvent at: 4)
  									= EventKeyChar]]])
  		ifTrue: [
  			firstCharacter := char1Value asCharacter.
  			secondCharacter := (peekEvent at: 3) asCharacter macToSqueak.
  			stream := ReadStream on: (String with: firstCharacter with: secondCharacter).
  			multiCharacter := converter nextFromStream: stream.
  			multiCharacter isOctetCharacter ifFalse: [
  				sensor nextEvent.
  			].
  			^ multiCharacter.
  		].
  	^ keyValue asCharacter.
  !

Item was changed:
+ ----- Method: WinKSX1001ClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinKSX1001ClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString squeakToMac convertFromSystemString.
  !

Item was changed:
+ ----- Method: WinKSX1001ClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinKSX1001ClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: text
  
  	| string |
  	"self halt."
  	string := text asString.
  	string isAsciiString ifTrue: [^ string asOctetString].
  	string isOctetString ifTrue: [^ string "hmm"].
  	^ string convertToSystemString squeakToMac.
  !

Item was changed:
+ ----- Method: WinKSX1001InputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: WinKSX1001InputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := EUCKRTextConverter new.
  !

Item was changed:
+ ----- Method: WinKSX1001InputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: WinKSX1001InputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstCharacter secondCharacter peekEvent char1Value keyValue pressType type stream multiCharacter |
  	keyValue := evtBuf third.
  	pressType := evtBuf fourth.
  	pressType = EventKeyDown ifTrue: [type := #keyDown].
  	pressType = EventKeyUp ifTrue: [type := #keyUp].
  	pressType = EventKeyChar ifTrue: [type := #keystroke].
  
  	char1Value := (Character value: keyValue) macToSqueak asciiValue.
  	((char1Value > 127 and: [char1Value < 160])
  		or: [char1Value > 223 and: [char1Value < 253]]) ifFalse: [
  			^ keyValue asCharacter.
  		].
  
  	peekEvent := sensor peekEvent.
  	"peekEvent printString displayAt: 0 at 0."
  	(peekEvent notNil and: [(peekEvent at: 4) = EventKeyDown])
  		ifTrue: [sensor nextEvent.
  			peekEvent := sensor peekEvent].
  	(type = #keystroke
  			and: [peekEvent notNil
  					and: [(peekEvent at: 1)
  								= EventTypeKeyboard
  							and: [(peekEvent at: 4)
  									= EventKeyChar]]])
  		ifTrue: [
  			firstCharacter := char1Value asCharacter.
  			secondCharacter := (peekEvent at: 3) asCharacter macToSqueak.
  			stream := ReadStream on: (String with: firstCharacter with: secondCharacter).
  			multiCharacter := converter nextFromStream: stream.
  			multiCharacter isOctetCharacter ifFalse: [
  				sensor nextEvent.
  			].
  			^ multiCharacter.
  		].
  	^ keyValue asCharacter.
  !

Item was changed:
+ ----- Method: WinShiftJISClipboardInterpreter>>fromSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinShiftJISClipboardInterpreter>>fromSystemClipboard: (in category 'as yet unclassified') -----
  fromSystemClipboard: aString
  
  	^ aString macToSqueak convertFromSystemString
  !

Item was changed:
+ ----- Method: WinShiftJISClipboardInterpreter>>toSystemClipboard: (in category 'conversion-clipboard') -----
- ----- Method: WinShiftJISClipboardInterpreter>>toSystemClipboard: (in category 'as yet unclassified') -----
  toSystemClipboard: text
  
  	| string |
  	"self halt."
  	string := text asString.
  	string isAsciiString ifTrue: [^ string asOctetString].
  	string isOctetString ifTrue: [^ string "hmm"].
  	^ string convertToSystemString squeakToMac.
  !

Item was changed:
+ ----- Method: WinShiftJISInputInterpreter>>initialize (in category 'initialize-release') -----
- ----- Method: WinShiftJISInputInterpreter>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	converter := ShiftJISTextConverter new.
  !

Item was changed:
+ ----- Method: WinShiftJISInputInterpreter>>nextCharFrom:firstEvt: (in category 'keyboard') -----
- ----- Method: WinShiftJISInputInterpreter>>nextCharFrom:firstEvt: (in category 'as yet unclassified') -----
  nextCharFrom: sensor firstEvt: evtBuf
  
  	| firstCharacter secondCharacter peekEvent char1Value keyValue pressType type stream multiCharacter |
  	keyValue := evtBuf third.
  	pressType := evtBuf fourth.
  	pressType = EventKeyDown ifTrue: [type := #keyDown].
  	pressType = EventKeyUp ifTrue: [type := #keyUp].
  	pressType = EventKeyChar ifTrue: [type := #keystroke].
  
  	char1Value := (Character value: keyValue) macToSqueak asciiValue.
  
  	(char1Value < 16r81) ifTrue: [^ keyValue asCharacter].
  	(char1Value > 16rA0 and: [char1Value < 16rE0]) ifTrue: [^ ShiftJISTextConverter basicNew katakanaValue: char1Value].
  
  	peekEvent := sensor peekEvent.
  	"peekEvent printString displayAt: 0 at 0."
  	(peekEvent notNil and: [(peekEvent at: 4) = EventKeyDown])
  		ifTrue: [sensor nextEvent.
  			peekEvent := sensor peekEvent].
  	(type = #keystroke
  			and: [peekEvent notNil
  					and: [(peekEvent at: 1)
  								= EventTypeKeyboard
  							and: [(peekEvent at: 4)
  									= EventKeyChar]]])
  		ifTrue: [
  			firstCharacter := char1Value asCharacter.
  			secondCharacter := (peekEvent at: 3) asCharacter macToSqueak.
  			stream := ReadStream on: (String with: firstCharacter with: secondCharacter).
  			multiCharacter := converter nextFromStream: stream.
  			multiCharacter isOctetCharacter ifFalse: [
  				sensor nextEvent.
  			].
  			^ multiCharacter.
  		].
  	^ keyValue asCharacter.
  !

Item was changed:
+ ----- Method: X11Encoding class>>encoding (in category 'encoding') -----
- ----- Method: X11Encoding class>>encoding (in category 'as yet unclassified') -----
  encoding
  
  	| enc |
  	enc := self getEncoding.
  	enc ifNil: [ ^ nil ].
  	^ enc asLowercase.!

Item was changed:
+ ----- Method: X11Encoding class>>getEncoding (in category 'primitives') -----
- ----- Method: X11Encoding class>>getEncoding (in category 'as yet unclassified') -----
  getEncoding
  	<primitive: 'primGetEncoding' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>getLocaleEncoding (in category 'primitives') -----
- ----- Method: X11Encoding class>>getLocaleEncoding (in category 'as yet unclassified') -----
  getLocaleEncoding
  	<primitive: 'primGetLocaleEncoding' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>getPathEnc (in category 'primitives') -----
- ----- Method: X11Encoding class>>getPathEnc (in category 'as yet unclassified') -----
  getPathEnc
  	<primitive: 'primGetPathEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>getTextEnc (in category 'primitives') -----
- ----- Method: X11Encoding class>>getTextEnc (in category 'as yet unclassified') -----
  getTextEnc
  	<primitive: 'primGetTextEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>getXWinEnc (in category 'primitives') -----
- ----- Method: X11Encoding class>>getXWinEnc (in category 'as yet unclassified') -----
  getXWinEnc
  	<primitive: 'primGetXWinEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>requestUTF8 (in category 'primitives') -----
- ----- Method: X11Encoding class>>requestUTF8 (in category 'as yet unclassified') -----
  requestUTF8
  	<primitive: 'primIsTextEncUTF8' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>requestUTF8: (in category 'primitives') -----
- ----- Method: X11Encoding class>>requestUTF8: (in category 'as yet unclassified') -----
  requestUTF8: bool
  	<primitive: 'primSetTextEncUTF8' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setEncoding: (in category 'primitives') -----
- ----- Method: X11Encoding class>>setEncoding: (in category 'as yet unclassified') -----
  setEncoding: encoding
  	<primitive: 'primSetEncoding' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setEncodingToLocale (in category 'primitives') -----
- ----- Method: X11Encoding class>>setEncodingToLocale (in category 'as yet unclassified') -----
  setEncodingToLocale
  	<primitive: 'primSetEncodingToLocale' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setPathEnc: (in category 'primitives') -----
- ----- Method: X11Encoding class>>setPathEnc: (in category 'as yet unclassified') -----
  setPathEnc: encoding
  	<primitive: 'primSetPathEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setPathEncToLocale (in category 'primitives') -----
- ----- Method: X11Encoding class>>setPathEncToLocale (in category 'as yet unclassified') -----
  setPathEncToLocale
  	<primitive: 'primSetPathEncToLocale' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setTextEnc: (in category 'primitives') -----
- ----- Method: X11Encoding class>>setTextEnc: (in category 'as yet unclassified') -----
  setTextEnc: encoding
  	<primitive: 'primSetTextEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setTextEncToLocale (in category 'primitives') -----
- ----- Method: X11Encoding class>>setTextEncToLocale (in category 'as yet unclassified') -----
  setTextEncToLocale
  	<primitive: 'primSetTextEncToLocale' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setXWinEnc: (in category 'primitives') -----
- ----- Method: X11Encoding class>>setXWinEnc: (in category 'as yet unclassified') -----
  setXWinEnc: encoding
  	<primitive: 'primSetXWinEnc' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>setXWinEncToLocale (in category 'primitives') -----
- ----- Method: X11Encoding class>>setXWinEncToLocale (in category 'as yet unclassified') -----
  setXWinEncToLocale
  	<primitive: 'primSetXWinEncToLocale' module: 'ImmX11Plugin'>
  	^ nil
  !

Item was changed:
+ ----- Method: X11Encoding class>>useEncoding: (in category 'encoding') -----
- ----- Method: X11Encoding class>>useEncoding: (in category 'as yet unclassified') -----
  useEncoding: encoding
  
  	self setEncoding: encoding.
  	LanguageEnvironment startUp.
  	^ self encoding.!

Item was changed:
+ ----- Method: X11Encoding class>>useLocaleEncoding (in category 'encoding') -----
- ----- Method: X11Encoding class>>useLocaleEncoding (in category 'as yet unclassified') -----
  useLocaleEncoding
  
  	self setEncodingToLocale.
  	LanguageEnvironment startUp.
  	^ self encoding.!




More information about the Squeak-dev mailing list