Test.hs 2.2 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970
  1. module Gidl.Backend.Haskell.Test where
  2. import Data.Monoid
  3. import Gidl.Interface
  4. import Gidl.Schema
  5. import Gidl.Backend.Haskell.Interface
  6. import Ivory.Artifact
  7. import Text.PrettyPrint.Mainland
  8. serializeTestModule :: [String] -> [Interface] -> Artifact
  9. serializeTestModule modulepath is =
  10. artifactText "SerializeTest.hs" $
  11. prettyLazyText 1000 $
  12. stack
  13. [ text "{-# LANGUAGE ScopedTypeVariables #-}"
  14. , empty
  15. , text "module Main where"
  16. , empty
  17. , text "import Data.Serialize"
  18. , text "import System.Exit (exitFailure, exitSuccess)"
  19. , text "import qualified Test.QuickCheck as Q"
  20. , empty
  21. , stack [ text "import" <+> im (ifModuleName i) | i <- is ]
  22. , empty
  23. , text "main :: IO ()"
  24. , text "main" <+> equals <+> text "do" <+> align (stack
  25. ([ testSchema i (producerSchema i) </> testSchema i (consumerSchema i)
  26. | i <- is ] ++
  27. [ text "exitSuccess" ]))
  28. , empty
  29. , props
  30. ]
  31. where
  32. im mname = mconcat $ punctuate dot
  33. $ map text (modulepath ++ ["Interface", mname])
  34. testSchema :: Interface -> Schema -> Doc
  35. testSchema i (Schema sn []) =
  36. text "-- no tests for empty schema" <+> text (ifModuleName i ++ sn)
  37. testSchema i (Schema sn _) = stack
  38. [ text "runQC" <+> parens
  39. (text "serializeRoundtrip ::" <+> text sname <+> text "-> Bool")
  40. , text "runQC" <+> parens
  41. (text "serializeManyRoundtrip ::" <+> brackets (text sname) <+> text "-> Bool")
  42. ]
  43. where sname = ifModuleName i ++ sn
  44. props :: Doc
  45. props = stack
  46. [ text "serializeRoundtrip :: (Serialize a, Eq a) => a -> Bool"
  47. , text "serializeRoundtrip v = case runGet get (runPut (put v)) of"
  48. , indent 2 $ text "Left e -> False"
  49. , indent 2 $ text "Right v' -> v == v'"
  50. , empty
  51. , text "serializeManyRoundtrip :: (Serialize a, Eq a) => [a] -> Bool"
  52. , text "serializeManyRoundtrip vs ="
  53. , indent 2 $ text "case runGet (mapM (const get) vs) (runPut (mapM_ put vs)) of"
  54. , indent 4 $ text "Left e -> False"
  55. , indent 4 $ text "Right vs' -> vs == vs'"
  56. , empty
  57. , text "runQC :: Q.Testable p => p -> IO ()"
  58. , text "runQC prop = do"
  59. , indent 2 $ text "r <- Q.quickCheckWithResult Q.stdArgs prop"
  60. , indent 2 $ text "case r of"
  61. , indent 4 $ text "Q.Success {} -> return ()"
  62. , indent 4 $ text "_ -> exitFailure"
  63. ]