Interface.hs 5.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160
  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 hiding (typeName)
  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 :: Bool -> [String] -> Interface -> Artifact
  12. interfaceModule useAeson modulepath i =
  13. artifactPath (intercalate "/" modulepath) $
  14. artifactText ((ifModuleName i) ++ ".hs") $
  15. prettyLazyText 1000 $
  16. stack $
  17. [ text "{-# LANGUAGE DeriveDataTypeable #-}"
  18. , text "{-# LANGUAGE DeriveGeneric #-}"
  19. , text "{-# OPTIONS_GHC -fno-warn-unused-imports #-}"
  20. , empty
  21. , text "module"
  22. <+> im (ifModuleName i)
  23. <+> text "where"
  24. , empty
  25. , stack $ typeimports ++ extraimports
  26. , empty
  27. , schemaDoc useAeson (ifModuleName i) (producerSchema i)
  28. , empty
  29. , schemaDoc useAeson (ifModuleName i) (consumerSchema i)
  30. , empty
  31. ]
  32. where
  33. im mname = mconcat $ punctuate dot
  34. $ map text (modulepath ++ [mname])
  35. tm mname = mconcat $ punctuate dot
  36. $ map text (typepath modulepath ++ ["Types", mname])
  37. where typepath = reverse . drop 1 . reverse
  38. typeimports = map (\a -> importDecl tm a </> qualifiedImportDecl tm a)
  39. $ nub
  40. $ map importType
  41. $ (++ [sequence_num_t])
  42. $ interfaceTypes i
  43. extraimports = [ text "import Data.Serialize"
  44. , text "import Data.Typeable"
  45. , text "import Data.Data"
  46. , text "import GHC.Generics (Generic)"
  47. , text "import qualified Test.QuickCheck as Q"
  48. ] ++
  49. [ text "import Data.Aeson (ToJSON,FromJSON)" | useAeson ]
  50. schemaDoc :: Bool -> String -> Schema -> Doc
  51. schemaDoc _ interfaceName (Schema schemaName []) =
  52. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  53. <+> text interfaceName <+> text "interface: schema is empty"
  54. schemaDoc useAeson interfaceName s@(Schema schemaName schema) = stack $
  55. [ text "-- Define" <+> text schemaName <+> text "schema for"
  56. <+> text interfaceName <+> text "interface"
  57. , text "data" <+> text typeName
  58. , indent 2 $ encloseStack equals deriv (text "|")
  59. [ text (constructorName n) <+> text (typeHaskellType t)
  60. | (_, (Message n t)) <- schema
  61. ]
  62. , empty
  63. , text ("put" ++ typeName) <+> colon <> colon <+> text "Putter" <+> text typeName
  64. , stack
  65. [ text ("put" ++ typeName)
  66. <+> parens (text (constructorName n) <+> text "m")
  67. <+> equals
  68. <+> primTypePutter (sizedPrim Bits32) <+> ppr h <+> text ">>"
  69. <+> text "put" <+> text "m"
  70. | (h, Message n _) <- schema ]
  71. , empty
  72. , text ("get" ++ typeName) <+> colon <> colon <+> text "Get" <+> text typeName
  73. , text ("get" ++ typeName) <+> equals <+> text "do"
  74. , indent 2 $ stack
  75. [ text "a <-" <+> primTypeGetter (sizedPrim Bits32)
  76. , text "case a of"
  77. , indent 2 $ stack $
  78. [ ppr h <+> text "-> do" </> (indent 2 (stack
  79. [ text "m <- get"
  80. , text "return" <+> parens (text (constructorName n) <+> text "m")
  81. ]))
  82. | (h,Message n _) <- schema
  83. ] ++
  84. [ text "_ -> fail"
  85. <+> dquotes (text "encountered unknown tag in get" <> text typeName)
  86. ]
  87. ]
  88. , empty
  89. , serializeInstance typeName
  90. , empty
  91. , text ("arbitrary" ++ typeName) <+> colon <> colon <+> text "Q.Gen" <+> text typeName
  92. , text ("arbitrary" ++ typeName) <+> equals
  93. , indent 2 $ text "Q.oneof" <+> encloseStack lbracket rbracket comma
  94. [ text "do" </> (indent 4 (stack
  95. [ text "a <- Q.arbitrary"
  96. , text "return" <+> parens (text (constructorName n) <+> text "a")
  97. ]))
  98. | (_, Message n _) <- schema
  99. ]
  100. , empty
  101. , arbitraryInstance typeName
  102. , empty
  103. ] ++
  104. [ toJSONInstance typeName | useAeson ] ++
  105. [ fromJSONInstance typeName | useAeson ] ++
  106. [ seqnumGetter typeName s ]
  107. where
  108. constructorName n = userTypeModuleName n ++ schemaName
  109. deriv = text "deriving (Eq, Show, Data, Typeable, Generic)"
  110. typeName = interfaceName ++ schemaName
  111. ifModuleName :: Interface -> String
  112. ifModuleName (Interface iname _ _) = aux iname
  113. where
  114. aux :: String -> String
  115. aux = first_cap . u_to_camel
  116. first_cap (s:ss) = (toUpper s) : ss
  117. first_cap [] = []
  118. u_to_camel ('_':'i':[]) = []
  119. u_to_camel ('_':[]) = []
  120. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  121. u_to_camel (a:as) = a : u_to_camel as
  122. u_to_camel [] = []
  123. seqnumGetter :: String -> Schema -> Doc
  124. seqnumGetter _ (Schema _ []) = empty
  125. seqnumGetter typeName (Schema schemaName ms) = stack
  126. [ text "seqNumGetter" <> text typeName
  127. <+> colon <> colon <+> text typeName
  128. <+> text "->" <+> text "SequenceNum"
  129. , stack [ text "seqNumGetter" <> text typeName
  130. <+> parens (text (constructorName mname) <+> text "_a")
  131. <+> equals <+> aux mtype
  132. | (_,Message mname mtype) <- ms
  133. ]
  134. ]
  135. where
  136. constructorName n = userTypeModuleName n ++ schemaName
  137. aux mtype
  138. | isSeqNum mtype = text "_a"
  139. | isSeqNumbered mtype = text (userTypeModuleName (structTypeName mtype))
  140. <> dot <> text "seqnum" <+> text "_a"
  141. | otherwise = text "error \"impossible: should not be asking for"
  142. <+> text "sequence number of non-attribute\""
  143. isSeqNum a = a == sequence_num_t
  144. -- XXX the following is ugly and i know it:
  145. isSeqNumbered (StructType _ [("seqnum",_),("val",_)]) = True
  146. isSeqNumbered _ = False
  147. structTypeName (StructType a _) = a
  148. structTypeName _ = error "impossible"