haskell-src-exts-1.17.0: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Copyright(c) Niklas Broberg 2004-2009, (c) The GHC Team, 1997-2000
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, d00nibro@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.Haskell.Exts.Syntax

Contents

Description

A suite of datatypes describing the abstract syntax of Haskell 98 http://www.haskell.org/onlinereport/ plus registered extensions, including:

  • multi-parameter type classes with functional dependencies (MultiParamTypeClasses, FunctionalDependencies)
  • parameters of type class assertions are unrestricted (FlexibleContexts)
  • forall types as universal and existential quantification (RankNTypes, ExistentialQuantification, etc)
  • pattern guards (PatternGuards)
  • implicit parameters (ImplicitParameters)
  • generalised algebraic data types (GADTs)
  • template haskell (TemplateHaskell)
  • empty data type declarations (EmptyDataDecls)
  • unboxed tuples (UnboxedTuples)
  • regular patterns (RegularPatterns)
  • HSP-style XML expressions and patterns (XmlSyntax)

Synopsis

Modules

data Module Source

A complete Haskell source module.

Instances

Eq Module Source 

Methods

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

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

Data Module Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module

toConstr :: Module -> Constr

dataTypeOf :: Module -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Module)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)

gmapT :: (forall b. Data b => b -> b) -> Module -> Module

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

Ord Module Source 
Show Module Source 
Generic Module Source 

Associated Types

type Rep Module :: * -> *

Methods

from :: Module -> Rep Module x

to :: Rep Module x -> Module

AppFixity Module Source 

Methods

applyFixities :: Monad m => [Fixity] -> Module -> m Module Source

Pretty Module Source 

Methods

pretty :: Module -> Doc

prettyPrec :: Int -> Module -> Doc

type Rep Module Source 

data WarningText Source

Warning text to optionally use in the module header of e.g. a deprecated module.

Instances

Eq WarningText Source 
Data WarningText Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningText -> c WarningText

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarningText

toConstr :: WarningText -> Constr

dataTypeOf :: WarningText -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WarningText)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningText)

gmapT :: (forall b. Data b => b -> b) -> WarningText -> WarningText

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningText -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningText -> r

gmapQ :: (forall d. Data d => d -> u) -> WarningText -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningText -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningText -> m WarningText

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningText -> m WarningText

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningText -> m WarningText

Ord WarningText Source 
Show WarningText Source 
Generic WarningText Source 

Associated Types

type Rep WarningText :: * -> *

type Rep WarningText Source 

data ExportSpec Source

An item in a module's export specification.

Constructors

EVar QName

variable.

EAbs Namespace QName

T: a class or datatype exported abstractly, or a type synonym.

EThingAll QName

T(..): a class exported with all of its methods, or a datatype exported with all of its constructors.

EThingWith QName [CName]

T(C_1,...,C_n): a class exported with some of its methods, or a datatype exported with some of its constructors.

EModuleContents ModuleName

module M: re-export a module.

Instances

Eq ExportSpec Source 
Data ExportSpec Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExportSpec -> c ExportSpec

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExportSpec

toConstr :: ExportSpec -> Constr

dataTypeOf :: ExportSpec -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExportSpec)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExportSpec)

gmapT :: (forall b. Data b => b -> b) -> ExportSpec -> ExportSpec

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExportSpec -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExportSpec -> r

gmapQ :: (forall d. Data d => d -> u) -> ExportSpec -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExportSpec -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExportSpec -> m ExportSpec

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExportSpec -> m ExportSpec

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExportSpec -> m ExportSpec

Ord ExportSpec Source 
Show ExportSpec Source 
Generic ExportSpec Source 

Associated Types

type Rep ExportSpec :: * -> *

Pretty ExportSpec Source 

Methods

pretty :: ExportSpec -> Doc

prettyPrec :: Int -> ExportSpec -> Doc

type Rep ExportSpec Source 

data ImportDecl Source

An import declaration.

Constructors

ImportDecl 

Fields

Instances

Eq ImportDecl Source 
Data ImportDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl -> c ImportDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportDecl

toConstr :: ImportDecl -> Constr

dataTypeOf :: ImportDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportDecl)

gmapT :: (forall b. Data b => b -> b) -> ImportDecl -> ImportDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl

Ord ImportDecl Source 
Show ImportDecl Source 
Generic ImportDecl Source 

Associated Types

type Rep ImportDecl :: * -> *

Pretty ImportDecl Source 

Methods

pretty :: ImportDecl -> Doc

prettyPrec :: Int -> ImportDecl -> Doc

type Rep ImportDecl Source 

data ImportSpec Source

An import specification, representing a single explicit item imported (or hidden) from a module.

Constructors

IVar Name

variable.

IAbs Namespace Name

T: the name of a class, datatype or type synonym.

IThingAll Name

T(..): a class imported with all of its methods, or a datatype imported with all of its constructors.

IThingWith Name [CName]

T(C_1,...,C_n): a class imported with some of its methods, or a datatype imported with some of its constructors.

Instances

Eq ImportSpec Source 
Data ImportSpec Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec

toConstr :: ImportSpec -> Constr

dataTypeOf :: ImportSpec -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)

gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r

gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec

Ord ImportSpec Source 
Show ImportSpec Source 
Generic ImportSpec Source 

Associated Types

type Rep ImportSpec :: * -> *

Pretty ImportSpec Source 

Methods

pretty :: ImportSpec -> Doc

prettyPrec :: Int -> ImportSpec -> Doc

type Rep ImportSpec Source 

data Assoc Source

Associativity of an operator.

Constructors

AssocNone

non-associative operator (declared with infix)

AssocLeft

left-associative operator (declared with infixl).

AssocRight

right-associative operator (declared with infixr)

Instances

Eq Assoc Source 

Methods

(==) :: Assoc -> Assoc -> Bool

(/=) :: Assoc -> Assoc -> Bool

Data Assoc Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assoc -> c Assoc

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Assoc

toConstr :: Assoc -> Constr

dataTypeOf :: Assoc -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Assoc)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Assoc)

gmapT :: (forall b. Data b => b -> b) -> Assoc -> Assoc

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assoc -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assoc -> r

gmapQ :: (forall d. Data d => d -> u) -> Assoc -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Assoc -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assoc -> m Assoc

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assoc -> m Assoc

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assoc -> m Assoc

Ord Assoc Source 

Methods

compare :: Assoc -> Assoc -> Ordering

(<) :: Assoc -> Assoc -> Bool

(<=) :: Assoc -> Assoc -> Bool

(>) :: Assoc -> Assoc -> Bool

(>=) :: Assoc -> Assoc -> Bool

max :: Assoc -> Assoc -> Assoc

min :: Assoc -> Assoc -> Assoc

Show Assoc Source 

Methods

showsPrec :: Int -> Assoc -> ShowS

show :: Assoc -> String

showList :: [Assoc] -> ShowS

Generic Assoc Source 

Associated Types

type Rep Assoc :: * -> *

Methods

from :: Assoc -> Rep Assoc x

to :: Rep Assoc x -> Assoc

Pretty Assoc Source 

Methods

pretty :: Assoc -> Doc

prettyPrec :: Int -> Assoc -> Doc

type Rep Assoc Source 

data Namespace Source

Namespaces for imports/exports.

Instances

Eq Namespace Source 
Data Namespace Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Namespace -> c Namespace

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Namespace

toConstr :: Namespace -> Constr

dataTypeOf :: Namespace -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Namespace)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Namespace)

gmapT :: (forall b. Data b => b -> b) -> Namespace -> Namespace

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Namespace -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Namespace -> r

gmapQ :: (forall d. Data d => d -> u) -> Namespace -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Namespace -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace

Ord Namespace Source 
Show Namespace Source 
Generic Namespace Source 

Associated Types

type Rep Namespace :: * -> *

Pretty Namespace Source 

Methods

pretty :: Namespace -> Doc

prettyPrec :: Int -> Namespace -> Doc

type Rep Namespace Source 

Declarations

data Decl Source

A top-level declaration.

Constructors

TypeDecl SrcLoc Name [TyVarBind] Type

A type declaration

TypeFamDecl SrcLoc Name [TyVarBind] (Maybe Kind)

A type family declaration

ClosedTypeFamDecl SrcLoc Name [TyVarBind] (Maybe Kind) [TypeEqn]

A closed type family declaration

DataDecl SrcLoc DataOrNew Context Name [TyVarBind] [QualConDecl] [Deriving]

A data OR newtype declaration

GDataDecl SrcLoc DataOrNew Context Name [TyVarBind] (Maybe Kind) [GadtDecl] [Deriving]

A data OR newtype declaration, GADT style

DataFamDecl SrcLoc Context Name [TyVarBind] (Maybe Kind)

A data family declaration

TypeInsDecl SrcLoc Type Type

A type family instance declaration

DataInsDecl SrcLoc DataOrNew Type [QualConDecl] [Deriving]

A data family instance declaration

GDataInsDecl SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]

A data family instance declaration, GADT style

ClassDecl SrcLoc Context Name [TyVarBind] [FunDep] [ClassDecl]

A declaration of a type class

InstDecl SrcLoc (Maybe Overlap) [TyVarBind] Context QName [Type] [InstDecl]

An declaration of a type class instance

DerivDecl SrcLoc (Maybe Overlap) [TyVarBind] Context QName [Type]

A standalone deriving declaration

InfixDecl SrcLoc Assoc Int [Op]

A declaration of operator fixity

DefaultDecl SrcLoc [Type]

A declaration of default types

SpliceDecl SrcLoc Exp

A Template Haskell splicing declaration

TypeSig SrcLoc [Name] Type

A type signature declaration

PatSynSig SrcLoc Name (Maybe [TyVarBind]) Context Context Type

Pattern Synonym Signature

FunBind [Match]

A set of function binding clauses

PatBind SrcLoc Pat Rhs (Maybe Binds)

A pattern binding

ForImp SrcLoc CallConv Safety String Name Type

A foreign import declaration

ForExp SrcLoc CallConv String Name Type

A foreign export declaration

PatSyn SrcLoc Pat Pat PatternSynDirection 
RulePragmaDecl SrcLoc [Rule]

A RULES pragma

DeprPragmaDecl SrcLoc [([Name], String)]

A DEPRECATED pragma

WarnPragmaDecl SrcLoc [([Name], String)]

A WARNING pragma

InlineSig SrcLoc Bool Activation QName

An INLINE pragma

InlineConlikeSig SrcLoc Activation QName

An INLINE CONLIKE pragma

SpecSig SrcLoc Activation QName [Type]

A SPECIALISE pragma

SpecInlineSig SrcLoc Bool Activation QName [Type]

A SPECIALISE INLINE pragma

InstSig SrcLoc [TyVarBind] Context QName [Type]

A SPECIALISE instance pragma

AnnPragma SrcLoc Annotation

An ANN pragma

MinimalPragma SrcLoc (Maybe BooleanFormula)

A MINIMAL pragma

RoleAnnotDecl SrcLoc QName [Role]

