Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Ast
Description
A model which provides a common syntax tree for Hydra serializers
Synopsis
- data Associativity
- _Associativity :: Name
- _Associativity_none :: Name
- _Associativity_left :: Name
- _Associativity_right :: Name
- _Associativity_both :: Name
- data BlockStyle = BlockStyle {}
- _BlockStyle :: Name
- _BlockStyle_indent :: Name
- _BlockStyle_newlineBeforeContent :: Name
- _BlockStyle_newlineAfterContent :: Name
- data BracketExpr = BracketExpr {}
- _BracketExpr :: Name
- _BracketExpr_brackets :: Name
- _BracketExpr_enclosed :: Name
- _BracketExpr_style :: Name
- data Brackets = Brackets {}
- _Brackets :: Name
- _Brackets_open :: Name
- _Brackets_close :: Name
- data Expr
- _Expr :: Name
- _Expr_const :: Name
- _Expr_indent :: Name
- _Expr_op :: Name
- _Expr_brackets :: Name
- data IndentedExpression = IndentedExpression {}
- _IndentedExpression :: Name
- _IndentedExpression_style :: Name
- _IndentedExpression_expr :: Name
- data IndentStyle
- _IndentStyle :: Name
- _IndentStyle_allLines :: Name
- _IndentStyle_subsequentLines :: Name
- data Op = Op {}
- _Op :: Name
- _Op_symbol :: Name
- _Op_padding :: Name
- _Op_precedence :: Name
- _Op_associativity :: Name
- data OpExpr = OpExpr {}
- _OpExpr :: Name
- _OpExpr_op :: Name
- _OpExpr_lhs :: Name
- _OpExpr_rhs :: Name
- data Padding = Padding {
- paddingLeft :: Ws
- paddingRight :: Ws
- _Padding :: Name
- _Padding_left :: Name
- _Padding_right :: Name
- newtype Precedence = Precedence {
- unPrecedence :: Int
- _Precedence :: Name
- newtype Symbol = Symbol {}
- _Symbol :: Name
- data Ws
- _Ws :: Name
- _Ws_none :: Name
- _Ws_space :: Name
- _Ws_break :: Name
- _Ws_breakAndIndent :: Name
- _Ws_doubleBreak :: Name
Documentation
data Associativity Source #
Operator associativity
Instances
Read Associativity Source # | |
Defined in Hydra.Ast Methods readsPrec :: Int -> ReadS Associativity # readList :: ReadS [Associativity] # | |
Show Associativity Source # | |
Defined in Hydra.Ast Methods showsPrec :: Int -> Associativity -> ShowS # show :: Associativity -> String # showList :: [Associativity] -> ShowS # | |
Eq Associativity Source # | |
Defined in Hydra.Ast Methods (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
Ord Associativity Source # | |
Defined in Hydra.Ast Methods compare :: Associativity -> Associativity -> Ordering # (<) :: Associativity -> Associativity -> Bool # (<=) :: Associativity -> Associativity -> Bool # (>) :: Associativity -> Associativity -> Bool # (>=) :: Associativity -> Associativity -> Bool # max :: Associativity -> Associativity -> Associativity # min :: Associativity -> Associativity -> Associativity # |
data BlockStyle Source #
Formatting option for code blocks
Constructors
BlockStyle | |
Instances
Read BlockStyle Source # | |
Defined in Hydra.Ast Methods readsPrec :: Int -> ReadS BlockStyle # readList :: ReadS [BlockStyle] # readPrec :: ReadPrec BlockStyle # readListPrec :: ReadPrec [BlockStyle] # | |
Show BlockStyle Source # | |
Defined in Hydra.Ast Methods showsPrec :: Int -> BlockStyle -> ShowS # show :: BlockStyle -> String # showList :: [BlockStyle] -> ShowS # | |
Eq BlockStyle Source # | |
Defined in Hydra.Ast | |
Ord BlockStyle Source # | |
Defined in Hydra.Ast Methods compare :: BlockStyle -> BlockStyle -> Ordering # (<) :: BlockStyle -> BlockStyle -> Bool # (<=) :: BlockStyle -> BlockStyle -> Bool # (>) :: BlockStyle -> BlockStyle -> Bool # (>=) :: BlockStyle -> BlockStyle -> Bool # max :: BlockStyle -> BlockStyle -> BlockStyle # min :: BlockStyle -> BlockStyle -> BlockStyle # |
_BlockStyle :: Name Source #
data BracketExpr Source #
An expression enclosed by brackets
Constructors
BracketExpr | |
Fields |
Instances
Read BracketExpr Source # | |
Defined in Hydra.Ast Methods readsPrec :: Int -> ReadS BracketExpr # readList :: ReadS [BracketExpr] # readPrec :: ReadPrec BracketExpr # readListPrec :: ReadPrec [BracketExpr] # | |
Show BracketExpr Source # | |
Defined in Hydra.Ast Methods showsPrec :: Int -> BracketExpr -> ShowS # show :: BracketExpr -> String # showList :: [BracketExpr] -> ShowS # | |
Eq BracketExpr Source # | |
Defined in Hydra.Ast | |
Ord BracketExpr Source # | |
Defined in Hydra.Ast Methods compare :: BracketExpr -> BracketExpr -> Ordering # (<) :: BracketExpr -> BracketExpr -> Bool # (<=) :: BracketExpr -> BracketExpr -> Bool # (>) :: BracketExpr -> BracketExpr -> Bool # (>=) :: BracketExpr -> BracketExpr -> Bool # max :: BracketExpr -> BracketExpr -> BracketExpr # min :: BracketExpr -> BracketExpr -> BracketExpr # |
_BracketExpr :: Name Source #
Matching open and close bracket symbols
Constructors
Brackets | |
Fields |
An abstract expression
_Expr_const :: Name Source #
_Expr_indent :: Name Source #
data IndentedExpression Source #
An expression indented in a certain style
Constructors
IndentedExpression | |
Fields |
Instances
data IndentStyle Source #
Any of several indentation styles
Constructors
IndentStyleAllLines String | |
IndentStyleSubsequentLines String |
Instances
Read IndentStyle Source # | |
Defined in Hydra.Ast Methods readsPrec :: Int -> ReadS IndentStyle # readList :: ReadS [IndentStyle] # readPrec :: ReadPrec IndentStyle # readListPrec :: ReadPrec [IndentStyle] # | |
Show IndentStyle Source # | |
Defined in Hydra.Ast Methods showsPrec :: Int -> IndentStyle -> ShowS # show :: IndentStyle -> String # showList :: [IndentStyle] -> ShowS # | |
Eq IndentStyle Source # | |
Defined in Hydra.Ast | |
Ord IndentStyle Source # | |
Defined in Hydra.Ast Methods compare :: IndentStyle -> IndentStyle -> Ordering # (<) :: IndentStyle -> IndentStyle -> Bool # (<=) :: IndentStyle -> IndentStyle -> Bool # (>) :: IndentStyle -> IndentStyle -> Bool # (>=) :: IndentStyle -> IndentStyle -> Bool # max :: IndentStyle -> IndentStyle -> IndentStyle # min :: IndentStyle -> IndentStyle -> IndentStyle # |
_IndentStyle :: Name Source #
An operator symbol
Constructors
Op | |
Fields |
_Op_symbol :: Name Source #
_Op_padding :: Name Source #
An operator expression
_OpExpr_op :: Name Source #
_OpExpr_lhs :: Name Source #
_OpExpr_rhs :: Name Source #
Left and right padding for an operator
Constructors
Padding | |
Fields
|
_Padding_left :: Name Source #
newtype Precedence Source #
Operator precedence
Constructors
Precedence | |
Fields
|
Instances
Read Precedence Source # | |
Defined in Hydra.Ast Methods readsPrec :: Int -> ReadS Precedence # readList :: ReadS [Precedence] # readPrec :: ReadPrec Precedence # readListPrec :: ReadPrec [Precedence] # | |
Show Precedence Source # | |
Defined in Hydra.Ast Methods showsPrec :: Int -> Precedence -> ShowS # show :: Precedence -> String # showList :: [Precedence] -> ShowS # | |
Eq Precedence Source # | |
Defined in Hydra.Ast | |
Ord Precedence Source # | |
Defined in Hydra.Ast Methods compare :: Precedence -> Precedence -> Ordering # (<) :: Precedence -> Precedence -> Bool # (<=) :: Precedence -> Precedence -> Bool # (>) :: Precedence -> Precedence -> Bool # (>=) :: Precedence -> Precedence -> Bool # max :: Precedence -> Precedence -> Precedence # min :: Precedence -> Precedence -> Precedence # |
_Precedence :: Name Source #
Any symbol