Schema.hs 5.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141
  1. module Gidl.Backend.Ivory.Schema where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Data.Char (toUpper)
  5. import Gidl.Interface
  6. import Gidl.Schema
  7. import Gidl.Backend.Ivory.Types
  8. import Ivory.Artifact
  9. import Text.PrettyPrint.Mainland
  10. schemaModule :: [String] -> Interface -> Schema -> Artifact
  11. schemaModule modulepath ir schema =
  12. artifactPath (intercalate "/" (modulepath ++ [ifModuleName ir])) $
  13. artifactText (schemaName ++ ".hs") $
  14. prettyLazyText 1000 $
  15. stack
  16. [ text "{-# LANGUAGE DataKinds #-}"
  17. , text "{-# LANGUAGE RankNTypes #-}"
  18. , text "{-# LANGUAGE ScopedTypeVariables #-}"
  19. , text "{-# OPTIONS_GHC -fno-warn-unused-imports #-}"
  20. , empty
  21. , text "module"
  22. <+> im (ifModuleName ir) <> dot <> text schemaName
  23. <+> text "where"
  24. , empty
  25. , stack $ typeimports ++ extraimports
  26. , empty
  27. , schemaDoc (ifModuleName ir) schema
  28. ]
  29. where
  30. (Schema schemaName _) = schema
  31. rootpath = reverse . drop 1 . reverse
  32. modAt path = mconcat (punctuate dot (map text path))
  33. im mname = modAt (modulepath ++ [mname])
  34. tm mname = modAt (rootpath modulepath ++ ["Types", mname])
  35. unpackMod = modAt (rootpath modulepath ++ ["Unpack"])
  36. typeimports = map (importDecl tm)
  37. $ nub
  38. $ map importType
  39. $ interfaceTypes ir
  40. extraimports = [ text "import" <+> unpackMod
  41. , text "import Ivory.Language"
  42. , text "import Ivory.Serialize"
  43. , text "import Ivory.Stdlib"
  44. ]
  45. schemaDoc :: String -> Schema -> Doc
  46. schemaDoc interfaceName (Schema schemaName []) =
  47. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  48. <+> text interfaceName <+> text "interface: schema is empty"
  49. schemaDoc interfaceName (Schema schemaName schema) = stack
  50. [ text "-- Define" <+> text schemaName <+> text "schema for"
  51. <+> text interfaceName <+> text "interface"
  52. , empty
  53. , text "data" <+> constructor <+> equals <+> constructor
  54. , indent 2 $ encloseStack lbrace rbrace comma
  55. [ text (accessorName n) <+> colon <> colon
  56. <+> parens (text "forall s r b s' . ConstRef s'"
  57. <+> typeIvoryArea t
  58. <+> text "-> Ivory ('Effects r b (Scope s)) IBool")
  59. | (_, (Message n t)) <- schema
  60. ]
  61. , empty
  62. , text (parserName typeName) <+> align
  63. (stack [ text ":: forall s0 r b s2 s3 n"
  64. , text " . (ANat n)"
  65. , text "=> ConstRef s2 (Array n (Stored Uint8))"
  66. , text "-> Ref s3 (Stored Uint32)"
  67. , text "->" <+> text typeName
  68. , text "-> Ivory ('Effects r b (Scope s0)) IBool"
  69. ])
  70. , text (parserName typeName) <+> text "arr offs iface = do"
  71. , indent 2 $ stack
  72. [ text "unpackWithCallback arr offs $ \\tag_ref -> do"
  73. , indent 2 $ text "(tag :: Uint32) <- deref tag_ref"
  74. , indent 2 $ text "cond" <+> encloseStack lbracket rbracket comma
  75. [ parens (text "tag ==?" <+> ppr h) <+> text "==>"
  76. <+> text "unpackWithCallback arr offs"
  77. <+> parens (text (accessorName n) <+> text "iface")
  78. | (h, Message n _) <- schema
  79. ]
  80. ]
  81. , empty
  82. , text (senderName typeName) <+> align
  83. (stack [ text ":: forall n s1 s2"
  84. , text " . (ANat n)"
  85. , text "=> Ref s1 (Array n (Stored Uint8))"
  86. , text "-> Ref s2 (Stored Uint32)"
  87. , text "->" <+> constructor
  88. ])
  89. , text (senderName typeName) <+> text "arr offs" <+> equals
  90. <+> constructor
  91. , indent 2 $ encloseStack lbrace rbrace comma
  92. [ text (accessorName n) <+> equals <+> text "\\m -> do" </> indent 4
  93. (stack [ text "o <- deref offs"
  94. , text "let required_size = fromInteger (packSize (packRep :: PackRep"
  95. <+> typeIvoryArea t <+> text ")"
  96. <+> text "+ packSize (packRep :: PackRep (Stored Uint32)))"
  97. , text " sufficient_space = (o + required_size) <? arrayLen arr"
  98. , text "when sufficient_space $ do"
  99. , indent 2 $ stack
  100. [ text "ident <- local (ival (" <+> ppr h <+> text ":: Uint32))"
  101. , text "packInto arr o (constRef ident)"
  102. , text "packInto arr (o + fromInteger (packSize (packRep :: PackRep (Stored Uint32)))) m"
  103. , text "offs += required_size"
  104. ]
  105. , text "return sufficient_space"
  106. ])
  107. | (h, (Message n t)) <- schema
  108. ]
  109. ]
  110. where
  111. constructor = text typeName
  112. accessorName n = userEnumValueName n ++ schemaName
  113. typeName = interfaceName ++ schemaName
  114. parserName :: String -> String
  115. parserName tn = userEnumValueName tn ++ "Parser"
  116. senderName :: String -> String
  117. senderName tn = userEnumValueName tn ++ "Sender"
  118. ifModuleName :: Interface -> String
  119. ifModuleName (Interface iname _ _) = aux iname
  120. where
  121. aux :: String -> String
  122. aux = first_cap . u_to_camel
  123. first_cap (s:ss) = (toUpper s) : ss
  124. first_cap [] = []
  125. u_to_camel ('_':'i':[]) = []
  126. u_to_camel ('_':[]) = []
  127. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  128. u_to_camel (a:as) = a : u_to_camel as
  129. u_to_camel [] = []