hydra-0.1.1: Type-aware transformations for data and programs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hydra.Ext.Haskell.Ast

Description

A Haskell syntax model, loosely based on Language.Haskell.Tools.AST

Synopsis

Documentation

newtype CaseRhs Source #

The right-hand side of a pattern-matching alternative

Constructors

CaseRhs 

Fields

Instances

Instances details
Read CaseRhs Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show CaseRhs Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq CaseRhs Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: CaseRhs -> CaseRhs -> Bool #

(/=) :: CaseRhs -> CaseRhs -> Bool #

Ord CaseRhs Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree CaseRhs Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: CaseRhs -> Expr Source #

data ConstructorWithComments Source #

A data constructor together with any comments

Instances

Instances details
Read ConstructorWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show ConstructorWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq ConstructorWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord ConstructorWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree ConstructorWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

data DataDeclaration_Keyword Source #

The 'data' versus 'newtype keyword

Instances

Instances details
Read DataDeclaration_Keyword Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show DataDeclaration_Keyword Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq DataDeclaration_Keyword Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord DataDeclaration_Keyword Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree DataDeclaration_Keyword Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

data DeclarationWithComments Source #

A data declaration together with any comments

Instances

Instances details
Read DeclarationWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show DeclarationWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq DeclarationWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord DeclarationWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree DeclarationWithComments Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

data DeclarationHead_Application Source #

An application-style declaration head

Instances

Instances details
Read DeclarationHead_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show DeclarationHead_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq DeclarationHead_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord DeclarationHead_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

newtype Deriving Source #

A 'deriving' statement

Constructors

Deriving 

Fields

data Export Source #

An export statement

Instances

Instances details
Read Export Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Export Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Export Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Export -> Export -> Bool #

(/=) :: Export -> Export -> Bool #

Ord Export Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

data Expression Source #

A data expression

data Expression_Application Source #

An application expression

Instances

Instances details
Read Expression_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Expression_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Expression_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord Expression_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree Expression_Application Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

data Expression_ConstructRecord Source #

A record constructor expression

Instances

Instances details
Read Expression_ConstructRecord Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Expression_ConstructRecord Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Expression_ConstructRecord Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord Expression_ConstructRecord Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree Expression_ConstructRecord Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

data Expression_InfixApplication Source #

An infix application expression

Instances

Instances details
Read Expression_InfixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Expression_InfixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Expression_InfixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord Expression_InfixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

data Expression_Lambda Source #

A lambda expression

data Expression_PrefixApplication Source #

A prefix expression

Instances

Instances details
Read Expression_PrefixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Expression_PrefixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Expression_PrefixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord Expression_PrefixApplication Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

data Expression_TypeSignature Source #

A type signature expression

data Expression_UpdateRecord Source #

An update record expression

data Field Source #

A field (name/type pair)

Constructors

Field 

Fields

Instances

Instances details
Read Field Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Field Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Eq Field Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

Ord Field Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

compare :: Field -> Field -> Ordering #

(<) :: Field -> Field -> Bool #

(<=) :: Field -> Field -> Bool #

(>) :: Field -> Field -> Bool #

(>=) :: Field -> Field -> Bool #

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

ToTree Field Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Field -> Expr Source #

data FieldWithComments Source #

A field together with any comments

data Import Source #

An import statement

Instances

Instances details
Read Import Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Import Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Import Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Import -> Import -> Bool #

(/=) :: Import -> Import -> Bool #

Ord Import Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree Import Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Import -> Expr Source #

data ImportExportSpec_Subspec Source #

data Module Source #

Instances

Instances details
Read Module Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Module Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Module Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Ord Module Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree Module Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Module -> Expr Source #

data Name Source #

Instances

Instances details
Read Name Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Name Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

ToTree Name Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Name -> Expr Source #

newtype NamePart Source #

Constructors

NamePart 

Fields

data Pattern_Application Source #

data Type Source #

Instances

Instances details
Read Type Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Type Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

ToTree Type Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Type -> Expr Source #

newtype Variable Source #

Constructors

Variable 

Fields

Instances

Instances details
Read Variable Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Show Variable Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Eq Variable Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

Ord Variable Source # 
Instance details

Defined in Hydra.Ext.Haskell.Ast

ToTree Variable Source # 
Instance details

Defined in Hydra.Ext.Haskell.Serde

Methods

toTree :: Variable -> Expr Source #