294 lines
17 KiB
Haskell
294 lines
17 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, enc64url, dec64url)
|
|
import Encoding.Url (encurl, decurl)
|
|
import Encoding.Base62 (enc62, dec62)
|
|
import Encoding.Base45 (enc45, dec45)
|
|
import Encoding.Base32 (enc32, dec32)
|
|
import Encoding.Base16 (enc16, dec16)
|
|
import Encoding.Base10 (enc10, dec10)
|
|
import Encoding.Base8 (enc8, dec8)
|
|
import Encoding.Base2 (enc2, dec2)
|
|
import Encoding.QuotedPrintable (encqp, decqp)
|
|
import Encoding.UnixToUnix (encuu, decuu)
|
|
import Encoding.Xx (encxx, decxx)
|
|
import Encoding.Yenc (ency, decy)
|
|
import Encoding.Rotate (rotate)
|
|
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 (dec64 \"\xFB\xFF\")," (BSU.fromString "+/8=") (dec64 $ BSU.fromString "\xFB\xFF")
|
|
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 \"+/8=\")," (BSU.fromString "\xFB\xFF") (dec64 $ BSU.fromString "+/8=")
|
|
assertEqual "for (dec64 \"8J+Ygg==\")," (BSU.fromString "😂") (dec64 $ BSU.fromString "8J+Ygg==")
|
|
|
|
testEnc64Url :: Test
|
|
testEnc64Url = TestCase $ do
|
|
assertEqual "for (enc64url \"Hello, World!\")," (BSU.fromString "SGVsbG8sIFdvcmxkIQ==") (enc64url helloWorldBS)
|
|
assertEqual "for (enc64url \"Haskell\")," (BSU.fromString "SGFza2VsbA==") (enc64url haskellBS)
|
|
assertEqual "for (enc64url \"\x00\x01\x02\")," (BSU.fromString "AAEC") (enc64url $ BSU.fromString "\x00\x01\x02")
|
|
-- assertEqual "for (enc64url \"\xFB\xFF\")," (BSU.fromString "-_8=") (enc64url $ BSU.fromString "\xFB\xFF")
|
|
assertEqual "for (enc64url \"😂\")," (BSU.fromString "8J-Ygg==") (enc64url emojiBS)
|
|
|
|
testDec64Url :: Test
|
|
testDec64Url = TestCase $ do
|
|
assertEqual "for (dec64url \"SGVsbG8sIFdvcmxkIQ==\")," helloWorldBS (dec64url $ BSU.fromString "SGVsbG8sIFdvcmxkIQ==")
|
|
assertEqual "for (dec64url \"SGFza2VsbA==\")," haskellBS (dec64url $ BSU.fromString "SGFza2VsbA==")
|
|
assertEqual "for (dec64url \"AAEC\")," (BSU.fromString "\x00\x01\x02") (dec64url $ BSU.fromString "AAEC")
|
|
-- assertEqual "for (dec64url \"-_8=\")," (BSU.fromString "\xFB\xFF") (dec64url $ BSU.fromString "-_8=")
|
|
assertEqual "for (dec64url \"8J-Ygg==\")," (BSU.fromString "😂") (dec64url $ BSU.fromString "8J-Ygg==")
|
|
|
|
testEncUrl :: Test
|
|
testEncUrl = TestCase $ do
|
|
assertEqual "for (encurl \"Hello, World\")," (BSU.fromString "Hello%2C%20World%21") (encurl helloWorldBS)
|
|
assertEqual "for (encurl \"http://example.com/?page=index.php\")," (BSU.fromString "http%3A%2F%2Fexample.com%2F%3Fpage%3Dindex.php") (encurl $ BSU.fromString "http://example.com/?page=index.php")
|
|
assertEqual "for (encurl \"😂\")," (BSU.fromString "%F0%9F%98%82") (encurl emojiBS)
|
|
|
|
testDecUrl :: Test
|
|
testDecUrl = TestCase $ do
|
|
assertEqual "for (decurl \"Hello%2C%20World%21\")," helloWorldBS (decurl $ BSU.fromString "Hello%2C%20World%21")
|
|
assertEqual "for (decurl \"http%3A%2F%2Fexample.com%2F%3Fpage%3Dindex.php\")," (BSU.fromString "http://example.com/?page=index.php") (decurl $ BSU.fromString "http%3A%2F%2Fexample.com%2F%3Fpage%3Dindex.php")
|
|
assertEqual "for (decurl \"%F0%9F%98%82\")," (BSU.fromString "😂") (decurl $ BSU.fromString "%F0%9F%98%82")
|
|
|
|
testEnc62 :: Test
|
|
testEnc62 = TestCase $ do
|
|
assertEqual "for (enc62 \"Hello, World!\")," (BSU.fromString "1wJfrzvdbtXUOlUjUf") (enc62 helloWorldBS)
|
|
assertEqual "for (enc62 \"Haskell\")," (BSU.fromString "1VJEByfMCK") (enc62 haskellBS)
|
|
assertEqual "for (enc62 \"😂\")," (BSU.fromString "4PCnnm") (enc62 emojiBS)
|
|
|
|
testDec62 :: Test
|
|
testDec62 = TestCase $ do
|
|
assertEqual "for (dec62 \"1wJfrzvdbtXUOlUjUf\")," helloWorldBS (dec62 $ BSU.fromString "1wJfrzvdbtXUOlUjUf")
|
|
assertEqual "for (dec62 \"1VJEByfMCK\")," haskellBS (dec62 $ BSU.fromString "1VJEByfMCK")
|
|
assertEqual "for (dec62 \"4PCnnm\")," emojiBS (dec62 $ BSU.fromString "4PCnnm")
|
|
|
|
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")
|
|
|
|
testEnc10 :: Test
|
|
testEnc10 = TestCase $ do
|
|
assertEqual "for (enc10 \"Hello, World!\")," (BSU.fromString "72 101 108 108 111 44 32 87 111 114 108 100 33") (enc10 helloWorldBS)
|
|
assertEqual "for (enc10 \"Haskell\")," (BSU.fromString "72 97 115 107 101 108 108") (enc10 haskellBS)
|
|
assertEqual "for (enc10 \"😂\")," (BSU.fromString "240 159 152 130") (enc10 emojiBS)
|
|
|
|
testDec10 :: Test
|
|
testDec10 = TestCase $ do
|
|
assertEqual "for (dec10 \"72 101 108 108 111 44 32 87 111 114 108 100 33\")," helloWorldBS (dec10 $ BSU.fromString "72 101 108 108 111 44 32 87 111 114 108 100 33")
|
|
assertEqual "for (dec10 \"72 97 115 107 101 108 108\")," haskellBS (dec10 $ BSU.fromString "72 97 115 107 101 108 108")
|
|
assertEqual "for (dec10 \"240 159 152 130\")," emojiBS (dec10 $ BSU.fromString "240 159 152 130")
|
|
|
|
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=\r\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\r\nsoftware=20has=20limits=20on=20line=20length.")
|
|
assertEqual "for (decqp \"=F0=9F=98=82\")," emojiBS (decqp $ BSU.fromString "=F0=9F=98=82")
|
|
|
|
testEncUu :: Test
|
|
testEncUu = TestCase $ do
|
|
assertEqual "for (encuu \"Hello, World!\")," (BSU.fromString "-2&5L;&\\L(%=O<FQD(0") (encuu helloWorldBS)
|
|
assertEqual "for (encuu \"Haskell\")," (BSU.fromString "'2&%S:V5L; ") (encuu haskellBS)
|
|
assertEqual "for (encuu \"😂\")," (BSU.fromString "$\\)^8@@") (encuu emojiBS)
|
|
|
|
testDecUu :: Test
|
|
testDecUu = TestCase $ do
|
|
assertEqual "for (decuu \"-2&5L;&\\L(%=O<FQD(0\")," helloWorldBS (decuu $ BSU.fromString "-2&5L;&\\L(%=O<FQD(0")
|
|
assertEqual "for (decuu \"'2&%S:V5L;\")," haskellBS (decuu $ BSU.fromString "'2&%S:V5L; ")
|
|
assertEqual "for (decuu \"$\\)^8@@\")," (BSU.fromString "😂") (decuu $ BSU.fromString "$\\)^8@@")
|
|
|
|
testEncXx :: Test
|
|
testEncXx = TestCase $ do
|
|
assertEqual "for (encxx \"Hello, World!\")," (BSU.fromString "G4JgP4wg63RjQalY6E") (encxx helloWorldBS)
|
|
assertEqual "for (encxx \"foobar\")," (BSU.fromString "NaxjMa3m") (encxx $ BSU.fromString "foobar")
|
|
assertEqual "for (encxx \"😂\")," (BSU.fromString "w7yMUU") (encxx emojiBS)
|
|
|
|
testDecXx :: Test
|
|
testDecXx = TestCase $ do
|
|
assertEqual "for (decxx \"G4JgP4wg63RjQalY6E\")," helloWorldBS (decxx $ BSU.fromString "G4JgP4wg63RjQalY6E")
|
|
assertEqual "for (decxx \"NaxjMa3m\")," (BSU.fromString "foobar") (decxx $ BSU.fromString "NaxjMa3m")
|
|
assertEqual "for (decxx \"w7yMUU\")," (BSU.fromString "😂") (decxx $ BSU.fromString "w7yMUU")
|
|
|
|
testEncYenc :: Test
|
|
testEncYenc = TestCase $ do
|
|
assertEqual "for (ency \"Hello, World!\")," (B.pack [114, 143, 150, 150, 153, 86, 74, 129, 153, 156, 150, 142, 75]) (ency helloWorldBS)
|
|
assertEqual "for (ency \"😂\")," (B.pack [26, 201, 194, 172] ) (ency emojiBS)
|
|
|
|
testDecYenc:: Test
|
|
testDecYenc= TestCase $ do
|
|
assertEqual "for (decy \"r<8f><96><96><99>VJ<81><99><9c><96><8e>K\")," helloWorldBS (decy $ B.pack [114, 143, 150, 150, 153, 86, 74, 129, 153, 156, 150, 142, 75] )
|
|
assertEqual "for (decy \"^Z<c9>¬\")," (BSU.fromString "😂") (decy $ B.pack [26, 201, 194, 172])
|
|
|
|
testRotate :: Test
|
|
testRotate = TestCase $ do
|
|
assertEqual "for (rotate 13 \"Hello, World!\")," (BSU.fromString "Uryyb, Jbeyq!") (rotate 13 (BSU.fromString "Hello, World!"))
|
|
assertEqual "for (rotate 8 \"Hello, World!\")," (BSU.fromString "Pmttw, Ewztl!") (rotate 8 (BSU.fromString "Hello, World!"))
|
|
assertEqual "for (rotate 2 \"😂\")," (BSU.fromString "😂") (rotate 2 (BSU.fromString "😂"))
|
|
|
|
|
|
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 enc64url" testEnc64Url,
|
|
TestLabel "Test dec64url" testDec64Url,
|
|
TestLabel "Test url" testEncUrl,
|
|
TestLabel "Test url" testDecUrl,
|
|
TestLabel "Test enc62" testEnc62,
|
|
TestLabel "Test dec62" testDec62,
|
|
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 enc10" testEnc10,
|
|
TestLabel "Test dec10" testDec10,
|
|
TestLabel "Test enc8 " testEnc8 ,
|
|
TestLabel "Test dec8 " testDec8 ,
|
|
TestLabel "Test dec2 " testDec2 ,
|
|
TestLabel "Test enc2 " testEnc2 ,
|
|
TestLabel "Test decqp" testDecQp,
|
|
TestLabel "Test encqp" testEncQp,
|
|
TestLabel "Test decuu" testDecUu,
|
|
TestLabel "Test encuu" testEncUu,
|
|
TestLabel "Test decuu" testDecXx,
|
|
TestLabel "Test encuu" testEncXx,
|
|
TestLabel "Test ency" testEncYenc,
|
|
TestLabel "Test rot" testRotate]
|
|
|
|
|
|
-- 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
|