[squeak-dev] Squeak 4.6: MultilingualTests-fbs.18.mcz

H. Hirzel hannes.hirzel at gmail.com
Thu Jan 19 09:51:02 UTC 2017


The changeset given in the report
http://www.bgaertner.gmxhome.de/Squeak38ExperienceRep.zip

files in fine if

      MultiCharacter

is replaced by

      Character

There is as well a bitmap font  "SofijaUC29.zip" which I have not
tried out yet to file in.

----------------------------------------------------------------------------------------------------------------------------

'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6485] on
3 December 2004 at 10:36:04 am'!
"Change Set:		ToyFonts
Date:			3 December 2004
Author:			Boris Gaertner

This change set contains code that is needed to create a font with
glyphs that show the Unicode codepoints. This is of very limited use,
essentially such a font is needed to test Unicode-related algorithms.
"!

Object subclass: #GlyphCreator
	instanceVariableNames: ''
	classVariableNames: 'Digits Gl0 Gl1 Gl2 Gl3 Gl4 Gl5 Gl6 Gl7 Gl8 Gl9
GlA GlB GlC GlD GlE GlF'
	poolDictionaries: ''
	category: 'Font-Tutorial'!

!GlyphCreator class methodsFor: 'class initialization' stamp: 'BG
11/25/2004 11:47'!
initialize
 "GlyphCreator initialize"
  Gl0 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2415919104 2415919104 2415919104
2415919104 1610612736)
	offset: 0 at 0).
 Gl1 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 536870912 1610612736 536870912 536870912 536870912 1879048192)
	offset: 0 at 0).
 Gl2 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2415919104 268435456 536870912 1073741824
4026531840)
	offset: 0 at 0).
 Gl3 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 268435456 1610612736 268435456 2415919104
1610612736)
	offset: 0 at 0).
 Gl4 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 536870912 1610612736 2684354560 4026531840 536870912 536870912)
	offset: 0 at 0).
 Gl5 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 3758096384 2147483648 3758096384 268435456 268435456
3758096384)
	offset: 0 at 0).
 Gl6 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2147483648 3758096384 2415919104
2415919104 1610612736)
	offset: 0 at 0).
Gl7 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 4026531840 268435456 536870912 1073741824 1073741824
1073741824)
	offset: 0 at 0).
Gl8 := (Form
	extent: 5 at 7
	depth: 1
fromArray: #( 0 1610612736 2415919104 1610612736 2415919104 2415919104
1610612736)
	offset: 0 at 0).
Gl9 := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2415919104 2415919104 1879048192 268435456
3758096384)
	offset: 0 at 0).
GlA := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2415919104 2415919104 4026531840
2415919104 2415919104)
	offset: 0 at 0)	.
GlB := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 3758096384 2415919104 3758096384 2415919104
2415919104 3758096384)
	offset: 0 at 0).
GlC := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 1610612736 2415919104 2147483648 2147483648
2415919104 1610612736)
	offset: 0 at 0).
GlD := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 3758096384 1342177280 1342177280 1342177280
1342177280 3758096384)
	offset: 0 at 0).
GlE := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 3758096384 2147483648 3758096384 2147483648
2147483648 3758096384)
	offset: 0 at 0).
GlF := (Form
	extent: 5 at 7
	depth: 1
	fromArray: #( 0 3758096384 2147483648 3758096384 2147483648
2147483648 2147483648)
	offset: 0 at 0).
 Digits := Array new: 16.
  Digits at: 1 put: Gl0;
         at: 2 put: Gl1;
          at: 3 put: Gl2;
          at: 4 put: Gl3;
          at: 5 put: Gl4;
          at: 6 put: Gl5;
          at: 7 put: Gl6;
          at: 8 put: Gl7;
          at: 9 put: Gl8;
          at: 10 put: Gl9;
          at: 11 put: GlA;
          at: 12 put: GlB;
          at: 13 put: GlC;
          at: 14 put: GlD;
          at: 15 put: GlE;
          at: 16 put: GlF.











! !

!GlyphCreator class methodsFor: 'class initialization' stamp: 'BG
11/25/2004 12:03'!
makeGlyphForCp: codepoint into: aForm

  | d1 d2 d3 d4 |


  d1 := (codepoint bitAnd: 16rF000) >> 12.
  d2 := (codepoint bitAnd: 16rF00) >> 8.
  d3 := (codepoint bitAnd: 16rF0) >> 4.
  d4 := (codepoint bitAnd: 16rF).
  aForm copy: (3 @ 3 extent: 5 at 7) from: 0 at 0 in: (Digits at: d1 + 1)
rule: Form over.
  aForm copy: (8 @ 3 extent: 5 at 7) from: 0 at 0 in: (Digits at: d2 + 1)
rule: Form over.
  aForm copy: (3 @ 10 extent: 5 at 7) from: 0 at 0 in: (Digits at: d3 + 1)
rule: Form over.
  aForm copy: (8 @ 10 extent: 5 at 7) from: 0 at 0 in: (Digits at: d4 + 1)
rule: Form over.

  aForm border: (aForm boundingBox insetBy: 2) width: 1 fillColor:
