CharacterEncoderImplementations__ISO10646_to_UTF8.st
branchjv
changeset 19863 513bd7237fe7
parent 18807 d79ce9fb5198
parent 19838 a6ca726d596c
child 21387 e3865533e6a6
--- a/CharacterEncoderImplementations__ISO10646_to_UTF8.st	Sun May 15 08:38:43 2016 +0100
+++ b/CharacterEncoderImplementations__ISO10646_to_UTF8.st	Tue May 17 10:05:14 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2004 by eXept Software AG
 	      All Rights Reserved
@@ -52,7 +54,7 @@
   Decoding (utf8 to unicode):
      |t|
 
-     t := ISO10646_to_UTF8 encodeString:'Helloœ'.
+     t := ISO10646_to_UTF8 encodeString:'Helloœ'.
      ISO10646_to_UTF8 decodeString:t.
 "
 ! !
@@ -100,238 +102,9 @@
      This is only useful, when reading from external sources or communicating with
      other systems 
      (ST/X never uses utf8 internally, but always uses strings of fully decoded unicode characters).
-     This only handles up-to 30bit characters.
-
-     If you work a lot with utf-8 encoded textFiles,
-     this is a first-class candidate for a primitive."
-
-    |sz anyAbove7BitAscii nBitsRequired
-     ascii "{ Class: SmallInteger }"
-     byte  "{ Class: SmallInteger }"
-     s newString idx next6Bits last6Bits
-     errorReporter|
-
-    "/ fast track, also avoid creation of new strings if aStringOrByteCollection is already a 7-bit string
-    aStringOrByteCollection containsNon7BitAscii ifFalse:[
-        ^ aStringOrByteCollection asSingleByteString
-    ].
-
-    errorReporter := [:msg | 
-                             DecodingError newException
-                                defaultValue:aStringOrByteCollection;
-                                raiseRequestWith:aStringOrByteCollection errorString:msg.
-                     ].
-
-    next6Bits := [
-                    | byte |
-
-                    byte := s nextByte.
-                    byte isNil ifTrue:[^ errorReporter value:'short utf8 string'].
-                    ascii := (ascii bitShift:6) bitOr:(byte bitAnd:2r00111111).
-                    (byte bitAnd:2r11000000) ~~ 2r10000000 ifTrue:[
-                        ^ errorReporter value:'illegal followbyte (next)'.
-                    ].
-                 ].
-
-    last6Bits := [
-                    | a byte |
-
-                    byte := s nextByte.
-                    byte isNil ifTrue:[^ errorReporter value:'short utf8 string'].
-                    a := (ascii bitShift:6) bitOr:(byte bitAnd:2r00111111).
-                    (a > 16r3FFFFFFF) ifTrue:[
-                        "/ ST/X can only represent 30 bit unicode characters.
-                        errorReporter value:'unicode character out of range'.
-                        a := 16r3FFFFFFF.
-                    ].
-                    ascii := a.
-                    (byte bitAnd:2r11000000) ~~ 2r10000000 ifTrue:[
-                        ^ errorReporter value:'illegal followbyte (last)'.
-                    ].
-                 ].
-
-    nBitsRequired := 8.
-    anyAbove7BitAscii := false.
-    sz := 0.
-    s := aStringOrByteCollection readStream.
+     This only handles up-to 30bit characters."
 