A role annotation

Instances

Eq Decl Source 

Methods

(==) :: Decl -> Decl -> Bool

(/=) :: Decl -> Decl -> Bool

Data Decl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decl -> c Decl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Decl

toConstr :: Decl -> Constr

dataTypeOf :: Decl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Decl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Decl)

gmapT :: (forall b. Data b => b -> b) -> Decl -> Decl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r

gmapQ :: (forall d. Data d => d -> u) -> Decl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Decl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decl -> m Decl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl

Ord Decl Source 

Methods

compare :: Decl -> Decl -> Ordering

(<) :: Decl -> Decl -> Bool

(<=) :: Decl -> Decl -> Bool

(>) :: Decl -> Decl -> Bool

(>=) :: Decl -> Decl -> Bool

max :: Decl -> Decl -> Decl

min :: Decl -> Decl -> Decl

Show Decl Source 

Methods

showsPrec :: Int -> Decl -> ShowS

show :: Decl -> String

showList :: [Decl] -> ShowS

Generic Decl Source 

Associated Types

type Rep Decl :: * -> *

Methods

from :: Decl -> Rep Decl x

to :: Rep Decl x -> Decl

AppFixity Decl Source 

Methods

applyFixities :: Monad m => [Fixity] -> Decl -> m Decl Source

Pretty Decl Source 

Methods

pretty :: Decl -> Doc

prettyPrec :: Int -> Decl -> Doc

type Rep Decl Source 

data Binds Source

A binding group inside a let or where clause.

Constructors

BDecls [Decl]

An ordinary binding group

IPBinds [IPBind]

A binding group for implicit parameters

Instances

Eq Binds Source 

Methods

(==) :: Binds -> Binds -> Bool

(/=) :: Binds -> Binds -> Bool

Data Binds Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binds -> c Binds

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binds

toConstr :: Binds -> Constr

dataTypeOf :: Binds -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Binds)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binds)

gmapT :: (forall b. Data b => b -> b) -> Binds -> Binds

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binds -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binds -> r

gmapQ :: (forall d. Data d => d -> u) -> Binds -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binds -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binds -> m Binds

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binds -> m Binds

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binds -> m Binds

Ord Binds Source 

Methods

compare :: Binds -> Binds -> Ordering

(<) :: Binds -> Binds -> Bool

(<=) :: Binds -> Binds -> Bool

(>) :: Binds -> Binds -> Bool

(>=) :: Binds -> Binds -> Bool

max :: Binds -> Binds -> Binds

min :: Binds -> Binds -> Binds

Show Binds Source 

Methods

showsPrec :: Int -> Binds -> ShowS

show :: Binds -> String

showList :: [Binds] -> ShowS

Generic Binds Source 

Associated Types

type Rep Binds :: * -> *

Methods

from :: Binds -> Rep Binds x

to :: Rep Binds x -> Binds

AppFixity Binds Source 

Methods

applyFixities :: Monad m => [Fixity] -> Binds -> m Binds Source

type Rep Binds Source 

data IPBind Source

A binding of an implicit parameter.

Constructors

IPBind SrcLoc IPName Exp 

Instances

Eq IPBind Source 

Methods

(==) :: IPBind -> IPBind -> Bool

(/=) :: IPBind -> IPBind -> Bool

Data IPBind Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind -> c IPBind

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPBind

toConstr :: IPBind -> Constr

dataTypeOf :: IPBind -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPBind)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPBind)

gmapT :: (forall b. Data b => b -> b) -> IPBind -> IPBind

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind -> r

gmapQ :: (forall d. Data d => d -> u) -> IPBind -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind -> m IPBind

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind -> m IPBind

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind -> m IPBind

Ord IPBind Source 
Show IPBind Source 
Generic IPBind Source 

Associated Types

type Rep IPBind :: * -> *

Methods

from :: IPBind -> Rep IPBind x

to :: Rep IPBind x -> IPBind

AppFixity IPBind Source 

Methods

applyFixities :: Monad m => [Fixity] -> IPBind -> m IPBind Source

Pretty IPBind Source 

Methods

pretty :: IPBind -> Doc

prettyPrec :: Int -> IPBind -> Doc

type Rep IPBind Source 

data PatternSynDirection Source

Constructors

Unidirectional

A unidirectional pattern synonym with "<-"

ImplicitBidirectional

A bidirectional pattern synonym with "="

ExplicitBidirectional [Decl]

A birectional pattern synonym with the construction specified.

Instances

Eq PatternSynDirection Source 
Data PatternSynDirection Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatternSynDirection -> c PatternSynDirection

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatternSynDirection

toConstr :: PatternSynDirection -> Constr

dataTypeOf :: PatternSynDirection -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatternSynDirection)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatternSynDirection)

gmapT :: (forall b. Data b => b -> b) -> PatternSynDirection -> PatternSynDirection

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatternSynDirection -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatternSynDirection -> r

gmapQ :: (forall d. Data d => d -> u) -> PatternSynDirection -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatternSynDirection -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatternSynDirection -> m PatternSynDirection

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSynDirection -> m PatternSynDirection

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSynDirection -> m PatternSynDirection

Ord PatternSynDirection Source 
Show PatternSynDirection Source 
Generic PatternSynDirection Source 
type Rep PatternSynDirection Source 

Type classes and instances

data ClassDecl Source

Declarations inside a class declaration.

Constructors

ClsDecl Decl

ordinary declaration

ClsDataFam SrcLoc Context Name [TyVarBind] (Maybe Kind)

declaration of an associated data type

ClsTyFam SrcLoc Name [TyVarBind] (Maybe Kind)

declaration of an associated type synonym

ClsTyDef SrcLoc Type Type

default choice for an associated type synonym

ClsDefSig SrcLoc Name Type

default signature

Instances

Eq ClassDecl Source 
Data ClassDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassDecl -> c ClassDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassDecl

toConstr :: ClassDecl -> Constr

dataTypeOf :: ClassDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ClassDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassDecl)

gmapT :: (forall b. Data b => b -> b) -> ClassDecl -> ClassDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> ClassDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl

Ord ClassDecl Source 
Show ClassDecl Source 
Generic ClassDecl Source 

Associated Types

type Rep ClassDecl :: * -> *

AppFixity ClassDecl Source 
Pretty ClassDecl Source 

Methods

pretty :: ClassDecl -> Doc

prettyPrec :: Int -> ClassDecl -> Doc

type Rep ClassDecl Source 

data InstDecl Source

Declarations inside an instance declaration.

Constructors

InsDecl Decl

ordinary declaration

InsType SrcLoc Type Type

an associated type definition

InsData SrcLoc DataOrNew Type [QualConDecl] [Deriving]

an associated data type implementation

InsGData SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]

an associated data type implemented using GADT style

Instances

Eq InstDecl Source 
Data InstDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl -> c InstDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstDecl

toConstr :: InstDecl -> Constr

dataTypeOf :: InstDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstDecl)

gmapT :: (forall b. Data b => b -> b) -> InstDecl -> InstDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> InstDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl -> m InstDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl -> m InstDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl -> m InstDecl

Ord InstDecl Source 
Show InstDecl Source 
Generic InstDecl Source 

Associated Types

type Rep InstDecl :: * -> *

AppFixity InstDecl Source 
Pretty InstDecl Source 

Methods

pretty :: InstDecl -> Doc

prettyPrec :: Int -> InstDecl -> Doc

type Rep InstDecl Source 

type Deriving = (QName, [Type]) Source

A single derived instance, which may have arguments since it may be a MPTC.

Data type declarations

data DataOrNew Source

A flag stating whether a declaration is a data or newtype declaration.

Constructors

DataType 
NewType 

Instances

Eq DataOrNew Source 
Data DataOrNew Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataOrNew -> c DataOrNew

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataOrNew

toConstr :: DataOrNew -> Constr

dataTypeOf :: DataOrNew -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DataOrNew)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataOrNew)

gmapT :: (forall b. Data b => b -> b) -> DataOrNew -> DataOrNew

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataOrNew -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataOrNew -> r

gmapQ :: (forall d. Data d => d -> u) -> DataOrNew -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataOrNew -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataOrNew -> m DataOrNew

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataOrNew -> m DataOrNew

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataOrNew -> m DataOrNew

Ord DataOrNew Source 
Show DataOrNew Source 
Generic DataOrNew Source 

Associated Types

type Rep DataOrNew :: * -> *

Pretty DataOrNew Source 

Methods

pretty :: DataOrNew -> Doc

prettyPrec :: Int -> DataOrNew -> Doc

type Rep DataOrNew Source 

data ConDecl Source

Declaration of an ordinary data constructor.

Constructors

ConDecl Name [Type]

ordinary data constructor

InfixConDecl Type Name Type

infix data constructor

RecDecl Name [([Name], Type)]

record constructor

Instances

Eq ConDecl Source 

Methods

(==) :: ConDecl -> ConDecl -> Bool

(/=) :: ConDecl -> ConDecl -> Bool

Data ConDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl -> c ConDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConDecl

toConstr :: ConDecl -> Constr

dataTypeOf :: ConDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConDecl)

gmapT :: (forall b. Data b => b -> b) -> ConDecl -> ConDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> ConDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl -> m ConDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl -> m ConDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl -> m ConDecl

Ord ConDecl Source 
Show ConDecl Source 
Generic ConDecl Source 

Associated Types

type Rep ConDecl :: * -> *

Methods

from :: ConDecl -> Rep ConDecl x

to :: Rep ConDecl x -> ConDecl

Pretty ConDecl Source 

Methods

pretty :: ConDecl -> Doc

prettyPrec :: Int -> ConDecl -> Doc

type Rep ConDecl Source 

data QualConDecl Source

A single constructor declaration within a data type declaration, which may have an existential quantification binding.

Instances

Eq QualConDecl Source 
Data QualConDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QualConDecl -> c QualConDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QualConDecl

toConstr :: QualConDecl -> Constr

dataTypeOf :: QualConDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QualConDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QualConDecl)

gmapT :: (forall b. Data b => b -> b) -> QualConDecl -> QualConDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QualConDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QualConDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> QualConDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QualConDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QualConDecl -> m QualConDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QualConDecl -> m QualConDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QualConDecl -> m QualConDecl

Ord QualConDecl Source 
Show QualConDecl Source 
Generic QualConDecl Source 

Associated Types

type Rep QualConDecl :: * -> *

Pretty QualConDecl Source 

Methods

pretty :: QualConDecl -> Doc

prettyPrec :: Int -> QualConDecl -> Doc

type Rep QualConDecl Source 

data GadtDecl Source

A single constructor declaration in a GADT data type declaration.

Constructors

GadtDecl SrcLoc Name [([Name], Type)] Type 

Instances

Eq GadtDecl Source 
Data GadtDecl Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GadtDecl -> c GadtDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GadtDecl

toConstr :: GadtDecl -> Constr

dataTypeOf :: GadtDecl -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GadtDecl)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GadtDecl)

