Interface.hs 2.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081
  1. module Gidl.Backend.Ivory.Interface where
  2. import Data.Monoid
  3. import Data.List (intercalate, nub)
  4. import Data.Char (toUpper)
  5. import Gidl.Types
  6. import Gidl.Interface
  7. import Gidl.Schema
  8. import Gidl.Backend.Ivory.Types
  9. import Ivory.Artifact
  10. import Text.PrettyPrint.Mainland
  11. interfaceModule :: [String] -> InterfaceRepr -> Artifact
  12. interfaceModule modulepath ir =
  13. artifactPath (intercalate "/" modulepath) $
  14. artifactText ((ifModuleName ir) ++ ".hs") $
  15. prettyLazyText 80 $
  16. stack
  17. [ text "{-# LANGUAGE DeriveDataTypeable #-}"
  18. , empty
  19. , text "module"
  20. <+> im (ifModuleName ir)
  21. <+> text "where"
  22. , empty
  23. , stack $ typeimports ++ extraimports
  24. , empty
  25. , schemaDoc (ifModuleName ir) (producerSchema ir)
  26. , empty
  27. , schemaDoc (ifModuleName ir) (consumerSchema ir)
  28. ]
  29. where
  30. im mname = mconcat $ punctuate dot
  31. $ map text (modulepath ++ [mname])
  32. tm mname = mconcat $ punctuate dot
  33. $ map text (typepath modulepath ++ ["Types", mname])
  34. where typepath = reverse . drop 1 . reverse
  35. typeimports = map (importDecl tm)
  36. $ nub
  37. $ map importType
  38. $ interfaceTypes ir
  39. extraimports = [ text "import Data.Serialize"
  40. , text "import Data.Typeable"
  41. , text "import Data.Data"
  42. , text "import qualified Test.QuickCheck as Q" ]
  43. schemaDoc :: String -> Schema -> Doc
  44. schemaDoc interfaceName (Schema schemaName []) =
  45. text "-- Cannot define" <+> text schemaName <+> text "schema for"
  46. <+> text interfaceName <+> text "interface: schema is empty"
  47. schemaDoc interfaceName (Schema schemaName schema) = stack
  48. [ text "-- Define" <+> text schemaName <+> text "schema for"
  49. <+> text interfaceName <+> text "interface"
  50. , text "data" <+> text typeName
  51. , indent 2 $ encloseStack equals deriv (text "|")
  52. [ text (constructorName n) <+> text (typeIvoryType t)
  53. | (_, (Message n t)) <- schema
  54. ]
  55. ]
  56. where
  57. constructorName n = userTypeModuleName n ++ schemaName
  58. deriv = text "deriving (Eq, Show, Data, Typeable)"
  59. typeName = interfaceName ++ schemaName
  60. ifModuleName :: InterfaceRepr -> String
  61. ifModuleName (InterfaceRepr iname _) = aux iname
  62. where
  63. aux :: String -> String
  64. aux = first_cap . u_to_camel
  65. first_cap (s:ss) = (toUpper s) : ss
  66. first_cap [] = []
  67. u_to_camel ('_':'i':[]) = []
  68. u_to_camel ('_':[]) = []
  69. u_to_camel ('_':a:as) = (toUpper a) : u_to_camel as
  70. u_to_camel (a:as) = a : u_to_camel as
  71. u_to_camel [] = []