Color black.! !


!Character methodsFor: 'converting' stamp: 'BG 11/25/2004 15:47'!
asUnicode

	| table charset v |
	charset _ EncodedCharSet charsetAt: self leadingChar.
	(charset isKindOf: EncodedCharSet) ifFalse: [^ self charCode].
	table _ charset ucsTable.
	table isNil ifTrue: [^ 16rFFFD].

	v _ table at: self charCode + 1.
	v = -1 ifTrue: [^ 16rFFFD].

	^ v.
! !

!Character methodsFor: 'converting' stamp: 'BG 11/26/2004 15:20'!
asUnicodeChar

	| table charset v |
	charset _ EncodedCharSet charsetAt: self leadingChar.
	(charset isKindOf: Unicode) ifTrue: [^ self].
	table _ charset ucsTable.
	table isNil ifTrue: [^ Character value: 16rFFFD].

	v _ table at: self charCode + 1.
	v = -1 ifTrue: [^ Character value: 16rFFFD].

	^ Character leadingChar: charset unicodeLeadingChar code: v.
! !


!StrikeFont methodsFor: 'Mac reader' stamp: 'BG 11/26/2004 08:12'!
initializeLargeToyFontNamed: nm startingAtAscii: startAscii to: endAscii
	ascent: a descent: d maxWidth: m
	"This builds a StrikeFont instance with default settings."

	| lastAscii form width ascii charForm missingForm tempGlyphs |
	name _ nm.
	ascent _ a.
	descent _ d.
	maxWidth _ m.
	pointSize _ a + d.
     form := Form extent: m @(ascent + descent).
     form border: (form boundingBox insetBy: 2) width: 1 fillColor: Color black.
	name _ (name copyWithout: Character space) ,
				(pointSize < 10
					ifTrue: ['0' , pointSize printString]
					ifFalse: [pointSize printString]).
	minAscii _ startAscii.
	maxAscii _ endAscii.
	superscript _ ascent - descent // 3.	
	subscript _ descent - ascent // 3.	
	emphasis _ 0.
	type _ 0.  "ignored for now"

	tempGlyphs _ Form extent: (maxWidth*(maxAscii - minAscii + 1)) @ self height.
	xTable _ (Array new: endAscii + 3) atAllPut: 0.
	xTable at: 1 put: 0.

	"Read character forms and blt into tempGlyphs"
	lastAscii _ -1.
	1 to: endAscii - startAscii + 1 do:
		[:i | GlyphCreator makeGlyphForCp: startAscii + i - 1 into: form.
          charForm := form.
          width _ charForm width.
		ascii _ startAscii-1+i.

		"ascii = 256" false
			ifTrue: [missingForm _ charForm deepCopy]
			ifFalse:
			[minAscii _ minAscii min: ascii.
			maxAscii _ maxAscii max: ascii.
			lastAscii+1 to: ascii-1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
			tempGlyphs copy: ((xTable at: ascii+1)@0
									extent: charForm extent)
						from: 0 at 0 in: charForm rule: Form over.
			xTable at: ascii+2 put: (xTable at: ascii+1) + width.
			lastAscii _ ascii]].
	lastAscii+1 to: maxAscii+1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
	missingForm == nil ifFalse:
		[tempGlyphs copy: missingForm boundingBox from: missingForm
				to: (xTable at: maxAscii+2)@0 rule: Form over.
		xTable at: maxAscii+3 put: (xTable at: maxAscii+2) + missingForm width].
	glyphs _ Form extent: (xTable at: maxAscii+3) @ self height.
	glyphs copy: glyphs boundingBox from: 0 at 0 in: tempGlyphs rule: Form over.
	xTable _ xTable copyFrom: 1 to: maxAscii+3.
! !

!StrikeFont methodsFor: 'Mac reader' stamp: 'BG 11/26/2004 08:12'!
initializeToyFontNamed: nm startingAtAscii: startAscii to: endAscii
	ascent: a descent: d maxWidth: m
	"This builds a StrikeFont instance with default settings."

	| lastAscii form width ascii charForm missingForm tempGlyphs |
	name _ nm.
	ascent _ a.
	descent _ d.
	maxWidth _ m.
	pointSize _ a + d.
     form := Form extent: m @(ascent + descent).
     form border: (form boundingBox insetBy: 2) width: 1 fillColor: Color black.
	name _ (name copyWithout: Character space) ,
				(pointSize < 10
					ifTrue: ['0' , pointSize printString]
					ifFalse: [pointSize printString]).
	minAscii _ 258.
	maxAscii _ 0.
	superscript _ ascent - descent // 3.	
	subscript _ descent - ascent // 3.	
	emphasis _ 0.
	type _ 0.  "ignored for now"

	tempGlyphs _ Form extent: (maxWidth*257) @ self height.
	xTable _ (Array new: 258) atAllPut: 0.
	xTable at: 1 put: 0.

	"Read character forms and blt into tempGlyphs"
	lastAscii _ -1.
	1 to: endAscii - startAscii + 1 do:
		[:i | GlyphCreator makeGlyphForCp: startAscii + i - 1 into: form.
          charForm _ form.

          width _ charForm width.
		ascii _ startAscii-1+i.

		ascii = 256
			ifTrue: [missingForm _ charForm deepCopy]
			ifFalse:
			[minAscii _ minAscii min: ascii.
			maxAscii _ maxAscii max: ascii.
			lastAscii+1 to: ascii-1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
			tempGlyphs copy: ((xTable at: ascii+1)@0
									extent: charForm extent)
						from: 0 at 0 in: charForm rule: Form over.
			xTable at: ascii+2 put: (xTable at: ascii+1) + width.
			lastAscii _ ascii]].
	lastAscii+1 to: maxAscii+1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
	missingForm == nil ifFalse:
		[tempGlyphs copy: missingForm boundingBox from: missingForm
				to: (xTable at: maxAscii+2)@0 rule: Form over.
		xTable at: maxAscii+3 put: (xTable at: maxAscii+2) + missingForm width].
	glyphs _ Form extent: (xTable at: maxAscii+3) @ self height.
	glyphs copy: glyphs boundingBox from: 0 at 0 in: tempGlyphs rule: Form over.
	xTable _ xTable copyFrom: 1 to: maxAscii+3.
