Interface.hs 2.5 KB

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