-    "first determine the string size"
-    [s atEnd] whileFalse:[
-        byte := ascii := s nextByte.
-        (byte bitAnd:16r80) ~~ 0 ifTrue:[
-            anyAbove7BitAscii := true.
-            (byte bitAnd:2r11100000) == 2r11000000 ifTrue:[
-                "/ 80 .. 7FF
-                ascii := (byte bitAnd:2r00011111).
-                next6Bits value.
-                ascii > 16rFF ifTrue:[
-                    nBitsRequired := nBitsRequired max:16
-                ].
-                "/ a strict utf8 decoder does not allow overlong sequences
-                ascii < 16r80 ifTrue:[
-                    errorReporter value:'overlong utf8 sequence'
-                ].
-            ] ifFalse:[
-                (byte bitAnd:2r11110000) == 2r11100000 ifTrue:[
-                    "/ 800 .. FFFF
-                    ascii := (byte bitAnd:2r00001111).
-                    next6Bits value.
-                    next6Bits value.
-                    ascii > 16rFF ifTrue:[
-                        nBitsRequired := nBitsRequired max:16
-                    ].
-                    ascii < 16r800 ifTrue:[
-                        errorReporter value:'overlong utf8 sequence'
-                    ].
-                ] ifFalse:[
-                    (byte bitAnd:2r11111000) == 2r11110000 ifTrue:[
-                        "/ 10000 .. 1FFFFF
-                        ascii := (byte bitAnd:2r00000111).
-                        next6Bits value.
-                        next6Bits value.
-                        next6Bits value.
-                        ascii > 16rFF ifTrue:[
-                            ascii > 16rFFFF ifTrue:[
-                                nBitsRequired := nBitsRequired max:32
-                            ] ifFalse:[
-                                nBitsRequired := nBitsRequired max:16
-                            ]
-                        ].
-                        ascii < 16r10000 ifTrue:[
-                            errorReporter value:'overlong utf8 sequence'
-                        ].
-                    ] ifFalse:[
-                        (byte bitAnd:2r11111100) == 2r11111000 ifTrue:[
-                            "/ 200000 .. 3FFFFFF
-                            ascii := (byte bitAnd:2r00000011).
-                            next6Bits value.
-                            next6Bits value.
-                            next6Bits value.
-                            next6Bits value.
-                            ascii > 16rFF ifTrue:[
-                                ascii > 16rFFFF ifTrue:[
-                                    nBitsRequired := nBitsRequired max:32
-                                ] ifFalse:[
-                                    nBitsRequired := nBitsRequired max:16
-                                ]
-                            ].
-                            ascii < 200000 ifTrue:[
-                                errorReporter value:'overlong utf8 sequence'
-                            ].
-                        ] ifFalse:[
-                            (byte bitAnd:2r11111110) == 2r11111100 ifTrue:[
-                                "/ 4000000 .. 7FFFFFFF
-                                ascii := (byte bitAnd:2r00000001).
-                                next6Bits value.
-                                next6Bits value.
-                                next6Bits value.
-                                next6Bits value.
-                                last6Bits value.
-                                ascii > 16rFF ifTrue:[
-                                    ascii > 16rFFFF ifTrue:[
-                                        nBitsRequired := nBitsRequired max:32
-                                    ] ifFalse:[
-                                        nBitsRequired := nBitsRequired max:16
-                                    ]
-                                ].
-                                ascii < 16r4000000 ifTrue:[
-                                    errorReporter value:'overlong utf8 sequence'
-                                ].
-                            ] ifFalse:[
-                                errorReporter value:'invalid utf8 encoding'
-                            ]
-                        ]
-                    ]
-                ]
-            ].
-        ].
-        sz := sz + 1.
-    ].
-    nBitsRequired == 8 ifTrue:[
-        anyAbove7BitAscii ifFalse:[
-            "/ can return the original string
-            aStringOrByteCollection isString ifTrue:[^ aStringOrByteCollection].
-        ].
-        newString := String uninitializedNew:sz
-    ] ifFalse:[
-        nBitsRequired <= 16 ifTrue:[
-            newString := Unicode16String new:sz
-        ] ifFalse:[
-            newString := Unicode32String new:sz
-        ]
-    ].
-
-    next6Bits := [
-                    |byte|
-
-                    byte := s nextByte.
-                    ascii := (ascii bitShift:6) bitOr:(byte bitAnd:2r00111111).
-                 ].
-
-    s reset.
-    idx := 1.
-
-    "now fill the string"
-    [s atEnd] whileFalse:[
-        byte := ascii := s nextByte.
-        (byte bitAnd:2r10000000) ~~ 0 ifTrue:[
-            (byte bitAnd:2r11100000) == 2r11000000 ifTrue:[
-                ascii := (byte bitAnd:2r00011111).
-                next6Bits value.
-            ] ifFalse:[
-                (byte bitAnd:2r11110000) == 2r11100000 ifTrue:[
-                    ascii := (byte bitAnd:2r00001111).
-                    next6Bits value.
-                    next6Bits value.
-                ] ifFalse:[
-                    (byte bitAnd:2r11111000) == 2r11110000 ifTrue:[
-                        ascii := (byte bitAnd:2r00000111).
-                        next6Bits value.
-                        next6Bits value.
-                        next6Bits value.
-                    ] ifFalse:[
-                        (byte bitAnd:2r11111100) == 2r11111000 ifTrue:[
-                            ascii := (byte bitAnd:2r00000011).
-                            next6Bits value.
-                            next6Bits value.
-                            next6Bits value.
-                            next6Bits value.
-                        ] ifFalse:[
-                            (byte bitAnd:2r11111110) == 2r11111100 ifTrue:[
-                                ascii := (byte bitAnd:2r00000001).
-                                next6Bits value.
-                                next6Bits value.
-                                next6Bits value.
-                                next6Bits value.
-                                last6Bits value.
-                            ]
-                        ]
-                    ]
-                ]
-            ].
-        ].
-        newString at:idx put:(Character value:ascii).
-        idx := idx + 1.
-    ].
-    ^ newString
-
-    "
-     CharacterArray fromUTF8Bytes:#[ 16r41 16r42 ]
-     CharacterArray fromUTF8Bytes:#[ 16rC1 16r02 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE0 16r81 16r02 ]
-     CharacterArray fromUTF8Bytes:#[ 16rEF 16rBF 16rBF ]
-
-   rfc2279 examples:
-     CharacterArray fromUTF8Bytes:#[ 16r41 16rE2 16r89 16rA2 16rCE 16r91 16r2E ]
-     CharacterArray fromUTF8Bytes:#[ 16rED 16r95 16r9C 16rEA 16rB5 16rAD 16rEC 16r96 16rB4 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE6 16r97 16rA5 16rE6 16r9C 16rAC 16rE8 16rAA 16r9E ]
-
-   invalid:
-     CharacterArray fromUTF8Bytes:#[ 16rC0 16r80 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE0 16r80 16r80 ]
-    "
-
-    "Modified: / 18-09-2006 / 19:55:52 / cg"
+    ^ CharacterArray decodeFromUTF8:aStringOrByteCollection.
 !
 
 encode:aCode