! !

!StrikeFont methodsFor: 'private' stamp: 'BG 11/26/2004 16:18'!
createCharacterToGlyphMap
	"Private. Create the character to glyph mapping for a font that
didn't have any before. This is basically equivalent to what the
former setStopCondition did, only based on indexes."
	| map |
	map _ Array new: maxAscii + 1.
	0 to: minAscii - 1 do:[:i| map at: i + 1 put: maxAscii + 1].
	minAscii to: maxAscii do:[:i| map at: i + 1 put: i].
	maxAscii + 1 to: 255 do:[:i| map at: i + 1 put: maxAscii + 1].
	^map! !

GlyphCreator initialize!

!GlyphCreator class reorganize!
('class initialization' initialize makeGlyphForCp:into:)
!


On 1/19/17, H. Hirzel <hannes.hirzel at gmail.com> wrote:
> On 1/19/17, Tobias Pape <Das.Linux at gmx.de> wrote:
>>
>> On 19.01.2017, at 07:57, H. Hirzel <hannes.hirzel at gmail.com> wrote:
>>
>>> Reactivating an old thread ...
>>>
>>> Taking the test above just gives a question mark for the fallback font
>>> case
>>>
>>>  | text font bb destPoint |
>>>        text := (Character value: 257) asString asText.
>>>        font := TextStyle default fontOfSize: 21.
>>>        text addAttribute: (TextFontReference toFont: font).
>>>        bb := (Form extent: 100 @ 30) getCanvas privatePort.
>>>        bb combinationRule: Form paint.
>>>
>>>        font installOn: bb foregroundColor: Color black
>>> backgroundColor: Color white.
>>>        destPoint := font displayString: text asString on: bb from: 1
>>> to: 1 at: 0 at 0 kern: 1.
>>>
>>>        bb destForm asMorph openInHand.
>>>
>>>
>>> Is there another fallback font readily available which gives for small
>>> hex numbers for the missing characters?
>>
>> No, not yet…
>> Also, fallback fonts do not really work like that, they only have exactly
>> one glyph that is used when the
>> falbackee (i mean the font in need of the fallback) says it does not have
>> the glyph requested.
>>
>> ----------
>> fallbackFont
>> 	"Answers the fallbackFont for the receiver. The fallback font must be
>> some
>> derivative of the receiver since it will not be asked to install itself
>> properly on the target BitBlt so rendering a completely different font
>> here
>> is simply not possible. The default implementation uses a synthetic font
>> that maps all characters to question marks."
>> 	^ fallbackFont
>> 		ifNil: [fallbackFont := FixedFaceFont new errorFont baseFont: self]
>> ----------
>>
>> But maybe we should change that.
>
> Yes, I was not aware of this limited concept of 'fallback' font.
>
> Why not create a glyph with 4 tiny hex digits on the fly, when requested?
>
> A report on http://www.bgaertner.gmxhome.de/Sqm17n.htm gives details
> about such a font
>
> http://www.bgaertner.gmxhome.de/Squeak38ExperienceRep.zip
>
> "Toy font"
>
>
>> The better alternative is to have actual good glyph coverage ;)
>
> Yes. A bitmap font with better glyph coverage is needed in  the image.
> Or on SqueakMap.
>
>
>> Best regards
>> 	-Tobias
>>
>>>
>>> --Hannes
>>>
>>> On Fri, 5 Jun 2015 20:20:36.139 0000, commits at source.squeak.org
>>> <commits at source.squeak.org> wrote:
>>>> Chris Muller uploaded a new version of MultilingualTests to project
>>>> Squeak
>>>> 4.6:
>>>> http://source.squeak.org/squeak46/MultilingualTests-fbs.18.mcz
>>>>
>>>> ==================== Summary ====================
>>>>
>>>> Name: MultilingualTests-fbs.18
>>>> Author: fbs
>>>> Time: 6 November 2013, 6:35:02.811 pm
>>>> UUID: 07e26018-8455-3349-9b44-9ecb4aaeefb2
>>>> Ancestors: MultilingualTests-nice.17
>>>>
>>>> More #shouldnt:raise: Error fixes.
>>>>
>>>> ==================== Snapshot ====================
>>>>
>>>> SystemOrganization addCategory: #'MultilingualTests-TextConversion'!
>>>> SystemOrganization addCategory: #'MultilingualTests-Display'!
>>>>
>>>> TestCase subclass: #FontTest
>>>> 	instanceVariableNames: ''
>>>> 	classVariableNames: ''
>>>> 	poolDictionaries: ''
>>>> 	category: 'MultilingualTests-Display'!
>>>>
>>>> !FontTest commentStamp: 'tak 3/11/2005 14:31' prior: 0!
>>>> I am mainly a test for fallback font.
>>>> FontTest buildSuite run!
>>>>
>>>> ----- Method: FontTest>>testDisplay (in category 'testing') -----
>>>> testDisplay
>>>> 	"self debug: #testDisplay"
>>>> 	| text font bb destPoint width |
>>>> 	text := 'test' asText.
>>>> 	font := TextStyle default fontOfSize: 21.
>>>> 	text addAttribute: (TextFontReference toFont: font).
>>>> 	bb := (Form extent: 100 @ 30) getCanvas privatePort.
>>>> 	bb combinationRule: Form paint.
>>>>
>>>> 	font installOn: bb foregroundColor: Color black backgroundColor: Color
>>>> white.
>>>> 	destPoint := font displayString: text asString on: bb from: 1 to: 4
>>>> at:
>>>> 0 at 0
>>>> kern: 1.
>>>>
>>>> 	width := text inject: 0 into: [:max :char | max + (font widthOf:
>>>> char)].
>>>> 	self assert: destPoint x = (width + 4).
>>>> 	"bb destForm asMorph openInHand."
>>>> !
>>>>
>>>> ----- Method: FontTest>>testFallback (in category 'testing') -----
>>>> testFallback
>>>> 	"self debug: #testFallback"
>>>> 	| text font bb destPoint |
>>>> 	text := (Character value: 257) asString asText.
>>>> 	font := TextStyle default fontOfSize: 21.
>>>> 	text addAttribute: (TextFontReference toFont: font).
>>>> 	bb := (Form extent: 100 @ 30) getCanvas privatePort.
>>>> 	bb combinationRule: Form paint.
>>>>
>>>> 	font installOn: bb foregroundColor: Color black backgroundColor: Color
>>>> white.
>>>> 	destPoint := font displayString: text asString on: bb from: 1 to: 1
>>>> at:
>>>> 0 at 0
>>>> kern: 1.
>>>>
>>>> 	"bb destForm asMorph openInHand."
>>>> 	self assert: destPoint x = ((font widthOf: $?) + 1).
>>>> !
>>>>
>>>> ----- Method: FontTest>>testMultistringFallbackFont (in category
>>>> 'testing')
>>>> -----
>>>> testMultistringFallbackFont
>>>> 	"self debug: #testMultistringFallbackFont"
>>>> 	| text p style height width |
>>>> 	[(TextStyle default fontArray at: JapaneseEnvironment leadingChar)
>>>> 		ifNil: [^ self]]
>>>> 		ifError: [:err :rcvr | ^ self].
>>>> 	text := ((#(20983874 20983876 20983878 )
>>>> 				collect: [:e | e asCharacter])
>>>> 				as: String) asText.
>>>> 	p := NewParagraph new.
>>>> 	style := TextStyle new leading: 0; newFontArray: {Preferences
>>>> standardFlapFont}.
>>>> 	p
>>>> 		compose: text
>>>> 		style: style
>>>> 		from: 1
>>>> 		in: (0 @ 0 corner: 100 @ 100).
>>>> 	"See CompositionScanner>>setActualFont: &
>>>> 	CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:"
>>>> 	height := style defaultFont height + style leading.
>>>> 	width := text
>>>> 				inject: 0
>>>> 				into: [:tally :next | tally
>>>> 						+ (style defaultFont widthOf: next)].
>>>> 	p adjustRightX.
>>>> 	self assert: p extent = (width @ height).
>>>> 	"Display getCanvas
>>>> 		paragraph: p
>>>> 		bounds: (10 @ 10 extent: 100 @ 100)
>>>> 		color: Color black"!
>>>>
>>>> ----- Method: FontTest>>testMultistringFont (in category 'testing')
>>>> -----
>>>> testMultistringFont
>>>> 	"self debug: #testMultistringFont"
>>>> 	| text p style height width |
>>>> 	[(TextStyle default fontArray at: JapaneseEnvironment leadingChar)
>>>> 		ifNil: [^ self]]
>>>> 		ifError: [:err :rcvr | ^ self].
>>>> 	text := ((#(20983874 20983876 20983878 )
>>>> 				collect: [:e | e asCharacter])
>>>> 				as: String) asText.
>>>> 	p := NewParagraph new.
>>>> 	style := TextStyle default.
>>>> 	p
>>>> 		compose: text
>>>> 		style: style
>>>> 		from: 1
>>>> 		in: (0 @ 0 corner: 100 @ 100).
>>>> 	"See CompositionScanner>>setActualFont: &
>>>> 	CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:"
>>>> 	height := style defaultFont height + style leading.
>>>> 	width := text
>>>> 				inject: 0
>>>> 				into: [:tally :next | tally
>>>> 						+ (style defaultFont widthOf: next)].
>>>> 	p adjustRightX.
>>>> 	self assert: p extent = (width @ height).
>>>> 	"Display getCanvas
>>>> 		paragraph: p
>>>> 		bounds: (10 @ 10 extent: 100 @ 100)
>>>> 		color: Color black"!
>>>>
>>>> ----- Method: FontTest>>testParagraph (in category 'testing') -----
>>>> testParagraph
>>>> 	"self debug: #testParagraph"
>>>> 	| text p style height width |
>>>> 	text := 'test' asText.
>>>> 	p := NewParagraph new.
>>>> 	style := TextStyle default.
>>>> 	p
>>>> 		compose: text
>>>> 		style: style
>>>> 		from: 1
>>>> 		in: (0 @ 0 corner: 100 @ 100).
>>>> 	"See CompositionScanner>>setActualFont: &
>>>> 	CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:"
>>>> 	height := style defaultFont height + style leading.
>>>> 	width := text
>>>> 				inject: 0
>>>> 				into: [:tally :next | tally
>>>> 						+ (style defaultFont widthOf: next)].
>>>> 	p adjustRightX.
>>>> 	self assert: p extent = (width @ height)!
>>>>
>>>> ----- Method: FontTest>>testParagraphFallback (in category 'testing')
>>>> -----
>>>> testParagraphFallback
>>>> 	"self debug: #testParagraphFallback"
>>>> 	| text p style height width e expect |
>>>> 	e := (Character value: 257) asString.
>>>> 	text := ('test' , e , e , e , e , 'test') asText.
>>>> 	expect := 'test????test'.
>>>> 	p := NewParagraph new.
>>>> 	style := TextStyle default.
>>>> 	p
>>>> 		compose: text
>>>> 		style: style
>>>> 		from: 1
>>>> 		in: (0 @ 0 corner: 100 @ 100).
>>>> 	"See CompositionScanner>>setActualFont: &
>>>> 	CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:"
>>>> 	height := style defaultFont height + style leading.
>>>> 	width := expect
>>>> 				inject: 0
>>>> 				into: [:tally :next | tally
>>>> 						+ (style defaultFont widthOf: next)].
>>>> 	p adjustRightX.
>>>> 	self assert: p extent = (width @ height).
>>>> 	"Display getCanvas
>>>> 		paragraph: p
>>>> 		bounds: (10 @ 10 extent: 100 @ 100)
>>>> 		color: Color black"!
>>>>
>>>> ----- Method: FontTest>>testResetAfterEmphasized (in category
>>>> 'testing')
>>>> -----
>>>> testResetAfterEmphasized
>>>> 	"self debug: #testResetAfterEmphasized"
>>>> 	| normal derivative |
>>>> 	normal := TextStyle defaultFont.
>>>> 	derivative := normal emphasized: 3.
>>>> 	self assert: (normal derivativeFonts at: 3) == derivative.
>>>> 	normal reset.
>>>> 	self assert: (normal derivativeFonts select:[:any| any isSynthetic])
>>>> isEmpty
>>>> !
>>>>
>>>> TestCase subclass: #MultiByteFileStreamTest
>>>> 	instanceVariableNames: 'fileName'
>>>> 	classVariableNames: ''
>>>> 	poolDictionaries: ''
>>>> 	category: 'MultilingualTests-TextConversion'!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>tearDown (in category 'running')
>>>> -----
>>>> tearDown
>>>>
>>>> 	fileName ifNotNil: [
>>>> 		FileDirectory default deleteFileNamed: fileName ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testAsciiBackChunk (in category
>>>> 'testing') -----
>>>> testAsciiBackChunk
>>>> 	
>>>> 	fileName := 'foobackchunk.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			lineEndConvention: #cr;
>>>> 			converter: UTF8TextConverter new;
>>>> 			cr; nextChunkPut: 'test1' printString;
>>>> 			cr; nextChunkPut: 'test2' printString.
>>>> 		self
>>>> 			assert: file backChunk = (String cr , 'test2' printString);
>>>> 			assert: file backChunk = (String cr , 'test1' printString) ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testBinaryUpTo (in category
>>>> 'testing') -----
>>>> testBinaryUpTo
>>>> 	"This is a non regression test for bug
>>>> http://bugs.squeak.org/view.php?id=6933"
>>>> 	
>>>> 	fileName := 'foobug6933'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			binary;
>>>> 			nextPutAll: #[ 1 2 3 4 ] ].
>>>> 	MultiByteFileStream oldFileNamed: fileName do: [ :file |
>>>> 		file binary.
>>>> 		self assert: (file upTo: 3) = #[ 1 2 ] ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testByteTextConverter (in
>>>> category
>>>> 'testing') -----
>>>> testByteTextConverter
>>>> 	| strings converterClasses |
>>>> 	strings := {
>>>> 		String newFrom: ((0 to: 255) collect: [:e | e asCharacter]).
>>>> 	}.
>>>> 	
>>>> 	converterClasses := ByteTextConverter allSubclasses.
>>>> 	converterClasses do: [:converterClass |
>>>> 		strings do: [:string | | converter stream encoded decoded encoded2 |
>>>> 			converter := converterClass new.
>>>> 			stream := string readStream.
>>>> 			encoded := string select: [:e | (converter nextFromStream: stream)
>>>> notNil].
>>>> 			stream := encoded readStream.
>>>> 			decoded := encoded collect: [:e | converter nextFromStream: stream].
>>>> 			self assert: stream atEnd.
>>>> 			stream := String new writeStream.
>>>> 			converter nextPutAll: decoded toStream: stream.
>>>> 			encoded2 := stream contents.
>>>> 			self assert: (encoded2 collect: [:e | e charCode] as: Array) =
>>>> (encoded
>>>> collect: [:e | e charCode] as: Array).
>>>> 			stream := String new writeStream.
>>>> 			decoded do: [:e | converter nextPut: e toStream: stream].
>>>> 			encoded2 := stream contents.
>>>> 			self assert: (encoded2 collect: [:e | e charCode] as: Array) =
>>>> (encoded
>>>> collect: [:e | e charCode] as: Array)]]!
>>>>
>>>> ----- Method:
>>>> MultiByteFileStreamTest>>testLineEndConvention:withConverter:ifFail:
>>>> (in
>>>> category 'helpers') -----
>>>> testLineEndConvention: lineEndConvention withConverter:
>>>> textConverterClass
>>>> ifFail: failBlock
>>>>
>>>> 	| expectedResult result |
>>>> 	[
>>>> 		MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 			file
>>>> 				converter: textConverterClass new;
>>>> 				lineEndConvention: lineEndConvention;
>>>> 				cr;
>>>> 				nextPut: Character cr;
>>>> 				nextPutAll: String cr;
>>>> 				nextPutAll: String cr asWideString ].
>>>> 		result := StandardFileStream oldFileNamed: fileName do: [ :file |
>>>> 			file contents ].
>>>> 		expectedResult := String streamContents: [ :stream |
>>>> 			4 timesRepeat: [ stream perform: lineEndConvention ] ].
>>>> 		result = expectedResult ifFalse: [
>>>> 			failBlock value: expectedResult asByteArray value: result
>>>> asByteArray
>>>> ]
>>>> ]
>>>> 		on: Error
>>>> 		do: [ :err | failBlock value: err messageText value: err messageText
>>>> ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testLineEndConversion (in
>>>> category
>>>> 'testing') -----
>>>> testLineEndConversion
>>>>
>>>> 	| failures |
>>>> 	fileName := 'foolinendconversion.txt'.
>>>> 	failures := OrderedCollection new.
>>>> 	TextConverter allSubclassesDo: [ :textConverterClass |
>>>> 		textConverterClass encodingNames ifNotEmpty: [
>>>> 			#(cr lf crlf) do: [ :lineEndConvention |
>>>> 				self
>>>> 					testLineEndConvention: lineEndConvention
>>>> 					withConverter: textConverterClass
>>>> 					ifFail: [ :expectedResult :result |
>>>> 						failures add: {
>>>> 							textConverterClass.
>>>> 							lineEndConvention.
>>>> 							expectedResult.
>>>> 							result } ] ] ] ].
>>>> 	self assert: failures isEmpty!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testLineEnding (in category
>>>> 'testing') -----
>>>> testLineEnding
>>>>
>>>> 	fileName := 'foolinend.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			wantsLineEndConversion: false;
>>>> 			nextPutAll: 'line 1'; cr;
>>>> 			nextPutAll: 'line 2'; crlf;
>>>> 			nextPutAll: 'line 3'; lf;
>>>> 			nextPutAll: 'line 4' ].
>>>> 	{
>>>> 		{#cr.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#lf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#crlf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr , 'line 4'}.
>>>> 		{nil.  'line 1' , String cr , 'line 2' , String crlf , 'line 3' ,
>>>> String
>>>> lf , 'line 4'}
>>>> 	} do: [:lineEndingResult |
>>>> 		MultiByteFileStream oldFileNamed: fileName do: [ :file |
>>>> 			file lineEndConvention: lineEndingResult first.
>>>> 			self assert: file upToEnd = lineEndingResult last ] ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testLineEndingChunk (in category
>>>> 'testing') -----
>>>> testLineEndingChunk
>>>>
>>>> 	fileName := 'foolinend.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			wantsLineEndConversion: false;
>>>> 			nextPutAll: 'line 1'; cr;
>>>> 			nextPutAll: 'line 2'; crlf;
>>>> 			nextPutAll: 'line 3'; lf;
>>>> 			nextPutAll: 'line 4'; nextPut: $!! ].
>>>> 	{
>>>> 		{#cr.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#lf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#crlf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr , 'line 4'}.
>>>> 		{nil.  'line 1' , String cr , 'line 2' , String crlf , 'line 3' ,
>>>> String
>>>> lf , 'line 4'}
>>>> 	} do: [:lineEndingResult |
>>>> 		MultiByteFileStream oldFileNamed: fileName do: [ :file |
>>>> 			file lineEndConvention: lineEndingResult first.
>>>> 			self assert: lineEndingResult last equals: file nextChunk ] ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testLineEndingWithWideStrings
>>>> (in
>>>> category 'testing') -----
>>>> testLineEndingWithWideStrings
>>>>
>>>> 	| cr lf crlf |
>>>> 	fileName := 'foolinend.txt'.
>>>> 	cr := String cr asWideString.
>>>> 	lf := String lf asWideString.
>>>> 	crlf := String crlf asWideString.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			wantsLineEndConversion: false;
>>>> 			nextPutAll: 'line 1'; nextPutAll: cr;
>>>> 			nextPutAll: 'line 2'; nextPutAll: crlf;
>>>> 			nextPutAll: 'line 3'; nextPutAll: lf;
>>>> 			nextPutAll: 'line 4' ].
>>>> 	{
>>>> 		{#cr.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#lf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr
>>>> , 'line 4'}.
>>>> 		{#crlf.  'line 1' , String cr , 'line 2' , String cr , 'line 3' ,
>>>> String
>>>> cr , 'line 4'}.
>>>> 		{nil.  'line 1' , String cr , 'line 2' , String crlf , 'line 3' ,
>>>> String
>>>> lf , 'line 4'}
>>>> 	} do: [ :lineEndingResult |
>>>> 		MultiByteFileStream oldFileNamed: fileName do: [ :file |
>>>> 			file lineEndConvention: lineEndingResult first.
>>>> 			self assert: file upToEnd = lineEndingResult last ] ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testMultiByteTextConverter (in
>>>> category 'testing') -----
>>>> testMultiByteTextConverter
>>>> 	| strings converterClasses |
>>>> 	strings := {
>>>> 		String newFrom: ((0 to: 255) collect: [:e | Unicode value: e]).
>>>> 		String newFrom: ((0 to: 1023) collect: [:e | Unicode value: e]).
>>>> 	}.
>>>> 	
>>>> 	converterClasses := {
>>>> 		UTF8TextConverter . UTF16TextConverter .
>>>> 		"CompoundTextConverter ."
>>>> 		"EUCJPTextConverter . CNGBTextConverter . ShiftJISTextConverter .
>>>> EUCKRTextConverter"}.
>>>> 	converterClasses do: [:converterClass |
>>>> 		strings do: [:string |
>>>> 			| converter stream |
>>>> 			converter := converterClass new.
>>>> 			stream := String new writeStream.
>>>> 			converter nextPutAll: string toStream: stream.
>>>> 			stream := stream contents readStream.
>>>> 			string do: [:e | | decoded |
>>>> 				decoded := converter nextFromStream: stream.
>>>> 				self assert: e charCode = decoded charCode].
>>>> 			self assert: stream atEnd.
>>>> 	
>>>> 			stream := String new writeStream.
>>>> 			string do: [:e | converter nextPut: e toStream: stream].
>>>> 			stream := stream contents readStream.
>>>> 			string do: [:e | | decoded |
>>>> 				decoded := converter nextFromStream: stream.
>>>> 				self assert: e charCode = decoded charCode].
>>>> 			self assert: stream atEnd]]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testNextLine (in category
>>>> 'testing')
>>>> -----
>>>> testNextLine
>>>>
>>>> 	fileName := 'foonextline.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			wantsLineEndConversion: false;
>>>> 			nextPutAll: 'line 1'; cr;
>>>> 			nextPutAll: 'line 2'; crlf;
>>>> 			nextPutAll: 'line 3'; lf;
>>>> 			nextPutAll: 'line 4' ].
>>>> 	#(cr lf crlf nil) do: [:lineEnding |
>>>> 		MultiByteFileStream oldFileNamed: fileName do: [ :file |
>>>> 			file lineEndConvention: lineEnding.
>>>> 			self
>>>> 				assert: file nextLine = 'line 1';
>>>> 				assert: file nextLine = 'line 2';
>>>> 				assert: file nextLine = 'line 3';
>>>> 				assert: file nextLine = 'line 4';
>>>> 				assert: file nextLine = nil ] ]!
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testNextPutAllStartingAt (in
>>>> category
>>>> 'testing') -----
>>>> testNextPutAllStartingAt
>>>>
>>>> 	| result |
>>>> 	fileName := 'foonextputallstartingat.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		{ 'abcde' asWideString. 'abcde' } do: [ :string |
>>>> 			file
>>>> 				next: 1 putAll: string startingAt: 5;
>>>> 				next: 3 putAll: string startingAt: 2;
>>>> 				next: 1 putAll: string startingAt: 1 ] ].
>>>> 	result := StandardFileStream readOnlyFileNamed: fileName do: [ :file |
>>>> 		file binary; contents ].
>>>> 	self assert: #[101 98 99 100 97 101 98 99 100 97] equals: result
>>>> !
>>>>
>>>> ----- Method: MultiByteFileStreamTest>>testNonAsciiBackChunk (in
>>>> category
>>>> 'testing') -----
>>>> testNonAsciiBackChunk
>>>> 	"Note: this is an expected failure: MultiByteFileStream is not
>>>> equipped
>>>> to
>>>> read back non ASCII String... (no comment)
>>>> 	As a consequence, never use non ASCII in method category nor in your
>>>> initials. That would make a few tools blind..."
>>>> 	
>>>> 	fileName :=  'foobackchunk.txt'.
>>>> 	MultiByteFileStream forceNewFileNamed: fileName do: [ :file |
>>>> 		file
>>>> 			lineEndConvention: #cr;
>>>> 			converter: UTF8TextConverter new;
>>>> 			cr; nextChunkPut: 'testé' printString;
>>>> 			cr; nextChunkPut: 'test' printString.
>>>> 		self assert: file backChunk = (String cr , 'test' printString).
>>>> 		self assert: file backChunk = (String cr , 'testé' printString) ]!
>>>>
>>>> TestCase subclass: #UTF16TextConverterTest
>>>> 	instanceVariableNames: ''
>>>> 	classVariableNames: ''
>>>> 	poolDictionaries: ''
>>>> 	category: 'MultilingualTests-TextConversion'!
>>>>
>>>> ----- Method: UTF16TextConverterTest>>testByteOrders (in category
>>>> 'testing')
>>>> -----
>>>> testByteOrders
>>>> 	|converter originalText bytes decodedText |
>>>> 	originalText := 'test'.
>>>> 	converter := UTF16TextConverter new.
>>>> 	
>>>> 	"Default (ie useLittleEndian instvar nil)"
>>>> 	bytes := (originalText convertToWithConverter: converter).
>>>> 	decodedText := bytes convertFromWithConverter: converter.
>>>> 	
>>>> 	self assert: originalText equals: decodedText.
>>>> 	
>>>> 	"Little-endian"
>>>> 	converter useLittleEndian: true.
>>>>
>>>> 	bytes := (originalText convertToWithConverter: converter).
>>>> 	decodedText := bytes convertFromWithConverter: converter.
>>>> 	
>>>> 	self assert: originalText equals: decodedText.
>>>> 	
>>>> 	"Big-endian"
>>>> 	converter useLittleEndian: false.
>>>>
>>>> 	bytes := (originalText convertToWithConverter: converter).
>>>> 	decodedText := bytes convertFromWithConverter: converter.
>>>> 	
>>>> 	self assert: originalText equals: decodedText.
>>>> 	
>>>> 	!
>>>>
>>>> ClassTestCase subclass: #UTF8TextConverterTest
>>>> 	instanceVariableNames: ''
>>>> 	classVariableNames: ''
>>>> 	poolDictionaries: ''
>>>> 	category: 'MultilingualTests-TextConversion'!
>>>>
>>>> ----- Method: UTF8TextConverterTest>>testLazyConversion (in category
>>>> 'tests') -----
>>>> testLazyConversion
>>>> 	"Ensure the lazy conversions do what they should"
>>>>
>>>> 	| strict result |
>>>> 	strict := UTF8TextConverter strictUtf8Conversions.
>>>> 	[UTF8TextConverter strictUtf8Conversions: false.
>>>> 	result := 'Grüß Gott' utf8ToSqueak.
>>>> 	] ensure:[UTF8TextConverter strictUtf8Conversions: strict].
>>>>
>>>> 	self assert: result = 'Grüß Gott'.
>>>> !
>>>>
>>>> ----- Method: UTF8TextConverterTest>>testSqueakToUtf8 (in category
>>>> 'tests')
>>>> -----
>>>> testSqueakToUtf8
>>>> 	"Ensure proper encoding"
>>>>
>>>> 	self assert: '' squeakToUtf8 equals: ''.
>>>> 	self assert: 'Hello World' squeakToUtf8 equals: 'Hello World'.
>>>> 	self assert: 'Grüß Gott' squeakToUtf8 asByteArray
>>>> 		equals: #[71 114 195 188 195 159 32 71 111 116 116]!
>>>>
>>>> ----- Method: UTF8TextConverterTest>>testStrictConversion (in category
>>>> 'tests') -----
>>>> testStrictConversion
>>>> 	"Ensure the strict conversions do what they should"
>>>>
>>>> 	| strict |
>>>> 	strict := UTF8TextConverter strictUtf8Conversions.
>>>> 	[UTF8TextConverter strictUtf8Conversions: true.
>>>> 	self should:[ 'Grüß Gott' utf8ToSqueak ] raise: Error.
>>>> 	] ensure:[UTF8TextConverter strictUtf8Conversions: strict].!
>>>>
>>>> ----- Method: UTF8TextConverterTest>>testUtf8ToSqueak (in category
>>>> 'tests')
>>>> -----
>>>> testUtf8ToSqueak
>>>> 	"Ensure proper encoding"
>>>>
>>>> 	self assert: '' utf8ToSqueak equals: ''.
>>>> 	self assert: 'Hello World' utf8ToSqueak equals: 'Hello World'.
>>>> 	self assert: #[71 114 195 188 195 159 32 71 111 116 116] asString
>>>> utf8ToSqueak
>>>> 		equals: 'Grüß Gott'
>>>>
>>>> !
>>>>
>>>>
>>>>
>>>
>>
>>
>>
>


More information about the Squeak-dev mailing list