{-# LANGUAGE OverloadedStrings #-} module Hydra.Sources.Tier4.Langs.Tabular where import Hydra.Sources.Tier3.All import Hydra.Dsl.Annotations import Hydra.Dsl.Bootstrap import Hydra.Dsl.Types as Types tabularModule :: Module tabularModule :: Module tabularModule = Namespace -> [Element] -> [Module] -> [Module] -> Maybe String -> Module Module Namespace ns [Element] elements [Module hydraCoreModule] [Module] tier0Modules (Maybe String -> Module) -> Maybe String -> Module forall a b. (a -> b) -> a -> b $ String -> Maybe String forall a. a -> Maybe a Just (String "A simple, untyped tabular data model, suitable for CSVs and TSVs") where ns :: Namespace ns = String -> Namespace Namespace String "hydra/langs/tabular" def :: String -> Type -> Element def = Namespace -> String -> Type -> Element datatype Namespace ns tabular :: String -> Type tabular = Namespace -> String -> Type typeref Namespace ns elements :: [Element] elements = [ String -> Type -> Element def String "DataRow" (Type -> Element) -> Type -> Element forall a b. (a -> b) -> a -> b $ String -> Type -> Type doc String "A data row, containing optional-valued cells; one per column" (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ String -> Type -> Type lambda String "v" (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ Type -> Type list (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ Type -> Type optional Type "v", String -> Type -> Element def String "HeaderRow" (Type -> Element) -> Type -> Element forall a b. (a -> b) -> a -> b $ String -> Type -> Type doc String "A header row, containing column names (but no types or data)" (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ Type -> Type list Type string, String -> Type -> Element def String "Table" (Type -> Element) -> Type -> Element forall a b. (a -> b) -> a -> b $ String -> Type -> Type doc String "A simple table as in a CSV file, having an optional header row and any number of data rows" (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ String -> Type -> Type lambda String "v" (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ [FieldType] -> Type record [ String "header"String -> Type -> FieldType >: String -> Type -> Type doc String "The optional header row of the table. If present, the header must have the same number of cells as each data row." (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ Type -> Type optional (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ String -> Type tabular String "HeaderRow", String "data"String -> Type -> FieldType >: String -> Type -> Type doc String "The data rows of the table. Each row must have the same number of cells." (Type -> Type) -> Type -> Type forall a b. (a -> b) -> a -> b $ Type -> Type list (String -> Type tabular String "DataRow" Type -> Type -> Type @@ Type "v")]]