@@ -341,87 +114,9 @@
 encodeString:aUnicodeString
     "return the UTF-8 representation of a Unicode string.
      The resulting string is only useful to be stored on some external file,
-     not for being used inside ST/X.
-
-     If you work a lot with utf8 encoded textFiles,
-     this is a first-class candidate for a primitive."
-
-    |s
-     stringSize "{ Class: SmallInteger }"|
-
-    "/ avoid creation of new strings if possible
-    aUnicodeString containsNon7BitAscii ifFalse:[
-        ^ aUnicodeString asSingleByteString
-    ].
-
-    stringSize := aUnicodeString size.
-    s := WriteStream on:(String uninitializedNew:(stringSize * 3 // 2)).
-    1 to:stringSize do:[:idx |
-        |character codePoint "{Class: SmallInteger }" b1 b2 b3 b4 b5 v "{Class: SmallInteger }"|
+     not for being used inside ST/X."
 
-        character := aUnicodeString at:idx.
-        codePoint := character codePoint.
-        codePoint <= 16r7F ifTrue:[
-            s nextPut:character.
-        ] ifFalse:[
-            b1 := Character value:((codePoint bitAnd:16r3F) bitOr:2r10000000).
-            v := codePoint bitShift:-6.
-            v <= 16r1F ifTrue:[
-                s nextPut:(Character value:(v bitOr:2r11000000)).
-                s nextPut:b1.
-            ] ifFalse:[
-                b2 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
-                v := v bitShift:-6.
-                v <= 16r0F ifTrue:[
-                    s nextPut:(Character value:(v bitOr:2r11100000)).
-                    s nextPut:b2; nextPut:b1.
-                ] ifFalse:[
-                    b3 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
-                    v := v bitShift:-6.
-                    v <= 16r07 ifTrue:[
-                        s nextPut:(Character value:(v bitOr:2r11110000)).
-                        s nextPut:b3; nextPut:b2; nextPut:b1.
-                    ] ifFalse:[
-                        b4 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
-                        v := v bitShift:-6.
-                        v <= 16r03 ifTrue:[
-                            s nextPut:(Character value:(v bitOr:2r11111000)).
-                            s nextPut:b4; nextPut:b3; nextPut:b2; nextPut:b1.
-                        ] ifFalse:[
-                            b5 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
-                            v := v bitShift:-6.
-                            v <= 16r01 ifTrue:[
-                                s nextPut:(Character value:(v bitOr:2r11111100)).
-                                s nextPut:b5; nextPut:b4; nextPut:b3; nextPut:b2; nextPut:b1.
-                            ] ifFalse:[
-                                "/ cannot happen - we only support up to 30 bit characters
-                                EncodingError raiseWith:character errorString:'codePoint > 31bit in #utf8Encode'.
-                            ]
-                        ].
-                    ].
-                ].
-            ].
-        ].
-    ].
-
-    ^ s contents
-
-    "
-     (self encodeString:'hello') asByteArray                             #[104 101 108 108 111]
-     (self encodeString:(Character value:16r40) asString) asByteArray    #[64]
-     (self encodeString:(Character value:16r7F) asString) asByteArray    #[127]
-     (self encodeString:(Character value:16r80) asString) asByteArray    #[194 128]
-     (self encodeString:(Character value:16rFF) asString) asByteArray    #[195 191]
-     (self encodeString:(Character value:16r100) asString) asByteArray   #[196 128]
-     (self encodeString:(Character value:16r200) asString) asByteArray   #[200 128]
-     (self encodeString:(Character value:16r400) asString) asByteArray   #[208 128]
-     (self encodeString:(Character value:16r800) asString) asByteArray   #[224 160 128]
-     (self encodeString:(Character value:16r1000) asString) asByteArray  #[225 128 128]
-     (self encodeString:(Character value:16r2000) asString) asByteArray  #[226 128 128]
-     (self encodeString:(Character value:16r4000) asString) asByteArray  #[228 128 128]
-     (self encodeString:(Character value:16r8000) asString) asByteArray  #[232 128 128]
-     (self encodeString:(Character value:16rFFFF) asString) asByteArray  #[239 191 191]
-    "
+    ^ aUnicodeString utf8Encoded.
 ! !
 
 !ISO10646_to_UTF8 methodsFor:'queries'!