Browse Source

gidl: haskell interfaces and types derive Data and Typeable

- for use with aeson, etc.
Pat Hickey 9 years ago
parent
commit
d51eff8e53
2 changed files with 12 additions and 5 deletions
  1. 6 2
      src/Gidl/Backend/Haskell/Interface.hs
  2. 6 3
      src/Gidl/Backend/Haskell/Types.hs

+ 6 - 2
src/Gidl/Backend/Haskell/Interface.hs

@@ -19,7 +19,9 @@ interfaceModule modulepath ir =
   artifactText ((ifModuleName ir) ++ ".hs") $
   prettyLazyText 80 $
   stack
-    [ text "module"
+    [ text "{-# LANGUAGE DeriveDataTypeable #-}"
+    , empty
+    , text "module"
       <+> im (ifModuleName ir)
       <+> text "where"
     , empty
@@ -41,6 +43,8 @@ interfaceModule modulepath ir =
               $ map importType
               $ interfaceTypes ir
   extraimports = [ text "import Data.Serialize"
+                 , text "import Data.Typeable"
+                 , text "import Data.Data"
                  , text "import qualified Test.QuickCheck as Q" ]
 
 schemaDoc :: String -> Schema -> Doc
@@ -98,7 +102,7 @@ schemaDoc interfaceName (Schema schemaName schema) = stack
     ]
   where
   constructorName n = userTypeModuleName n ++ schemaName
-  deriv = text "deriving (Eq, Show)"
+  deriv = text "deriving (Eq, Show, Data, Typeable)"
   typeName = interfaceName ++ schemaName
 
 ifModuleName :: InterfaceRepr -> String

+ 6 - 3
src/Gidl/Backend/Haskell/Types.hs

@@ -17,6 +17,7 @@ typeModule modulepath tr@(TypeRepr _ td) =
   prettyLazyText 80 $
   stack
     [ text "{-# LANGUAGE RecordWildCards #-}"
+    , text "{-# LANGUAGE DeriveDataTypeable #-}"
     , empty
     , text "module"
       <+> tm (typeModuleName tr)
@@ -24,6 +25,8 @@ typeModule modulepath tr@(TypeRepr _ td) =
     , empty
     , stack (imports ++
               [ text "import Data.Serialize"
+              , text "import Data.Typeable"
+              , text "import Data.Data"
               , text "import qualified Test.QuickCheck as Q"
               ])
     , empty
@@ -122,14 +125,14 @@ typeDecl tname (StructType (Struct ss)) = stack
   , empty
   , arbitraryInstance tname
   ]
-  where deriv = typeDeriving ["Eq", "Show"]
+  where deriv = typeDeriving ["Eq", "Show", "Data", "Typeable"]
 
 typeDecl tname (NewtypeType (Newtype n)) = stack
   [ text "newtype" <+> text tname <+> equals
   , indent 2 $ text tname <+> align
         (lbrace <+> text ("un" ++ tname) <+> text "::" <+>
          text (typeHaskellType n) </>
-         rbrace <+> typeDeriving ["Eq", "Show"])
+         rbrace <+> typeDeriving ["Eq", "Show", "Data", "Typeable"])
   , empty
   , text ("put" ++ tname) <+> colon <> colon <+> text "Putter" <+> text tname
   , text ("put" ++ tname) <+> parens (text tname <+> text "a") <+> equals <+> text "put a"
@@ -190,7 +193,7 @@ typeDecl tname (EnumType (EnumT s es)) = stack
   , empty
   , arbitraryInstance tname
   ]
-  where deriv = typeDeriving ["Eq", "Show", "Ord"]
+  where deriv = typeDeriving ["Eq", "Show", "Ord", "Data", "Typeable"]
 
 typeDecl tn _ = error ("typeDecl: cannot create decl for built in type " ++ tn)