{- copyright (c) sreservoir. licensed under mit (x11). -} module Main where import Text.Regex.Less import Data.List import Test.HUnit main :: IO () main = mapM_ runTestTT tests tests :: [Test] tests = map TestList [ tests0, tests1, tests2, tests3, tests4, tests5, tests6, tests7 ] tests0 :: [Test] tests0 = [ TestLabel "sanity" $ TestCase (assertEqual "" (a+a) (2*a)) | a <- [ 1,19 .. 963 ] :: [Int] ] alnums :: [Char] alnums = '_' : ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] tests1 :: [Test] tests1 = [ TestLabel "alnum `w" $ TestCase (assertBool (show a ++ " not `w?") (truth ([a] =~ "`w"))) | a <- alnums ] tests2 :: [Test] tests2 = [ TestLabel "alnum not `W" $ TestCase (assertBool (show a ++ " is `W?") (not (truth ([a] =~ "`W")))) | a <- alnums ] tests3 :: [Test] tests3 = [ TestLabel "other `W" $ TestCase (assertBool (show a ++ " not `W?") (truth ([a] =~ "`W"))) | a <- ['\0'..'\DEL'] \\ alnums ] tests4 :: [Test] tests4 = [ TestLabel "other not `w" $ TestCase (assertBool (show a ++ " is `w?") (not (truth ([a] =~ "`w")))) | a <- ['\0'..'\DEL'] \\ alnums ] prints :: [Char] prints = [' '..'~'] tests5 :: [Test] tests5 = [ TestLabel "simple once-substitution" $ TestCase (assertEqual "doubling" (subs (a =~ ".*") "`0`0") (a ++ a)) | b <- prints, c <- prints, a <- [[b,c]] ] tests6 :: [Test] tests6 = [ TestLabel "extracting numbers" $ TestCase (assertEqual "numbers" (read (bref (fst a =~ "`d*") 0)) (snd a)) | b <- [ 1,1000 .. 100000 ] :: [Integer], a <- [(show b,b)] ] tests7 :: [Test] tests7 = [ TestLabel "testing primes :P" $ TestCase (assertEqual "primes" (snd a) (truth (replicate (fst a) '1' =~ "^1?$|^(11+?)`1+$"))) | a <- [( 2,False),( 3,False),( 4, True),( 5,False), ( 6, True),( 7,False),( 8, True),( 9, True), (10, True),(11,False),(12, True),(13,False), (14, True),(15, True),(16, True),(17,False), (18, True),(19,False),(20, True),(21, True), (22, True),(23,False),(24, True),(25, True), (26, True),(27, True),(28, True),(29,False)] ]