gmapT :: (forall b. Data b => b -> b) -> GadtDecl -> GadtDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GadtDecl -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GadtDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> GadtDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> GadtDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GadtDecl -> m GadtDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GadtDecl -> m GadtDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GadtDecl -> m GadtDecl

Ord GadtDecl Source 
Show GadtDecl Source 
Generic GadtDecl Source 

Associated Types

type Rep GadtDecl :: * -> *

Pretty GadtDecl Source 

Methods

pretty :: GadtDecl -> Doc

prettyPrec :: Int -> GadtDecl -> Doc

type Rep GadtDecl Source 

data BangType Source

The type of a constructor argument or field, optionally including a strictness annotation.

Constructors

BangedTy

strict component, marked with "!"

UnpackedTy

unboxed component, marked with an UNPACK pragma

Instances

Eq BangType Source 
Data BangType Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BangType -> c BangType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BangType

toConstr :: BangType -> Constr

dataTypeOf :: BangType -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BangType)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BangType)

gmapT :: (forall b. Data b => b -> b) -> BangType -> BangType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BangType -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BangType -> r

gmapQ :: (forall d. Data d => d -> u) -> BangType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> BangType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BangType -> m BangType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BangType -> m BangType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BangType -> m BangType

Ord BangType Source 
Show BangType Source 
Generic BangType Source 

Associated Types

type Rep BangType :: * -> *

Pretty BangType Source 

Methods

pretty :: BangType -> Doc

prettyPrec :: Int -> BangType -> Doc

type Rep BangType Source 

Function bindings

data Match Source

Clauses of a function binding.

Constructors

Match SrcLoc Name [Pat] (Maybe Type) Rhs (Maybe Binds) 

Instances

Eq Match Source 

Methods

(==) :: Match -> Match -> Bool

(/=) :: Match -> Match -> Bool

Data Match Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match -> c Match

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Match

toConstr :: Match -> Constr

dataTypeOf :: Match -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Match)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Match)

gmapT :: (forall b. Data b => b -> b) -> Match -> Match

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r

gmapQ :: (forall d. Data d => d -> u) -> Match -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match -> m Match

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match

Ord Match Source 

Methods

compare :: Match -> Match -> Ordering

(<) :: Match -> Match -> Bool

(<=) :: Match -> Match -> Bool

(>) :: Match -> Match -> Bool

(>=) :: Match -> Match -> Bool

max :: Match -> Match -> Match

min :: Match -> Match -> Match

Show Match Source 

Methods

showsPrec :: Int -> Match -> ShowS

show :: Match -> String

showList :: [Match] -> ShowS

Generic Match Source 

Associated Types

type Rep Match :: * -> *

Methods

from :: Match -> Rep Match x

to :: Rep Match x -> Match

AppFixity Match Source 

Methods

applyFixities :: Monad m => [Fixity] -> Match -> m Match Source

Pretty Match Source 

Methods

pretty :: Match -> Doc

prettyPrec :: Int -> Match -> Doc

type Rep Match Source 

data Rhs Source

The right hand side of a function binding, pattern binding, or a case alternative.

Constructors

UnGuardedRhs Exp

unguarded right hand side (exp)

GuardedRhss [GuardedRhs]

guarded right hand side (gdrhs)

Instances

Eq Rhs Source 

Methods

(==) :: Rhs -> Rhs -> Bool

(/=) :: Rhs -> Rhs -> Bool

Data Rhs Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rhs -> c Rhs

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rhs

toConstr :: Rhs -> Constr

dataTypeOf :: Rhs -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Rhs)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rhs)

gmapT :: (forall b. Data b => b -> b) -> Rhs -> Rhs

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rhs -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rhs -> r

gmapQ :: (forall d. Data d => d -> u) -> Rhs -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rhs -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rhs -> m Rhs

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rhs -> m Rhs

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rhs -> m Rhs

Ord Rhs Source 

Methods

compare :: Rhs -> Rhs -> Ordering

(<) :: Rhs -> Rhs -> Bool

(<=) :: Rhs -> Rhs -> Bool

(>) :: Rhs -> Rhs -> Bool

(>=) :: Rhs -> Rhs -> Bool

max :: Rhs -> Rhs -> Rhs

min :: Rhs -> Rhs -> Rhs

Show Rhs Source 

Methods

showsPrec :: Int -> Rhs -> ShowS

show :: Rhs -> String

showList :: [Rhs] -> ShowS

Generic Rhs Source 

Associated Types

type Rep Rhs :: * -> *

Methods

from :: Rhs -> Rep Rhs x

to :: Rep Rhs x -> Rhs

AppFixity Rhs Source 

Methods

applyFixities :: Monad m => [Fixity] -> Rhs -> m Rhs Source

Pretty Rhs Source 

Methods

pretty :: Rhs -> Doc

prettyPrec :: Int -> Rhs -> Doc

type Rep Rhs Source 

data GuardedRhs Source

A guarded right hand side | stmts = exp, or | stmts -> exp for case alternatives. The guard is a series of statements when using pattern guards, otherwise it will be a single qualifier expression.

Constructors

GuardedRhs SrcLoc [Stmt] Exp 

Instances

Eq GuardedRhs Source 
Data GuardedRhs Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GuardedRhs -> c GuardedRhs

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GuardedRhs

toConstr :: GuardedRhs -> Constr

dataTypeOf :: GuardedRhs -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GuardedRhs)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GuardedRhs)

gmapT :: (forall b. Data b => b -> b) -> GuardedRhs -> GuardedRhs

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GuardedRhs -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GuardedRhs -> r

gmapQ :: (forall d. Data d => d -> u) -> GuardedRhs -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> GuardedRhs -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GuardedRhs -> m GuardedRhs

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GuardedRhs -> m GuardedRhs

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GuardedRhs -> m GuardedRhs

Ord GuardedRhs Source 
Show GuardedRhs Source 
Generic GuardedRhs Source 

Associated Types

type Rep GuardedRhs :: * -> *

AppFixity GuardedRhs Source 
Pretty GuardedRhs Source 

Methods

pretty :: GuardedRhs -> Doc

prettyPrec :: Int -> GuardedRhs -> Doc

type Rep GuardedRhs Source 

Class Assertions and Contexts

type Context = [Asst] Source

A context is a set of assertions

data FunDep Source

A functional dependency, given on the form l1 l2 ... ln -> r2 r3 .. rn

Constructors

FunDep [Name] [Name] 

Instances

Eq FunDep Source 

Methods

(==) :: FunDep -> FunDep -> Bool

(/=) :: FunDep -> FunDep -> Bool

Data FunDep Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep -> c FunDep

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunDep

toConstr :: FunDep -> Constr

dataTypeOf :: FunDep -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FunDep)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunDep)

gmapT :: (forall b. Data b => b -> b) -> FunDep -> FunDep

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r

gmapQ :: (forall d. Data d => d -> u) -> FunDep -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep

Ord FunDep Source 
Show FunDep Source 
Generic FunDep Source 

Associated Types

type Rep FunDep :: * -> *

Methods

from :: FunDep -> Rep FunDep x

to :: Rep FunDep x -> FunDep

Pretty FunDep Source 

Methods

pretty :: FunDep -> Doc

prettyPrec :: Int -> FunDep -> Doc

type Rep FunDep Source 

data Asst Source

Class assertions. In Haskell 98, the argument would be a tyvar, but this definition allows multiple parameters, and allows them to be types. Also extended with support for implicit parameters and equality constraints.

Constructors

ClassA QName [Type]

ordinary class assertion

AppA Name [Type]

constraint kind assertion, Dict :: cxt a => Dict cxt

InfixA Type QName Type

class assertion where the class name is given infix

IParam IPName Type

implicit parameter assertion

EqualP Type Type

type equality constraint

ParenA Asst

parenthesised class assertion

WildCardA (Maybe Name)

A wildcard

Instances

Eq Asst Source 

Methods

(==) :: Asst -> Asst -> Bool

(/=) :: Asst -> Asst -> Bool

Data Asst Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Asst -> c Asst

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Asst

toConstr :: Asst -> Constr

dataTypeOf :: Asst -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Asst)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Asst)

gmapT :: (forall b. Data b => b -> b) -> Asst -> Asst

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Asst -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Asst -> r

gmapQ :: (forall d. Data d => d -> u) -> Asst -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Asst -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Asst -> m Asst

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Asst -> m Asst

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Asst -> m Asst

Ord Asst Source 

Methods

compare :: Asst -> Asst -> Ordering

(<) :: Asst -> Asst -> Bool

(<=) :: Asst -> Asst -> Bool

(>) :: Asst -> Asst -> Bool

(>=) :: Asst -> Asst -> Bool

max :: Asst -> Asst -> Asst

min :: Asst -> Asst -> Asst

Show Asst Source 

Methods

showsPrec :: Int -> Asst -> ShowS

show :: Asst -> String

showList :: [Asst] -> ShowS

Generic Asst Source 

Associated Types

type Rep Asst :: * -> *

Methods

from :: Asst -> Rep Asst x

to :: Rep Asst x -> Asst

Pretty Asst Source 

Methods

pretty :: Asst -> Doc

prettyPrec :: Int -> Asst -> Doc

type Rep Asst Source 

Types

data Type Source

A type qualified with a context. An unqualified type has an empty context.

Constructors

TyForall (Maybe [TyVarBind]) Context Type

qualified type

TyFun Type Type

function type

TyTuple Boxed [Type]

tuple type, possibly boxed

TyList Type

list syntax, e.g. [a], as opposed to [] a

TyParArray Type

parallel array syntax, e.g. [:a:]

TyApp Type Type

application of a type constructor

TyVar Name

type variable

TyCon QName

named type or type constructor

TyParen Type

type surrounded by parentheses

TyInfix Type QName Type

infix type constructor

TyKind Type Kind

type with explicit kind signature

TyPromoted Promoted

promoted data type (-XDataKinds)

TyEquals Type Type

type equality predicate enabled by ConstraintKinds

TySplice Splice

template haskell splice type

TyBang BangType Type

Strict type marked with "!" or type marked with UNPACK pragma.

TyWildCard (Maybe Name)

Type wildcard

Instances

Eq Type Source 

Methods

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

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

Data Type Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type

toConstr :: Type -> Constr

dataTypeOf :: Type -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Type)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)

gmapT :: (forall b. Data b => b -> b) -> Type -> Type

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r

gmapQ :: (forall d. Data d => d -> u) -> Type -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type

Ord Type Source 

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

Show Type Source 

Methods

showsPrec :: Int -> Type -> ShowS

show :: Type -> String

showList :: [Type] -> ShowS

Pretty Type Source 

Methods

pretty :: Type -> Doc

prettyPrec :: Int -> Type -> Doc

data Boxed Source

Flag denoting whether a tuple is boxed or unboxed.

Constructors

Boxed 
Unboxed 

Instances

Eq Boxed Source 

Methods

(==) :: Boxed -> Boxed -> Bool

(/=) :: Boxed -> Boxed -> Bool

Data Boxed Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxed -> c Boxed

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxed

toConstr :: Boxed -> Constr

dataTypeOf :: Boxed -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Boxed)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxed)

