Types.hs 6.3 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194
  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. -- invariant: only make a typeModule from a StructType, NewtypeType, or EnumType
  9. -- i.e. when isUserDefined is true.
  10. typeModule :: [String] -> TypeRepr -> Artifact
  11. typeModule modulepath tr@(TypeRepr _ td) =
  12. artifactPath (intercalate "/" modulepath) $
  13. artifactText ((typeModuleName tr) ++ ".hs") $
  14. prettyLazyText 80 $
  15. stack
  16. [ text "{-# LANGUAGE DataKinds #-}"
  17. , text "{-# LANGUAGE TypeOperators #-}"
  18. , text "{-# LANGUAGE QuasiQuotes #-}"
  19. , text "{-# LANGUAGE GeneralizedNewtypeDeriving #-}"
  20. , text "{-# LANGUAGE FlexibleInstances #-}"
  21. , text "{-# OPTIONS_GHC -fno-warn-orphans #-}"
  22. , empty
  23. , text "module"
  24. <+> tm (typeModuleName tr)
  25. <+> text "where"
  26. , empty
  27. , stack (imports ++
  28. [ text "import Ivory.Language"
  29. , text "import Ivory.Serialize"
  30. ])
  31. , empty
  32. , typeDecl typename td
  33. ]
  34. where
  35. imports = map (importDecl tm)
  36. $ nub
  37. $ map importType
  38. $ typeLeaves td
  39. typename = typeModuleName tr
  40. tm mname = mconcat $ punctuate dot
  41. $ map text (modulepath ++ [mname])
  42. typeIvoryType :: TypeRepr -> String
  43. typeIvoryType (TypeRepr tn (StructType _)) = "Struct \"" ++ userTypeStructName tn ++ "\""
  44. typeIvoryType (TypeRepr tn (NewtypeType _)) = userTypeModuleName tn
  45. typeIvoryType (TypeRepr tn (EnumType _)) = userTypeModuleName tn
  46. typeIvoryType (TypeRepr _ (AtomType a)) = case a of
  47. AtomInt Bits8 -> "Sint8"
  48. AtomInt Bits16 -> "Sint16"
  49. AtomInt Bits32 -> "Sint32"
  50. AtomInt Bits64 -> "Sint64"
  51. AtomWord Bits8 -> "Uint8"
  52. AtomWord Bits16 -> "Uint16"
  53. AtomWord Bits32 -> "Uint32"
  54. AtomWord Bits64 -> "Uint64"
  55. AtomFloat -> "IFloat"
  56. AtomDouble -> "IDouble"
  57. typeIvoryType (TypeRepr _ VoidType) = "()" -- XXX this is gonna cause trouble buddy
  58. typeModuleName :: TypeRepr -> String
  59. typeModuleName (TypeRepr tn (StructType _)) = userTypeModuleName tn
  60. typeModuleName (TypeRepr tn (NewtypeType _)) = userTypeModuleName tn
  61. typeModuleName (TypeRepr tn (EnumType _)) = userTypeModuleName tn
  62. typeModuleName (TypeRepr _ (AtomType _)) = error "do not take typeModuleName of an AtomType"
  63. typeModuleName (TypeRepr _ VoidType) = error "do not take typeModuleName of a VoidType"
  64. userTypeModuleName :: String -> String
  65. userTypeModuleName = first_cap . userEnumValueName
  66. where
  67. first_cap (s:ss) = (toUpper s) : ss
  68. first_cap [] = []
  69. userEnumValueName :: String -> String
  70. userEnumValueName = first_lower . u_to_camel
  71. where
  72. first_lower (s:ss) = (toLower s) : ss
  73. first_lower [] = []
  74. u_to_camel ('_':'t':[]) = []
  75. u_to_camel ('_':[]) = []
  76. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  77. u_to_camel (a:as) = a : u_to_camel as
  78. u_to_camel [] = []
  79. userTypeStructName :: String -> String
  80. userTypeStructName = first_lower . drop_t_suffix
  81. where
  82. first_lower (s:ss) = (toLower s) : ss
  83. first_lower [] = []
  84. drop_t_suffix [] = []
  85. drop_t_suffix ('_':'t':[]) = []
  86. drop_t_suffix (a:as) = a : drop_t_suffix as
  87. typeDecl :: TypeName -> Type TypeRepr -> Doc
  88. typeDecl tname td@(StructType (Struct ss)) = stack
  89. [ text "[ivory|"
  90. , text "struct" <+> structname
  91. , indent 2 $ encloseStack lbrace rbrace semi
  92. [ text i <+> colon <> colon <+> text "Stored" <+> text (typeIvoryType t) -- XXX AREA TYPE
  93. | (i,t) <- ss ]
  94. , text "|]"
  95. , empty
  96. , text (userEnumValueName tname) <> text "TypesModule :: Module"
  97. , text (userEnumValueName tname) <> text "TypesModule" <+> equals
  98. <+> text "package" <+> dquotes (structname <> text "_types") <+> text "$ do"
  99. , indent 2 $ stack
  100. [ text "defStruct"
  101. <+> parens (text "Proxy :: Proxy" <+> dquotes structname)
  102. , text "depend serializeModule"
  103. , stack is
  104. ]
  105. ]
  106. where
  107. is = map userIModDependency $ nub $ typeLeaves td
  108. structname = text (userTypeStructName tname)
  109. typeDecl tname (NewtypeType (Newtype n)) =
  110. case baseType n of
  111. TypeRepr _ (StructType _) -> stack
  112. [ text "type" <+> text tname <+> equals <+> text (typeIvoryType (baseType n)) ]
  113. _ -> stack
  114. [ text "newtype" <+> text tname <+> equals
  115. , indent 2 $ text tname <+> align
  116. (lbrace <+> text ("un" ++ tname) <+> text "::" <+>
  117. text (typeIvoryType n) </>
  118. rbrace <+> typeDeriving (words "IvoryType IvoryVar IvoryExpr IvoryEq IvoryStore IvoryInit IvoryZeroVal"))
  119. ]
  120. typeDecl tname (EnumType (EnumT s es)) = stack
  121. [ text "newtype" <+> text tname <+> equals
  122. , indent 2 $ text tname <+> align
  123. (lbrace <+> text ("un" ++ tname) <+> text "::" <+>
  124. text bt </>
  125. rbrace <+> typeDeriving (words "IvoryType IvoryVar IvoryExpr IvoryEq IvoryStore IvoryInit IvoryZeroVal"))
  126. , empty
  127. , stack
  128. [ stack
  129. [ empty
  130. , text (userEnumValueName i) <+> colon <> colon <+> text tname
  131. , text (userEnumValueName i) <+> equals <+> text tname <+> ppr e
  132. ]
  133. | (i,e) <- es ]
  134. ]
  135. where
  136. bt = case s of
  137. Bits8 -> "Uint8"
  138. Bits16 -> "Uint16"
  139. Bits32 -> "Uint32"
  140. Bits64 -> "Uint64"
  141. typeDecl tn _ = error ("typeDecl: cannot create decl for built in type " ++ tn)
  142. typeDeriving :: [String] -> Doc
  143. typeDeriving cs = text "deriving" <+> parens (commasep (map text cs))
  144. data ImportType = LibraryType String
  145. | UserType String
  146. | NoImport
  147. deriving (Eq, Show)
  148. importType :: TypeRepr -> ImportType
  149. importType (TypeRepr _ (AtomType _)) = NoImport
  150. importType (TypeRepr _ VoidType) = NoImport
  151. importType (TypeRepr n _) = UserType n
  152. isUserDefined :: TypeRepr -> Bool
  153. isUserDefined tr = case importType tr of
  154. UserType _ -> True
  155. _ -> False
  156. userIModDependency :: TypeRepr -> Doc
  157. userIModDependency tr = case baseType tr of
  158. (TypeRepr sn (StructType _)) ->
  159. text "depend" <+> text (userTypeStructName sn) <> text "TypesModule"
  160. _ -> empty
  161. importDecl :: (String -> Doc) -> ImportType -> Doc
  162. importDecl _ (LibraryType p) =
  163. text "import" <+> text p
  164. importDecl mkpath (UserType t) =
  165. text "import" <+> mkpath (userTypeModuleName t)
  166. importDecl _ NoImport = empty
  167. encloseStack :: Doc -> Doc -> Doc -> [Doc] -> Doc
  168. encloseStack l r p ds = case ds of
  169. [] -> empty -- l </> r
  170. [d] -> l <+> d </> r
  171. _ -> align (l <+> (folddoc (\a b -> a </> p <+> b) ds) </> r)