Types.hs 11 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302
  1. module Gidl.Backend.Ivory.Types where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Data.Char (toUpper, toLower)
  5. import Gidl.Types
  6. import Ivory.Artifact
  7. import Text.PrettyPrint.Mainland
  8. typeUmbrella :: [String] -> [Type] -> Artifact
  9. typeUmbrella modulepath ts =
  10. artifactPath (intercalate "/" modulepath) $
  11. artifactText ("Types.hs") $
  12. prettyLazyText 1000 $
  13. stack
  14. [ text "module" <+> typeModulePath modulepath "Types" <+> text "where"
  15. , empty
  16. , text "import Ivory.Language"
  17. , stack
  18. [ importDecl (typeModulePath (modulepath ++ ["Types"])) (importType t)
  19. | t <- ts ]
  20. , empty
  21. , text "typeModules :: [Module]"
  22. , text "typeModules ="
  23. , indent 2 $ encloseStack lbracket rbracket comma
  24. [ text tname <> dot
  25. <> text (userEnumValueName tname) <> text "TypesModule"
  26. | t <- ts
  27. , let tname = typeModuleName t
  28. ]
  29. ]
  30. -- invariant: only make a typeModule from a StructType, Newtype, or EnumType
  31. -- i.e. when isUserDefined is true.
  32. typeModule :: [String] -> Type -> Artifact
  33. typeModule modulepath t =
  34. artifactPath (intercalate "/" modulepath) $
  35. artifactText ((typeModuleName t) ++ ".hs") $
  36. prettyLazyText 1000 $
  37. stack
  38. [ text "{-# LANGUAGE DataKinds #-}"
  39. , text "{-# LANGUAGE TypeOperators #-}"
  40. , text "{-# LANGUAGE QuasiQuotes #-}"
  41. , text "{-# LANGUAGE GeneralizedNewtypeDeriving #-}"
  42. , text "{-# LANGUAGE FlexibleInstances #-}"
  43. , text "{-# OPTIONS_GHC -fno-warn-orphans #-}"
  44. , empty
  45. , text "module"
  46. <+> typeModulePath modulepath (typeModuleName t)
  47. <+> text "where"
  48. , empty
  49. , stack (imports ++
  50. [ text "import Ivory.Language"
  51. , text "import Ivory.Serialize"
  52. ])
  53. , empty
  54. , typeDecl t
  55. ]
  56. where
  57. imports = map (importDecl (typeModulePath modulepath))
  58. $ nub
  59. $ map importType
  60. $ typeLeaves t
  61. typeModulePath :: [String] -> String -> Doc
  62. typeModulePath modulepath mname = mconcat $ punctuate dot
  63. $ map text (modulepath ++ [mname])
  64. typeImportedIvoryType :: Type -> String
  65. typeImportedIvoryType t@(PrimType (Newtype tn _)) =
  66. userTypeModuleName tn ++ "." ++ typeIvoryType t
  67. typeImportedIvoryType t@(PrimType (EnumType "bool_t" _ _)) = typeIvoryType t
  68. typeImportedIvoryType t@(PrimType (EnumType tn _ _)) =
  69. userTypeModuleName tn ++ "." ++ typeIvoryType t
  70. typeImportedIvoryType t = typeIvoryType t
  71. typeIvoryArea :: Type -> Doc
  72. typeIvoryArea t@(StructType _ _) = parens (text (typeIvoryType t))
  73. typeIvoryArea t@(PrimType (AtomType _)) = parens (text "Stored" <+> text (typeIvoryType t))
  74. typeIvoryArea t@(PrimType (EnumType "bool_t" _ _)) = parens (text "Stored" <+> text (typeIvoryType t))
  75. typeIvoryArea t@(PrimType _) = parens (text "Stored" <+> text (typeIvoryType t) <> dot <> text (typeIvoryType t))
  76. typeIvoryAreaStructQQ :: Type -> Doc
  77. typeIvoryAreaStructQQ (StructType n _) = text "Struct" <+> text (userTypeStructName n)
  78. typeIvoryAreaStructQQ t = typeIvoryArea t
  79. typeIvoryType :: Type -> String
  80. typeIvoryType (StructType tn _) = "Struct \"" ++ userTypeStructName tn ++ "\""
  81. typeIvoryType (PrimType (Newtype tn _)) = userTypeModuleName tn
  82. typeIvoryType (PrimType (EnumType "bool_t" _ _)) = "IBool"
  83. typeIvoryType (PrimType (EnumType tn _ _)) = userTypeModuleName tn
  84. typeIvoryType (PrimType (AtomType a)) = case a of
  85. AtomInt Bits8 -> "Sint8"
  86. AtomInt Bits16 -> "Sint16"
  87. AtomInt Bits32 -> "Sint32"
  88. AtomInt Bits64 -> "Sint64"
  89. AtomWord Bits8 -> "Uint8"
  90. AtomWord Bits16 -> "Uint16"
  91. AtomWord Bits32 -> "Uint32"
  92. AtomWord Bits64 -> "Uint64"
  93. AtomFloat -> "IFloat"
  94. AtomDouble -> "IDouble"
  95. typeModuleName :: Type -> String
  96. typeModuleName (StructType tn _) = userTypeModuleName tn
  97. typeModuleName (PrimType (Newtype tn _)) = userTypeModuleName tn
  98. typeModuleName (PrimType (EnumType tn _ _)) = userTypeModuleName tn
  99. typeModuleName (PrimType (AtomType _)) = error "do not take typeModuleName of an AtomType"
  100. userTypeModuleName :: String -> String
  101. userTypeModuleName = first_cap . userEnumValueName
  102. where
  103. first_cap (s:ss) = (toUpper s) : ss
  104. first_cap [] = []
  105. userEnumValueName :: String -> String
  106. userEnumValueName = first_lower . u_to_camel
  107. where
  108. first_lower (s:ss) = (toLower s) : ss
  109. first_lower [] = []
  110. u_to_camel ('_':'t':[]) = []
  111. u_to_camel ('_':[]) = []
  112. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  113. u_to_camel (a:as) = a : u_to_camel as
  114. u_to_camel [] = []
  115. userTypeStructName :: String -> String
  116. userTypeStructName = first_lower . drop_t_suffix
  117. where
  118. first_lower (s:ss) = (toLower s) : ss
  119. first_lower [] = []
  120. drop_t_suffix [] = []
  121. drop_t_suffix ('_':'t':[]) = []
  122. drop_t_suffix (a:as) = a : drop_t_suffix as
  123. ivoryPackageName :: Type -> String
  124. ivoryPackageName (StructType tname _) = userEnumValueName tname ++ "TypesModule"
  125. ivoryPackageName (PrimType (Newtype tname _)) = userEnumValueName tname ++ "TypesModule"
  126. ivoryPackageName (PrimType (EnumType tname _ _)) = userEnumValueName tname ++ "TypesModule"
  127. ivoryPackageName _ = error "can't take ivoryPackageName of builtin type"
  128. qualifiedIvoryPackageName :: Type -> String
  129. qualifiedIvoryPackageName t = typeModuleName t ++ "." ++ ivoryPackageName t
  130. typeDecl :: Type -> Doc
  131. typeDecl t@(StructType tname ss) = stack
  132. [ text "[ivory|"
  133. , text "struct" <+> structname
  134. , indent 2 $ encloseStack lbrace rbrace semi
  135. [ text i <+> colon <> colon
  136. <+> typeIvoryAreaStructQQ st
  137. | (i,st) <- ss ]
  138. , text "|]"
  139. , empty
  140. , packRep <+> colon <> colon <+> text "WrappedPackRep" <+> storedType
  141. , packRep <+> equals <+> text "wrapPackRep" <+> dquotes structname <+> text "$"
  142. , indent 2 $ text "packStruct" <+> encloseStack lbracket rbracket comma
  143. [ text "packLabel" <+> text i
  144. | (i,_) <- ss]
  145. , empty
  146. , text "instance Packable" <+> storedType <+> text "where"
  147. , indent 2 $ text "packRep" <+> equals <+> text "wrappedPackRep" <+> packRep
  148. , empty
  149. , text (ivoryPackageName t) <+> text ":: Module"
  150. , text (ivoryPackageName t) <+> equals
  151. <+> text "package" <+> dquotes (structname <> text "_types") <+> text "$ do"
  152. , indent 2 $ stack $
  153. [ text "defStruct"
  154. <+> parens (text "Proxy :: Proxy" <+> dquotes structname)
  155. , text "depend serializeModule"
  156. , text "wrappedPackMod" <+> packRep
  157. ] ++
  158. [ text "depend" <+> text (qualifiedIvoryPackageName dt)
  159. | dt <- typeLeaves t
  160. , isUserDefined dt
  161. ]
  162. ]
  163. where
  164. storedType = parens (text "Struct" <+> dquotes structname)
  165. structname = text (userTypeStructName tname)
  166. packRep = text "pack" <> text (userTypeModuleName tname)
  167. typeDecl t@(PrimType (Newtype tname n)) = stack
  168. [ text "newtype" <+> text typename <+> equals
  169. , indent 2 $ text typename <+> align
  170. (lbrace <+> text ("un" ++ typename ) <+> text "::"
  171. <+> text (typeImportedIvoryType (PrimType n))
  172. </> rbrace <+> typeDeriving (words ("IvoryType IvoryVar IvoryExpr " ++
  173. "IvoryEq IvoryStore IvoryInit IvoryZeroVal Num")))
  174. , empty
  175. , packRep <+> colon <> colon <+> text "WrappedPackRep" <+> storedType
  176. , packRep <+> equals <+> text "wrapPackRep" <+> dquotes (text tname) <+> text "$"
  177. , indent 2 $ text "repackV" <+> text typename <+> text ("un" ++ typename) <+> text "packRep"
  178. , empty
  179. , text "instance Packable" <+> storedType <+> text "where"
  180. , indent 2 $ text "packRep" <+> equals <+> text "wrappedPackRep" <+> packRep
  181. , empty
  182. , text (ivoryPackageName t) <+> text ":: Module"
  183. , text (ivoryPackageName t) <+> equals
  184. <+> text "package"
  185. <+> dquotes (text (userTypeStructName tname) <> text "_types")
  186. <+> text "$ do"
  187. , indent 2 $ stack $
  188. [ text "depend serializeModule"
  189. , text "wrappedPackMod" <+> packRep
  190. ] ++
  191. [ text "depend" <+> text (qualifiedIvoryPackageName dt)
  192. | dt <- typeLeaves t
  193. , isUserDefined dt
  194. ]
  195. ]
  196. where
  197. typename = userTypeModuleName tname
  198. storedType = parens (text "Stored" <+> text typename)
  199. packRep = text "pack" <> text typename
  200. typeDecl t@(PrimType (EnumType tname s es)) = stack
  201. [ text "newtype" <+> text typename <+> equals
  202. , indent 2 $ text typename <+> align
  203. (lbrace <+> text ("un" ++ typename) <+> text "::" <+>
  204. text bt </>
  205. rbrace <+> typeDeriving (words ("IvoryType IvoryVar IvoryExpr IvoryEq "
  206. ++ "IvoryStore IvoryInit IvoryZeroVal")))
  207. , empty
  208. , stack
  209. [ stack
  210. [ empty
  211. , text (userEnumValueName i) <+> colon <> colon <+> text typename
  212. , text (userEnumValueName i) <+> equals <+> text typename <+> ppr e
  213. ]
  214. | (i,e) <- es ]
  215. , empty
  216. , packRep <+> colon <> colon <+> text "WrappedPackRep" <+> storedType
  217. , packRep <+> equals <+> text "wrapPackRep" <+> dquotes (text tname) <+> text "$"
  218. , indent 2 $ text "repackV" <+> text typename <+> text ("un" ++ typename) <+> text "packRep"
  219. , empty
  220. , text "instance Packable" <+> storedType <+> text "where"
  221. , indent 2 $ text "packRep" <+> equals <+> text "wrappedPackRep" <+> packRep
  222. , empty
  223. , text (ivoryPackageName t) <+> text ":: Module"
  224. , text (ivoryPackageName t) <+> equals
  225. <+> text "package"
  226. <+> dquotes (text (userTypeStructName tname) <> text "_types")
  227. <+> text "$ do"
  228. , indent 2 $ stack
  229. [ text "depend serializeModule"
  230. , text "wrappedPackMod" <+> packRep
  231. ]
  232. ]
  233. where
  234. typename = userTypeModuleName tname
  235. packRep = text "pack" <> text typename
  236. storedType = parens (text "Stored" <+> text typename)
  237. bt = case s of
  238. Bits8 -> "Uint8"
  239. Bits16 -> "Uint16"
  240. Bits32 -> "Uint32"
  241. Bits64 -> "Uint64"
  242. typeDecl a = error ("typeDecl: broken invariant, cannot create type for " ++ show a)
  243. typeDeriving :: [String] -> Doc
  244. typeDeriving cs = text "deriving" <+> parens (commasep (map text cs))
  245. data ImportType = LibraryType String
  246. | UserType String
  247. | NoImport
  248. deriving (Eq, Show)
  249. importType :: Type -> ImportType
  250. importType (StructType n _) = UserType n
  251. importType (PrimType (EnumType "bool_t" _ _)) = NoImport
  252. importType (PrimType (EnumType n _ _)) = UserType n
  253. importType (PrimType (Newtype n _)) = UserType n
  254. importType (PrimType (AtomType _)) = NoImport
  255. isUserDefined :: Type -> Bool
  256. isUserDefined t = case importType t of
  257. UserType _ -> True
  258. _ -> False
  259. importPrefix :: ImportType -> Doc
  260. importPrefix (UserType t) = text (userTypeModuleName t)
  261. importPrefix _ = empty
  262. importDecl :: (String -> Doc) -> ImportType -> Doc
  263. importDecl _ (LibraryType p) =
  264. text "import" <+> text p
  265. importDecl mkpath (UserType t) =
  266. text "import qualified" <+> mkpath (userTypeModuleName t)
  267. <+> text "as" <+> text (userTypeModuleName t)
  268. importDecl _ NoImport = empty
  269. encloseStack :: Doc -> Doc -> Doc -> [Doc] -> Doc
  270. encloseStack l r p ds = case ds of
  271. [] -> empty -- l </> r
  272. [d] -> align (l <+> d </> r)
  273. _ -> align (l <+> (folddoc (\a b -> a </> p <+> b) ds) </> r)