Squeak 4.6: MultilingualTests-fbs.18.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

Squeak 4.6: MultilingualTests-fbs.18.mcz

commits-2
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@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@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'

!