{-| Description: Copyright: (c) 2020 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: experimental Portability: portable -} module Data.Text.Encoding.MsJIS.Test.Unit (tests) where import qualified Test.HUnit as U import Test.HUnit ( (@=?), (@?=), (~:) ) import qualified Data.ByteString as BS import qualified Data.Maybe as Y import qualified Data.Text as T import qualified System.IO.Unsafe as IO.U import Data.Text.Encoding.MsJIS import Test.Libcdio.Unit.Common testFile :: FilePath testFile = dataFile "CP932.txt" charRef :: [(JISChar, T.Text)] charRef = IO.U.unsafePerformIO $ do ls <- lines <$> readFile testFile return . flip Y.mapMaybe ls $ \l -> case words l of [] -> Nothing [_] -> Nothing (('#':_):_) -> Nothing (_:('#':_):_) -> Nothing (j:u:_) -> Just (toJIS $ read j, T.singleton . toEnum $ read u) where toJIS i | i > 0xFF = uncurry Double . mapBoth fromIntegral $ divMod i (0x100 :: Word) | otherwise = Single $ fromIntegral i tests :: U.Test tests = "Data.Text.Encoding.MsJIS" ~: U.TestList [ decode , encode , duplicatesDuplicated ] decode :: U.Test decode = "JIS characters are read correctly" ~: U.TestList [ show j ++ " -> " ++ T.unpack u ~: U.TestCase (decodeMsJIS' (unpack j) @?= Right u) | (j, u) <- charRef ] encode :: U.Test encode = "JIS characters are encoded correctly" ~: U.TestList [ T.unpack u ++ " -> " ++ show j ~: U.TestCase (Right (unpack j) @=? encodeMsJIS' u) | (j, u) <- charRef , notElem j duplicateChars ] duplicatesDuplicated :: U.Test duplicatesDuplicated = "Duplicate JIS characters roundtrip to something else" ~: U.TestList [ U.TestCase $ do c <- either decodeFailure return $ decodeMsJIS' bs bs' <- either encodeFailure return $ encodeMsJIS' c U.assert $ bs /= bs' | bs <- map unpack duplicateChars ] where decodeFailure = U.assertFailure . mappend "JIS decode failed with " . show encodeFailure = U.assertFailure . mappend "JIS encode failed with " . show unpack :: JISChar -> BS.ByteString unpack (Single w) = BS.singleton w unpack (Double l t) = BS.pack [l, t] duplicateChars :: [JISChar] duplicateChars = [ Double 0x81 0xBE , Double 0x81 0xBF , Double 0x81 0xCA , Double 0x81 0xDA , Double 0x81 0xDB , Double 0x81 0xDF , Double 0x81 0xE0 , Double 0x81 0xE3 , Double 0x81 0xE6 , Double 0x81 0xE7 ] ++ [ Double 0x87 t | t <- [0x54..0x5D] ] ++ [ Double 0x87 0x82 , Double 0x87 0x84 , Double 0x87 0x8A , Double 0x87 0x9A ] ++ [ Double 0xED t | t <- [0x40..0x7E] ++ [0x80..0xFC] ] ++ [ Double 0xEE t | t <- [0x40..0x7E] ++ [0x80..0xEC] ++ [0xEF..0xFC] ]