gmapT :: (forall b. Data b => b -> b) -> Boxed -> Boxed

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxed -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxed -> r

gmapQ :: (forall d. Data d => d -> u) -> Boxed -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxed -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxed -> m Boxed

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxed -> m Boxed

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxed -> m Boxed

Ord Boxed Source 

Methods

compare :: Boxed -> Boxed -> Ordering

(<) :: Boxed -> Boxed -> Bool

(<=) :: Boxed -> Boxed -> Bool

(>) :: Boxed -> Boxed -> Bool

(>=) :: Boxed -> Boxed -> Bool

max :: Boxed -> Boxed -> Boxed

min :: Boxed -> Boxed -> Boxed

Show Boxed Source 

Methods

showsPrec :: Int -> Boxed -> ShowS

show :: Boxed -> String

showList :: [Boxed] -> ShowS

Generic Boxed Source 

Associated Types

type Rep Boxed :: * -> *

Methods

from :: Boxed -> Rep Boxed x

to :: Rep Boxed x -> Boxed

type Rep Boxed Source 

data Kind Source

An explicit kind annotation.

Constructors

KindStar

*, the kind of types

KindFn Kind Kind

->, the kind of a type constructor

KindParen Kind

a kind surrounded by parentheses

KindVar QName

a kind variable (as of yet unsupported by compilers)

KindApp Kind Kind
k1 k2
KindTuple [Kind]

(k1,k2,k3), kind of a promoted tuple

KindList Kind

[k1], kind of a promoted list

Instances

Eq Kind Source 

Methods

(==) :: Kind -> Kind -> Bool

(/=) :: Kind -> Kind -> Bool

Data Kind Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Kind -> c Kind

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Kind

toConstr :: Kind -> Constr

dataTypeOf :: Kind -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Kind)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Kind)

gmapT :: (forall b. Data b => b -> b) -> Kind -> Kind

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Kind -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Kind -> r

gmapQ :: (forall d. Data d => d -> u) -> Kind -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Kind -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Kind -> m Kind

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Kind -> m Kind

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Kind -> m Kind

Ord Kind Source 

Methods

compare :: Kind -> Kind -> Ordering

(<) :: Kind -> Kind -> Bool

(<=) :: Kind -> Kind -> Bool

(>) :: Kind -> Kind -> Bool

(>=) :: Kind -> Kind -> Bool

max :: Kind -> Kind -> Kind

min :: Kind -> Kind -> Kind

Show Kind Source 

Methods

showsPrec :: Int -> Kind -> ShowS

show :: Kind -> String

showList :: [Kind] -> ShowS

Generic Kind Source 

Associated Types

type Rep Kind :: * -> *

Methods

from :: Kind -> Rep Kind x

to :: Rep Kind x -> Kind

Pretty Kind Source 

Methods

pretty :: Kind -> Doc

prettyPrec :: Int -> Kind -> Doc

type Rep Kind Source 

data TyVarBind Source

A type variable declaration, optionally with an explicit kind annotation.

Constructors

KindedVar Name Kind

variable binding with kind annotation

UnkindedVar Name

ordinary variable binding

Instances

Eq TyVarBind Source 
Data TyVarBind Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyVarBind -> c TyVarBind

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyVarBind

toConstr :: TyVarBind -> Constr

dataTypeOf :: TyVarBind -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TyVarBind)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyVarBind)

gmapT :: (forall b. Data b => b -> b) -> TyVarBind -> TyVarBind

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBind -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBind -> r

gmapQ :: (forall d. Data d => d -> u) -> TyVarBind -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyVarBind -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyVarBind -> m TyVarBind

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBind -> m TyVarBind

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBind -> m TyVarBind

Ord TyVarBind Source 
Show TyVarBind Source 
Generic TyVarBind Source 

Associated Types

type Rep TyVarBind :: * -> *

Pretty TyVarBind Source 

Methods

pretty :: TyVarBind -> Doc

prettyPrec :: Int -> TyVarBind -> Doc

type Rep TyVarBind Source 

data Promoted Source

Instances

Eq Promoted Source 
Data Promoted Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Promoted -> c Promoted

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Promoted

toConstr :: Promoted -> Constr

dataTypeOf :: Promoted -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Promoted)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Promoted)

gmapT :: (forall b. Data b => b -> b) -> Promoted -> Promoted

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Promoted -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Promoted -> r

gmapQ :: (forall d. Data d => d -> u) -> Promoted -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Promoted -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted

Ord Promoted Source 
Show Promoted Source 
Generic Promoted Source 

Associated Types

type Rep Promoted :: * -> *

Pretty Promoted Source 

Methods

pretty :: Promoted -> Doc

prettyPrec :: Int -> Promoted -> Doc

type Rep Promoted Source 

data TypeEqn Source

A type equation of the form rhs = lhs used in closed type families.

Constructors

TypeEqn Type Type 

Instances

Eq TypeEqn Source 

Methods

(==) :: TypeEqn -> TypeEqn -> Bool

(/=) :: TypeEqn -> TypeEqn -> Bool

Data TypeEqn Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeEqn -> c TypeEqn

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeEqn

toConstr :: TypeEqn -> Constr

dataTypeOf :: TypeEqn -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TypeEqn)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeEqn)

gmapT :: (forall b. Data b => b -> b) -> TypeEqn -> TypeEqn

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeEqn -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeEqn -> r

gmapQ :: (forall d. Data d => d -> u) -> TypeEqn -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeEqn -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeEqn -> m TypeEqn

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeEqn -> m TypeEqn

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeEqn -> m TypeEqn

Ord TypeEqn Source 
Show TypeEqn Source 
Generic TypeEqn Source 

Associated Types

type Rep TypeEqn :: * -> *

Methods

from :: TypeEqn -> Rep TypeEqn x

to :: Rep TypeEqn x -> TypeEqn

Pretty TypeEqn Source 

Methods

pretty :: TypeEqn -> Doc

prettyPrec :: Int -> TypeEqn -> Doc

type Rep TypeEqn Source 

Expressions

data Exp Source

Haskell expressions.

Constructors

Var QName

variable

IPVar IPName

implicit parameter variable

Con QName

data constructor

Lit Literal

literal constant

InfixApp Exp QOp Exp

infix application

App Exp Exp

ordinary application

NegApp Exp

negation expression -exp (unary minus)

Lambda SrcLoc [Pat] Exp

lambda expression

Let Binds Exp

local declarations with let ... in ...

If Exp Exp Exp

if exp then exp else exp

MultiIf [GuardedRhs]

if | exp -> exp ...

Case Exp [Alt]

case exp of alts

Do [Stmt]

do-expression: the last statement in the list should be an expression.

MDo [Stmt]

mdo-expression

Tuple Boxed [Exp]

tuple expression

TupleSection Boxed [Maybe Exp]

tuple section expression, e.g. (,,3)

List [Exp]

list expression

ParArray [Exp]

parallel array expression

Paren Exp

parenthesised expression

LeftSection Exp QOp

left section (exp qop)

RightSection QOp Exp

right section (qop exp)

RecConstr QName [FieldUpdate]

record construction expression

RecUpdate Exp [FieldUpdate]

record update expression

EnumFrom Exp

unbounded arithmetic sequence, incrementing by 1: [from ..]

EnumFromTo Exp Exp

bounded arithmetic sequence, incrementing by 1 [from .. to]

EnumFromThen Exp Exp

unbounded arithmetic sequence, with first two elements given [from, then ..]

EnumFromThenTo Exp Exp Exp

bounded arithmetic sequence, with first two elements given [from, then .. to]

ParArrayFromTo Exp Exp

bounded arithmetic sequence, incrementing by 1 [from .. to]

ParArrayFromThenTo Exp Exp Exp

bounded arithmetic sequence, with first two elements given [from, then .. to]

ListComp Exp [QualStmt]

ordinary list comprehension

ParComp Exp [[QualStmt]]

parallel list comprehension

ParArrayComp Exp [[QualStmt]]

parallel array comprehension

ExpTypeSig SrcLoc Exp Type

expression with explicit type signature

VarQuote QName

'x for template haskell reifying of expressions

TypQuote QName

''T for template haskell reifying of types

BracketExp Bracket

template haskell bracket expression

SpliceExp Splice

template haskell splice expression

QuasiQuote String String

quasi-quotaion: [$name| string |]

XTag SrcLoc XName [XAttr] (Maybe Exp) [Exp]

xml element, with attributes and children

XETag SrcLoc XName [XAttr] (Maybe Exp)

empty xml element, with attributes

XPcdata String

PCDATA child element

XExpTag Exp

escaped haskell expression inside xml

XChildTag SrcLoc [Exp]

children of an xml element

CorePragma String Exp

CORE pragma

SCCPragma String Exp

SCC pragma

GenPragma String (Int, Int) (Int, Int) Exp

GENERATED pragma

Proc SrcLoc Pat Exp

arrows proc: proc pat -> exp

LeftArrApp Exp Exp

arrow application (from left): exp -< exp

RightArrApp Exp Exp

arrow application (from right): exp >- exp

LeftArrHighApp Exp Exp

higher-order arrow application (from left): exp -<< exp

RightArrHighApp Exp Exp

higher-order arrow application (from right): exp >>- exp

LCase [Alt]

case alts

ExprHole

Expression hole

Instances

Eq Exp Source 

Methods

(==) :: Exp -> Exp -> Bool

(/=) :: Exp -> Exp -> Bool

Data Exp Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp

toConstr :: Exp -> Constr

dataTypeOf :: Exp -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Exp)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp)

gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r

gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp

Ord Exp Source 

Methods

compare :: Exp -> Exp -> Ordering

(<) :: Exp -> Exp -> Bool

(<=) :: Exp -> Exp -> Bool

(>) :: Exp -> Exp -> Bool

(>=) :: Exp -> Exp -> Bool

max :: Exp -> Exp -> Exp

min :: Exp -> Exp -> Exp

Show Exp Source 

Methods

showsPrec :: Int -> Exp -> ShowS

show :: Exp -> String

showList :: [Exp] -> ShowS

Generic Exp Source 

Associated Types

type Rep Exp :: * -> *

Methods

from :: Exp -> Rep Exp x

to :: Rep Exp x -> Exp

AppFixity Exp Source 

Methods

applyFixities :: Monad m => [Fixity] -> Exp -> m Exp Source

Pretty Exp Source 

Methods

pretty :: Exp -> Doc

prettyPrec :: Int -> Exp -> Doc

type Rep Exp Source 

data Stmt Source

A statement, representing both a stmt in a do-expression, an ordinary qual in a list comprehension, as well as a stmt in a pattern guard.

Constructors

Generator SrcLoc Pat Exp

a generator: pat <- exp

Qualifier Exp

an exp by itself: in a do-expression, an action whose result is discarded; in a list comprehension and pattern guard, a guard expression

LetStmt Binds

local bindings

RecStmt [Stmt]

a recursive binding group for arrows

Instances

Eq Stmt Source 

Methods

(==) :: Stmt -> Stmt -> Bool

