Server.hs 7.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211
  1. module Gidl.Backend.Tower.Server where
  2. import Data.Monoid
  3. import Data.List (intercalate)
  4. import Gidl.Interface
  5. import Gidl.Schema
  6. import Gidl.Backend.Ivory.Types
  7. import Gidl.Backend.Ivory.Schema (ifModuleName)
  8. import Ivory.Artifact
  9. import Text.PrettyPrint.Mainland
  10. umbrellaModule :: [String] -> Interface -> Artifact
  11. umbrellaModule modulepath i =
  12. artifactPath (intercalate "/" modulepath) $
  13. artifactText (ifModuleName i ++ ".hs") $
  14. prettyLazyText 80 $
  15. stack
  16. [ text "module" <+> mname
  17. , indent 2 $ encloseStack lparen (rparen <+> text "where") comma
  18. [ text "module" <+> im "Producer"
  19. , text "module" <+> im "Consumer"
  20. , text "module" <+> im "Server"
  21. ]
  22. , text "import" <+> im "Producer"
  23. , text "import" <+> im "Consumer"
  24. , text "import" <+> im "Server"
  25. ]
  26. where
  27. modAt path = mconcat (punctuate dot (map text path))
  28. mname = modAt (modulepath ++ [ifModuleName i])
  29. im m = modAt (modulepath ++ [ifModuleName i, m])
  30. serverModule :: [String] -> Interface -> Artifact
  31. serverModule modulepath i =
  32. artifactPath (intercalate "/" (modulepath ++ [ifModuleName i])) $
  33. artifactText "Server.hs" $
  34. prettyLazyText 80 $
  35. stack
  36. [ text "{-# LANGUAGE DataKinds #-}"
  37. , text "{-# LANGUAGE RankNTypes #-}"
  38. , text "{-# LANGUAGE ScopedTypeVariables #-}"
  39. , text "{-# LANGUAGE KindSignatures #-}"
  40. , text "{-# LANGUAGE RecordWildCards #-}"
  41. , text "{-# OPTIONS_GHC -fno-warn-unused-imports #-}"
  42. , text "{-# OPTIONS_GHC -fno-warn-unused-matches #-}"
  43. , empty
  44. , text "module"
  45. <+> im "Server"
  46. <+> text "where"
  47. , empty
  48. , stack imports
  49. , empty
  50. , attrsDataType i
  51. , empty
  52. , attrsTowerConstructor i
  53. , empty
  54. , attrsInitializer i
  55. , empty
  56. , streamsDataType i
  57. , empty
  58. , streamsTowerConstructor i
  59. , empty
  60. , interfaceServer i
  61. ]
  62. where
  63. rootpath = reverse . drop 2 . reverse
  64. modAt path = mconcat (punctuate dot (map text path))
  65. im mname = modAt (modulepath ++ [ifModuleName i, mname])
  66. imports =
  67. [ text "import" <+> modAt (rootpath modulepath ++ ["Tower", "Attr"])
  68. , text "import" <+> im "Producer"
  69. , text "import" <+> im "Consumer"
  70. , text "import Ivory.Language"
  71. , text "import Ivory.Tower"
  72. ]
  73. attrsDataType :: Interface -> Doc
  74. attrsDataType i = text "data" <+> constructor <+> text "(p :: Area * -> *) ="
  75. </> indent 2 constructor
  76. </> indent 4 body
  77. where
  78. constructor = text (ifModuleName i) <> text "Attrs"
  79. body = encloseStack lbrace rbrace comma
  80. [ text n <+> colon <> colon <+> text "p"
  81. <+> parens (text (typeIvoryType t))
  82. | (aname, AttrMethod _ t) <- interfaceMethods i
  83. , let n = userEnumValueName aname
  84. ]
  85. attrsTowerConstructor :: Interface -> Doc
  86. attrsTowerConstructor i = typesig </> decl </> indent 2 body </> indent 2 ret
  87. where
  88. constructor = text (ifModuleName i) <> text "Attrs"
  89. typesig = text "tower" <> constructor <+> colon <> colon
  90. <+> constructor <+> text "Init"
  91. <+> text "->"
  92. <+> text "Tower e" <+> parens (constructor <+> text "Attr")
  93. decl = text "tower" <> constructor <+> text "ivals = do"
  94. body = stack
  95. [ text n <> text "_p <- towerAttr"
  96. <+> dquotes (text aname)
  97. <+> parens (text n <+> text "ivals")
  98. | (aname, AttrMethod _ _) <- interfaceMethods i
  99. , let n = userEnumValueName aname
  100. ]
  101. ret = text "return" <+> constructor <+> encloseStack lbrace rbrace comma
  102. [ text n <+> equals <+> text n <> text "_p"
  103. | (aname, AttrMethod _ _) <- interfaceMethods i
  104. , let n = userEnumValueName aname
  105. ]
  106. attrsInitializer :: Interface -> Doc
  107. attrsInitializer i = typesig </> decl </> indent 2 body
  108. where
  109. constructor = text (ifModuleName i) <> text "Attrs"
  110. typesig = text "init" <> constructor <+> colon <> colon
  111. <+> constructor <+> text "Init"
  112. decl = text "init" <> constructor <+> equals <+> constructor
  113. body = encloseStack lbrace rbrace comma
  114. [ text n <+> equals <+> text "izero"
  115. | (aname, AttrMethod _ _) <- interfaceMethods i
  116. , let n = userEnumValueName aname
  117. ]
  118. streamsDataType :: Interface -> Doc
  119. streamsDataType i = text "data" <+> constructor <+> text "(p :: Area * -> *) ="
  120. </> indent 2 constructor
  121. </> indent 4 body
  122. where
  123. constructor = text (ifModuleName i) <> text "Streams"
  124. body = encloseStack lbrace rbrace comma
  125. [ text n <+> colon <> colon <+> text "p"
  126. <+> parens (text (typeIvoryType t))
  127. | (aname, StreamMethod _ t) <- interfaceMethods i
  128. , let n = userEnumValueName aname
  129. ]
  130. streamsTowerConstructor :: Interface -> Doc
  131. streamsTowerConstructor i = typesig </> decl </> indent 2 body </> indent 2 ret
  132. where
  133. constructor = text (ifModuleName i) <> text "Streams"
  134. typesig = text "tower" <> constructor <+> colon <> colon
  135. <+> text "Tower e"
  136. <+> parens (constructor <+> text "ChanInput" <> comma
  137. <+> constructor <+> text "ChanOutput")
  138. decl = text "tower" <> constructor <+> text "= do"
  139. body = stack
  140. [ text n <> text "_c <- channel"
  141. | (aname, StreamMethod _ _) <- interfaceMethods i
  142. , let n = userEnumValueName aname
  143. ]
  144. ret = text "return" <+> encloseStack lparen rparen comma
  145. [ mkstream "fst", mkstream "snd"]
  146. mkstream acc = constructor </> indent 2 (encloseStack lbrace rbrace comma
  147. [ text n <+> equals <+> text acc <+> text n <> text "_c"
  148. | (aname, StreamMethod _ _) <- interfaceMethods i
  149. , let n = userEnumValueName aname
  150. ])
  151. interfaceServer :: Interface -> Doc
  152. interfaceServer i =
  153. stack [typedef, decl, indent 2 body, indent 2 ret]
  154. where
  155. constructor postfix = text (ifModuleName i) <> text postfix
  156. fname = text "tower" <> constructor "Server"
  157. typedef = fname <+> align (stack
  158. [ guardEmptySchema (consumerSchema i)
  159. (text "::" <+> constructor "Consumer")
  160. (text ":: -- no consumer schema")
  161. , guardEmptySchema (consumerSchema i) (text "->") (text " ")
  162. <+> constructor "Attrs Attr"
  163. , text "->" <+> constructor "Streams ChanOutput"
  164. , text "->" <+> text "Tower e"
  165. <+> guardEmptySchema (producerSchema i)
  166. (constructor "Producer")
  167. (text "()")
  168. ])
  169. decl = fname <+> guardEmptySchema (consumerSchema i)
  170. (constructor "Consumer{..}")
  171. empty
  172. <+> constructor "Attrs{..}"
  173. <+> constructor "Streams{..}"
  174. <+> equals <+> text "do"
  175. body = stack [ methodBody (text (userEnumValueName n)) m
  176. | (n,m) <- interfaceMethods i ]
  177. ret = text "return" <+> guardEmptySchema (producerSchema i)
  178. (constructor "Producer{..}")
  179. (text "()")
  180. methodBody n (StreamMethod _ _) =
  181. text "let" <+> n <> text "Producer" <+> equals <+> n
  182. methodBody n (AttrMethod Read _) =
  183. n <> text "ValProducer" <+> text "<- readableAttrServer"
  184. <+> n <+> n <> text "GetConsumer"
  185. methodBody n (AttrMethod Write _) =
  186. text "writableAttrServer" <+> n <+> n <> text "SetConsumer"
  187. methodBody n (AttrMethod ReadWrite _) =
  188. n <> text "ValProducer" <+> text "<- readwritableAttrServer"
  189. <+> n <+> n <> text "GetConsumer" <+> n <> text "SetConsumer"
  190. guardEmptySchema :: Schema -> Doc -> Doc -> Doc
  191. guardEmptySchema (Schema _ []) _ d = d
  192. guardEmptySchema (Schema _ _) d _ = d