{-# LANGUAGE OverloadedStrings #-} module Hydra.Impl.Haskell.Sources.Module where import Hydra.All import Hydra.Impl.Haskell.Dsl.Types as Types import Hydra.Impl.Haskell.Dsl.Standard import Hydra.Impl.Haskell.Sources.Mantle hydraModuleModule :: Module Meta hydraModuleModule :: Module Meta hydraModuleModule = forall m. Namespace -> [Element m] -> [Module m] -> Maybe String -> Module m Module Namespace ns [Element Meta] elements [Module Meta hydraMantleModule] forall a b. (a -> b) -> a -> b $ forall a. a -> Maybe a Just String "A model for Hydra namespaces and modules (collections of elements in the same namespace)" where ns :: Namespace ns = String -> Namespace Namespace String "hydra/module" mantle :: String -> Type m mantle = forall m. Namespace -> String -> Type m nsref forall a b. (a -> b) -> a -> b $ forall m. Module m -> Namespace moduleNamespace Module Meta hydraMantleModule mod :: String -> Type m mod = forall m. Namespace -> String -> Type m nsref Namespace ns def :: String -> Type m -> Element m def = forall m. Namespace -> String -> Type m -> Element m datatype Namespace ns elements :: [Element Meta] elements = [ forall {m}. String -> Type m -> Element m def String "FileExtension" forall m. Type m string, forall {m}. String -> Type m -> Element m def String "Module" forall a b. (a -> b) -> a -> b $ String -> Type Meta -> Type Meta doc String "A logical collection of elements in the same namespace, having dependencies on zero or more other modules" forall a b. (a -> b) -> a -> b $ forall m. String -> Type m -> Type m lambda String "m" forall a b. (a -> b) -> a -> b $ forall m. [FieldType m] -> Type m record [ String "namespace"forall m. String -> Type m -> FieldType m >: String -> Type Meta -> Type Meta doc String "A common prefix for all element names in the module" forall a b. (a -> b) -> a -> b $ forall {m}. String -> Type m mod String "Namespace", String "elements"forall m. String -> Type m -> FieldType m >: String -> Type Meta -> Type Meta doc String "The elements defined in this module" forall a b. (a -> b) -> a -> b $ forall m. Type m -> Type m list forall a b. (a -> b) -> a -> b $ forall {m}. String -> Type m mantle String "Element" forall m. Type m -> Type m -> Type m @@ Type Meta "m", String "dependencies"forall m. String -> Type m -> FieldType m >: String -> Type Meta -> Type Meta doc String "Any additional modules this one has a direct dependency upon" forall a b. (a -> b) -> a -> b $ forall m. Type m -> Type m list forall a b. (a -> b) -> a -> b $ forall {m}. String -> Type m mod String "Module" forall m. Type m -> Type m -> Type m @@ Type Meta "m", String "description"forall m. String -> Type m -> FieldType m >: String -> Type Meta -> Type Meta doc String "An optional human-readable description of the module" forall a b. (a -> b) -> a -> b $ forall m. Type m -> Type m optional forall m. Type m string], forall {m}. String -> Type m -> Element m def String "Namespace" forall a b. (a -> b) -> a -> b $ String -> Type Meta -> Type Meta doc String "A prefix for element names" forall m. Type m string]