(/=) :: Stmt -> Stmt -> Bool

Data Stmt Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt -> c Stmt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stmt

toConstr :: Stmt -> Constr

dataTypeOf :: Stmt -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Stmt)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stmt)

gmapT :: (forall b. Data b => b -> b) -> Stmt -> Stmt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r

gmapQ :: (forall d. Data d => d -> u) -> Stmt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

Ord Stmt Source 

Methods

compare :: Stmt -> Stmt -> Ordering

(<) :: Stmt -> Stmt -> Bool

(<=) :: Stmt -> Stmt -> Bool

(>) :: Stmt -> Stmt -> Bool

(>=) :: Stmt -> Stmt -> Bool

max :: Stmt -> Stmt -> Stmt

min :: Stmt -> Stmt -> Stmt

Show Stmt Source 

Methods

showsPrec :: Int -> Stmt -> ShowS

show :: Stmt -> String

showList :: [Stmt] -> ShowS

Generic Stmt Source 

Associated Types

type Rep Stmt :: * -> *

Methods

from :: Stmt -> Rep Stmt x

to :: Rep Stmt x -> Stmt

AppFixity Stmt Source 

Methods

applyFixities :: Monad m => [Fixity] -> Stmt -> m Stmt Source

Pretty Stmt Source 

Methods

pretty :: Stmt -> Doc

prettyPrec :: Int -> Stmt -> Doc

type Rep Stmt Source 

data QualStmt Source

A general transqual in a list comprehension, which could potentially be a transform of the kind enabled by TransformListComp.

Constructors

QualStmt Stmt

an ordinary statement

ThenTrans Exp

then exp

ThenBy Exp Exp

then exp by exp

GroupBy Exp

then group by exp

GroupUsing Exp

then group using exp

GroupByUsing Exp Exp

then group by exp using exp

Instances

Eq QualStmt Source 
Data QualStmt Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QualStmt -> c QualStmt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QualStmt

toConstr :: QualStmt -> Constr

dataTypeOf :: QualStmt -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QualStmt)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QualStmt)

gmapT :: (forall b. Data b => b -> b) -> QualStmt -> QualStmt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QualStmt -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QualStmt -> r

gmapQ :: (forall d. Data d => d -> u) -> QualStmt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QualStmt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QualStmt -> m QualStmt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QualStmt -> m QualStmt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QualStmt -> m QualStmt

Ord QualStmt Source 
Show QualStmt Source 
Generic QualStmt Source 

Associated Types

type Rep QualStmt :: * -> *

AppFixity QualStmt Source 
Pretty QualStmt Source 

Methods

pretty :: QualStmt -> Doc

prettyPrec :: Int -> QualStmt -> Doc

type Rep QualStmt Source 

data FieldUpdate Source

An fbind in a labeled construction or update expression.

Constructors

FieldUpdate QName Exp

ordinary label-expresion pair

FieldPun QName

record field pun

FieldWildcard

record field wildcard

Instances

Eq FieldUpdate Source 
Data FieldUpdate Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldUpdate -> c FieldUpdate

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldUpdate

toConstr :: FieldUpdate -> Constr

dataTypeOf :: FieldUpdate -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldUpdate)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldUpdate)

gmapT :: (forall b. Data b => b -> b) -> FieldUpdate -> FieldUpdate

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldUpdate -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldUpdate -> r

gmapQ :: (forall d. Data d => d -> u) -> FieldUpdate -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldUpdate -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldUpdate -> m FieldUpdate

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldUpdate -> m FieldUpdate

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldUpdate -> m FieldUpdate

Ord FieldUpdate Source 
Show FieldUpdate Source 
Generic FieldUpdate Source 

Associated Types

type Rep FieldUpdate :: * -> *

AppFixity FieldUpdate Source 
Pretty FieldUpdate Source 

Methods

pretty :: FieldUpdate -> Doc

prettyPrec :: Int -> FieldUpdate -> Doc

type Rep FieldUpdate Source 

data Alt Source

An alt alternative in a case expression.

Constructors

Alt SrcLoc Pat Rhs (Maybe Binds) 

Instances

Eq Alt Source 

Methods

(==) :: Alt -> Alt -> Bool

(/=) :: Alt -> Alt -> Bool

Data Alt Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt -> c Alt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alt

toConstr :: Alt -> Constr

dataTypeOf :: Alt -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Alt)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alt)

gmapT :: (forall b. Data b => b -> b) -> Alt -> Alt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt -> r

gmapQ :: (forall d. Data d => d -> u) -> Alt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt -> m Alt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt -> m Alt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt -> m Alt

Ord Alt Source 

Methods

compare :: Alt -> Alt -> Ordering

(<) :: Alt -> Alt -> Bool

(<=) :: Alt -> Alt -> Bool

(>) :: Alt -> Alt -> Bool

(>=) :: Alt -> Alt -> Bool

max :: Alt -> Alt -> Alt

min :: Alt -> Alt -> Alt

Show Alt Source 

Methods

showsPrec :: Int -> Alt -> ShowS

show :: Alt -> String

showList :: [Alt] -> ShowS

Generic Alt Source 

Associated Types

type Rep Alt :: * -> *

Methods

from :: Alt -> Rep Alt x

to :: Rep Alt x -> Alt

AppFixity Alt Source 

Methods

applyFixities :: Monad m => [Fixity] -> Alt -> m Alt Source

Pretty Alt Source 

Methods

pretty :: Alt -> Doc

prettyPrec :: Int -> Alt -> Doc

type Rep Alt Source 

data XAttr Source

An xml attribute, which is a name-expression pair.

Constructors

XAttr XName Exp 

Instances

Eq XAttr Source 

Methods

(==) :: XAttr -> XAttr -> Bool

(/=) :: XAttr -> XAttr -> Bool

Data XAttr Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XAttr -> c XAttr

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XAttr

toConstr :: XAttr -> Constr

dataTypeOf :: XAttr -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c XAttr)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XAttr)

gmapT :: (forall b. Data b => b -> b) -> XAttr -> XAttr

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XAttr -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XAttr -> r

gmapQ :: (forall d. Data d => d -> u) -> XAttr -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> XAttr -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XAttr -> m XAttr

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XAttr -> m XAttr

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XAttr -> m XAttr

Ord XAttr Source 

Methods

compare :: XAttr -> XAttr -> Ordering

(<) :: XAttr -> XAttr -> Bool

(<=) :: XAttr -> XAttr -> Bool

(>) :: XAttr -> XAttr -> Bool

(>=) :: XAttr -> XAttr -> Bool

max :: XAttr -> XAttr -> XAttr

min :: XAttr -> XAttr -> XAttr

Show XAttr Source 

Methods

showsPrec :: Int -> XAttr -> ShowS

show :: XAttr -> String

showList :: [XAttr] -> ShowS

Generic XAttr Source 

Associated Types

type Rep XAttr :: * -> *

Methods

from :: XAttr -> Rep XAttr x

to :: Rep XAttr x -> XAttr

AppFixity XAttr Source 

Methods

applyFixities :: Monad m => [Fixity] -> XAttr -> m XAttr Source

Pretty XAttr Source 

Methods

pretty :: XAttr -> Doc

prettyPrec :: Int -> XAttr -> Doc

type Rep XAttr Source 

Patterns

data Pat Source

A pattern, to be matched against a value.

Constructors

PVar Name

variable

PLit Sign Literal

literal constant

PNPlusK Name Integer

n+k pattern

PInfixApp Pat QName Pat

pattern with an infix data constructor

PApp QName [Pat]

data constructor and argument patterns

PTuple Boxed [Pat]

tuple pattern

PList [Pat]

list pattern

PParen Pat

parenthesized pattern

PRec QName [PatField]

labelled pattern, record style

PAsPat Name Pat

@-pattern

PWildCard

wildcard pattern: _

PIrrPat Pat

irrefutable pattern: ~pat

PatTypeSig SrcLoc Pat Type

pattern with type signature

PViewPat Exp Pat

view patterns of the form (exp -> pat)

PRPat [RPat]

regular list pattern

PXTag SrcLoc XName [PXAttr] (Maybe Pat) [Pat]

XML element pattern

PXETag SrcLoc XName [PXAttr] (Maybe Pat)

XML singleton element pattern

PXPcdata String

XML PCDATA pattern

PXPatTag Pat

XML embedded pattern

PXRPats [RPat]

XML regular list pattern

PQuasiQuote String String

quasi quote patter: [$name| string |]

PBangPat Pat

strict (bang) pattern: f !x = ...

Instances

Eq Pat Source 

Methods

(==) :: Pat -> Pat -> Bool

(/=) :: Pat -> Pat -> Bool

Data Pat Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat -> c Pat

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pat

toConstr :: Pat -> Constr

dataTypeOf :: Pat -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Pat)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pat)

gmapT :: (forall b. Data b => b -> b) -> Pat -> Pat

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r

gmapQ :: (forall d. Data d => d -> u) -> Pat -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat -> m Pat

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat

Ord Pat Source 

Methods

compare :: Pat -> Pat -> Ordering

(<) :: Pat -> Pat -> Bool

(<=) :: Pat -> Pat -> Bool

(>) :: Pat -> Pat -> Bool

(>=) :: Pat -> Pat -> Bool

max :: Pat -> Pat -> Pat

min :: Pat -> Pat -> Pat

Show Pat Source 

Methods

showsPrec :: Int -> Pat -> ShowS

show :: Pat -> String

showList :: [Pat] -> ShowS

Generic Pat Source 

Associated Types

type Rep Pat :: * -> *

Methods

from :: Pat -> Rep Pat x

to :: Rep Pat x -> Pat

AppFixity Pat Source 

Methods

applyFixities :: Monad m => [Fixity] -> Pat -> m Pat Source

Pretty Pat Source 

Methods

pretty :: Pat -> Doc

prettyPrec :: Int -> Pat -> Doc

type Rep Pat Source 

data PatField Source

An fpat in a labeled record pattern.

Constructors

PFieldPat QName Pat

ordinary label-pattern pair

PFieldPun QName

record field pun

PFieldWildcard

record field wildcard

Instances

Eq PatField Source 
Data PatField Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatField -> c PatField

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatField

toConstr :: PatField -> Constr

dataTypeOf :: PatField -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatField)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatField)

gmapT :: (forall b. Data b => b -> b) -> PatField -> PatField

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatField -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatField -> r

gmapQ :: (forall d. Data d => d -> u) -> PatField -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatField -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatField -> m PatField

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatField -> m PatField

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatField -> m PatField

Ord PatField Source 
Show PatField Source 
Generic PatField Source 

Associated Types

type Rep PatField :: * -> *

AppFixity PatField Source 
Pretty PatField Source 

Methods

pretty :: PatField -> Doc

prettyPrec :: Int -> PatField -> Doc

type Rep PatField Source 

data PXAttr Source

An XML attribute in a pattern.

Constructors

PXAttr XName Pat 

Instances

Eq PXAttr Source 

Methods

(==) :: PXAttr -> PXAttr -> Bool

