65 lines
1.7 KiB
Haskell

-- | Generate test cases for Nim
module TestGen.TestPermutation where
--------------------------------------------------------------------------------
import Data.Array
import Data.List
import System.IO
import Permutations
import Goldilocks
import Common
import TestGen.Shared
--------------------------------------------------------------------------------
perms :: String -> (State -> State) -> [State] -> String
perms varname f xs = unlines (header : stuff ++ footer) where
header = "const " ++ varname ++ "* : array[" ++ show (length xs) ++ ", tuple[xs:F12, ys:F12]] = "
footer = [" ]",""]
stuff = showListWith nimShowStatePair [ (x, f x) | x<-xs ]
--------------------------------------------------------------------------------
testStates12 :: [State]
testStates12 =
[ listToState' 12 [ fromInteger (a + b*i) | i<-[0..11] ]
| a <- [0,10,200,3000]
, b <- [1, 7, 23, 666]
]
testStates16 :: [State]
testStates16 =
[ listToState' 16 [ fromInteger (a + b*i) | i<-[0..15] ]
| a <- [0,10,200,3000]
, b <- [1, 7, 23, 666]
]
testStates :: Hash -> [State]
testStates hash = case hashT hash of
12 -> testStates12
16 -> testStates16
--------------------------------------------------------------------------------
printTests :: Hash -> IO ()
printTests hash = hPrintTests stdout hash
hPrintTests :: Handle -> Hash -> IO ()
hPrintTests h hash = hPutStrLn h $ unlines
[ perms "testcases_perm" (permute hash) (testStates hash)
]
writeTests :: Hash -> IO ()
writeTests hash = withFile "permTestCases.nim" WriteMode $ \h -> do
hPutStrLn h "# generated by TestGen/TestPermutation.hs\n"
hPutStrLn h "import goldilocks_hash/types\n"
hPrintTests h hash
--------------------------------------------------------------------------------