module Hydra.Sources.Tier0.Ast where
import qualified Data.List as L
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Maybe as Y
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import qualified Hydra.Dsl.Terms as Terms
import Hydra.Dsl.Types as Types
import Hydra.Sources.Core
hydraAstModule :: Module
hydraAstModule :: Module
hydraAstModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
hydraCoreModule] [Module
hydraCoreModule] (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"A model which provides a common syntax tree for Hydra serializers"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/ast"
def :: String -> Type -> Element
def = Namespace -> String -> Type -> Element
datatype Namespace
ns
ast :: String -> Type
ast = Namespace -> String -> Type
typeref Namespace
ns
elements :: [Element]
elements = [
String -> Type -> Element
def String
"Associativity" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Operator associativity" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"none", String
"left", String
"right", String
"both"],
String -> Type -> Element
def String
"BlockStyle" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Formatting option for code blocks" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"indent"String -> Type -> FieldType
>: Type -> Type
optional Type
string,
String
"newlineBeforeContent"String -> Type -> FieldType
>: Type
boolean,
String
"newlineAfterContent"String -> Type -> FieldType
>: Type
boolean],
String -> Type -> Element
def String
"BracketExpr" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An expression enclosed by brackets" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"brackets"String -> Type -> FieldType
>: String -> Type
ast String
"Brackets",
String
"enclosed"String -> Type -> FieldType
>: String -> Type
ast String
"Expr",
String
"style"String -> Type -> FieldType
>: String -> Type
ast String
"BlockStyle"],
String -> Type -> Element
def String
"Brackets" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Matching open and close bracket symbols" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"open"String -> Type -> FieldType
>: String -> Type
ast String
"Symbol",
String
"close"String -> Type -> FieldType
>: String -> Type
ast String
"Symbol"],
String -> Type -> Element
def String
"Expr" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An abstract expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"const"String -> Type -> FieldType
>: String -> Type
ast String
"Symbol",
String
"indent"String -> Type -> FieldType
>: String -> Type
ast String
"IndentedExpression",
String
"op"String -> Type -> FieldType
>: String -> Type
ast String
"OpExpr",
String
"brackets"String -> Type -> FieldType
>: String -> Type
ast String
"BracketExpr"],
String -> Type -> Element
def String
"IndentedExpression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An expression indented in a certain style" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"style"String -> Type -> FieldType
>: String -> Type
ast String
"IndentStyle",
String
"expr"String -> Type -> FieldType
>: String -> Type
ast String
"Expr"],
String -> Type -> Element
def String
"IndentStyle" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Any of several indentation styles" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"allLines"String -> Type -> FieldType
>: Type
string,
String
"subsequentLines"String -> Type -> FieldType
>: Type
string],
String -> Type -> Element
def String
"Op" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An operator symbol" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"symbol"String -> Type -> FieldType
>: String -> Type
ast String
"Symbol",
String
"padding"String -> Type -> FieldType
>: String -> Type
ast String
"Padding",
String
"precedence"String -> Type -> FieldType
>: String -> Type
ast String
"Precedence",
String
"associativity"String -> Type -> FieldType
>: String -> Type
ast String
"Associativity"],
String -> Type -> Element
def String
"OpExpr" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An operator expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"op"String -> Type -> FieldType
>: String -> Type
ast String
"Op",
String
"lhs"String -> Type -> FieldType
>: String -> Type
ast String
"Expr",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"Expr"],
String -> Type -> Element
def String
"Padding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Left and right padding for an operator" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"left"String -> Type -> FieldType
>: String -> Type
ast String
"Ws",
String
"right"String -> Type -> FieldType
>: String -> Type
ast String
"Ws"],
String -> Type -> Element
def String
"Precedence" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Operator precedence" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type
int32,
String -> Type -> Element
def String
"Symbol" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Any symbol"
Type
string,
String -> Type -> Element
def String
"Ws" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"One of several classes of whitespace" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"none"String -> Type -> FieldType
>: Type
unit,
String
"space"String -> Type -> FieldType
>: Type
unit,
String
"break"String -> Type -> FieldType
>: Type
unit,
String
"breakAndIndent"String -> Type -> FieldType
>: Type
string,
String
"doubleBreak"String -> Type -> FieldType
>: Type
unit]]