(/=) :: PXAttr -> PXAttr -> Bool

Data PXAttr Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PXAttr -> c PXAttr

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PXAttr

toConstr :: PXAttr -> Constr

dataTypeOf :: PXAttr -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PXAttr)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PXAttr)

gmapT :: (forall b. Data b => b -> b) -> PXAttr -> PXAttr

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PXAttr -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PXAttr -> r

gmapQ :: (forall d. Data d => d -> u) -> PXAttr -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PXAttr -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PXAttr -> m PXAttr

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PXAttr -> m PXAttr

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PXAttr -> m PXAttr

Ord PXAttr Source 
Show PXAttr Source 
Generic PXAttr Source 

Associated Types

type Rep PXAttr :: * -> *

Methods

from :: PXAttr -> Rep PXAttr x

to :: Rep PXAttr x -> PXAttr

AppFixity PXAttr Source 

Methods

applyFixities :: Monad m => [Fixity] -> PXAttr -> m PXAttr Source

Pretty PXAttr Source 

Methods

pretty :: PXAttr -> Doc

prettyPrec :: Int -> PXAttr -> Doc

type Rep PXAttr Source 

data RPat Source

An entity in a regular pattern.

Constructors

RPOp RPat RPatOp

operator pattern, e.g. pat*

RPEither RPat RPat

choice pattern, e.g. (1 | 2)

RPSeq [RPat]

sequence pattern, e.g. (| 1, 2, 3 |)

RPGuard Pat [Stmt]

guarded pattern, e.g. (| p | p < 3 |)

RPCAs Name RPat

non-linear variable binding, e.g. (foo@:(1 | 2))*

RPAs Name RPat

linear variable binding, e.g. foo@(1 | 2)

RPParen RPat

parenthesised pattern, e.g. (2*)

RPPat Pat

an ordinary pattern

Instances

Eq RPat Source 

Methods

(==) :: RPat -> RPat -> Bool

(/=) :: RPat -> RPat -> Bool

Data RPat Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RPat -> c RPat

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RPat

toConstr :: RPat -> Constr

dataTypeOf :: RPat -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RPat)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RPat)

gmapT :: (forall b. Data b => b -> b) -> RPat -> RPat

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RPat -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RPat -> r

gmapQ :: (forall d. Data d => d -> u) -> RPat -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> RPat -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RPat -> m RPat

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RPat -> m RPat

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RPat -> m RPat

Ord RPat Source 

Methods

compare :: RPat -> RPat -> Ordering

(<) :: RPat -> RPat -> Bool

(<=) :: RPat -> RPat -> Bool

(>) :: RPat -> RPat -> Bool

(>=) :: RPat -> RPat -> Bool

max :: RPat -> RPat -> RPat

min :: RPat -> RPat -> RPat

Show RPat Source 

Methods

showsPrec :: Int -> RPat -> ShowS

show :: RPat -> String

showList :: [RPat] -> ShowS

Generic RPat Source 

Associated Types

type Rep RPat :: * -> *

Methods

from :: RPat -> Rep RPat x

to :: Rep RPat x -> RPat

AppFixity RPat Source 

Methods

applyFixities :: Monad m => [Fixity] -> RPat -> m RPat Source

Pretty RPat Source 

Methods

pretty :: RPat -> Doc

prettyPrec :: Int -> RPat -> Doc

type Rep RPat Source 

data RPatOp Source

A regular pattern operator.

Constructors

RPStar

* = 0 or more

RPStarG

*! = 0 or more, greedy

RPPlus

+ = 1 or more

RPPlusG

+! = 1 or more, greedy

RPOpt

? = 0 or 1

RPOptG

?! = 0 or 1, greedy

Instances

Eq RPatOp Source 

Methods

(==) :: RPatOp -> RPatOp -> Bool

(/=) :: RPatOp -> RPatOp -> Bool

Data RPatOp Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RPatOp -> c RPatOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RPatOp

toConstr :: RPatOp -> Constr

dataTypeOf :: RPatOp -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RPatOp)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RPatOp)

gmapT :: (forall b. Data b => b -> b) -> RPatOp -> RPatOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RPatOp -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RPatOp -> r

gmapQ :: (forall d. Data d => d -> u) -> RPatOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> RPatOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RPatOp -> m RPatOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RPatOp -> m RPatOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RPatOp -> m RPatOp

Ord RPatOp Source 
Show RPatOp Source 
Generic RPatOp Source 

Associated Types

type Rep RPatOp :: * -> *

Methods

from :: RPatOp -> Rep RPatOp x

to :: Rep RPatOp x -> RPatOp

Pretty RPatOp Source 

Methods

pretty :: RPatOp -> Doc

prettyPrec :: Int -> RPatOp -> Doc

type Rep RPatOp Source 

Literals

data Literal Source

literal Values of this type hold the abstract value of the literal, not the precise string representation used. For example, 10, 0o12 and 0xa have the same representation.

Constructors

Char Char

character literal

String String

string literal

Int Integer

integer literal

Frac Rational

floating point literal

PrimInt Integer

unboxed integer literal

PrimWord Integer

unboxed word literal

PrimFloat Rational

unboxed float literal

PrimDouble Rational

unboxed double literal

PrimChar Char

unboxed character literal

PrimString String

unboxed string literal

Instances

Eq Literal Source 

Methods

(==) :: Literal -> Literal -> Bool

(/=) :: Literal -> Literal -> Bool

Data Literal Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal

toConstr :: Literal -> Constr

dataTypeOf :: Literal -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Literal)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal)

gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r

gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal

Ord Literal Source 
Show Literal Source 
Generic Literal Source 

Associated Types

type Rep Literal :: * -> *

Methods

from :: Literal -> Rep Literal x

to :: Rep Literal x -> Literal

Pretty Literal Source 

Methods

pretty :: Literal -> Doc

prettyPrec :: Int -> Literal -> Doc

type Rep Literal Source 

data Sign Source

An indication whether a literal pattern has been negated or not.

Constructors

Signless 
Negative 

Instances

Eq Sign Source 

Methods

(==) :: Sign -> Sign -> Bool

(/=) :: Sign -> Sign -> Bool

Data Sign Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign

toConstr :: Sign -> Constr

dataTypeOf :: Sign -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sign)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign)

gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r

gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign

Ord Sign Source 

Methods

compare :: Sign -> Sign -> Ordering

(<) :: Sign -> Sign -> Bool

(<=) :: Sign -> Sign -> Bool

(>) :: Sign -> Sign -> Bool

(>=) :: Sign -> Sign -> Bool

max :: Sign -> Sign -> Sign

min :: Sign -> Sign -> Sign

Show Sign Source 

Methods

showsPrec :: Int -> Sign -> ShowS

show :: Sign -> String

showList :: [Sign] -> ShowS

Generic Sign Source 

Associated Types

type Rep Sign :: * -> *

Methods

from :: Sign -> Rep Sign x

to :: Rep Sign x -> Sign

type Rep Sign Source 

Variables, Constructors and Operators

newtype ModuleName Source

The name of a Haskell module.

Constructors

ModuleName String 

Instances

Eq ModuleName Source 
Data ModuleName Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName

toConstr :: ModuleName -> Constr

dataTypeOf :: ModuleName -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName)

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName

Ord ModuleName Source 
Show ModuleName Source 
Generic ModuleName Source 

Associated Types

type Rep ModuleName :: * -> *

Pretty ModuleName Source 

Methods

pretty :: ModuleName -> Doc

prettyPrec :: Int -> ModuleName -> Doc

type Rep ModuleName Source 

data QName Source

This type is used to represent qualified variables, and also qualified constructors.

Constructors

Qual ModuleName Name

name qualified with a module name

UnQual Name

unqualified local name

Special SpecialCon

built-in constructor with special syntax

Instances

Eq QName Source 

Methods

(==) :: QName -> QName -> Bool

(/=) :: QName -> QName -> Bool

Data QName Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QName -> c QName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QName

toConstr :: QName -> Constr

dataTypeOf :: QName -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QName)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QName)

gmapT :: (forall b. Data b => b -> b) -> QName -> QName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r

gmapQ :: (forall d. Data d => d -> u) -> QName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QName -> m QName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QName -> m QName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QName -> m QName

Ord QName Source 

Methods

compare :: QName -> QName -> Ordering

(<) :: QName -> QName -> Bool

(<=) :: QName -> QName -> Bool

(>) :: QName -> QName -> Bool

(>=) :: QName -> QName -> Bool

max :: QName -> QName -> QName

min :: QName -> QName -> QName

Show QName Source 

Methods

showsPrec :: Int -> QName -> ShowS

show :: QName -> String

showList :: [QName] -> ShowS

Generic QName Source 

Associated Types

type Rep QName :: * -> *

Methods

from :: QName -> Rep QName x

to :: Rep QName x -> QName

Pretty QName Source 

Methods

pretty :: QName -> Doc

prettyPrec :: Int -> QName -> Doc

type Rep QName Source 

data Name Source

This type is used to represent variables, and also constructors.

Constructors

Ident String

varid or conid.

Symbol String

varsym or consym

Instances

Eq Name Source 

Methods

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

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

Data Name Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name

toConstr :: Name -> Constr

dataTypeOf :: Name -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Name)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name)

gmapT :: (forall b. Data b => b -> b) -> Name -> Name

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name

Ord Name Source 

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

Show Name Source 

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

Generic Name Source 

Associated Types

type Rep Name :: * -> *

Methods

from :: Name -> Rep Name x

to :: Rep Name x -> Name

Pretty Name Source 

Methods

pretty :: Name -> Doc

prettyPrec :: Int -> Name -> Doc

type Rep Name Source 

data QOp Source

Possibly qualified infix operators (qop), appearing in expressions.

Constructors

QVarOp QName

variable operator (qvarop)

QConOp QName

constructor operator (qconop)

Instances

Eq QOp Source 

Methods

(==) :: QOp -> QOp -> Bool

(/=) :: QOp -> QOp -> Bool

Data QOp Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QOp -> c QOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QOp

toConstr :: QOp -> Constr

dataTypeOf :: QOp -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QOp)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QOp)

gmapT :: (forall b. Data b => b -> b) -> QOp -> QOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QOp -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QOp -> r

gmapQ :: (forall d. Data d => d -> u) -> QOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QOp -> m QOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QOp -> m QOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QOp -> m QOp

Ord QOp Source 

Methods

compare :: QOp -> QOp -> Ordering

(<) :: QOp -> QOp -> Bool

(<=) :: QOp -> QOp -> Bool

(>) :: QOp -> QOp -> Bool

(>=) :: QOp -> QOp -> Bool

max :: QOp -> QOp -> QOp

min :: QOp -> QOp -> QOp

Show QOp Source 

Methods

showsPrec :: Int -> QOp -> ShowS

show :: QOp -> String

showList :: [QOp] -> ShowS

Generic QOp Source 

Associated Types

type Rep QOp :: * -> *

Methods

from :: QOp -> Rep QOp x

to :: Rep QOp x -> QOp

Pretty QOp Source 

Methods

pretty :: QOp -> Doc

