Interface.hs 3.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117
  1. module Gidl.Backend.Haskell.Interface where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Data.Char (toUpper)
  5. import Gidl.Types
  6. import Gidl.Interface
  7. import Gidl.Schema
  8. import Gidl.Backend.Haskell.Types
  9. import Ivory.Artifact
  10. import Text.PrettyPrint.Mainland
  11. interfaceModule :: [String] -> InterfaceRepr -> Artifact
  12. interfaceModule modulepath ir =
  13. artifactPath (intercalate "/" modulepath) $
  14. artifactText ((ifModuleName ir) ++ ".hs") $
  15. prettyLazyText 80 $
  16. stack
  17. [ text "module"
  18. <+> im (ifModuleName ir)
  19. <+> text "where"
  20. , empty
  21. , stack $ typeimports ++ extraimports
  22. , empty
  23. , schemaDoc (ifModuleName ir) (producerSchema ir)
  24. , empty
  25. , schemaDoc (ifModuleName ir) (consumerSchema ir)
  26. ]
  27. where
  28. im mname = mconcat $ punctuate dot
  29. $ map text (modulepath ++ [mname])
  30. tm mname = mconcat $ punctuate dot
  31. $ map text (typepath modulepath ++ ["Types", mname])
  32. where typepath = reverse . drop 1 . reverse
  33. typeimports = map (importDecl tm)
  34. $ nub
  35. $ map importType
  36. $ interfaceTypes ir
  37. extraimports = [ text "import Data.Serialize"
  38. , text "import qualified Test.QuickCheck as Q" ]
  39. schemaDoc :: String -> Schema -> Doc
  40. schemaDoc interfaceName (Schema schemaName []) =
  41. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  42. <+> text interfaceName <+> text "interface: schema is empty"
  43. schemaDoc interfaceName (Schema schemaName schema) = stack
  44. [ text "-- Define" <+> text schemaName <+> text "schema for"
  45. <+> text interfaceName <+> text "interface"
  46. , text "data" <+> text typeName
  47. , indent 2 $ encloseStack equals deriv (text "|")
  48. [ text (constructorName n) <+> text (typeHaskellType t)
  49. | (_, (Message n t)) <- schema
  50. ]
  51. , empty
  52. , text ("put" ++ typeName) <+> colon <> colon <+> text "Putter" <+> text typeName
  53. , stack
  54. [ text ("put" ++ typeName)
  55. <+> parens (text (constructorName n) <+> text "m")
  56. <+> equals
  57. <+> text "put" <> text (cerealSize Bits32) <+> ppr h <+> text ">>"
  58. <+> text "put" <+> text "m"
  59. | (h, Message n _) <- schema ]
  60. , empty
  61. , text ("get" ++ typeName) <+> colon <> colon <+> text "Get" <+> text typeName
  62. , text ("get" ++ typeName) <+> equals <+> text "do"
  63. , indent 2 $ stack
  64. [ text "a" <+> text "<- get" <> text (cerealSize Bits32)
  65. , text "case a of"
  66. , indent 2 $ stack $
  67. [ ppr h <+> text "-> do" </> (indent 2 (stack
  68. [ text "m <- get"
  69. , text "return" <+> parens (text (constructorName n) <+> text "m")
  70. ]))
  71. | (h,Message n _) <- schema
  72. ] ++
  73. [ text "_ -> fail"
  74. <+> dquotes (text "encountered unknown tag in get" <> text typeName)
  75. ]
  76. ]
  77. , empty
  78. , serializeInstance typeName
  79. , empty
  80. , text ("arbitrary" ++ typeName) <+> colon <> colon <+> text "Q.Gen" <+> text typeName
  81. , text ("arbitrary" ++ typeName) <+> equals
  82. , indent 2 $ text "Q.oneof" <+> encloseStack lbracket rbracket comma
  83. [ text "do" </> (indent 4 (stack
  84. [ text "a <- Q.arbitrary"
  85. , text "return" <+> parens (text (constructorName n) <+> text "a")
  86. ]))
  87. | (_, Message n _) <- schema
  88. ]
  89. , empty
  90. , arbitraryInstance typeName
  91. ]
  92. where
  93. constructorName n = userTypeModuleName n ++ schemaName
  94. deriv = text "deriving (Eq, Show)"
  95. typeName = interfaceName ++ schemaName
  96. ifModuleName :: InterfaceRepr -> String
  97. ifModuleName (InterfaceRepr iname _) = aux iname
  98. where
  99. aux :: String -> String
  100. aux = first_cap . u_to_camel
  101. first_cap (s:ss) = (toUpper s) : ss
  102. first_cap [] = []
  103. u_to_camel ('_':'i':[]) = []
  104. u_to_camel ('_':[]) = []
  105. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  106. u_to_camel (a:as) = a : u_to_camel as
  107. u_to_camel [] = []