2024-10-01 11:19:19 +02:00

65 lines
1.9 KiB
Haskell

-- | Generate test cases for Nim
module TestGen.TestPermutation where
--------------------------------------------------------------------------------
import Data.Array
import Data.List
import System.IO
import Goldilocks
import Poseidon2
--------------------------------------------------------------------------------
nimShowF :: F -> String
nimShowF x = "toF( " ++ show x ++ "'u64 )"
nimShowState :: State -> String
nimShowState xs = "[ " ++ intercalate ", " (map nimShowF (elems xs)) ++ " ]"
nimShowStatePair :: (State,State) -> String
nimShowStatePair (x,y) = "( " ++ nimShowState x ++ " , " ++ nimShowState y ++ " )"
showListWith :: (a -> String) -> [a] -> [String]
showListWith f xys = zipWith (++) prefix (map f xys) where
prefix = " [ " : repeat " , "
----------------------------------------
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 ]
--------------------------------------------------------------------------------
testStates :: [State]
testStates =
[ listToState [ fromInteger (a + b*i) | i<-[0..11] ]
| a <- [0,10,200,3000]
, b <- [1, 7, 23, 666]
]
--------------------------------------------------------------------------------
printTests :: IO ()
printTests = hPrintTests stdout
hPrintTests :: Handle -> IO ()
hPrintTests h = hPutStrLn h $ unlines
[ perms "testcases_perm" permutation testStates
]
writeTests :: IO ()
writeTests = withFile "permTestCases.nim" WriteMode $ \h -> do
hPutStrLn h "# generated by TestGen/TestPermutation.hs\n"
-- hPutStrLn h "import poseidon2/types\n"
hPrintTests h
--------------------------------------------------------------------------------