prettyPrec :: Int -> QOp -> Doc

type Rep QOp Source 

data Op Source

Operators appearing in infix declarations are never qualified.

Constructors

VarOp Name

variable operator (varop)

ConOp Name

constructor operator (conop)

Instances

Eq Op Source 

Methods

(==) :: Op -> Op -> Bool

(/=) :: Op -> Op -> Bool

Data Op Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op

toConstr :: Op -> Constr

dataTypeOf :: Op -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Op)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op)

gmapT :: (forall b. Data b => b -> b) -> Op -> Op

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r

gmapQ :: (forall d. Data d => d -> u) -> Op -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op

Ord Op Source 

Methods

compare :: Op -> Op -> Ordering

(<) :: Op -> Op -> Bool

(<=) :: Op -> Op -> Bool

(>) :: Op -> Op -> Bool

(>=) :: Op -> Op -> Bool

max :: Op -> Op -> Op

min :: Op -> Op -> Op

Show Op Source 

Methods

showsPrec :: Int -> Op -> ShowS

show :: Op -> String

showList :: [Op] -> ShowS

Generic Op Source 

Associated Types

type Rep Op :: * -> *

Methods

from :: Op -> Rep Op x

to :: Rep Op x -> Op

Pretty Op Source 

Methods

pretty :: Op -> Doc

prettyPrec :: Int -> Op -> Doc

type Rep Op Source 

data SpecialCon Source

Constructors with special syntax. These names are never qualified, and always refer to builtin type or data constructors.

Constructors

UnitCon

unit type and data constructor ()

ListCon

list type constructor []

FunCon

function type constructor ->

TupleCon Boxed Int

n-ary tuple type and data constructors (,) etc, possibly boxed (#,#)

Cons

list data constructor (:)

UnboxedSingleCon

unboxed singleton tuple constructor (# #)

Instances

Eq SpecialCon Source 
Data SpecialCon Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpecialCon -> c SpecialCon

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpecialCon

toConstr :: SpecialCon -> Constr

dataTypeOf :: SpecialCon -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SpecialCon)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpecialCon)

gmapT :: (forall b. Data b => b -> b) -> SpecialCon -> SpecialCon

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpecialCon -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpecialCon -> r

gmapQ :: (forall d. Data d => d -> u) -> SpecialCon -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpecialCon -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpecialCon -> m SpecialCon

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecialCon -> m SpecialCon

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecialCon -> m SpecialCon

Ord SpecialCon Source 
Show SpecialCon Source 
Generic SpecialCon Source 

Associated Types

type Rep SpecialCon :: * -> *

Pretty SpecialCon Source 

Methods

pretty :: SpecialCon -> Doc

prettyPrec :: Int -> SpecialCon -> Doc

type Rep SpecialCon Source 

data CName Source

A name (cname) of a component of a class or data type in an import or export specification.

Constructors

VarName Name

name of a method or field

ConName Name

name of a data constructor

Instances

Eq CName Source 

Methods

(==) :: CName -> CName -> Bool

(/=) :: CName -> CName -> Bool

Data CName Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CName -> c CName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CName

toConstr :: CName -> Constr

dataTypeOf :: CName -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CName)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CName)

gmapT :: (forall b. Data b => b -> b) -> CName -> CName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CName -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CName -> r

gmapQ :: (forall d. Data d => d -> u) -> CName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CName -> m CName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CName -> m CName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CName -> m CName

Ord CName Source 

Methods

compare :: CName -> CName -> Ordering

(<) :: CName -> CName -> Bool

(<=) :: CName -> CName -> Bool

(>) :: CName -> CName -> Bool

(>=) :: CName -> CName -> Bool

max :: CName -> CName -> CName

min :: CName -> CName -> CName

Show CName Source 

Methods

showsPrec :: Int -> CName -> ShowS

show :: CName -> String

showList :: [CName] -> ShowS

Generic CName Source 

Associated Types

type Rep CName :: * -> *

Methods

from :: CName -> Rep CName x

to :: Rep CName x -> CName

Pretty CName Source 

Methods

pretty :: CName -> Doc

prettyPrec :: Int -> CName -> Doc

type Rep CName Source 

data IPName Source

An implicit parameter name.

Constructors

IPDup String

?ident, non-linear implicit parameter

IPLin String

%ident, linear implicit parameter

Instances

Eq IPName Source 

Methods

(==) :: IPName -> IPName -> Bool

(/=) :: IPName -> IPName -> Bool

Data IPName Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPName -> c IPName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPName

toConstr :: IPName -> Constr

dataTypeOf :: IPName -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPName)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPName)

gmapT :: (forall b. Data b => b -> b) -> IPName -> IPName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPName -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPName -> r

gmapQ :: (forall d. Data d => d -> u) -> IPName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPName -> m IPName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPName -> m IPName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPName -> m IPName

Ord IPName Source 
Show IPName Source 
Generic IPName Source 

Associated Types

type Rep IPName :: * -> *

Methods

from :: IPName -> Rep IPName x

to :: Rep IPName x -> IPName

Pretty IPName Source 

Methods

pretty :: IPName -> Doc

prettyPrec :: Int -> IPName -> Doc

type Rep IPName Source 

data XName Source

The name of an xml element or attribute, possibly qualified with a namespace.

Instances

Eq XName Source 

Methods

(==) :: XName -> XName -> Bool

(/=) :: XName -> XName -> Bool

Data XName Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XName -> c XName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XName

toConstr :: XName -> Constr

dataTypeOf :: XName -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c XName)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XName)

gmapT :: (forall b. Data b => b -> b) -> XName -> XName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XName -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XName -> r

gmapQ :: (forall d. Data d => d -> u) -> XName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> XName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XName -> m XName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XName -> m XName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XName -> m XName

Ord XName Source 

Methods

compare :: XName -> XName -> Ordering

(<) :: XName -> XName -> Bool

(<=) :: XName -> XName -> Bool

(>) :: XName -> XName -> Bool

(>=) :: XName -> XName -> Bool

max :: XName -> XName -> XName

min :: XName -> XName -> XName

Show XName Source 

Methods

showsPrec :: Int -> XName -> ShowS

show :: XName -> String

showList :: [XName] -> ShowS

Generic XName Source 

Associated Types

type Rep XName :: * -> *

Methods

from :: XName -> Rep XName x

to :: Rep XName x -> XName

Pretty XName Source 

Methods

pretty :: XName -> Doc

prettyPrec :: Int -> XName -> Doc

type Rep XName Source 

data Role Source

Instances

Eq Role Source 

Methods

(==) :: Role -> Role -> Bool

(/=) :: Role -> Role -> Bool

Data Role Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role

toConstr :: Role -> Constr

dataTypeOf :: Role -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Role)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role)

gmapT :: (forall b. Data b => b -> b) -> Role -> Role

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r

gmapQ :: (forall d. Data d => d -> u) -> Role -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role

Ord Role Source 

Methods

compare :: Role -> Role -> Ordering

(<) :: Role -> Role -> Bool

(<=) :: Role -> Role -> Bool

(>) :: Role -> Role -> Bool

(>=) :: Role -> Role -> Bool

max :: Role -> Role -> Role

min :: Role -> Role -> Role

Show Role Source 

Methods

showsPrec :: Int -> Role -> ShowS

show :: Role -> String

showList :: [Role] -> ShowS

Generic Role Source 

Associated Types

type Rep Role :: * -> *

Methods

from :: Role -> Rep Role x

to :: Rep Role x -> Role

Pretty Role Source 

Methods

pretty :: Role -> Doc

prettyPrec :: Int -> Role -> Doc

type Rep Role Source 

Template Haskell

data Bracket Source

A template haskell bracket expression.

Constructors

ExpBracket Exp

expression bracket: [| ... |]

PatBracket Pat

pattern bracket: [p| ... |]

TypeBracket Type

type bracket: [t| ... |]

DeclBracket [Decl]

declaration bracket: [d| ... |]

Instances

Eq Bracket Source 

Methods

(==) :: Bracket -> Bracket -> Bool

(/=) :: Bracket -> Bracket -> Bool

Data Bracket Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bracket -> c Bracket

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bracket

toConstr :: Bracket -> Constr

dataTypeOf :: Bracket -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bracket)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bracket)

gmapT :: (forall b. Data b => b -> b) -> Bracket -> Bracket

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bracket -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bracket -> r

gmapQ :: (forall d. Data d => d -> u) -> Bracket -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bracket -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bracket -> m Bracket

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bracket -> m Bracket

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bracket -> m Bracket

Ord Bracket Source 
Show Bracket Source 
Generic Bracket Source 

Associated Types

type Rep Bracket :: * -> *

Methods

from :: Bracket -> Rep Bracket x

to :: Rep Bracket x -> Bracket

AppFixity Bracket Source 

Methods

applyFixities :: Monad m => [Fixity] -> Bracket -> m Bracket Source

Pretty Bracket Source 

Methods

pretty :: Bracket -> Doc

prettyPrec :: Int -> Bracket -> Doc

type Rep Bracket Source 

data Splice Source

A template haskell splice expression

Constructors

IdSplice String

variable splice: $var

ParenSplice Exp

parenthesised expression splice: $(exp)

Instances

Eq Splice Source 

Methods

(==) :: Splice -> Splice -> Bool

(/=) :: Splice -> Splice -> Bool

Data Splice Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Splice -> c Splice

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Splice

toConstr :: Splice -> Constr

dataTypeOf :: Splice -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Splice)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Splice)

gmapT :: (forall b. Data b => b -> b) -> Splice -> Splice

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Splice -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Splice -> r

gmapQ :: (forall d. Data d => d -> u) -> Splice -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Splice -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Splice -> m Splice

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Splice -> m Splice

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Splice -> m Splice

Ord Splice Source 
Show Splice Source 
Generic Splice Source 

Associated Types

type Rep Splice :: * -> *

Methods

from :: Splice -> Rep Splice x

to :: Rep Splice x -> Splice

AppFixity Splice Source 

Methods

applyFixities :: Monad m => [Fixity] -> Splice -> m Splice Source

Pretty Splice Source 

Methods

pretty :: Splice -> Doc

prettyPrec :: Int -> Splice -> Doc

type Rep Splice Source 

FFI

data Safety Source

The safety of a foreign function call.

Constructors

PlayRisky

unsafe

PlaySafe Bool

safe (False) or threadsafe (True)

PlayInterruptible

interruptible

Instances

Eq Safety Source 

Methods

(==) :: Safety -> Safety -> Bool

(/=) :: Safety -> Safety -> Bool

Data Safety Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety -> c Safety

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Safety

toConstr :: Safety -> Constr

dataTypeOf :: Safety -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Safety)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Safety)

gmapT :: (forall b. Data b => b -> b) -> Safety -> Safety

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r

gmapQ :: (forall d. Data d => d -> u) -> Safety -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety -> m Safety

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety

Ord Safety Source 
Show Safety Source 
Generic Safety Source 

Associated Types

type Rep Safety :: * -> *

Methods

from :: Safety -> Rep Safety x

