192 lines
11 KiB
Haskell
192 lines
11 KiB
Haskell
module Main where
|
|
|
|
import Test.HUnit
|
|
import Data.ByteString as B
|
|
import Data.ByteString.UTF8 as BSU
|
|
import Encoding.Base91 (enc91, dec91)
|
|
import Encoding.Base85 (enc85, dec85)
|
|
import Encoding.Base64 (enc64, dec64)
|
|
import Encoding.Base45 (enc45, dec45)
|
|
import Encoding.Base32 (enc32, dec32)
|
|
import Encoding.Base16 (enc16, dec16)
|
|
import Encoding.Base8 (enc8, dec8)
|
|
import Encoding.Base2 (enc2, dec2)
|
|
import Encoding.QuotedPrintable (encqp, decqp)
|
|
import Encoding.UnixToUnix (encuu, decuu)
|
|
import System.Exit (exitFailure, exitSuccess)
|
|
|
|
helloWorldBS :: B.ByteString
|
|
helloWorldBS = BSU.fromString "Hello, World!"
|
|
|
|
haskellBS :: B.ByteString
|
|
haskellBS = BSU.fromString "Haskell"
|
|
|
|
emojiBS :: B.ByteString
|
|
emojiBS = BSU.fromString "😂"
|
|
|
|
|
|
testEnc91 :: Test
|
|
testEnc91 = TestCase $ do
|
|
assertEqual "for (enc91 \"Hello, World!\")," (BSU.fromString ">OwJh>}AQ;r@@Y?F") (enc91 helloWorldBS)
|
|
assertEqual "for (enc91 \"Haskell\")," (BSU.fromString "3D8=d,[*G") (enc91 haskellBS)
|
|
assertEqual "for (enc91 \"😂\")," (BSU.fromString "=~m6g") (enc91 emojiBS)
|
|
|
|
testDec91 :: Test
|
|
testDec91 = TestCase $ do
|
|
assertEqual "for (dec91 \">OwJh>}AQ;r@@Y?F\")," helloWorldBS (dec91 $ BSU.fromString ">OwJh>}AQ;r@@Y?F")
|
|
assertEqual "for (dec91 \"3D8=d,[*G\")," haskellBS (dec91 $ BSU.fromString "3D8=d,[*G")
|
|
assertEqual "for (dec91 \"=~m6g\")," emojiBS (dec91 $ BSU.fromString "=~m6g")
|
|
|
|
testEnc85 :: Test
|
|
testEnc85 = TestCase $ do
|
|
assertEqual "for (enc85 \"Hello, World!\")," (BSU.fromString "87cURD_*#4DfTZ)+T") (enc85 helloWorldBS)
|
|
assertEqual "for (enc85 \"Haskell\")," (BSU.fromString "87?RTASc/") (enc85 haskellBS)
|
|
assertEqual "for (enc85 \"😂\")," (BSU.fromString "n=Q)\"") (enc85 emojiBS)
|
|
|
|
testDec85 :: Test
|
|
testDec85 = TestCase $ do
|
|
assertEqual "for (dec85 \"87cURD_*#4DfTZ)+T\")," helloWorldBS (dec85 $ BSU.fromString "87cURD_*#4DfTZ)+T")
|
|
assertEqual "for (dec85 \"87?RTASc/\")," haskellBS (dec85 $ BSU.fromString "87?RTASc/")
|
|
assertEqual "for (dec85 \"n=Q)\"\")," emojiBS (dec85 $ BSU.fromString "n=Q)\"")
|
|
|
|
testEnc64 :: Test
|
|
testEnc64 = TestCase $ do
|
|
assertEqual "for (enc64 \"Hello, World!\")," (BSU.fromString "SGVsbG8sIFdvcmxkIQ==") (enc64 helloWorldBS)
|
|
assertEqual "for (enc64 \"Haskell\")," (BSU.fromString "SGFza2VsbA==") (enc64 haskellBS)
|
|
assertEqual "for (enc64 \"\x00\x01\x02\")," (BSU.fromString "AAEC") (enc64 $ BSU.fromString "\x00\x01\x02")
|
|
assertEqual "for (enc64 \"😂\")," (BSU.fromString "8J+Ygg==") (enc64 emojiBS)
|
|
|
|
testDec64 :: Test
|
|
testDec64 = TestCase $ do
|
|
assertEqual "for (dec64 \"SGVsbG8sIFdvcmxkIQ==\")," helloWorldBS (dec64 $ BSU.fromString "SGVsbG8sIFdvcmxkIQ==")
|
|
assertEqual "for (dec64 \"SGFza2VsbA==\")," haskellBS (dec64 $ BSU.fromString "SGFza2VsbA==")
|
|
assertEqual "for (dec64 \"AAEC\")," (BSU.fromString "\x00\x01\x02") (dec64 $ BSU.fromString "AAEC")
|
|
assertEqual "for (dec64 \"8J+Ygg==\")," (BSU.fromString "😂") (dec64 $ BSU.fromString "8J+Ygg==")
|
|
|
|
testEnc45 :: Test
|
|
testEnc45 = TestCase $ do
|
|
assertEqual "for (enc45 \"Hello, World!\")," (BSU.fromString "%69 VDK2E:3404ESVDX0") (enc45 helloWorldBS)
|
|
assertEqual "for (enc45 \"Haskell\")," (BSU.fromString "Y69RQE: CI2") (enc45 haskellBS)
|
|
assertEqual "for (enc45 \"😂\")," (BSU.fromString "*IURCJ") (enc45 emojiBS)
|
|
|
|
testDec45 :: Test
|
|
testDec45 = TestCase $ do
|
|
assertEqual "for (dec45 \"%69 VDK2E:3404ESVDX0\")," helloWorldBS (dec45 $ BSU.fromString "%69 VDK2E:3404ESVDX0")
|
|
assertEqual "for (dec45 \"Y69RQE: CI2\")," haskellBS (dec45 $ BSU.fromString "Y69RQE: CI2")
|
|
assertEqual "for (dec45 \"*IURCJ\")," emojiBS (dec45 $ BSU.fromString "*IURCJ")
|
|
|
|
testEnc32 :: Test
|
|
testEnc32 = TestCase $ do
|
|
assertEqual "for (enc32 \"Hello, World!\")," (BSU.fromString "JBSWY3DPFQQFO33SNRSCC===") (enc32 helloWorldBS)
|
|
assertEqual "for (enc32 \"Haskell\")," (BSU.fromString "JBQXG23FNRWA====") (enc32 haskellBS)
|
|
assertEqual "for (enc32 \"😂\")," (BSU.fromString "6CPZRAQ=") (enc32 emojiBS)
|
|
|
|
testDec32 :: Test
|
|
testDec32 = TestCase $ do
|
|
assertEqual "for (dec32 \"JBSWY3DPFQQFO33SNRSCC===\")," helloWorldBS (dec32 $ BSU.fromString "JBSWY3DPFQQFO33SNRSCC===")
|
|
assertEqual "for (dec32 \"JBQXG23FNRWA====\")," haskellBS (dec32 $ BSU.fromString "JBQXG23FNRWA====")
|
|
-- assertEqual "for (dec32 \"AAEC\")," "\x00\x01\x02" (dec32 "AAEC")
|
|
assertEqual "for (dec32 \"6CPZRAQ=\")," emojiBS (dec32 $ BSU.fromString "6CPZRAQ=")
|
|
|
|
testEnc16 :: Test
|
|
testEnc16 = TestCase $ do
|
|
assertEqual "for (enc16 \"Hello, World!\")," (BSU.fromString "48656C6C6F2C20576F726C6421") (enc16 helloWorldBS)
|
|
assertEqual "for (enc16 \"Haskell\")," (BSU.fromString "4861736B656C6C") (enc16 haskellBS)
|
|
assertEqual "for (enc16 \"😂\")," (BSU.fromString "F09F9882") (enc16 emojiBS)
|
|
|
|
testDec16 :: Test
|
|
testDec16 = TestCase $ do
|
|
assertEqual "for (dec16 \"48656C6C6F2C20576F726C6421\")," helloWorldBS (dec16 $ BSU.fromString "48656C6C6F2C20576F726C6421")
|
|
assertEqual "for (dec16 \"4861736B656C6C\")," haskellBS (dec16 $ BSU.fromString "4861736B656C6C")
|
|
assertEqual "for (dec16 \"F09F9882\")," emojiBS (dec16 $ BSU.fromString "F09F9882")
|
|
|
|
testEnc8 :: Test
|
|
testEnc8 = TestCase $ do
|
|
assertEqual "for (enc8 \"Hello, World!\")," (BSU.fromString "110 145 154 154 157 54 40 127 157 162 154 144 41") (enc8 helloWorldBS)
|
|
assertEqual "for (enc8 \"Haskell\")," (BSU.fromString "110 141 163 153 145 154 154") (enc8 haskellBS)
|
|
assertEqual "for (enc8 \"😂\")," (BSU.fromString "360 237 230 202") (enc8 emojiBS)
|
|
|
|
testDec8 :: Test
|
|
testDec8 = TestCase $ do
|
|
assertEqual "for (dec8 \"110 145 154 154 157 54 40 127 157 162 154 144 41\")," helloWorldBS (dec8 $ BSU.fromString "110 145 154 154 157 54 40 127 157 162 154 144 41")
|
|
assertEqual "for (dec8 \"110 141 163 153 145 154 154\")," haskellBS (dec8 $ BSU.fromString "110 141 163 153 145 154 154")
|
|
assertEqual "for (dec8 \"360 237 230 202\")," emojiBS (dec8 $ BSU.fromString "360 237 230 202")
|
|
|
|
testEnc2 :: Test
|
|
testEnc2 = TestCase $ do
|
|
assertEqual "for (enc2 \"Hello, World!\")," (BSU.fromString "01001000 01100101 01101100 01101100 01101111 00101100 00100000 01010111 01101111 01110010 01101100 01100100 00100001") (enc2 helloWorldBS)
|
|
assertEqual "for (enc2 \"Haskell\")," (BSU.fromString "01001000 01100001 01110011 01101011 01100101 01101100 01101100") (enc2 haskellBS)
|
|
assertEqual "for (enc2 \"😂\")," (BSU.fromString "11110000 10011111 10011000 10000010") (enc2 emojiBS)
|
|
|
|
testDec2 :: Test
|
|
testDec2 = TestCase $ do
|
|
assertEqual "for (dec2 \"01001000 01100101 01101100 01101100 01101111 00101100 00100000 01010111 01101111 01110010 01101100 01100100 00100001\")," helloWorldBS (dec2 $ BSU.fromString "01001000 01100101 01101100 01101100 01101111 00101100 00100000 01010111 01101111 01110010 01101100 01100100 00100001")
|
|
assertEqual "for (dec2 \"01001000 01100001 01110011 01101011 01100101 01101100 01101100\")," haskellBS (dec2 $ BSU.fromString "01001000 01100001 01110011 01101011 01100101 01101100 01101100")
|
|
assertEqual "for (dec2 \"11110000 10011111 10011000 10000010\")," emojiBS (dec2 $ BSU.fromString "11110000 10011111 10011000 10000010")
|
|
|
|
testEncQp :: Test
|
|
testEncQp = TestCase $ do
|
|
assertEqual "for (encqp \"Hello, World!\")," (BSU.fromString "Hello,=20World!") (encqp helloWorldBS)
|
|
assertEqual "for (encqp \"QP works by using the equals sign = as an escape character. It also limits line length to 76, as some software has limits on line length.\")," (BSU.fromString "QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\r\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\r\nsoftware=20has=20limits=20on=20line=20length.") (encqp $ BSU.fromString "QP works by using the equals sign = as an escape character. It also limits line length to 76, as some software has limits on line length.")
|
|
assertEqual "for (encqp \"😂\")," (BSU.fromString "=F0=9F=98=82") (encqp emojiBS)
|
|
|
|
testDecQp :: Test
|
|
testDecQp = TestCase $ do
|
|
assertEqual "for (decqp \"Hello,=20World!\")," helloWorldBS (decqp $ BSU.fromString "Hello,=20World!")
|
|
assertEqual "for (decqp \"QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\r\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\r\nsoftware=20has=20limits=20on=20line=20length.\")," (BSU.fromString "QP works by using the equals sign = as an escape character. It also limits line length to 76, as some software has limits on line length.") (decqp $ BSU.fromString "QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\nsoftware=20has=20limits=20on=20line=20length.")
|
|
assertEqual "for (decqp \"=F0=9F=98=82\")," emojiBS (decqp $ BSU.fromString "=F0=9F=98=82")
|
|
|
|
-- testEnUu :: Test
|
|
-- testEnUu = TestCase $ do
|
|
-- assertEqual "for (encuu \"Hello, World!\")," "110 145 154 154 157 54 40 127 157 162 154 144 41" (encuu "Hello, World!")
|
|
-- assertEqual "for (encuu \"Haskell\")," "110 141 163 153 145 154 154" (encuu "Haskell")
|
|
-- assertEqual "for (encuu \"😂\")," "360 237 230 202" (encuu "😂")
|
|
|
|
-- testDecUu :: Test
|
|
-- testDecUu = TestCase $ do
|
|
-- assertEqual "for (decuu \"110 145 154 154 157 54 40 127 157 162 154 144 41\")," "Hello, World!" (decuu "110 145 154 154 157 54 40 127 157 162 154 144 41")
|
|
-- assertEqual "for (decuu \"110 141 163 153 145 154 154\")," "Haskell" (decuu "110 141 163 153 145 154 154")
|
|
-- assertEqual "for (decuu \"360 237 230 202\")," "😂" (decuu "360 237 230 202")
|
|
|
|
|
|
tests :: Test
|
|
tests = TestList [TestLabel "Test enc91" testEnc91,
|
|
TestLabel "Test dec91" testDec91,
|
|
TestLabel "Test enc85" testEnc85,
|
|
TestLabel "Test dec85" testDec85,
|
|
TestLabel "Test enc64" testEnc64,
|
|
TestLabel "Test dec64" testDec64,
|
|
TestLabel "Test enc45" testEnc45,
|
|
TestLabel "Test dec45" testDec45,
|
|
TestLabel "Test enc32" testEnc32,
|
|
TestLabel "Test dec32" testDec32,
|
|
TestLabel "Test enc16" testEnc16,
|
|
TestLabel "Test dec16" testDec16,
|
|
TestLabel "Test enc8 " testEnc8 ,
|
|
TestLabel "Test dec8 " testDec8 ,
|
|
TestLabel "Test dec2 " testDec2 ,
|
|
TestLabel "Test enc2 " testEnc2 ,
|
|
TestLabel "Test decqp" testDecQp,
|
|
TestLabel "Test encqp" testEncQp]
|
|
|
|
|
|
-- main :: IO Counts
|
|
-- main = runTestTT tests >>= \counts -> print counts >> runTestTTAndExit tests
|
|
|
|
-- runAndPrint :: Test -> IO Counts
|
|
-- runAndPrint t = do
|
|
-- counts <- runTestTT t
|
|
-- let label = case t of
|
|
-- TestLabel l _ -> l
|
|
-- _ -> "Unnamed test."
|
|
-- putStrLn $ label ++ ": " ++ if errors counts + failures counts == 0 then "[OK]" else "[FAIL]"
|
|
-- return counts
|
|
|
|
main :: IO ()
|
|
main = do
|
|
counts <- runTestTT tests
|
|
print counts
|
|
if errors counts + failures counts == 0
|
|
then exitSuccess
|
|
else exitFailure
|