Schema.hs 7.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192
  1. module Gidl.Backend.Tower.Schema where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Gidl.Types hiding (typeName)
  5. import Gidl.Interface
  6. import Gidl.Schema
  7. import Gidl.Backend.Ivory.Types
  8. import Gidl.Backend.Ivory.Schema (ifModuleName, parserName, senderName)
  9. import Ivory.Artifact
  10. import Text.PrettyPrint.Mainland
  11. schemaModule :: [String] -> Interface -> Schema -> Artifact
  12. schemaModule modulepath ir schema =
  13. artifactPath (intercalate "/" (modulepath ++ [ifModuleName ir])) $
  14. artifactText (schemaName ++ ".hs") $
  15. prettyLazyText 80 $
  16. stack
  17. [ text "{-# LANGUAGE DataKinds #-}"
  18. , text "{-# LANGUAGE RankNTypes #-}"
  19. , text "{-# LANGUAGE ScopedTypeVariables #-}"
  20. , text "{-# OPTIONS_GHC -fno-warn-unused-imports #-}"
  21. , empty
  22. , text "module"
  23. <+> im (ifModuleName ir) <> dot <> text schemaName
  24. <+> text "where"
  25. , empty
  26. , stack $ typeimports ++ extraimports
  27. , empty
  28. , schemaDoc (ifModuleName ir) schema
  29. ]
  30. where
  31. (Schema schemaName _) = schema
  32. rootpath = reverse . drop 2 . reverse
  33. modAt path = mconcat (punctuate dot (map text path))
  34. im mname = modAt (modulepath ++ [mname])
  35. tm mname = modAt (rootpath modulepath ++ ["Ivory","Types", mname])
  36. ivoryIFMod = modAt (rootpath modulepath
  37. ++ ["Ivory","Interface", ifModuleName ir, schemaName])
  38. typeimports = map (importDecl tm)
  39. $ nub
  40. $ map importType
  41. $ interfaceTypes ir
  42. extraimports = [ text "import" <+> modAt (rootpath modulepath ++ ["Ivory", "Types"])
  43. , text "import qualified" <+> ivoryIFMod <+> text "as I"
  44. , text "import Ivory.Language"
  45. , text "import Ivory.Stdlib"
  46. , text "import Ivory.Tower"
  47. , text "import Ivory.Serialize"
  48. ]
  49. schemaDoc :: String -> Schema -> Doc
  50. schemaDoc interfaceName (Schema schemaName []) =
  51. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  52. <+> text interfaceName <+> text "interface: schema is empty"
  53. schemaDoc interfaceName (Schema schemaName schema) = stack
  54. [ text "-- Define" <+> text schemaName <+> text "schema for"
  55. <+> text interfaceName <+> text "interface"
  56. , empty
  57. , text "data" <+> constructor<+> equals <+> constructor
  58. , indent 2 $ encloseStack lbrace rbrace comma
  59. [ case t of
  60. PrimType VoidType -> accessorName n <+> colon <> colon
  61. <+> text "ChanOutput (Stored IBool)"
  62. _ -> accessorName n <+> colon <> colon
  63. <+> text "ChanOutput" <+> typeIvoryArea t
  64. | (_, (Message n t)) <- schema
  65. ]
  66. , empty
  67. , text (inputFuncName typeName) <+> align
  68. (stack [ text ":: (ANat n)"
  69. , text "=> ChanOutput (Array n (Stored Uint8))"
  70. , text "-> Tower e" <+> constructor
  71. ])
  72. , text (inputFuncName typeName) <+> text "frame_ch" <+> equals <+> text "do"
  73. , indent 2 $ stack
  74. [ towerMonadDependencies
  75. , stack [ chanName n <+> text "<- channel"
  76. | (_, Message n _) <- schema ]
  77. , empty
  78. , text "monitor" <+> dquotes (text (outputFuncName typeName))
  79. <+> text "$ do"
  80. , indent 2 $ stack
  81. [ text "handler frame_ch \"parse_frame\" $ do"
  82. , indent 2 $ stack
  83. [ stack [ emitterName n <+> text "<- emitter"
  84. <+> parens (text "fst" <+> chanName n)
  85. <+> text "1"
  86. | (_, Message n _) <- schema
  87. ]
  88. , text "callback $ \\f -> do"
  89. , indent 2 $ stack
  90. [ text "offs <- local izero"
  91. , text "_ <- I." <> text (parserName typeName)
  92. <+> text "f offs $ I." <> constructor
  93. , indent 2 $ encloseStack lbrace rbrace comma
  94. [ case t of
  95. PrimType VoidType ->
  96. text "I." <> accessorName n <+> equals
  97. <+> text "emitV" <+> emitterName n
  98. <+> text "true >> return true"
  99. _ -> text "I." <> accessorName n <+> equals
  100. <+> text "\\v -> emit" <+> emitterName n
  101. <+> text "v >> return true"
  102. | (_, Message n t) <- schema
  103. ]
  104. , text "return ()"
  105. ]
  106. ]
  107. ]
  108. , empty
  109. , text "return" <+> constructor <+> encloseStack lbrace rbrace comma
  110. [ accessorName n <+> equals
  111. <+> parens (text "snd" <+> chanName n)
  112. | (_, Message n _) <- schema
  113. ]
  114. ]
  115. , empty
  116. , text (outputFuncName typeName) <> align
  117. (stack [ text ":: (ANat n)"
  118. , text "=>" <+> constructor
  119. , text "-> Tower e (ChanOutput (Array n (Stored Uint8)))"
  120. ])
  121. , text (outputFuncName typeName) <+> text "a" <+> equals <+> text "do"
  122. , indent 2 $ stack
  123. [ towerMonadDependencies
  124. , text "frame_ch <- channel"
  125. , text "monitor" <+> dquotes (text (outputFuncName typeName))
  126. <+> text "$ do"
  127. , indent 2 $ stack
  128. [ text "handler" <+> parens (accessorName n <+> text "a")
  129. <+> dquotes (accessorName n) <+> text "$ do"
  130. </> indent 2 (parseEmitBody n t)
  131. </> empty
  132. | (_, Message n t) <- schema
  133. ]
  134. , text "return (snd frame_ch)"
  135. ]
  136. ]
  137. where
  138. constructor = text typeName
  139. accessorName n = text (userEnumValueName n ++ schemaName)
  140. typeName = interfaceName ++ schemaName
  141. chanName s = text "ch_" <> text s
  142. emitterName s = text "emitter_" <> text s
  143. parseEmitBody n (PrimType VoidType) = stack
  144. [ text "e <- emitter (fst frame_ch) 1"
  145. , text "callback $ \\_ -> do"
  146. , indent 2 $ stack
  147. [ text "f <- local izero"
  148. , text "o <- local izero"
  149. , text "ok <-" <+> text "I." <> accessorName n
  150. <+> parens (text "I." <> text (senderName typeName)
  151. <+> text "f o")
  152. , text "ifte_ ok (emit e (constRef f)) (return ())"
  153. ]
  154. ]
  155. parseEmitBody n _ = stack
  156. [ text "e <- emitter (fst frame_ch) 1"
  157. , text "callback $ \\w -> do"
  158. , indent 2 $ stack
  159. [ text "f <- local izero"
  160. , text "o <- local izero"
  161. , text "ok <-" <+> text "I." <> accessorName n
  162. <+> parens (text "I." <> text (senderName typeName)
  163. <+> text "f o")
  164. <+> text "w"
  165. , text "ifte_ ok (emit e (constRef f)) (return ())"
  166. ]
  167. ]
  168. towerMonadDependencies = stack
  169. [ text "towerModule serializeModule"
  170. , text "mapM_ towerArtifact serializeArtifacts"
  171. , text "mapM_ towerModule typeModules"
  172. , text "mapM_ towerDepends typeModules"
  173. , empty
  174. ]
  175. inputFuncName :: String -> String
  176. inputFuncName tn = userEnumValueName tn ++ "Input"
  177. outputFuncName :: String -> String
  178. outputFuncName tn = userEnumValueName tn ++ "Output"