to :: Rep Safety x -> Safety

Pretty Safety Source 

Methods

pretty :: Safety -> Doc

prettyPrec :: Int -> Safety -> Doc

type Rep Safety Source 

data CallConv Source

The calling convention of a foreign function call.

Instances

Eq CallConv Source 
Data CallConv Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CallConv -> c CallConv

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CallConv

toConstr :: CallConv -> Constr

dataTypeOf :: CallConv -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CallConv)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CallConv)

gmapT :: (forall b. Data b => b -> b) -> CallConv -> CallConv

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CallConv -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CallConv -> r

gmapQ :: (forall d. Data d => d -> u) -> CallConv -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CallConv -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CallConv -> m CallConv

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CallConv -> m CallConv

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CallConv -> m CallConv

Ord CallConv Source 
Show CallConv Source 
Generic CallConv Source 

Associated Types

type Rep CallConv :: * -> *

Pretty CallConv Source 

Methods

pretty :: CallConv -> Doc

prettyPrec :: Int -> CallConv -> Doc

type Rep CallConv Source 

Pragmas

data ModulePragma Source

A top level options pragma, preceding the module header.

Constructors

LanguagePragma SrcLoc [Name]

LANGUAGE pragma

OptionsPragma SrcLoc (Maybe Tool) String

OPTIONS pragma, possibly qualified with a tool, e.g. OPTIONS_GHC

AnnModulePragma SrcLoc Annotation

ANN pragma with module scope

Instances

Eq ModulePragma Source 
Data ModulePragma Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModulePragma -> c ModulePragma

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModulePragma

toConstr :: ModulePragma -> Constr

dataTypeOf :: ModulePragma -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModulePragma)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModulePragma)

gmapT :: (forall b. Data b => b -> b) -> ModulePragma -> ModulePragma

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModulePragma -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModulePragma -> r

gmapQ :: (forall d. Data d => d -> u) -> ModulePragma -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModulePragma -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModulePragma -> m ModulePragma

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModulePragma -> m ModulePragma

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModulePragma -> m ModulePragma

Ord ModulePragma Source 
Show ModulePragma Source 
Generic ModulePragma Source 

Associated Types

type Rep ModulePragma :: * -> *

Pretty ModulePragma Source 

Methods

pretty :: ModulePragma -> Doc

prettyPrec :: Int -> ModulePragma -> Doc

type Rep ModulePragma Source 

data Tool Source

Recognised tools for OPTIONS pragmas.

Instances

Eq Tool Source 

Methods

(==) :: Tool -> Tool -> Bool

(/=) :: Tool -> Tool -> Bool

Data Tool Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tool -> c Tool

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tool

toConstr :: Tool -> Constr

dataTypeOf :: Tool -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tool)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tool)

gmapT :: (forall b. Data b => b -> b) -> Tool -> Tool

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tool -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tool -> r

gmapQ :: (forall d. Data d => d -> u) -> Tool -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tool -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tool -> m Tool

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tool -> m Tool

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tool -> m Tool

Ord Tool Source 

Methods

compare :: Tool -> Tool -> Ordering

(<) :: Tool -> Tool -> Bool

(<=) :: Tool -> Tool -> Bool

(>) :: Tool -> Tool -> Bool

(>=) :: Tool -> Tool -> Bool

max :: Tool -> Tool -> Tool

min :: Tool -> Tool -> Tool

Show Tool Source 

Methods

showsPrec :: Int -> Tool -> ShowS

show :: Tool -> String

showList :: [Tool] -> ShowS

Generic Tool Source 

Associated Types

type Rep Tool :: * -> *

Methods

from :: Tool -> Rep Tool x

to :: Rep Tool x -> Tool

Pretty Tool Source 

Methods

pretty :: Tool -> Doc

prettyPrec :: Int -> Tool -> Doc

type Rep Tool Source 

data Overlap Source

Recognised overlaps for overlap pragmas.

Constructors

NoOverlap

NO_OVERLAP pragma

Overlap

OVERLAP pragma

Incoherent

INCOHERENT pragma

Instances

Eq Overlap Source 

Methods

(==) :: Overlap -> Overlap -> Bool

(/=) :: Overlap -> Overlap -> Bool

Data Overlap Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Overlap -> c Overlap

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Overlap

toConstr :: Overlap -> Constr

dataTypeOf :: Overlap -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Overlap)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Overlap)

gmapT :: (forall b. Data b => b -> b) -> Overlap -> Overlap

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r

gmapQ :: (forall d. Data d => d -> u) -> Overlap -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Overlap -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap

Ord Overlap Source 
Show Overlap Source 
Generic Overlap Source 

Associated Types

type Rep Overlap :: * -> *

Methods

from :: Overlap -> Rep Overlap x

to :: Rep Overlap x -> Overlap

Pretty Overlap Source 

Methods

pretty :: Overlap -> Doc

prettyPrec :: Int -> Overlap -> Doc

type Rep Overlap Source 

data Rule Source

The body of a RULES pragma.

Instances

Eq Rule Source 

Methods

(==) :: Rule -> Rule -> Bool

(/=) :: Rule -> Rule -> Bool

Data Rule Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rule -> c Rule

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rule

toConstr :: Rule -> Constr

dataTypeOf :: Rule -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Rule)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule)

gmapT :: (forall b. Data b => b -> b) -> Rule -> Rule

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r

gmapQ :: (forall d. Data d => d -> u) -> Rule -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule -> m Rule

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule

Ord Rule Source 

Methods

compare :: Rule -> Rule -> Ordering

(<) :: Rule -> Rule -> Bool

(<=) :: Rule -> Rule -> Bool

(>) :: Rule -> Rule -> Bool

(>=) :: Rule -> Rule -> Bool

max :: Rule -> Rule -> Rule

min :: Rule -> Rule -> Rule

Show Rule Source 

Methods

showsPrec :: Int -> Rule -> ShowS

show :: Rule -> String

showList :: [Rule] -> ShowS

Generic Rule Source 

Associated Types

type Rep Rule :: * -> *

Methods

from :: Rule -> Rep Rule x

to :: Rep Rule x -> Rule

Pretty Rule Source 

Methods

pretty :: Rule -> Doc

prettyPrec :: Int -> Rule -> Doc

type Rep Rule Source 

data RuleVar Source

Variables used in a RULES pragma, optionally annotated with types

Instances

Eq RuleVar Source 

Methods

(==) :: RuleVar -> RuleVar -> Bool

(/=) :: RuleVar -> RuleVar -> Bool

Data RuleVar Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleVar -> c RuleVar

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleVar

toConstr :: RuleVar -> Constr

dataTypeOf :: RuleVar -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RuleVar)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleVar)

gmapT :: (forall b. Data b => b -> b) -> RuleVar -> RuleVar

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleVar -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleVar -> r

gmapQ :: (forall d. Data d => d -> u) -> RuleVar -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleVar -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleVar -> m RuleVar

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleVar -> m RuleVar

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleVar -> m RuleVar

Ord RuleVar Source 
Show RuleVar Source 
Generic RuleVar Source 

Associated Types

type Rep RuleVar :: * -> *

Methods

from :: RuleVar -> Rep RuleVar x

to :: Rep RuleVar x -> RuleVar

Pretty RuleVar Source 

Methods

pretty :: RuleVar -> Doc

prettyPrec :: Int -> RuleVar -> Doc

type Rep RuleVar Source 

data Activation Source

Activation clause of a RULES pragma.

Instances

Eq Activation Source 
Data Activation Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation -> c Activation

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation

toConstr :: Activation -> Constr

dataTypeOf :: Activation -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Activation)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)

gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r

gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation

Ord Activation Source 
Show Activation Source 
Generic Activation Source 

Associated Types

type Rep Activation :: * -> *

Pretty Activation Source 

Methods

pretty :: Activation -> Doc

prettyPrec :: Int -> Activation -> Doc

type Rep Activation Source 

data Annotation Source

An annotation through an ANN pragma.

Constructors

Ann Name Exp

An annotation for a declared name.

TypeAnn Name Exp

An annotation for a declared type.

ModuleAnn Exp

An annotation for the defining module.

Instances

Eq Annotation Source 
Data Annotation Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation

toConstr :: Annotation -> Constr

dataTypeOf :: Annotation -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Annotation)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation)

gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r

gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

Ord Annotation Source 
Show Annotation Source 
Generic Annotation Source 

Associated Types

type Rep Annotation :: * -> *

AppFixity Annotation Source 
Pretty Annotation Source 

Methods

pretty :: Annotation -> Doc

prettyPrec :: Int -> Annotation -> Doc

type Rep Annotation Source 

data BooleanFormula Source

A boolean formula for MINIMAL pragmas.

Constructors

VarFormula Name

A variable.

AndFormula [BooleanFormula]

And boolean formulas.

OrFormula [BooleanFormula]

Or boolean formulas.

ParenFormula BooleanFormula

Parenthesized boolean formulas.

Instances

Eq BooleanFormula Source 
Data BooleanFormula Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BooleanFormula -> c BooleanFormula

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BooleanFormula

toConstr :: BooleanFormula -> Constr

dataTypeOf :: BooleanFormula -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BooleanFormula)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BooleanFormula)

gmapT :: (forall b. Data b => b -> b) -> BooleanFormula -> BooleanFormula

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BooleanFormula -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BooleanFormula -> r

gmapQ :: (forall d. Data d => d -> u) -> BooleanFormula -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> BooleanFormula -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BooleanFormula -> m BooleanFormula

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanFormula -> m BooleanFormula

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanFormula -> m BooleanFormula

Ord BooleanFormula Source 
Show BooleanFormula Source 
Generic BooleanFormula Source 

Associated Types

type Rep BooleanFormula :: * -> *

Pretty BooleanFormula Source 

Methods

pretty :: BooleanFormula -> Doc

prettyPrec :: Int -> BooleanFormula -> Doc

type Rep BooleanFormula Source 

Builtin names

Modules

Main function of a program

Constructors

Special identifiers

Type constructors

Source coordinates

data SrcLoc Source

A single position in the source.

Constructors

SrcLoc 

Instances

Eq SrcLoc Source 

Methods

(==) :: SrcLoc -> SrcLoc -> Bool

(/=) :: SrcLoc -> SrcLoc -> Bool

Data SrcLoc Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcLoc -> c SrcLoc

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcLoc

toConstr :: SrcLoc -> Constr

dataTypeOf :: SrcLoc -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SrcLoc)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc)

gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r

gmapQ :: (forall d. Data d => d -> u) -> SrcLoc -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcLoc -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

Ord SrcLoc Source 
Show SrcLoc Source 
Generic SrcLoc Source 

Associated Types

type Rep SrcLoc :: * -> *

Methods

from :: SrcLoc -> Rep SrcLoc x

to :: Rep SrcLoc x -> SrcLoc

SrcInfo SrcLoc Source 
Pretty SrcLoc Source 

Methods

pretty :: SrcLoc -> Doc

prettyPrec :: Int -> SrcLoc -> Doc

type Rep SrcLoc Source