{-# LANGUAGE OverloadedStrings #-} {-| Description: Emulating tests from @encoding/big5-encoder.html@ Copyright: (c) 2020 Samuel May License: MPL-2.0 Maintainer: ag.eitilt@gmail.com Stability: experimental Portability: portable -} module Test.Willow.WebPlatformTests.Manual.Encoding.Big5 ( tests ) where import qualified Data.ByteString as BS import qualified Data.Text as T import qualified Test.HUnit as U import Test.HUnit ( (~:), (~?=) ) import Web.Willow.Common.Encoding import Test.Willow.WebPlatformTests.Manual.Common tests :: U.Test tests = "big5-encoder.html" ~: U.TestList $ map testGroup testData where testGroup (n, ts) = n ~: U.TestList $ map test ts test t = nameE t ~: encodeEnc' Big5 (wrapText $ inputE t) ~?= (wrapBytes $ outputE t) wrapText s = T.snoc (T.cons 'X' s) 'X' wrapBytes bs = BS.snoc (BS.cons 0x58 bs) 0x58 testData :: [(String, [InlineEncode])] testData = [ ("sanity", [ InlineEncode { inputE = "ab" , outputE = "ab" , nameE = "very basic" } ] ), ("edge cases", [ InlineEncode { inputE = "\x9EA6" , outputE = "\x26\x23\&40614\x3B" , nameE = "Highest-pointer BMP character excluded from encoder" } , InlineEncode { inputE = "\x2626B" , outputE = "\x26\x23\&156267\x3B" , nameE = "Highest-pointer character excluded from encoder" } , InlineEncode { inputE = "\x3000" , outputE = "\xA1@" , nameE = "Lowest-pointer character included in encoder" } , InlineEncode { inputE = "\x20AC" , outputE = "\xA3\xE1" , nameE = "Euro; the highest-pointer character before a range of 30 unmapped pointers" } , InlineEncode { inputE = "\x4E00" , outputE = "\xA4@" , nameE = "The lowest-pointer character after the range of 30 unmapped pointers" } , InlineEncode { inputE = "\x27607" , outputE = "\xC8\xA4" , nameE = "The highest-pointer character before a range of 41 unmapped pointers" } , InlineEncode { inputE = "\xFFE2" , outputE = "\xC8\xCD" , nameE = "The lowest-pointer character after the range of 41 unmapped pointers" } , InlineEncode { inputE = "\x79D4" , outputE = "\xFE\xFE" , nameE = "The last character in the index" } ] ), ("not in index", [ InlineEncode { inputE = "\x2603" , outputE = "\x26\x23\&9731\x3B" , nameE = "The canonical BMP test character that is not in the index" } , InlineEncode { inputE = "\x1F4A9" , outputE = "\x26\x23\&128169\x3B" , nameE = "The canonical astral test character that is not in the index" } ] ), ("duplicate low bits", [ InlineEncode { inputE = "\x203B5" , outputE = "\xFD\&j" , nameE = "A Plane 2 character whose low 16 bits match a BMP character that has a lower pointer" } ] ), ("prefer last", [ InlineEncode { inputE = "\x2550" , outputE = "\xF9\xF9" , nameE = "A duplicate-mapped code point that prefers the highest pointer in the encoder" } ] )]