Interface.hs 6.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178
  1. module Gidl.Backend.Tower.Interface where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Gidl.Types
  5. import Gidl.Interface
  6. import Gidl.Schema
  7. import Gidl.Backend.Ivory.Types
  8. import Gidl.Backend.Ivory.Interface (ifModuleName, parserName, senderName)
  9. import Ivory.Artifact
  10. import Text.PrettyPrint.Mainland
  11. interfaceModule :: [String] -> Interface -> Schema -> Artifact
  12. interfaceModule 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 3 . 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 qualified" <+> ivoryIFMod <+> text "as I"
  43. , text "import Ivory.Language"
  44. , text "import Ivory.Stdlib"
  45. , text "import Ivory.Tower"
  46. , text "import Ivory.Serialize"
  47. ]
  48. schemaDoc :: String -> Schema -> Doc
  49. schemaDoc interfaceName (Schema schemaName []) =
  50. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  51. <+> text interfaceName <+> text "interface: schema is empty"
  52. schemaDoc interfaceName (Schema schemaName schema) = stack
  53. [ text "-- Define" <+> text schemaName <+> text "schema for"
  54. <+> text interfaceName <+> text "interface"
  55. , empty
  56. , text "data" <+> constructor <+> text "c" <+> equals <+> constructor
  57. , indent 2 $ encloseStack lbrace rbrace comma
  58. [ case t of
  59. PrimType VoidType -> accessorName n <+> colon <> colon
  60. <+> text "c (Stored IBool)"
  61. _ -> accessorName n <+> colon <> colon
  62. <+> text "c"
  63. <+> parens (text (typeIvoryType 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" <+> parens (constructor <+> text "ChanOutput")
  71. ])
  72. , text (inputFuncName typeName) <+> text "frame_ch" <+> equals <+> text "do"
  73. , indent 2 $ stack
  74. [ stack [ chanName n <+> text "<- channel"
  75. | (_, Message n _) <- schema ]
  76. , empty
  77. , text "monitor" <+> dquotes (text (outputFuncName typeName))
  78. <+> text "$ do"
  79. , indent 2 $ stack
  80. [ text "handler frame_ch \"parse_frame\" $ do"
  81. , indent 2 $ stack
  82. [ stack [ emitterName n <+> text "<- emitter"
  83. <+> parens (text "fst" <+> chanName n)
  84. <+> text "1"
  85. | (_, Message n _) <- schema
  86. ]
  87. , text "callback $ \\f -> do"
  88. , indent 2 $ stack
  89. [ text "offs <- local izero"
  90. , text "_ <- I." <> text (parserName typeName)
  91. <+> text "f offs $ I." <> constructor
  92. , indent 2 $ encloseStack lbrace rbrace comma
  93. [ case t of
  94. PrimType VoidType ->
  95. text "I." <> accessorName n <+> equals
  96. <+> text "emitV" <+> emitterName n
  97. <+> text "true >> return true"
  98. _ -> text "I." <> accessorName n <+> equals
  99. <+> text "\\v -> emit" <+> emitterName n
  100. <+> text "v >> return true"
  101. | (_, Message n t) <- schema
  102. ]
  103. , text "return ()"
  104. ]
  105. ]
  106. ]
  107. , empty
  108. , text "return" <+> constructor <+> encloseStack lbrace rbrace comma
  109. [ accessorName n <+> equals
  110. <+> parens (text "snd" <+> chanName n)
  111. | (_, Message n _) <- schema
  112. ]
  113. ]
  114. , empty
  115. , text (outputFuncName typeName) <> align
  116. (stack [ text ":: (ANat n)"
  117. , text "=>" <+> constructor <+> text "ChanOutput"
  118. , text "-> Tower e (ChanOutput (Array n (Stored Uint8)))"
  119. ])
  120. , text (outputFuncName typeName) <+> text "a" <+> equals <+> text "do"
  121. , indent 2 $ stack
  122. [ text "frame_ch <- channel"
  123. , text "monitor" <+> dquotes (text (outputFuncName typeName))
  124. <+> text "$ do"
  125. , indent 2 $ stack
  126. [ text "handler" <+> parens (accessorName n <+> text "a")
  127. <+> dquotes (accessorName n) <+> text "$ do"
  128. </> indent 2 (parseEmitBody n t)
  129. </> empty
  130. | (_, Message n t) <- schema
  131. ]
  132. , text "return (snd frame_ch)"
  133. ]
  134. ]
  135. where
  136. constructor = text typeName
  137. accessorName n = text (userEnumValueName n ++ schemaName)
  138. typeName = interfaceName ++ schemaName
  139. inputFuncName tn = userEnumValueName tn ++ "Input"
  140. outputFuncName tn = userEnumValueName tn ++ "Output"
  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. ]