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.Annotated.Syntax

Contents

Description

A suite of datatypes describing the (semi-concrete) 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)

All nodes in the syntax tree are annotated with something of a user-definable data type. When parsing, this annotation will contain information about the source location that the particular node comes from.

Synopsis

Modules

data Module l Source

A complete Haskell source module.

Constructors

Module l (Maybe (ModuleHead l)) [ModulePragma l] [ImportDecl l] [Decl l]

an ordinary Haskell module

XmlPage l (ModuleName l) [ModulePragma l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l]

a module consisting of a single XML document. The ModuleName never appears in the source but is needed for semantic purposes, it will be the same as the file name.

XmlHybrid l (Maybe (ModuleHead l)) [ModulePragma l] [ImportDecl l] [Decl l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l]

a hybrid module combining an XML document with an ordinary module

Instances

Functor Module Source 

Methods

fmap :: (a -> b) -> Module a -> Module b

(<$) :: a -> Module b -> Module a

Foldable Module Source 

Methods

fold :: Monoid m => Module m -> m

foldMap :: Monoid m => (a -> m) -> Module a -> m

foldr :: (a -> b -> b) -> b -> Module a -> b

foldr' :: (a -> b -> b) -> b -> Module a -> b

foldl :: (b -> a -> b) -> b -> Module a -> b

foldl' :: (b -> a -> b) -> b -> Module a -> b

foldr1 :: (a -> a -> a) -> Module a -> a

foldl1 :: (a -> a -> a) -> Module a -> a

toList :: Module a -> [a]

null :: Module a -> Bool

length :: Module a -> Int

elem :: Eq a => a -> Module a -> Bool

maximum :: Ord a => Module a -> a

minimum :: Ord a => Module a -> a

sum :: Num a => Module a -> a

product :: Num a => Module a -> a

Traversable Module Source 

Methods

traverse :: Applicative f => (a -> f b) -> Module a -> f (Module b)

sequenceA :: Applicative f => Module (f a) -> f (Module a)

mapM :: Monad m => (a -> m b) -> Module a -> m (Module b)

sequence :: Monad m => Module (m a) -> m (Module a)

Annotated Module Source 

Methods

ann :: Module l -> l Source

amap :: (l -> l) -> Module l -> Module l Source

ExactP Module Source 

Methods

exactP :: Module SrcSpanInfo -> EP ()

AppFixity Module Source 
Eq l => Eq (Module l) Source 

Methods

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

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

Data l => Data (Module l) Source 

Methods

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

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

toConstr :: Module l -> Constr

dataTypeOf :: Module l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Module l) Source 

Methods

compare :: Module l -> Module l -> Ordering

(<) :: Module l -> Module l -> Bool

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

(>) :: Module l -> Module l -> Bool

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

max :: Module l -> Module l -> Module l

min :: Module l -> Module l -> Module l

Show l => Show (Module l) Source 

Methods

showsPrec :: Int -> Module l -> ShowS

show :: Module l -> String

showList :: [Module l] -> ShowS

Generic (Module l) Source 

Associated Types

type Rep (Module l) :: * -> *

Methods

from :: Module l -> Rep (Module l) x

to :: Rep (Module l) x -> Module l

SrcInfo pos => Pretty (Module pos) Source 

Methods

pretty :: Module pos -> Doc

prettyPrec :: Int -> Module pos -> Doc

type Rep (Module l) Source 

data ModuleHead l Source

The head of a module, including the name and export specification.

Constructors

ModuleHead l (ModuleName l) (Maybe (WarningText l)) (Maybe (ExportSpecList l)) 

Instances

Functor ModuleHead Source 

Methods

fmap :: (a -> b) -> ModuleHead a -> ModuleHead b

(<$) :: a -> ModuleHead b -> ModuleHead a

Foldable ModuleHead Source 

Methods

fold :: Monoid m => ModuleHead m -> m

foldMap :: Monoid m => (a -> m) -> ModuleHead a -> m

foldr :: (a -> b -> b) -> b -> ModuleHead a -> b

foldr' :: (a -> b -> b) -> b -> ModuleHead a -> b

foldl :: (b -> a -> b) -> b -> ModuleHead a -> b

foldl' :: (b -> a -> b) -> b -> ModuleHead a -> b

foldr1 :: (a -> a -> a) -> ModuleHead a -> a

foldl1 :: (a -> a -> a) -> ModuleHead a -> a

toList :: ModuleHead a -> [a]

null :: ModuleHead a -> Bool

length :: ModuleHead a -> Int

elem :: Eq a => a -> ModuleHead a -> Bool

maximum :: Ord a => ModuleHead a -> a

minimum :: Ord a => ModuleHead a -> a

sum :: Num a => ModuleHead a -> a

product :: Num a => ModuleHead a -> a

Traversable ModuleHead Source 

Methods

traverse :: Applicative f => (a -> f b) -> ModuleHead a -> f (ModuleHead b)

sequenceA :: Applicative f => ModuleHead (f a) -> f (ModuleHead a)

mapM :: Monad m => (a -> m b) -> ModuleHead a -> m (ModuleHead b)

sequence :: Monad m => ModuleHead (m a) -> m (ModuleHead a)

Annotated ModuleHead Source 

Methods

ann :: ModuleHead l -> l Source

amap :: (l -> l) -> ModuleHead l -> ModuleHead l Source

ExactP ModuleHead Source 

Methods

exactP :: ModuleHead SrcSpanInfo -> EP ()

Eq l => Eq (ModuleHead l) Source 

Methods

(==) :: ModuleHead l -> ModuleHead l -> Bool

(/=) :: ModuleHead l -> ModuleHead l -> Bool

Data l => Data (ModuleHead l) Source 

Methods

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

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

toConstr :: ModuleHead l -> Constr

dataTypeOf :: ModuleHead l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> ModuleHead l -> ModuleHead l

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

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

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

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

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

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

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

Ord l => Ord (ModuleHead l) Source 
Show l => Show (ModuleHead l) Source 
Generic (ModuleHead l) Source 

Associated Types

type Rep (ModuleHead l) :: * -> *

Methods

from :: ModuleHead l -> Rep (ModuleHead l) x

to :: Rep (ModuleHead l) x -> ModuleHead l

Pretty (ModuleHead l) Source 

Methods

pretty :: ModuleHead l -> Doc

prettyPrec :: Int -> ModuleHead l -> Doc

type Rep (ModuleHead l) Source 

data WarningText l Source

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

Constructors

DeprText l String 
WarnText l String 

Instances

Functor WarningText Source 

Methods

fmap :: (a -> b) -> WarningText a -> WarningText b

(<$) :: a -> WarningText b -> WarningText a

Foldable WarningText Source 

Methods

fold :: Monoid m => WarningText m -> m

foldMap :: Monoid m => (a -> m) -> WarningText a -> m

foldr :: (a -> b -> b) -> b -> WarningText a -> b

foldr' :: (a -> b -> b) -> b -> WarningText a -> b

foldl :: (b -> a -> b) -> b -> WarningText a -> b

foldl' :: (b -> a -> b) -> b -> WarningText a -> b

foldr1 :: (a -> a -> a) -> WarningText a -> a

foldl1 :: (a -> a -> a) -> WarningText a -> a

toList :: WarningText a -> [a]

null :: WarningText a -> Bool

length :: WarningText a -> Int

elem :: Eq a => a -> WarningText a -> Bool

maximum :: Ord a => WarningText a -> a

minimum :: Ord a => WarningText a -> a

sum :: Num a => WarningText a -> a

product :: Num a => WarningText a -> a

Traversable WarningText Source 

Methods

traverse :: Applicative f => (a -> f b) -> WarningText a -> f (WarningText b)

sequenceA :: Applicative f => WarningText (f a) -> f (WarningText a)

mapM :: Monad m => (a -> m b) -> WarningText a -> m (WarningText b)

sequence :: Monad m => WarningText (m a) -> m (WarningText a)

Annotated WarningText Source 

Methods

ann :: WarningText l -> l Source

amap :: (l -> l) -> WarningText l -> WarningText l Source

ExactP WarningText Source 

Methods

exactP :: WarningText SrcSpanInfo -> EP ()

Eq l => Eq (WarningText l) Source 
Data l => Data (WarningText l) Source 

Methods

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

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

toConstr :: WarningText l -> Constr

dataTypeOf :: WarningText l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (WarningText l) Source 
Show l => Show (WarningText l) Source 
Generic (WarningText l) Source 

Associated Types

type Rep (WarningText l) :: * -> *

Methods

from :: WarningText l -> Rep (WarningText l) x

to :: Rep (WarningText l) x -> WarningText l

Pretty (WarningText l) Source 

Methods

pretty :: WarningText l -> Doc

prettyPrec :: Int -> WarningText l -> Doc

type Rep (WarningText l) Source 

data ExportSpecList l Source

An explicit export specification.

Constructors

ExportSpecList l [ExportSpec l] 

Instances

Functor ExportSpecList Source 

Methods

fmap :: (a -> b) -> ExportSpecList a -> ExportSpecList b

(<$) :: a -> ExportSpecList b -> ExportSpecList a

Foldable ExportSpecList Source 

Methods

fold :: Monoid m => ExportSpecList m -> m

foldMap :: Monoid m => (a -> m) -> ExportSpecList a -> m

foldr :: (a -> b -> b) -> b -> ExportSpecList a -> b

foldr' :: (a -> b -> b) -> b -> ExportSpecList a -> b

foldl :: (b -> a -> b) -> b -> ExportSpecList a -> b

foldl' :: (b -> a -> b) -> b -> ExportSpecList a -> b

foldr1 :: (a -> a -> a) -> ExportSpecList a -> a

foldl1 :: (a -> a -> a) -> ExportSpecList a -> a

toList :: ExportSpecList a -> [a]

null :: ExportSpecList a -> Bool

length :: ExportSpecList a -> Int

elem :: Eq a => a -> ExportSpecList a -> Bool

maximum :: Ord a => ExportSpecList a -> a

minimum :: Ord a => ExportSpecList a -> a

sum :: Num a => ExportSpecList a -> a

product :: Num a => ExportSpecList a -> a

Traversable ExportSpecList Source 

Methods

traverse :: Applicative f => (a -> f b) -> ExportSpecList a -> f (ExportSpecList b)

sequenceA :: Applicative f => ExportSpecList (f a) -> f (ExportSpecList a)

mapM :: Monad m => (a -> m b) -> ExportSpecList a -> m (ExportSpecList b)

sequence :: Monad m => ExportSpecList (m a) -> m (ExportSpecList a)

Annotated ExportSpecList Source 

Methods

ann :: ExportSpecList l -> l Source

amap :: (l -> l) -> ExportSpecList l -> ExportSpecList l Source

ExactP ExportSpecList Source 

Methods

exactP :: ExportSpecList SrcSpanInfo -> EP ()

Eq l => Eq (ExportSpecList l) Source 
Data l => Data (ExportSpecList l) Source 

Methods

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

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

toConstr :: ExportSpecList l -> Constr

dataTypeOf :: ExportSpecList l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> ExportSpecList l -> ExportSpecList l

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

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

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

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

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

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

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

Ord l => Ord (ExportSpecList l) Source 
Show l => Show (ExportSpecList l) Source 
Generic (ExportSpecList l) Source 

Associated Types

type Rep (ExportSpecList l) :: * -> *

Pretty (ExportSpecList l) Source 

Methods

pretty :: ExportSpecList l -> Doc

prettyPrec :: Int -> ExportSpecList l -> Doc

type Rep (ExportSpecList l) Source 

data ExportSpec l Source

An item in a module's export specification.

Constructors

EVar l (QName l)

variable.

EAbs l (Namespace l) (QName l)

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

EThingAll l (QName l)

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

EThingWith l (QName l) [CName l]

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

EModuleContents l (ModuleName l)

module M: re-export a module.

Instances

Functor ExportSpec Source 

Methods

fmap :: (a -> b) -> ExportSpec a -> ExportSpec b

(<$) :: a -> ExportSpec b -> ExportSpec a

Foldable ExportSpec Source 

Methods

fold :: Monoid m => ExportSpec m -> m

foldMap :: Monoid m => (a -> m) -> ExportSpec a -> m

foldr :: (a -> b -> b) -> b -> ExportSpec a -> b

foldr' :: (a -> b -> b) -> b -> ExportSpec a -> b

foldl :: (b -> a -> b) -> b -> ExportSpec a -> b

foldl' :: (b -> a -> b) -> b -> ExportSpec a -> b

foldr1 :: (a -> a -> a) -> ExportSpec a -> a

foldl1 :: (a -> a -> a) -> ExportSpec a -> a

toList :: ExportSpec a -> [a]

null :: ExportSpec a -> Bool

length :: ExportSpec a -> Int

elem :: Eq a => a -> ExportSpec a -> Bool

maximum :: Ord a => ExportSpec a -> a

minimum :: Ord a => ExportSpec a -> a

sum :: Num a => ExportSpec a -> a

product :: Num a => ExportSpec a -> a

Traversable ExportSpec Source 

Methods

traverse :: Applicative f => (a -> f b) -> ExportSpec a -> f (ExportSpec b)

sequenceA :: Applicative f => ExportSpec (f a) -> f (ExportSpec a)

mapM :: Monad m => (a -> m b) -> ExportSpec a -> m (ExportSpec b)

sequence :: Monad m => ExportSpec (m a) -> m (ExportSpec a)

Annotated ExportSpec Source 

Methods

ann :: ExportSpec l -> l Source

amap :: (l -> l) -> ExportSpec l -> ExportSpec l Source

ExactP ExportSpec Source 

Methods

exactP :: ExportSpec SrcSpanInfo -> EP ()

Eq l => Eq (ExportSpec l) Source 

Methods

(==) :: ExportSpec l -> ExportSpec l -> Bool

(/=) :: ExportSpec l -> ExportSpec l -> Bool

Data l => Data (ExportSpec l) Source 

Methods

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

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

toConstr :: ExportSpec l -> Constr

dataTypeOf :: ExportSpec l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ExportSpec l) Source 
Show l => Show (ExportSpec l) Source 
Generic (ExportSpec l) Source 

Associated Types

type Rep (ExportSpec l) :: * -> *

Methods

from :: ExportSpec l -> Rep (ExportSpec l) x

to :: Rep (ExportSpec l) x -> ExportSpec l

Pretty (ExportSpec l) Source 

Methods

pretty :: ExportSpec l -> Doc

prettyPrec :: Int -> ExportSpec l -> Doc

type Rep (ExportSpec l) Source 

data ImportDecl l Source

An import declaration.

Constructors

ImportDecl 

Fields

Instances

Functor ImportDecl Source 

Methods

fmap :: (a -> b) -> ImportDecl a -> ImportDecl b

(<$) :: a -> ImportDecl b -> ImportDecl a

Foldable ImportDecl Source 

Methods

fold :: Monoid m => ImportDecl m -> m

foldMap :: Monoid m => (a -> m) -> ImportDecl a -> m

foldr :: (a -> b -> b) -> b -> ImportDecl a -> b

foldr' :: (a -> b -> b) -> b -> ImportDecl a -> b

foldl :: (b -> a -> b) -> b -> ImportDecl a -> b

foldl' :: (b -> a -> b) -> b -> ImportDecl a -> b

foldr1 :: (a -> a -> a) -> ImportDecl a -> a

foldl1 :: (a -> a -> a) -> ImportDecl a -> a

toList :: ImportDecl a -> [a]

null :: ImportDecl a -> Bool

length :: ImportDecl a -> Int

elem :: Eq a => a -> ImportDecl a -> Bool

maximum :: Ord a => ImportDecl a -> a

minimum :: Ord a => ImportDecl a -> a

sum :: Num a => ImportDecl a -> a

product :: Num a => ImportDecl a -> a

Traversable ImportDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> ImportDecl a -> f (ImportDecl b)

sequenceA :: Applicative f => ImportDecl (f a) -> f (ImportDecl a)

mapM :: Monad m => (a -> m b) -> ImportDecl a -> m (ImportDecl b)

sequence :: Monad m => ImportDecl (m a) -> m (ImportDecl a)

Annotated ImportDecl Source 

Methods

ann :: ImportDecl l -> l Source

amap :: (l -> l) -> ImportDecl l -> ImportDecl l Source

ExactP ImportDecl Source 

Methods

exactP :: ImportDecl SrcSpanInfo -> EP ()

Eq l => Eq (ImportDecl l) Source 

Methods

(==) :: ImportDecl l -> ImportDecl l -> Bool

(/=) :: ImportDecl l -> ImportDecl l -> Bool

Data l => Data (ImportDecl l) Source 

Methods

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

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

toConstr :: ImportDecl l -> Constr

dataTypeOf :: ImportDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ImportDecl l) Source 
Show l => Show (ImportDecl l) Source 
Generic (ImportDecl l) Source 

Associated Types

type Rep (ImportDecl l) :: * -> *

Methods

from :: ImportDecl l -> Rep (ImportDecl l) x

to :: Rep (ImportDecl l) x -> ImportDecl l

SrcInfo pos => Pretty (ImportDecl pos) Source 

Methods

pretty :: ImportDecl pos -> Doc

prettyPrec :: Int -> ImportDecl pos -> Doc

type Rep (ImportDecl l) Source 

data ImportSpecList l Source

An explicit import specification list.

Constructors

ImportSpecList l Bool [ImportSpec l] 

Instances

Functor ImportSpecList Source 

Methods

fmap :: (a -> b) -> ImportSpecList a -> ImportSpecList b

(<$) :: a -> ImportSpecList b -> ImportSpecList a

Foldable ImportSpecList Source 

Methods

fold :: Monoid m => ImportSpecList m -> m

foldMap :: Monoid m => (a -> m) -> ImportSpecList a -> m

foldr :: (a -> b -> b) -> b -> ImportSpecList a -> b

foldr' :: (a -> b -> b) -> b -> ImportSpecList a -> b

foldl :: (b -> a -> b) -> b -> ImportSpecList a -> b

foldl' :: (b -> a -> b) -> b -> ImportSpecList a -> b

foldr1 :: (a -> a -> a) -> ImportSpecList a -> a

foldl1 :: (a -> a -> a) -> ImportSpecList a -> a

toList :: ImportSpecList a -> [a]

null :: ImportSpecList a -> Bool

length :: ImportSpecList a -> Int

elem :: Eq a => a -> ImportSpecList a -> Bool

maximum :: Ord a => ImportSpecList a -> a

minimum :: Ord a => ImportSpecList a -> a

sum :: Num a => ImportSpecList a -> a

product :: Num a => ImportSpecList a -> a

Traversable ImportSpecList Source 

Methods

traverse :: Applicative f => (a -> f b) -> ImportSpecList a -> f (ImportSpecList b)

sequenceA :: Applicative f => ImportSpecList (f a) -> f (ImportSpecList a)

mapM :: Monad m => (a -> m b) -> ImportSpecList a -> m (ImportSpecList b)

sequence :: Monad m => ImportSpecList (m a) -> m (ImportSpecList a)

Annotated ImportSpecList Source 

Methods

ann :: ImportSpecList l -> l Source

amap :: (l -> l) -> ImportSpecList l -> ImportSpecList l Source

ExactP ImportSpecList Source 

Methods

exactP :: ImportSpecList SrcSpanInfo -> EP ()

Eq l => Eq (ImportSpecList l) Source 
Data l => Data (ImportSpecList l) Source 

Methods

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

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

toConstr :: ImportSpecList l -> Constr

dataTypeOf :: ImportSpecList l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> ImportSpecList l -> ImportSpecList l

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

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

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

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

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

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

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

Ord l => Ord (ImportSpecList l) Source 
Show l => Show (ImportSpecList l) Source 
Generic (ImportSpecList l) Source 

Associated Types

type Rep (ImportSpecList l) :: * -> *

Pretty (ImportSpecList l) Source 

Methods

pretty :: ImportSpecList l -> Doc

prettyPrec :: Int -> ImportSpecList l -> Doc

type Rep (ImportSpecList l) Source 

data ImportSpec l Source

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

Constructors

IVar l (Name l)

variable

IAbs l (Namespace l) (Name l)

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

IThingAll l (Name l)

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

IThingWith l (Name l) [CName l]

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

Instances

Functor ImportSpec Source 

Methods

fmap :: (a -> b) -> ImportSpec a -> ImportSpec b

(<$) :: a -> ImportSpec b -> ImportSpec a

Foldable ImportSpec Source 

Methods

fold :: Monoid m => ImportSpec m -> m

foldMap :: Monoid m => (a -> m) -> ImportSpec a -> m

foldr :: (a -> b -> b) -> b -> ImportSpec a -> b

foldr' :: (a -> b -> b) -> b -> ImportSpec a -> b

foldl :: (b -> a -> b) -> b -> ImportSpec a -> b

foldl' :: (b -> a -> b) -> b -> ImportSpec a -> b

foldr1 :: (a -> a -> a) -> ImportSpec a -> a

foldl1 :: (a -> a -> a) -> ImportSpec a -> a

toList :: ImportSpec a -> [a]

null :: ImportSpec a -> Bool

length :: ImportSpec a -> Int

elem :: Eq a => a -> ImportSpec a -> Bool

maximum :: Ord a => ImportSpec a -> a

minimum :: Ord a => ImportSpec a -> a

sum :: Num a => ImportSpec a -> a

product :: Num a => ImportSpec a -> a

Traversable ImportSpec Source 

Methods

traverse :: Applicative f => (a -> f b) -> ImportSpec a -> f (ImportSpec b)

sequenceA :: Applicative f => ImportSpec (f a) -> f (ImportSpec a)

mapM :: Monad m => (a -> m b) -> ImportSpec a -> m (ImportSpec b)

sequence :: Monad m => ImportSpec (m a) -> m (ImportSpec a)

Annotated ImportSpec Source 

Methods

ann :: ImportSpec l -> l Source

amap :: (l -> l) -> ImportSpec l -> ImportSpec l Source

ExactP ImportSpec Source 

Methods

exactP :: ImportSpec SrcSpanInfo -> EP ()

Eq l => Eq (ImportSpec l) Source 

Methods

(==) :: ImportSpec l -> ImportSpec l -> Bool

(/=) :: ImportSpec l -> ImportSpec l -> Bool

Data l => Data (ImportSpec l) Source 

Methods

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

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

toConstr :: ImportSpec l -> Constr

dataTypeOf :: ImportSpec l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ImportSpec l) Source 
Show l => Show (ImportSpec l) Source 
Generic (ImportSpec l) Source 

Associated Types

type Rep (ImportSpec l) :: * -> *

Methods

from :: ImportSpec l -> Rep (ImportSpec l) x

to :: Rep (ImportSpec l) x -> ImportSpec l

Pretty (ImportSpec l) Source 

Methods

pretty :: ImportSpec l -> Doc

prettyPrec :: Int -> ImportSpec l -> Doc

type Rep (ImportSpec l) Source 

data Assoc l Source

Associativity of an operator.

Constructors

AssocNone l

non-associative operator (declared with infix)

AssocLeft l

left-associative operator (declared with infixl).

AssocRight l

right-associative operator (declared with infixr)

Instances

Functor Assoc Source 

Methods

fmap :: (a -> b) -> Assoc a -> Assoc b

(<$) :: a -> Assoc b -> Assoc a

Foldable Assoc Source 

Methods

fold :: Monoid m => Assoc m -> m

foldMap :: Monoid m => (a -> m) -> Assoc a -> m

foldr :: (a -> b -> b) -> b -> Assoc a -> b

foldr' :: (a -> b -> b) -> b -> Assoc a -> b

foldl :: (b -> a -> b) -> b -> Assoc a -> b

foldl' :: (b -> a -> b) -> b -> Assoc a -> b

foldr1 :: (a -> a -> a) -> Assoc a -> a

foldl1 :: (a -> a -> a) -> Assoc a -> a

toList :: Assoc a -> [a]

null :: Assoc a -> Bool

length :: Assoc a -> Int

elem :: Eq a => a -> Assoc a -> Bool

maximum :: Ord a => Assoc a -> a

minimum :: Ord a => Assoc a -> a

sum :: Num a => Assoc a -> a

product :: Num a => Assoc a -> a

Traversable Assoc Source 

Methods

traverse :: Applicative f => (a -> f b) -> Assoc a -> f (Assoc b)

sequenceA :: Applicative f => Assoc (f a) -> f (Assoc a)

mapM :: Monad m => (a -> m b) -> Assoc a -> m (Assoc b)

sequence :: Monad m => Assoc (m a) -> m (Assoc a)

Annotated Assoc Source 

Methods

ann :: Assoc l -> l Source

amap :: (l -> l) -> Assoc l -> Assoc l Source

ExactP Assoc Source 

Methods

exactP :: Assoc SrcSpanInfo -> EP ()

Eq l => Eq (Assoc l) Source 

Methods

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

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

Data l => Data (Assoc l) Source 

Methods

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

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

toConstr :: Assoc l -> Constr

dataTypeOf :: Assoc l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Assoc l) Source 

Methods

compare :: Assoc l -> Assoc l -> Ordering

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

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

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

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

max :: Assoc l -> Assoc l -> Assoc l

min :: Assoc l -> Assoc l -> Assoc l

Show l => Show (Assoc l) Source 

Methods

showsPrec :: Int -> Assoc l -> ShowS

show :: Assoc l -> String

showList :: [Assoc l] -> ShowS

Generic (Assoc l) Source 

Associated Types

type Rep (Assoc l) :: * -> *

Methods

from :: Assoc l -> Rep (Assoc l) x

to :: Rep (Assoc l) x -> Assoc l

Pretty (Assoc l) Source 

Methods

pretty :: Assoc l -> Doc

prettyPrec :: Int -> Assoc l -> Doc

type Rep (Assoc l) Source 

data Namespace l Source

Namespaces for imports/exports.

Instances

Functor Namespace Source 

Methods

fmap :: (a -> b) -> Namespace a -> Namespace b

(<$) :: a -> Namespace b -> Namespace a

Foldable Namespace Source 

Methods

fold :: Monoid m => Namespace m -> m

foldMap :: Monoid m => (a -> m) -> Namespace a -> m

foldr :: (a -> b -> b) -> b -> Namespace a -> b

foldr' :: (a -> b -> b) -> b -> Namespace a -> b

foldl :: (b -> a -> b) -> b -> Namespace a -> b

foldl' :: (b -> a -> b) -> b -> Namespace a -> b

foldr1 :: (a -> a -> a) -> Namespace a -> a

foldl1 :: (a -> a -> a) -> Namespace a -> a

toList :: Namespace a -> [a]

null :: Namespace a -> Bool

length :: Namespace a -> Int

elem :: Eq a => a -> Namespace a -> Bool

maximum :: Ord a => Namespace a -> a

minimum :: Ord a => Namespace a -> a

sum :: Num a => Namespace a -> a

product :: Num a => Namespace a -> a

Traversable Namespace Source 

Methods

traverse :: Applicative f => (a -> f b) -> Namespace a -> f (Namespace b)

sequenceA :: Applicative f => Namespace (f a) -> f (Namespace a)

mapM :: Monad m => (a -> m b) -> Namespace a -> m (Namespace b)

sequence :: Monad m => Namespace (m a) -> m (Namespace a)

Annotated Namespace Source 

Methods

ann :: Namespace l -> l Source

amap :: (l -> l) -> Namespace l -> Namespace l Source

ExactP Namespace Source 

Methods

exactP :: Namespace SrcSpanInfo -> EP ()

Eq l => Eq (Namespace l) Source 

Methods

(==) :: Namespace l -> Namespace l -> Bool

(/=) :: Namespace l -> Namespace l -> Bool

Data l => Data (Namespace l) Source 

Methods

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

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

toConstr :: Namespace l -> Constr

dataTypeOf :: Namespace l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Namespace l) Source 
Show l => Show (Namespace l) Source 
Generic (Namespace l) Source 

Associated Types

type Rep (Namespace l) :: * -> *

Methods

from :: Namespace l -> Rep (Namespace l) x

to :: Rep (Namespace l) x -> Namespace l

type Rep (Namespace l) Source 

Declarations

data Decl l Source

A top-level declaration.

Constructors

TypeDecl l (DeclHead l) (Type l)

A type declaration

TypeFamDecl l (DeclHead l) (Maybe (Kind l))

A type family declaration

ClosedTypeFamDecl l (DeclHead l) (Maybe (Kind l)) [TypeEqn l]

A closed type family declaration

DataDecl l (DataOrNew l) (Maybe (Context l)) (DeclHead l) [QualConDecl l] (Maybe (Deriving l))

A data OR newtype declaration

GDataDecl l (DataOrNew l) (Maybe (Context l)) (DeclHead l) (Maybe (Kind l)) [GadtDecl l] (Maybe (Deriving l))

A data OR newtype declaration, GADT style

DataFamDecl l (Maybe (Context l)) (DeclHead l) (Maybe (Kind l))

A data family declaration

TypeInsDecl l (Type l) (Type l)

A type family instance declaration

DataInsDecl l (DataOrNew l) (Type l) [QualConDecl l] (Maybe (Deriving l))

A data family instance declaration

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

A data family instance declaration, GADT style

ClassDecl l (Maybe (Context l)) (DeclHead l) [FunDep l] (Maybe [ClassDecl l])

A declaration of a type class

InstDecl l (Maybe (Overlap l)) (InstRule l) (Maybe [InstDecl l])

An declaration of a type class instance

DerivDecl l (Maybe (Overlap l)) (InstRule l)

A standalone deriving declaration

InfixDecl l (Assoc l) (Maybe Int) [Op l]

A declaration of operator fixity

DefaultDecl l [Type l]

A declaration of default types

SpliceDecl l (Exp l)

A Template Haskell splicing declaration

TypeSig l [Name l] (Type l)

A type signature declaration

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

A pattern synonym signature declation

FunBind l [Match l]

A set of function binding clauses

PatBind l (Pat l) (Rhs l) (Maybe (Binds l))

A pattern binding

PatSyn l (Pat l) (Pat l) (PatternSynDirection l)

A pattern synonym binding

ForImp l (CallConv l) (Maybe (Safety l)) (Maybe String) (Name l) (Type l)

A foreign import declaration

ForExp l (CallConv l) (Maybe String) (Name l) (Type l)

A foreign export declaration

RulePragmaDecl l [Rule l]

A RULES pragma

DeprPragmaDecl l [([Name l], String)]

A DEPRECATED pragma

WarnPragmaDecl l [([Name l], String)]

A WARNING pragma

InlineSig l Bool (Maybe (Activation l)) (QName l)

An INLINE pragma

InlineConlikeSig l (Maybe (Activation l)) (QName l)

An INLINE CONLIKE pragma

SpecSig l (Maybe (Activation l)) (QName l) [Type l]

A SPECIALISE pragma

SpecInlineSig l Bool (Maybe (Activation l)) (QName l) [Type l]

A SPECIALISE INLINE pragma

InstSig l (InstRule l)

A SPECIALISE instance pragma

AnnPragma l (Annotation l)

An ANN pragma

MinimalPragma l (Maybe (BooleanFormula l))

A MINIMAL pragma

RoleAnnotDecl l (QName l) [Role l]

A role annotation

Instances

Functor Decl Source 

Methods

fmap :: (a -> b) -> Decl a -> Decl b

(<$) :: a -> Decl b -> Decl a

Foldable Decl Source 

Methods

fold :: Monoid m => Decl m -> m

foldMap :: Monoid m => (a -> m) -> Decl a -> m

foldr :: (a -> b -> b) -> b -> Decl a -> b

foldr' :: (a -> b -> b) -> b -> Decl a -> b

foldl :: (b -> a -> b) -> b -> Decl a -> b

foldl' :: (b -> a -> b) -> b -> Decl a -> b

foldr1 :: (a -> a -> a) -> Decl a -> a

foldl1 :: (a -> a -> a) -> Decl a -> a

toList :: Decl a -> [a]

null :: Decl a -> Bool

length :: Decl a -> Int

elem :: Eq a => a -> Decl a -> Bool

maximum :: Ord a => Decl a -> a

minimum :: Ord a => Decl a -> a

sum :: Num a => Decl a -> a

product :: Num a => Decl a -> a

Traversable Decl Source 

Methods

traverse :: Applicative f => (a -> f b) -> Decl a -> f (Decl b)

sequenceA :: Applicative f => Decl (f a) -> f (Decl a)

mapM :: Monad m => (a -> m b) -> Decl a -> m (Decl b)

sequence :: Monad m => Decl (m a) -> m (Decl a)

Annotated Decl Source 

Methods

ann :: Decl l -> l Source

amap :: (l -> l) -> Decl l -> Decl l Source

ExactP Decl Source 

Methods

exactP :: Decl SrcSpanInfo -> EP ()

AppFixity Decl Source 
Eq l => Eq (Decl l) Source 

Methods

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

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

Data l => Data (Decl l) Source 

Methods

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

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

toConstr :: Decl l -> Constr

dataTypeOf :: Decl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Decl l) Source 

Methods

compare :: Decl l -> Decl l -> Ordering

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

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

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

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

max :: Decl l -> Decl l -> Decl l

min :: Decl l -> Decl l -> Decl l

Show l => Show (Decl l) Source 

Methods

showsPrec :: Int -> Decl l -> ShowS

show :: Decl l -> String

showList :: [Decl l] -> ShowS

Generic (Decl l) Source 

Associated Types

type Rep (Decl l) :: * -> *

Methods

from :: Decl l -> Rep (Decl l) x

to :: Rep (Decl l) x -> Decl l

SrcInfo pos => Pretty (Decl pos) Source 

Methods

pretty :: Decl pos -> Doc

prettyPrec :: Int -> Decl pos -> Doc

type Rep (Decl l) Source 

data DeclHead l Source

The head of a type or class declaration, which consists of the type or class name applied to some type variables

class C a b is represented as

DHApp
   ()
   (DHApp
      () (DHead () (Ident () "C")) (UnkindedVar () (Ident () "a")))
   (UnkindedVar () (Ident () "b"))

(where the annotation type l is instantiated with ())

class (a :< b) c is represented as

DHApp
   ()
   (DHParen
      ()
      (DHApp
         ()
         (DHInfix () (UnkindedVar () (Ident () "a")) (Symbol () ":<"))
         (UnkindedVar () (Ident () "b"))))
   (UnkindedVar () (Ident () "c"))

Constructors

DHead l (Name l)

type or class name

DHInfix l (TyVarBind l) (Name l)

infix application of the type/class name to the left operand

DHParen l (DeclHead l)

parenthesized declaration head

DHApp l (DeclHead l) (TyVarBind l)

application to one more type variable

Instances

Functor DeclHead Source 

Methods

fmap :: (a -> b) -> DeclHead a -> DeclHead b

(<$) :: a -> DeclHead b -> DeclHead a

Foldable DeclHead Source 

Methods

fold :: Monoid m => DeclHead m -> m

foldMap :: Monoid m => (a -> m) -> DeclHead a -> m

foldr :: (a -> b -> b) -> b -> DeclHead a -> b

foldr' :: (a -> b -> b) -> b -> DeclHead a -> b

foldl :: (b -> a -> b) -> b -> DeclHead a -> b

foldl' :: (b -> a -> b) -> b -> DeclHead a -> b

foldr1 :: (a -> a -> a) -> DeclHead a -> a

foldl1 :: (a -> a -> a) -> DeclHead a -> a

toList :: DeclHead a -> [a]

null :: DeclHead a -> Bool

length :: DeclHead a -> Int

elem :: Eq a => a -> DeclHead a -> Bool

maximum :: Ord a => DeclHead a -> a

minimum :: Ord a => DeclHead a -> a

sum :: Num a => DeclHead a -> a

product :: Num a => DeclHead a -> a

Traversable DeclHead Source 

Methods

traverse :: Applicative f => (a -> f b) -> DeclHead a -> f (DeclHead b)

sequenceA :: Applicative f => DeclHead (f a) -> f (DeclHead a)

mapM :: Monad m => (a -> m b) -> DeclHead a -> m (DeclHead b)

sequence :: Monad m => DeclHead (m a) -> m (DeclHead a)

Annotated DeclHead Source 

Methods

ann :: DeclHead l -> l Source

amap :: (l -> l) -> DeclHead l -> DeclHead l Source

ExactP DeclHead Source 

Methods

exactP :: DeclHead SrcSpanInfo -> EP ()

Eq l => Eq (DeclHead l) Source 

Methods

(==) :: DeclHead l -> DeclHead l -> Bool

(/=) :: DeclHead l -> DeclHead l -> Bool

Data l => Data (DeclHead l) Source 

Methods

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

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

toConstr :: DeclHead l -> Constr

dataTypeOf :: DeclHead l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> DeclHead l -> DeclHead l

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

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

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

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

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

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

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

Ord l => Ord (DeclHead l) Source 

Methods

compare :: DeclHead l -> DeclHead l -> Ordering

(<) :: DeclHead l -> DeclHead l -> Bool

(<=) :: DeclHead l -> DeclHead l -> Bool

(>) :: DeclHead l -> DeclHead l -> Bool

(>=) :: DeclHead l -> DeclHead l -> Bool

max :: DeclHead l -> DeclHead l -> DeclHead l

min :: DeclHead l -> DeclHead l -> DeclHead l

Show l => Show (DeclHead l) Source 

Methods

showsPrec :: Int -> DeclHead l -> ShowS

show :: DeclHead l -> String

showList :: [DeclHead l] -> ShowS

Generic (DeclHead l) Source 

Associated Types

type Rep (DeclHead l) :: * -> *

Methods

from :: DeclHead l -> Rep (DeclHead l) x

to :: Rep (DeclHead l) x -> DeclHead l

Pretty (DeclHead l) Source 

Methods

pretty :: DeclHead l -> Doc

prettyPrec :: Int -> DeclHead l -> Doc

type Rep (DeclHead l) Source 

data InstRule l Source

The instance declaration rule, which is, roughly, the part of the instance declaration before the where keyword.

Example: instance Ord a => Ord (Maybe a) is represented as

IRule
   ()
   Nothing
   (Just
      (CxSingle
         ()
         (ClassA
            () (UnQual () (Ident () "Ord")) [ TyVar () (Ident () "a") ])))
   (IHApp
      ()
      (IHCon () (UnQual () (Ident () "Ord")))
      (TyParen
         ()
         (TyApp
            ()
            (TyCon () (UnQual () (Ident () "Maybe")))
            (TyVar () (Ident () "a")))))

An optional explicit forall after instance is supported: instance forall a . Ord a => Ord (Maybe a) where becomes

IRule
   ()
   (Just [ UnkindedVar () (Ident () "a") ])
   ...

Constructors

IRule l (Maybe [TyVarBind l]) (Maybe (Context l)) (InstHead l) 
IParen l (InstRule l) 

Instances

Functor InstRule Source 

Methods

fmap :: (a -> b) -> InstRule a -> InstRule b

(<$) :: a -> InstRule b -> InstRule a

Foldable InstRule Source 

Methods

fold :: Monoid m => InstRule m -> m

foldMap :: Monoid m => (a -> m) -> InstRule a -> m

foldr :: (a -> b -> b) -> b -> InstRule a -> b

foldr' :: (a -> b -> b) -> b -> InstRule a -> b

foldl :: (b -> a -> b) -> b -> InstRule a -> b

foldl' :: (b -> a -> b) -> b -> InstRule a -> b

foldr1 :: (a -> a -> a) -> InstRule a -> a

foldl1 :: (a -> a -> a) -> InstRule a -> a

toList :: InstRule a -> [a]

null :: InstRule a -> Bool

length :: InstRule a -> Int

elem :: Eq a => a -> InstRule a -> Bool

maximum :: Ord a => InstRule a -> a

minimum :: Ord a => InstRule a -> a

sum :: Num a => InstRule a -> a

product :: Num a => InstRule a -> a

Traversable InstRule Source 

Methods

traverse :: Applicative f => (a -> f b) -> InstRule a -> f (InstRule b)

sequenceA :: Applicative f => InstRule (f a) -> f (InstRule a)

mapM :: Monad m => (a -> m b) -> InstRule a -> m (InstRule b)

sequence :: Monad m => InstRule (m a) -> m (InstRule a)

Annotated InstRule Source 

Methods

ann :: InstRule l -> l Source

amap :: (l -> l) -> InstRule l -> InstRule l Source

ExactP InstRule Source 

Methods

exactP :: InstRule SrcSpanInfo -> EP ()

Eq l => Eq (InstRule l) Source 

Methods

(==) :: InstRule l -> InstRule l -> Bool

(/=) :: InstRule l -> InstRule l -> Bool

Data l => Data (InstRule l) Source 

Methods

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

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

toConstr :: InstRule l -> Constr

dataTypeOf :: InstRule l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> InstRule l -> InstRule l

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

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

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

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

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

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

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

Ord l => Ord (InstRule l) Source 

Methods

compare :: InstRule l -> InstRule l -> Ordering

(<) :: InstRule l -> InstRule l -> Bool

(<=) :: InstRule l -> InstRule l -> Bool

(>) :: InstRule l -> InstRule l -> Bool

(>=) :: InstRule l -> InstRule l -> Bool

max :: InstRule l -> InstRule l -> InstRule l

min :: InstRule l -> InstRule l -> InstRule l

Show l => Show (InstRule l) Source 

Methods

showsPrec :: Int -> InstRule l -> ShowS

show :: InstRule l -> String

showList :: [InstRule l] -> ShowS

Generic (InstRule l) Source 

Associated Types

type Rep (InstRule l) :: * -> *

Methods

from :: InstRule l -> Rep (InstRule l) x

to :: Rep (InstRule l) x -> InstRule l

SrcInfo l => Pretty (InstRule l) Source 

Methods

pretty :: InstRule l -> Doc

prettyPrec :: Int -> InstRule l -> Doc

type Rep (InstRule l) Source 

data InstHead l Source

The instance head. The split between rule/head allow us to represent instance (Bounded a => Bounded [a]) where faithfully.

The structure of InstHead follows one of DeclHead.

For example, instance C (Maybe a) Int where is represented as

IHApp
   ()
   (IHApp
      ()
      (IHCon () (UnQual () (Ident () "C")))
      (TyParen
         ()
         (TyApp
            ()
            (TyCon () (UnQual () (Ident () "Maybe")))
            (TyVar () (Ident () "a")))))
   (TyCon () (UnQual () (Ident () "Int")))))

Constructors

IHCon l (QName l)

type or class name

IHInfix l (Type l) (QName l)

infix application of the type/class name to the left operand

IHParen l (InstHead l)

parenthesized instance head

IHApp l (InstHead l) (Type l)

application to one more type

Instances

Functor InstHead Source 

Methods

fmap :: (a -> b) -> InstHead a -> InstHead b

(<$) :: a -> InstHead b -> InstHead a

Foldable InstHead Source 

Methods

fold :: Monoid m => InstHead m -> m

foldMap :: Monoid m => (a -> m) -> InstHead a -> m

foldr :: (a -> b -> b) -> b -> InstHead a -> b

foldr' :: (a -> b -> b) -> b -> InstHead a -> b

foldl :: (b -> a -> b) -> b -> InstHead a -> b

foldl' :: (b -> a -> b) -> b -> InstHead a -> b

foldr1 :: (a -> a -> a) -> InstHead a -> a

foldl1 :: (a -> a -> a) -> InstHead a -> a

toList :: InstHead a -> [a]

null :: InstHead a -> Bool

length :: InstHead a -> Int

elem :: Eq a => a -> InstHead a -> Bool

maximum :: Ord a => InstHead a -> a

minimum :: Ord a => InstHead a -> a

sum :: Num a => InstHead a -> a

product :: Num a => InstHead a -> a

Traversable InstHead Source 

Methods

traverse :: Applicative f => (a -> f b) -> InstHead a -> f (InstHead b)

sequenceA :: Applicative f => InstHead (f a) -> f (InstHead a)

mapM :: Monad m => (a -> m b) -> InstHead a -> m (InstHead b)

sequence :: Monad m => InstHead (m a) -> m (InstHead a)

Annotated InstHead Source 

Methods

ann :: InstHead l -> l Source

amap :: (l -> l) -> InstHead l -> InstHead l Source

ExactP InstHead Source 

Methods

exactP :: InstHead SrcSpanInfo -> EP ()

Eq l => Eq (InstHead l) Source 

Methods

(==) :: InstHead l -> InstHead l -> Bool

(/=) :: InstHead l -> InstHead l -> Bool

Data l => Data (InstHead l) Source 

Methods

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

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

toConstr :: InstHead l -> Constr

dataTypeOf :: InstHead l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> InstHead l -> InstHead l

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

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

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

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

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

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

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

Ord l => Ord (InstHead l) Source 

Methods

compare :: InstHead l -> InstHead l -> Ordering

(<) :: InstHead l -> InstHead l -> Bool

(<=) :: InstHead l -> InstHead l -> Bool

(>) :: InstHead l -> InstHead l -> Bool

(>=) :: InstHead l -> InstHead l -> Bool

max :: InstHead l -> InstHead l -> InstHead l

min :: InstHead l -> InstHead l -> InstHead l

Show l => Show (InstHead l) Source 

Methods

showsPrec :: Int -> InstHead l -> ShowS

show :: InstHead l -> String

showList :: [InstHead l] -> ShowS

Generic (InstHead l) Source 

Associated Types

type Rep (InstHead l) :: * -> *

Methods

from :: InstHead l -> Rep (InstHead l) x

to :: Rep (InstHead l) x -> InstHead l

SrcInfo l => Pretty (InstHead l) Source 

Methods

pretty :: InstHead l -> Doc

prettyPrec :: Int -> InstHead l -> Doc

type Rep (InstHead l) Source 

data Binds l Source

A binding group inside a let or where clause.

Constructors

BDecls l [Decl l]

An ordinary binding group

IPBinds l [IPBind l]

A binding group for implicit parameters

Instances

Functor Binds Source 

Methods

fmap :: (a -> b) -> Binds a -> Binds b

(<$) :: a -> Binds b -> Binds a

Foldable Binds Source 

Methods

fold :: Monoid m => Binds m -> m

foldMap :: Monoid m => (a -> m) -> Binds a -> m

foldr :: (a -> b -> b) -> b -> Binds a -> b

foldr' :: (a -> b -> b) -> b -> Binds a -> b

foldl :: (b -> a -> b) -> b -> Binds a -> b

foldl' :: (b -> a -> b) -> b -> Binds a -> b

foldr1 :: (a -> a -> a) -> Binds a -> a

foldl1 :: (a -> a -> a) -> Binds a -> a

toList :: Binds a -> [a]

null :: Binds a -> Bool

length :: Binds a -> Int

elem :: Eq a => a -> Binds a -> Bool

maximum :: Ord a => Binds a -> a

minimum :: Ord a => Binds a -> a

sum :: Num a => Binds a -> a

product :: Num a => Binds a -> a

Traversable Binds Source 

Methods

traverse :: Applicative f => (a -> f b) -> Binds a -> f (Binds b)

sequenceA :: Applicative f => Binds (f a) -> f (Binds a)

mapM :: Monad m => (a -> m b) -> Binds a -> m (Binds b)

sequence :: Monad m => Binds (m a) -> m (Binds a)

Annotated Binds Source 

Methods

ann :: Binds l -> l Source

amap :: (l -> l) -> Binds l -> Binds l Source

ExactP Binds Source 

Methods

exactP :: Binds SrcSpanInfo -> EP ()

AppFixity Binds Source 
Eq l => Eq (Binds l) Source 

Methods

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

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

Data l => Data (Binds l) Source 

Methods

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

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

toConstr :: Binds l -> Constr

dataTypeOf :: Binds l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Binds l) Source 

Methods

compare :: Binds l -> Binds l -> Ordering

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

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

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

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

max :: Binds l -> Binds l -> Binds l

min :: Binds l -> Binds l -> Binds l

Show l => Show (Binds l) Source 

Methods

showsPrec :: Int -> Binds l -> ShowS

show :: Binds l -> String

showList :: [Binds l] -> ShowS

Generic (Binds l) Source 

Associated Types

type Rep (Binds l) :: * -> *

Methods

from :: Binds l -> Rep (Binds l) x

to :: Rep (Binds l) x -> Binds l

type Rep (Binds l) Source 

data IPBind l Source

A binding of an implicit parameter.

Constructors

IPBind l (IPName l) (Exp l) 

Instances

Functor IPBind Source 

Methods

fmap :: (a -> b) -> IPBind a -> IPBind b

(<$) :: a -> IPBind b -> IPBind a

Foldable IPBind Source 

Methods

fold :: Monoid m => IPBind m -> m

foldMap :: Monoid m => (a -> m) -> IPBind a -> m

foldr :: (a -> b -> b) -> b -> IPBind a -> b

foldr' :: (a -> b -> b) -> b -> IPBind a -> b

foldl :: (b -> a -> b) -> b -> IPBind a -> b

foldl' :: (b -> a -> b) -> b -> IPBind a -> b

foldr1 :: (a -> a -> a) -> IPBind a -> a

foldl1 :: (a -> a -> a) -> IPBind a -> a

toList :: IPBind a -> [a]

null :: IPBind a -> Bool

length :: IPBind a -> Int

elem :: Eq a => a -> IPBind a -> Bool

maximum :: Ord a => IPBind a -> a

minimum :: Ord a => IPBind a -> a

sum :: Num a => IPBind a -> a

product :: Num a => IPBind a -> a

Traversable IPBind Source 

Methods

traverse :: Applicative f => (a -> f b) -> IPBind a -> f (IPBind b)

sequenceA :: Applicative f => IPBind (f a) -> f (IPBind a)

mapM :: Monad m => (a -> m b) -> IPBind a -> m (IPBind b)

sequence :: Monad m => IPBind (m a) -> m (IPBind a)

Annotated IPBind Source 

Methods

ann :: IPBind l -> l Source

amap :: (l -> l) -> IPBind l -> IPBind l Source

ExactP IPBind Source 

Methods

exactP :: IPBind SrcSpanInfo -> EP ()

AppFixity IPBind Source 
Eq l => Eq (IPBind l) Source 

Methods

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

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

Data l => Data (IPBind l) Source 

Methods

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

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

toConstr :: IPBind l -> Constr

dataTypeOf :: IPBind l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (IPBind l) Source 

Methods

compare :: IPBind l -> IPBind l -> Ordering

(<) :: IPBind l -> IPBind l -> Bool

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

(>) :: IPBind l -> IPBind l -> Bool

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

max :: IPBind l -> IPBind l -> IPBind l

min :: IPBind l -> IPBind l -> IPBind l

Show l => Show (IPBind l) Source 

Methods

showsPrec :: Int -> IPBind l -> ShowS

show :: IPBind l -> String

showList :: [IPBind l] -> ShowS

Generic (IPBind l) Source 

Associated Types

type Rep (IPBind l) :: * -> *

Methods

from :: IPBind l -> Rep (IPBind l) x

to :: Rep (IPBind l) x -> IPBind l

SrcInfo loc => Pretty (IPBind loc) Source 

Methods

pretty :: IPBind loc -> Doc

prettyPrec :: Int -> IPBind loc -> Doc

type Rep (IPBind l) Source 

data PatternSynDirection l Source

Constructors

Unidirectional

A unidirectional pattern synonym with "<-"

ImplicitBidirectional

A bidirectional pattern synonym with "="

ExplicitBidirectional l [Decl l]

A birectional pattern synonym with the construction specified.

Instances

Functor PatternSynDirection Source 
Foldable PatternSynDirection Source 

Methods

fold :: Monoid m => PatternSynDirection m -> m

foldMap :: Monoid m => (a -> m) -> PatternSynDirection a -> m

foldr :: (a -> b -> b) -> b -> PatternSynDirection a -> b

foldr' :: (a -> b -> b) -> b -> PatternSynDirection a -> b

foldl :: (b -> a -> b) -> b -> PatternSynDirection a -> b

foldl' :: (b -> a -> b) -> b -> PatternSynDirection a -> b

foldr1 :: (a -> a -> a) -> PatternSynDirection a -> a

foldl1 :: (a -> a -> a) -> PatternSynDirection a -> a

toList :: PatternSynDirection a -> [a]

null :: PatternSynDirection a -> Bool

length :: PatternSynDirection a -> Int

elem :: Eq a => a -> PatternSynDirection a -> Bool

maximum :: Ord a => PatternSynDirection a -> a

minimum :: Ord a => PatternSynDirection a -> a

sum :: Num a => PatternSynDirection a -> a

product :: Num a => PatternSynDirection a -> a

Traversable PatternSynDirection Source 
Eq l => Eq (PatternSynDirection l) Source 
Data l => Data (PatternSynDirection l) Source 

Methods

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

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

toConstr :: PatternSynDirection l -> Constr

dataTypeOf :: PatternSynDirection l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (PatternSynDirection l) Source 
Show l => Show (PatternSynDirection l) Source 
Generic (PatternSynDirection l) Source 

Associated Types

type Rep (PatternSynDirection l) :: * -> *

type Rep (PatternSynDirection l) Source 

Type classes and instances

data ClassDecl l Source

Declarations inside a class declaration.

Constructors

ClsDecl l (Decl l)

ordinary declaration

ClsDataFam l (Maybe (Context l)) (DeclHead l) (Maybe (Kind l))

declaration of an associated data type

ClsTyFam l (DeclHead l) (Maybe (Kind l))

declaration of an associated type synonym

ClsTyDef l (Type l) (Type l)

default choice for an associated type synonym

ClsDefSig l (Name l) (Type l)

default signature

Instances

Functor ClassDecl Source 

Methods

fmap :: (a -> b) -> ClassDecl a -> ClassDecl b

(<$) :: a -> ClassDecl b -> ClassDecl a

Foldable ClassDecl Source 

Methods

fold :: Monoid m => ClassDecl m -> m

foldMap :: Monoid m => (a -> m) -> ClassDecl a -> m

foldr :: (a -> b -> b) -> b -> ClassDecl a -> b

foldr' :: (a -> b -> b) -> b -> ClassDecl a -> b

foldl :: (b -> a -> b) -> b -> ClassDecl a -> b

foldl' :: (b -> a -> b) -> b -> ClassDecl a -> b

foldr1 :: (a -> a -> a) -> ClassDecl a -> a

foldl1 :: (a -> a -> a) -> ClassDecl a -> a

toList :: ClassDecl a -> [a]

null :: ClassDecl a -> Bool

length :: ClassDecl a -> Int

elem :: Eq a => a -> ClassDecl a -> Bool

maximum :: Ord a => ClassDecl a -> a

minimum :: Ord a => ClassDecl a -> a

sum :: Num a => ClassDecl a -> a

product :: Num a => ClassDecl a -> a

Traversable ClassDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> ClassDecl a -> f (ClassDecl b)

sequenceA :: Applicative f => ClassDecl (f a) -> f (ClassDecl a)

mapM :: Monad m => (a -> m b) -> ClassDecl a -> m (ClassDecl b)

sequence :: Monad m => ClassDecl (m a) -> m (ClassDecl a)

Annotated ClassDecl Source 

Methods

ann :: ClassDecl l -> l Source

amap :: (l -> l) -> ClassDecl l -> ClassDecl l Source

ExactP ClassDecl Source 

Methods

exactP :: ClassDecl SrcSpanInfo -> EP ()

AppFixity ClassDecl Source 
Eq l => Eq (ClassDecl l) Source 

Methods

(==) :: ClassDecl l -> ClassDecl l -> Bool

(/=) :: ClassDecl l -> ClassDecl l -> Bool

Data l => Data (ClassDecl l) Source 

Methods

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

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

toConstr :: ClassDecl l -> Constr

dataTypeOf :: ClassDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ClassDecl l) Source 
Show l => Show (ClassDecl l) Source 
Generic (ClassDecl l) Source 

Associated Types

type Rep (ClassDecl l) :: * -> *

Methods

from :: ClassDecl l -> Rep (ClassDecl l) x

to :: Rep (ClassDecl l) x -> ClassDecl l

SrcInfo loc => Pretty (ClassDecl loc) Source 

Methods

pretty :: ClassDecl loc -> Doc

prettyPrec :: Int -> ClassDecl loc -> Doc

type Rep (ClassDecl l) Source 

data InstDecl l Source

Declarations inside an instance declaration.

Constructors

InsDecl l (Decl l)

ordinary declaration

InsType l (Type l) (Type l)

an associated type definition

InsData l (DataOrNew l) (Type l) [QualConDecl l] (Maybe (Deriving l))

an associated data type implementation

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

an associated data type implemented using GADT style

Instances

Functor InstDecl Source 

Methods

fmap :: (a -> b) -> InstDecl a -> InstDecl b

(<$) :: a -> InstDecl b -> InstDecl a

Foldable InstDecl Source 

Methods

fold :: Monoid m => InstDecl m -> m

foldMap :: Monoid m => (a -> m) -> InstDecl a -> m

foldr :: (a -> b -> b) -> b -> InstDecl a -> b

foldr' :: (a -> b -> b) -> b -> InstDecl a -> b

foldl :: (b -> a -> b) -> b -> InstDecl a -> b

foldl' :: (b -> a -> b) -> b -> InstDecl a -> b

foldr1 :: (a -> a -> a) -> InstDecl a -> a

foldl1 :: (a -> a -> a) -> InstDecl a -> a

toList :: InstDecl a -> [a]

null :: InstDecl a -> Bool

length :: InstDecl a -> Int

elem :: Eq a => a -> InstDecl a -> Bool

maximum :: Ord a => InstDecl a -> a

minimum :: Ord a => InstDecl a -> a

sum :: Num a => InstDecl a -> a

product :: Num a => InstDecl a -> a

Traversable InstDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> InstDecl a -> f (InstDecl b)

sequenceA :: Applicative f => InstDecl (f a) -> f (InstDecl a)

mapM :: Monad m => (a -> m b) -> InstDecl a -> m (InstDecl b)

sequence :: Monad m => InstDecl (m a) -> m (InstDecl a)

Annotated InstDecl Source 

Methods

ann :: InstDecl l -> l Source

amap :: (l -> l) -> InstDecl l -> InstDecl l Source

ExactP InstDecl Source 

Methods

exactP :: InstDecl SrcSpanInfo -> EP ()

AppFixity InstDecl Source 
Eq l => Eq (InstDecl l) Source 

Methods

(==) :: InstDecl l -> InstDecl l -> Bool

(/=) :: InstDecl l -> InstDecl l -> Bool

Data l => Data (InstDecl l) Source 

Methods

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

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

toConstr :: InstDecl l -> Constr

dataTypeOf :: InstDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (InstDecl l) Source 

Methods

compare :: InstDecl l -> InstDecl l -> Ordering

(<) :: InstDecl l -> InstDecl l -> Bool

(<=) :: InstDecl l -> InstDecl l -> Bool

(>) :: InstDecl l -> InstDecl l -> Bool

(>=) :: InstDecl l -> InstDecl l -> Bool

max :: InstDecl l -> InstDecl l -> InstDecl l

min :: InstDecl l -> InstDecl l -> InstDecl l

Show l => Show (InstDecl l) Source 

Methods

showsPrec :: Int -> InstDecl l -> ShowS

show :: InstDecl l -> String

showList :: [InstDecl l] -> ShowS

Generic (InstDecl l) Source 

Associated Types

type Rep (InstDecl l) :: * -> *

Methods

from :: InstDecl l -> Rep (InstDecl l) x

to :: Rep (InstDecl l) x -> InstDecl l

SrcInfo loc => Pretty (InstDecl loc) Source 

Methods

pretty :: InstDecl loc -> Doc

prettyPrec :: Int -> InstDecl loc -> Doc

type Rep (InstDecl l) Source 

data Deriving l Source

A deriving clause following a data type declaration.

Constructors

Deriving l [InstRule l] 

Instances

Functor Deriving Source 

Methods

fmap :: (a -> b) -> Deriving a -> Deriving b

(<$) :: a -> Deriving b -> Deriving a

Foldable Deriving Source 

Methods

fold :: Monoid m => Deriving m -> m

foldMap :: Monoid m => (a -> m) -> Deriving a -> m

foldr :: (a -> b -> b) -> b -> Deriving a -> b

foldr' :: (a -> b -> b) -> b -> Deriving a -> b

foldl :: (b -> a -> b) -> b -> Deriving a -> b

foldl' :: (b -> a -> b) -> b -> Deriving a -> b

foldr1 :: (a -> a -> a) -> Deriving a -> a

foldl1 :: (a -> a -> a) -> Deriving a -> a

toList :: Deriving a -> [a]

null :: Deriving a -> Bool

length :: Deriving a -> Int

elem :: Eq a => a -> Deriving a -> Bool

maximum :: Ord a => Deriving a -> a

minimum :: Ord a => Deriving a -> a

sum :: Num a => Deriving a -> a

product :: Num a => Deriving a -> a

Traversable Deriving Source 

Methods

traverse :: Applicative f => (a -> f b) -> Deriving a -> f (Deriving b)

sequenceA :: Applicative f => Deriving (f a) -> f (Deriving a)

mapM :: Monad m => (a -> m b) -> Deriving a -> m (Deriving b)

sequence :: Monad m => Deriving (m a) -> m (Deriving a)

Annotated Deriving Source 

Methods

ann :: Deriving l -> l Source

amap :: (l -> l) -> Deriving l -> Deriving l Source

ExactP Deriving Source 

Methods

exactP :: Deriving SrcSpanInfo -> EP ()

Eq l => Eq (Deriving l) Source 

Methods

(==) :: Deriving l -> Deriving l -> Bool

(/=) :: Deriving l -> Deriving l -> Bool

Data l => Data (Deriving l) Source 

Methods

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

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

toConstr :: Deriving l -> Constr

dataTypeOf :: Deriving l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> Deriving l -> Deriving l

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

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

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

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

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

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

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

Ord l => Ord (Deriving l) Source 

Methods

compare :: Deriving l -> Deriving l -> Ordering

(<) :: Deriving l -> Deriving l -> Bool

(<=) :: Deriving l -> Deriving l -> Bool

(>) :: Deriving l -> Deriving l -> Bool

(>=) :: Deriving l -> Deriving l -> Bool

max :: Deriving l -> Deriving l -> Deriving l

min :: Deriving l -> Deriving l -> Deriving l

Show l => Show (Deriving l) Source 

Methods

showsPrec :: Int -> Deriving l -> ShowS

show :: Deriving l -> String

showList :: [Deriving l] -> ShowS

Generic (Deriving l) Source 

Associated Types

type Rep (Deriving l) :: * -> *

Methods

from :: Deriving l -> Rep (Deriving l) x

to :: Rep (Deriving l) x -> Deriving l

SrcInfo l => Pretty (Deriving l) Source 

Methods

pretty :: Deriving l -> Doc

prettyPrec :: Int -> Deriving l -> Doc

type Rep (Deriving l) Source 

Data type declarations

data DataOrNew l Source

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

Constructors

DataType l 
NewType l 

Instances

Functor DataOrNew Source 

Methods

fmap :: (a -> b) -> DataOrNew a -> DataOrNew b

(<$) :: a -> DataOrNew b -> DataOrNew a

Foldable DataOrNew Source 

Methods

fold :: Monoid m => DataOrNew m -> m

foldMap :: Monoid m => (a -> m) -> DataOrNew a -> m

foldr :: (a -> b -> b) -> b -> DataOrNew a -> b

foldr' :: (a -> b -> b) -> b -> DataOrNew a -> b

foldl :: (b -> a -> b) -> b -> DataOrNew a -> b

foldl' :: (b -> a -> b) -> b -> DataOrNew a -> b

foldr1 :: (a -> a -> a) -> DataOrNew a -> a

foldl1 :: (a -> a -> a) -> DataOrNew a -> a

toList :: DataOrNew a -> [a]

null :: DataOrNew a -> Bool

length :: DataOrNew a -> Int

elem :: Eq a => a -> DataOrNew a -> Bool

maximum :: Ord a => DataOrNew a -> a

minimum :: Ord a => DataOrNew a -> a

sum :: Num a => DataOrNew a -> a

product :: Num a => DataOrNew a -> a

Traversable DataOrNew Source 

Methods

traverse :: Applicative f => (a -> f b) -> DataOrNew a -> f (DataOrNew b)

sequenceA :: Applicative f => DataOrNew (f a) -> f (DataOrNew a)

mapM :: Monad m => (a -> m b) -> DataOrNew a -> m (DataOrNew b)

sequence :: Monad m => DataOrNew (m a) -> m (DataOrNew a)

Annotated DataOrNew Source 

Methods

ann :: DataOrNew l -> l Source

amap :: (l -> l) -> DataOrNew l -> DataOrNew l Source

ExactP DataOrNew Source 

Methods

exactP :: DataOrNew SrcSpanInfo -> EP ()

Eq l => Eq (DataOrNew l) Source 

Methods

(==) :: DataOrNew l -> DataOrNew l -> Bool

(/=) :: DataOrNew l -> DataOrNew l -> Bool

Data l => Data (DataOrNew l) Source 

Methods

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

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

toConstr :: DataOrNew l -> Constr

dataTypeOf :: DataOrNew l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (DataOrNew l) Source 
Show l => Show (DataOrNew l) Source 
Generic (DataOrNew l) Source 

Associated Types

type Rep (DataOrNew l) :: * -> *

Methods

from :: DataOrNew l -> Rep (DataOrNew l) x

to :: Rep (DataOrNew l) x -> DataOrNew l

Pretty (DataOrNew l) Source 

Methods

pretty :: DataOrNew l -> Doc

prettyPrec :: Int -> DataOrNew l -> Doc

type Rep (DataOrNew l) Source 

data ConDecl l Source

Declaration of an ordinary data constructor.

Constructors

ConDecl l (Name l) [Type l]

ordinary data constructor

InfixConDecl l (Type l) (Name l) (Type l)

infix data constructor

RecDecl l (Name l) [FieldDecl l]

record constructor

Instances

Functor ConDecl Source 

Methods

fmap :: (a -> b) -> ConDecl a -> ConDecl b

(<$) :: a -> ConDecl b -> ConDecl a

Foldable ConDecl Source 

Methods

fold :: Monoid m => ConDecl m -> m

foldMap :: Monoid m => (a -> m) -> ConDecl a -> m

foldr :: (a -> b -> b) -> b -> ConDecl a -> b

foldr' :: (a -> b -> b) -> b -> ConDecl a -> b

foldl :: (b -> a -> b) -> b -> ConDecl a -> b

foldl' :: (b -> a -> b) -> b -> ConDecl a -> b

foldr1 :: (a -> a -> a) -> ConDecl a -> a

foldl1 :: (a -> a -> a) -> ConDecl a -> a

toList :: ConDecl a -> [a]

null :: ConDecl a -> Bool

length :: ConDecl a -> Int

elem :: Eq a => a -> ConDecl a -> Bool

maximum :: Ord a => ConDecl a -> a

minimum :: Ord a => ConDecl a -> a

sum :: Num a => ConDecl a -> a

product :: Num a => ConDecl a -> a

Traversable ConDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> ConDecl a -> f (ConDecl b)

sequenceA :: Applicative f => ConDecl (f a) -> f (ConDecl a)

mapM :: Monad m => (a -> m b) -> ConDecl a -> m (ConDecl b)

sequence :: Monad m => ConDecl (m a) -> m (ConDecl a)

Annotated ConDecl Source 

Methods

ann :: ConDecl l -> l Source

amap :: (l -> l) -> ConDecl l -> ConDecl l Source

ExactP ConDecl Source 

Methods

exactP :: ConDecl SrcSpanInfo -> EP ()

Eq l => Eq (ConDecl l) Source 

Methods

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

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

Data l => Data (ConDecl l) Source 

Methods

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

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

toConstr :: ConDecl l -> Constr

dataTypeOf :: ConDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ConDecl l) Source 

Methods

compare :: ConDecl l -> ConDecl l -> Ordering

(<) :: ConDecl l -> ConDecl l -> Bool

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

(>) :: ConDecl l -> ConDecl l -> Bool

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

max :: ConDecl l -> ConDecl l -> ConDecl l

min :: ConDecl l -> ConDecl l -> ConDecl l

Show l => Show (ConDecl l) Source 

Methods

showsPrec :: Int -> ConDecl l -> ShowS

show :: ConDecl l -> String

showList :: [ConDecl l] -> ShowS

Generic (ConDecl l) Source 

Associated Types

type Rep (ConDecl l) :: * -> *

Methods

from :: ConDecl l -> Rep (ConDecl l) x

to :: Rep (ConDecl l) x -> ConDecl l

SrcInfo l => Pretty (ConDecl l) Source 

Methods

pretty :: ConDecl l -> Doc

prettyPrec :: Int -> ConDecl l -> Doc

type Rep (ConDecl l) Source 

data FieldDecl l Source

Declaration of a (list of) named field(s).

Constructors

FieldDecl l [Name l] (Type l) 

Instances

Functor FieldDecl Source 

Methods

fmap :: (a -> b) -> FieldDecl a -> FieldDecl b

(<$) :: a -> FieldDecl b -> FieldDecl a

Foldable FieldDecl Source 

Methods

fold :: Monoid m => FieldDecl m -> m

foldMap :: Monoid m => (a -> m) -> FieldDecl a -> m

foldr :: (a -> b -> b) -> b -> FieldDecl a -> b

foldr' :: (a -> b -> b) -> b -> FieldDecl a -> b

foldl :: (b -> a -> b) -> b -> FieldDecl a -> b

foldl' :: (b -> a -> b) -> b -> FieldDecl a -> b

foldr1 :: (a -> a -> a) -> FieldDecl a -> a

foldl1 :: (a -> a -> a) -> FieldDecl a -> a

toList :: FieldDecl a -> [a]

null :: FieldDecl a -> Bool

length :: FieldDecl a -> Int

elem :: Eq a => a -> FieldDecl a -> Bool

maximum :: Ord a => FieldDecl a -> a

minimum :: Ord a => FieldDecl a -> a

sum :: Num a => FieldDecl a -> a

product :: Num a => FieldDecl a -> a

Traversable FieldDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> FieldDecl a -> f (FieldDecl b)

sequenceA :: Applicative f => FieldDecl (f a) -> f (FieldDecl a)

mapM :: Monad m => (a -> m b) -> FieldDecl a -> m (FieldDecl b)

sequence :: Monad m => FieldDecl (m a) -> m (FieldDecl a)

Annotated FieldDecl Source 

Methods

ann :: FieldDecl l -> l Source

amap :: (l -> l) -> FieldDecl l -> FieldDecl l Source

ExactP FieldDecl Source 

Methods

exactP :: FieldDecl SrcSpanInfo -> EP ()

Eq l => Eq (FieldDecl l) Source 

Methods

(==) :: FieldDecl l -> FieldDecl l -> Bool

(/=) :: FieldDecl l -> FieldDecl l -> Bool

Data l => Data (FieldDecl l) Source 

Methods

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

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

toConstr :: FieldDecl l -> Constr

dataTypeOf :: FieldDecl l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> FieldDecl l -> FieldDecl l

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

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

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

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

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

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

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

Ord l => Ord (FieldDecl l) Source 
Show l => Show (FieldDecl l) Source 
Generic (FieldDecl l) Source 

Associated Types

type Rep (FieldDecl l) :: * -> *

Methods

from :: FieldDecl l -> Rep (FieldDecl l) x

to :: Rep (FieldDecl l) x -> FieldDecl l

SrcInfo l => Pretty (FieldDecl l) Source 

Methods

pretty :: FieldDecl l -> Doc

prettyPrec :: Int -> FieldDecl l -> Doc

type Rep (FieldDecl l) Source 

data QualConDecl l Source

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

Constructors

QualConDecl l (Maybe [TyVarBind l]) (Maybe (Context l)) (ConDecl l) 

Instances

Functor QualConDecl Source 

Methods

fmap :: (a -> b) -> QualConDecl a -> QualConDecl b

(<$) :: a -> QualConDecl b -> QualConDecl a

Foldable QualConDecl Source 

Methods

fold :: Monoid m => QualConDecl m -> m

foldMap :: Monoid m => (a -> m) -> QualConDecl a -> m

foldr :: (a -> b -> b) -> b -> QualConDecl a -> b

foldr' :: (a -> b -> b) -> b -> QualConDecl a -> b

foldl :: (b -> a -> b) -> b -> QualConDecl a -> b

foldl' :: (b -> a -> b) -> b -> QualConDecl a -> b

foldr1 :: (a -> a -> a) -> QualConDecl a -> a

foldl1 :: (a -> a -> a) -> QualConDecl a -> a

toList :: QualConDecl a -> [a]

null :: QualConDecl a -> Bool

length :: QualConDecl a -> Int

elem :: Eq a => a -> QualConDecl a -> Bool

maximum :: Ord a => QualConDecl a -> a

minimum :: Ord a => QualConDecl a -> a

sum :: Num a => QualConDecl a -> a

product :: Num a => QualConDecl a -> a

Traversable QualConDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> QualConDecl a -> f (QualConDecl b)

sequenceA :: Applicative f => QualConDecl (f a) -> f (QualConDecl a)

mapM :: Monad m => (a -> m b) -> QualConDecl a -> m (QualConDecl b)

sequence :: Monad m => QualConDecl (m a) -> m (QualConDecl a)

Annotated QualConDecl Source 

Methods

ann :: QualConDecl l -> l Source

amap :: (l -> l) -> QualConDecl l -> QualConDecl l Source

ExactP QualConDecl Source 

Methods

exactP :: QualConDecl SrcSpanInfo -> EP ()

Eq l => Eq (QualConDecl l) Source 
Data l => Data (QualConDecl l) Source 

Methods

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

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

toConstr :: QualConDecl l -> Constr

dataTypeOf :: QualConDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (QualConDecl l) Source 
Show l => Show (QualConDecl l) Source 
Generic (QualConDecl l) Source 

Associated Types

type Rep (QualConDecl l) :: * -> *

Methods

from :: QualConDecl l -> Rep (QualConDecl l) x

to :: Rep (QualConDecl l) x -> QualConDecl l

SrcInfo l => Pretty (QualConDecl l) Source 

Methods

pretty :: QualConDecl l -> Doc

prettyPrec :: Int -> QualConDecl l -> Doc

type Rep (QualConDecl l) Source 

data GadtDecl l Source

A single constructor declaration in a GADT data type declaration.

If the GADT is declared using the record syntax, e.g.

data Ty where
  TCon :: { field1 :: Int, field2 :: Bool } -> Ty

then the fields are stored as a list of FieldDecls, and the final type (Ty in the above example) is stored in the last Type field.

If the GADT is declared using the ordinary syntax, e.g.

data Ty where
  TCon :: Int -> Bool -> Ty

then Maybe [FieldDecl l] is Nothing, and the whole constructor's type (such as Int -> Bool -> Ty) is stored in the last Type field.

Constructors

GadtDecl l (Name l) (Maybe [FieldDecl l]) (Type l) 

Instances

Functor GadtDecl Source 

Methods

fmap :: (a -> b) -> GadtDecl a -> GadtDecl b

(<$) :: a -> GadtDecl b -> GadtDecl a

Foldable GadtDecl Source 

Methods

fold :: Monoid m => GadtDecl m -> m

foldMap :: Monoid m => (a -> m) -> GadtDecl a -> m

foldr :: (a -> b -> b) -> b -> GadtDecl a -> b

foldr' :: (a -> b -> b) -> b -> GadtDecl a -> b

foldl :: (b -> a -> b) -> b -> GadtDecl a -> b

foldl' :: (b -> a -> b) -> b -> GadtDecl a -> b

foldr1 :: (a -> a -> a) -> GadtDecl a -> a

foldl1 :: (a -> a -> a) -> GadtDecl a -> a

toList :: GadtDecl a -> [a]

null :: GadtDecl a -> Bool

length :: GadtDecl a -> Int

elem :: Eq a => a -> GadtDecl a -> Bool

maximum :: Ord a => GadtDecl a -> a

minimum :: Ord a => GadtDecl a -> a

sum :: Num a => GadtDecl a -> a

product :: Num a => GadtDecl a -> a

Traversable GadtDecl Source 

Methods

traverse :: Applicative f => (a -> f b) -> GadtDecl a -> f (GadtDecl b)

sequenceA :: Applicative f => GadtDecl (f a) -> f (GadtDecl a)

mapM :: Monad m => (a -> m b) -> GadtDecl a -> m (GadtDecl b)

sequence :: Monad m => GadtDecl (m a) -> m (GadtDecl a)

Annotated GadtDecl Source 

Methods

ann :: GadtDecl l -> l Source

amap :: (l -> l) -> GadtDecl l -> GadtDecl l Source

ExactP GadtDecl Source 

Methods

exactP :: GadtDecl SrcSpanInfo -> EP ()

Eq l => Eq (GadtDecl l) Source 

Methods

(==) :: GadtDecl l -> GadtDecl l -> Bool

(/=) :: GadtDecl l -> GadtDecl l -> Bool

Data l => Data (GadtDecl l) Source 

Methods

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

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

toConstr :: GadtDecl l -> Constr

dataTypeOf :: GadtDecl l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (GadtDecl l) Source 

Methods

compare :: GadtDecl l -> GadtDecl l -> Ordering

(<) :: GadtDecl l -> GadtDecl l -> Bool

(<=) :: GadtDecl l -> GadtDecl l -> Bool

(>) :: GadtDecl l -> GadtDecl l -> Bool

(>=) :: GadtDecl l -> GadtDecl l -> Bool

max :: GadtDecl l -> GadtDecl l -> GadtDecl l

min :: GadtDecl l -> GadtDecl l -> GadtDecl l

Show l => Show (GadtDecl l) Source 

Methods

showsPrec :: Int -> GadtDecl l -> ShowS

show :: GadtDecl l -> String

showList :: [GadtDecl l] -> ShowS

Generic (GadtDecl l) Source 

Associated Types

type Rep (GadtDecl l) :: * -> *

Methods

from :: GadtDecl l -> Rep (GadtDecl l) x

to :: Rep (GadtDecl l) x -> GadtDecl l

SrcInfo l => Pretty (GadtDecl l) Source 

Methods

pretty :: GadtDecl l -> Doc

prettyPrec :: Int -> GadtDecl l -> Doc

type Rep (GadtDecl l) Source 

data BangType l Source

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

Constructors

BangedTy l

strict component, marked with "!"

UnpackedTy l

unboxed component, marked with an UNPACK pragma

Instances

Functor BangType Source 

Methods

fmap :: (a -> b) -> BangType a -> BangType b

(<$) :: a -> BangType b -> BangType a

Foldable BangType Source 

Methods

fold :: Monoid m => BangType m -> m

foldMap :: Monoid m => (a -> m) -> BangType a -> m

foldr :: (a -> b -> b) -> b -> BangType a -> b

foldr' :: (a -> b -> b) -> b -> BangType a -> b

foldl :: (b -> a -> b) -> b -> BangType a -> b

foldl' :: (b -> a -> b) -> b -> BangType a -> b

foldr1 :: (a -> a -> a) -> BangType a -> a

foldl1 :: (a -> a -> a) -> BangType a -> a

toList :: BangType a -> [a]

null :: BangType a -> Bool

length :: BangType a -> Int

elem :: Eq a => a -> BangType a -> Bool

maximum :: Ord a => BangType a -> a

minimum :: Ord a => BangType a -> a

sum :: Num a => BangType a -> a

product :: Num a => BangType a -> a

Traversable BangType Source 

Methods

traverse :: Applicative f => (a -> f b) -> BangType a -> f (BangType b)

sequenceA :: Applicative f => BangType (f a) -> f (BangType a)

mapM :: Monad m => (a -> m b) -> BangType a -> m (BangType b)

sequence :: Monad m => BangType (m a) -> m (BangType a)

Annotated BangType Source 

Methods

ann :: BangType l -> l Source

amap :: (l -> l) -> BangType l -> BangType l Source

ExactP BangType Source 

Methods

exactP :: BangType SrcSpanInfo -> EP ()

Eq l => Eq (BangType l) Source 

Methods

(==) :: BangType l -> BangType l -> Bool

(/=) :: BangType l -> BangType l -> Bool

Data l => Data (BangType l) Source 

Methods

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

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

toConstr :: BangType l -> Constr

dataTypeOf :: BangType l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (BangType l) Source 

Methods

compare :: BangType l -> BangType l -> Ordering

(<) :: BangType l -> BangType l -> Bool

(<=) :: BangType l -> BangType l -> Bool

(>) :: BangType l -> BangType l -> Bool

(>=) :: BangType l -> BangType l -> Bool

max :: BangType l -> BangType l -> BangType l

min :: BangType l -> BangType l -> BangType l

Show l => Show (BangType l) Source 

Methods

showsPrec :: Int -> BangType l -> ShowS

show :: BangType l -> String

showList :: [BangType l] -> ShowS

Generic (BangType l) Source 

Associated Types

type Rep (BangType l) :: * -> *

Methods

from :: BangType l -> Rep (BangType l) x

to :: Rep (BangType l) x -> BangType l

SrcInfo l => Pretty (BangType l) Source 

Methods

pretty :: BangType l -> Doc

prettyPrec :: Int -> BangType l -> Doc

type Rep (BangType l) Source 

Function bindings

data Match l Source

Clauses of a function binding.

Constructors

Match l (Name l) [Pat l] (Rhs l) (Maybe (Binds l))

A clause defined with prefix notation, i.e. the function name followed by its argument patterns, the right-hand side and an optional where clause.

InfixMatch l (Pat l) (Name l) [Pat l] (Rhs l) (Maybe (Binds l))

A clause defined with infix notation, i.e. first its first argument pattern, then the function name, then its following argument(s), the right-hand side and an optional where clause. Note that there can be more than two arguments to a function declared infix, hence the list of pattern arguments.

Instances

Functor Match Source 

Methods

fmap :: (a -> b) -> Match a -> Match b

(<$) :: a -> Match b -> Match a

Foldable Match Source 

Methods

fold :: Monoid m => Match m -> m

foldMap :: Monoid m => (a -> m) -> Match a -> m

foldr :: (a -> b -> b) -> b -> Match a -> b

foldr' :: (a -> b -> b) -> b -> Match a -> b

foldl :: (b -> a -> b) -> b -> Match a -> b

foldl' :: (b -> a -> b) -> b -> Match a -> b

foldr1 :: (a -> a -> a) -> Match a -> a

foldl1 :: (a -> a -> a) -> Match a -> a

toList :: Match a -> [a]

null :: Match a -> Bool

length :: Match a -> Int

elem :: Eq a => a -> Match a -> Bool

maximum :: Ord a => Match a -> a

minimum :: Ord a => Match a -> a

sum :: Num a => Match a -> a

product :: Num a => Match a -> a

Traversable Match Source 

Methods

traverse :: Applicative f => (a -> f b) -> Match a -> f (Match b)

sequenceA :: Applicative f => Match (f a) -> f (Match a)

mapM :: Monad m => (a -> m b) -> Match a -> m (Match b)

sequence :: Monad m => Match (m a) -> m (Match a)

Annotated Match Source 

Methods

ann :: Match l -> l Source

amap :: (l -> l) -> Match l -> Match l Source

ExactP Match Source 

Methods

exactP :: Match SrcSpanInfo -> EP ()

AppFixity Match Source 
Eq l => Eq (Match l) Source 

Methods

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

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

Data l => Data (Match l) Source 

Methods

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

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

toConstr :: Match l -> Constr

dataTypeOf :: Match l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Match l) Source 

Methods

compare :: Match l -> Match l -> Ordering

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

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

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

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

max :: Match l -> Match l -> Match l

min :: Match l -> Match l -> Match l

Show l => Show (Match l) Source 

Methods

showsPrec :: Int -> Match l -> ShowS

show :: Match l -> String

showList :: [Match l] -> ShowS

Generic (Match l) Source 

Associated Types

type Rep (Match l) :: * -> *

Methods

from :: Match l -> Rep (Match l) x

to :: Rep (Match l) x -> Match l

SrcInfo pos => Pretty (Match pos) Source 

Methods

pretty :: Match pos -> Doc

prettyPrec :: Int -> Match pos -> Doc

type Rep (Match l) Source 

data Rhs l Source

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

Constructors

UnGuardedRhs l (Exp l)

unguarded right hand side (exp)

GuardedRhss l [GuardedRhs l]

guarded right hand side (gdrhs)

Instances

Functor Rhs Source 

Methods

fmap :: (a -> b) -> Rhs a -> Rhs b

(<$) :: a -> Rhs b -> Rhs a

Foldable Rhs Source 

Methods

fold :: Monoid m => Rhs m -> m

foldMap :: Monoid m => (a -> m) -> Rhs a -> m

foldr :: (a -> b -> b) -> b -> Rhs a -> b

foldr' :: (a -> b -> b) -> b -> Rhs a -> b

foldl :: (b -> a -> b) -> b -> Rhs a -> b

foldl' :: (b -> a -> b) -> b -> Rhs a -> b

foldr1 :: (a -> a -> a) -> Rhs a -> a

foldl1 :: (a -> a -> a) -> Rhs a -> a

toList :: Rhs a -> [a]

null :: Rhs a -> Bool

length :: Rhs a -> Int

elem :: Eq a => a -> Rhs a -> Bool

maximum :: Ord a => Rhs a -> a

minimum :: Ord a => Rhs a -> a

sum :: Num a => Rhs a -> a

product :: Num a => Rhs a -> a

Traversable Rhs Source 

Methods

traverse :: Applicative f => (a -> f b) -> Rhs a -> f (Rhs b)

sequenceA :: Applicative f => Rhs (f a) -> f (Rhs a)

mapM :: Monad m => (a -> m b) -> Rhs a -> m (Rhs b)

sequence :: Monad m => Rhs (m a) -> m (Rhs a)

Annotated Rhs Source 

Methods

ann :: Rhs l -> l Source

amap :: (l -> l) -> Rhs l -> Rhs l Source

ExactP Rhs Source 

Methods

exactP :: Rhs SrcSpanInfo -> EP ()

AppFixity Rhs Source 
Eq l => Eq (Rhs l) Source 

Methods

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

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

Data l => Data (Rhs l) Source 

Methods

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

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

toConstr :: Rhs l -> Constr

dataTypeOf :: Rhs l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Rhs l) Source 

Methods

compare :: Rhs l -> Rhs l -> Ordering

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

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

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

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

max :: Rhs l -> Rhs l -> Rhs l

min :: Rhs l -> Rhs l -> Rhs l

Show l => Show (Rhs l) Source 

Methods

showsPrec :: Int -> Rhs l -> ShowS

show :: Rhs l -> String

showList :: [Rhs l] -> ShowS

Generic (Rhs l) Source 

Associated Types

type Rep (Rhs l) :: * -> *

Methods

from :: Rhs l -> Rep (Rhs l) x

to :: Rep (Rhs l) x -> Rhs l

SrcInfo loc => Pretty (Rhs loc) Source 

Methods

pretty :: Rhs loc -> Doc

prettyPrec :: Int -> Rhs loc -> Doc

type Rep (Rhs l) Source 

data GuardedRhs l 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 l [Stmt l] (Exp l) 

Instances

Functor GuardedRhs Source 

Methods

fmap :: (a -> b) -> GuardedRhs a -> GuardedRhs b

(<$) :: a -> GuardedRhs b -> GuardedRhs a

Foldable GuardedRhs Source 

Methods

fold :: Monoid m => GuardedRhs m -> m

foldMap :: Monoid m => (a -> m) -> GuardedRhs a -> m

foldr :: (a -> b -> b) -> b -> GuardedRhs a -> b

foldr' :: (a -> b -> b) -> b -> GuardedRhs a -> b

foldl :: (b -> a -> b) -> b -> GuardedRhs a -> b

foldl' :: (b -> a -> b) -> b -> GuardedRhs a -> b

foldr1 :: (a -> a -> a) -> GuardedRhs a -> a

foldl1 :: (a -> a -> a) -> GuardedRhs a -> a

toList :: GuardedRhs a -> [a]

null :: GuardedRhs a -> Bool

length :: GuardedRhs a -> Int

elem :: Eq a => a -> GuardedRhs a -> Bool

maximum :: Ord a => GuardedRhs a -> a

minimum :: Ord a => GuardedRhs a -> a

sum :: Num a => GuardedRhs a -> a

product :: Num a => GuardedRhs a -> a

Traversable GuardedRhs Source 

Methods

traverse :: Applicative f => (a -> f b) -> GuardedRhs a -> f (GuardedRhs b)

sequenceA :: Applicative f => GuardedRhs (f a) -> f (GuardedRhs a)

mapM :: Monad m => (a -> m b) -> GuardedRhs a -> m (GuardedRhs b)

sequence :: Monad m => GuardedRhs (m a) -> m (GuardedRhs a)

Annotated GuardedRhs Source 

Methods

ann :: GuardedRhs l -> l Source

amap :: (l -> l) -> GuardedRhs l -> GuardedRhs l Source

ExactP GuardedRhs Source 

Methods

exactP :: GuardedRhs SrcSpanInfo -> EP ()

AppFixity GuardedRhs Source 
Eq l => Eq (GuardedRhs l) Source 

Methods

(==) :: GuardedRhs l -> GuardedRhs l -> Bool

(/=) :: GuardedRhs l -> GuardedRhs l -> Bool

Data l => Data (GuardedRhs l) Source 

Methods

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

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

toConstr :: GuardedRhs l -> Constr

dataTypeOf :: GuardedRhs l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (GuardedRhs l) Source 
Show l => Show (GuardedRhs l) Source 
Generic (GuardedRhs l) Source 

Associated Types

type Rep (GuardedRhs l) :: * -> *

Methods

from :: GuardedRhs l -> Rep (GuardedRhs l) x

to :: Rep (GuardedRhs l) x -> GuardedRhs l

SrcInfo loc => Pretty (GuardedRhs loc) Source 

Methods

pretty :: GuardedRhs loc -> Doc

prettyPrec :: Int -> GuardedRhs loc -> Doc

type Rep (GuardedRhs l) Source 

Class Assertions and Contexts

data Context l Source

A context is a set of assertions

Constructors

CxSingle l (Asst l) 
CxTuple l [Asst l] 
CxEmpty l 

Instances

Functor Context Source 

Methods

fmap :: (a -> b) -> Context a -> Context b

(<$) :: a -> Context b -> Context a

Foldable Context Source 

Methods

fold :: Monoid m => Context m -> m

foldMap :: Monoid m => (a -> m) -> Context a -> m

foldr :: (a -> b -> b) -> b -> Context a -> b

foldr' :: (a -> b -> b) -> b -> Context a -> b

foldl :: (b -> a -> b) -> b -> Context a -> b

foldl' :: (b -> a -> b) -> b -> Context a -> b

foldr1 :: (a -> a -> a) -> Context a -> a

foldl1 :: (a -> a -> a) -> Context a -> a

toList :: Context a -> [a]

null :: Context a -> Bool

length :: Context a -> Int

elem :: Eq a => a -> Context a -> Bool

maximum :: Ord a => Context a -> a

minimum :: Ord a => Context a -> a

sum :: Num a => Context a -> a

product :: Num a => Context a -> a

Traversable Context Source 

Methods

traverse :: Applicative f => (a -> f b) -> Context a -> f (Context b)

sequenceA :: Applicative f => Context (f a) -> f (Context a)

mapM :: Monad m => (a -> m b) -> Context a -> m (Context b)

sequence :: Monad m => Context (m a) -> m (Context a)

Annotated Context Source 

Methods

ann :: Context l -> l Source

amap :: (l -> l) -> Context l -> Context l Source

ExactP Context Source 

Methods

exactP :: Context SrcSpanInfo -> EP ()

Eq l => Eq (Context l) Source 

Methods

(==) :: Context l -> Context l -> Bool

(/=) :: Context l -> Context l -> Bool

Data l => Data (Context l) Source 

Methods

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

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

toConstr :: Context l -> Constr

dataTypeOf :: Context l -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> Context l -> Context l

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

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

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

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

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

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

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

Ord l => Ord (Context l) Source 

Methods

compare :: Context l -> Context l -> Ordering

(<) :: Context l -> Context l -> Bool

(<=) :: Context l -> Context l -> Bool

(>) :: Context l -> Context l -> Bool

(>=) :: Context l -> Context l -> Bool

max :: Context l -> Context l -> Context l

min :: Context l -> Context l -> Context l

Show l => Show (Context l) Source 

Methods

showsPrec :: Int -> Context l -> ShowS

show :: Context l -> String

showList :: [Context l] -> ShowS

Generic (Context l) Source 

Associated Types

type Rep (Context l) :: * -> *

Methods

from :: Context l -> Rep (Context l) x

to :: Rep (Context l) x -> Context l

SrcInfo l => Pretty (Context l) Source 

Methods

pretty :: Context l -> Doc

prettyPrec :: Int -> Context l -> Doc

type Rep (Context l) Source 

data FunDep l Source

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

Constructors

FunDep l [Name l] [Name l] 

Instances

Functor FunDep Source 

Methods

fmap :: (a -> b) -> FunDep a -> FunDep b

(<$) :: a -> FunDep b -> FunDep a

Foldable FunDep Source 

Methods

fold :: Monoid m => FunDep m -> m

foldMap :: Monoid m => (a -> m) -> FunDep a -> m

foldr :: (a -> b -> b) -> b -> FunDep a -> b

foldr' :: (a -> b -> b) -> b -> FunDep a -> b

foldl :: (b -> a -> b) -> b -> FunDep a -> b

foldl' :: (b -> a -> b) -> b -> FunDep a -> b

foldr1 :: (a -> a -> a) -> FunDep a -> a

foldl1 :: (a -> a -> a) -> FunDep a -> a

toList :: FunDep a -> [a]

null :: FunDep a -> Bool

length :: FunDep a -> Int

elem :: Eq a => a -> FunDep a -> Bool

maximum :: Ord a => FunDep a -> a

minimum :: Ord a => FunDep a -> a

sum :: Num a => FunDep a -> a

product :: Num a => FunDep a -> a

Traversable FunDep Source 

Methods

traverse :: Applicative f => (a -> f b) -> FunDep a -> f (FunDep b)

sequenceA :: Applicative f => FunDep (f a) -> f (FunDep a)

mapM :: Monad m => (a -> m b) -> FunDep a -> m (FunDep b)

sequence :: Monad m => FunDep (m a) -> m (FunDep a)

Annotated FunDep Source 

Methods

ann :: FunDep l -> l Source

amap :: (l -> l) -> FunDep l -> FunDep l Source

ExactP FunDep Source 

Methods

exactP :: FunDep SrcSpanInfo -> EP ()

Eq l => Eq (FunDep l) Source 

Methods

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

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

Data l => Data (FunDep l) Source 

Methods

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

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

toConstr :: FunDep l -> Constr

dataTypeOf :: FunDep l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (FunDep l) Source 

Methods

compare :: FunDep l -> FunDep l -> Ordering

(<) :: FunDep l -> FunDep l -> Bool

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

(>) :: FunDep l -> FunDep l -> Bool

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

max :: FunDep l -> FunDep l -> FunDep l

min :: FunDep l -> FunDep l -> FunDep l

Show l => Show (FunDep l) Source 

Methods

showsPrec :: Int -> FunDep l -> ShowS

show :: FunDep l -> String

showList :: [FunDep l] -> ShowS

Generic (FunDep l) Source 

Associated Types

type Rep (FunDep l) :: * -> *

Methods

from :: FunDep l -> Rep (FunDep l) x

to :: Rep (FunDep l) x -> FunDep l

Pretty (FunDep l) Source 

Methods

pretty :: FunDep l -> Doc

prettyPrec :: Int -> FunDep l -> Doc

type Rep (FunDep l) Source 

data Asst l 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 l (QName l) [Type l]

ordinary class assertion

AppA l (Name l) [Type l]

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

InfixA l (Type l) (QName l) (Type l)

class assertion where the class name is given infix

IParam l (IPName l) (Type l)

implicit parameter assertion

EqualP l (Type l) (Type l)

type equality constraint

ParenA l (Asst l)

parenthesised class assertion

WildCardA l (Maybe (Name l))

Context Wildcard

Instances

Functor Asst Source 

Methods

fmap :: (a -> b) -> Asst a -> Asst b

(<$) :: a -> Asst b -> Asst a

Foldable Asst Source 

Methods

fold :: Monoid m => Asst m -> m

foldMap :: Monoid m => (a -> m) -> Asst a -> m

foldr :: (a -> b -> b) -> b -> Asst a -> b

foldr' :: (a -> b -> b) -> b -> Asst a -> b

foldl :: (b -> a -> b) -> b -> Asst a -> b

foldl' :: (b -> a -> b) -> b -> Asst a -> b

foldr1 :: (a -> a -> a) -> Asst a -> a

foldl1 :: (a -> a -> a) -> Asst a -> a

toList :: Asst a -> [a]

null :: Asst a -> Bool

length :: Asst a -> Int

elem :: Eq a => a -> Asst a -> Bool

maximum :: Ord a => Asst a -> a

minimum :: Ord a => Asst a -> a

sum :: Num a => Asst a -> a

product :: Num a => Asst a -> a

Traversable Asst Source 

Methods

traverse :: Applicative f => (a -> f b) -> Asst a -> f (Asst b)

sequenceA :: Applicative f => Asst (f a) -> f (Asst a)

mapM :: Monad m => (a -> m b) -> Asst a -> m (Asst b)

sequence :: Monad m => Asst (m a) -> m (Asst a)

Annotated Asst Source 

Methods

ann :: Asst l -> l Source

amap :: (l -> l) -> Asst l -> Asst l Source

ExactP Asst Source 

Methods

exactP :: Asst SrcSpanInfo -> EP ()

Eq l => Eq (Asst l) Source 

Methods

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

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

Data l => Data (Asst l) Source 

Methods

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

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

toConstr :: Asst l -> Constr

dataTypeOf :: Asst l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Asst l) Source 

Methods

compare :: Asst l -> Asst l -> Ordering

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

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

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

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

max :: Asst l -> Asst l -> Asst l

min :: Asst l -> Asst l -> Asst l

Show l => Show (Asst l) Source 

Methods

showsPrec :: Int -> Asst l -> ShowS

show :: Asst l -> String

showList :: [Asst l] -> ShowS

Generic (Asst l) Source 

Associated Types

type Rep (Asst l) :: * -> *

Methods

from :: Asst l -> Rep (Asst l) x

to :: Rep (Asst l) x -> Asst l

SrcInfo l => Pretty (Asst l) Source 

Methods

pretty :: Asst l -> Doc

prettyPrec :: Int -> Asst l -> Doc

type Rep (Asst l) Source 

Types

data Type l Source

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

Constructors

TyForall l (Maybe [TyVarBind l]) (Maybe (Context l)) (Type l)

qualified type

TyFun l (Type l) (Type l)

function type

TyTuple l Boxed [Type l]

tuple type, possibly boxed

TyList l (Type l)

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

TyParArray l (Type l)

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

TyApp l (Type l) (Type l)

application of a type constructor

TyVar l (Name l)

type variable

TyCon l (QName l)

named type or type constructor

TyParen l (Type l)

type surrounded by parentheses

TyInfix l (Type l) (QName l) (Type l)

infix type constructor

TyKind l (Type l) (Kind l)

type with explicit kind signature

TyPromoted l (Promoted l)

'K, a promoted data type (-XDataKinds).

TyEquals l (Type l) (Type l)

type equality predicate enabled by ConstraintKinds

TySplice l (Splice l)

template haskell splice type

TyBang l (BangType l) (Type l)

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

TyWildCard l (Maybe (Name l))

Either an anonymous of named type wildcard

Instances

Functor Type Source 

Methods

fmap :: (a -> b) -> Type a -> Type b

(<$) :: a -> Type b -> Type a

Foldable Type Source 

Methods

fold :: Monoid m => Type m -> m

foldMap :: Monoid m => (a -> m) -> Type a -> m

foldr :: (a -> b -> b) -> b -> Type a -> b

foldr' :: (a -> b -> b) -> b -> Type a -> b

foldl :: (b -> a -> b) -> b -> Type a -> b

foldl' :: (b -> a -> b) -> b -> Type a -> b

foldr1 :: (a -> a -> a) -> Type a -> a

foldl1 :: (a -> a -> a) -> Type a -> a

toList :: Type a -> [a]

null :: Type a -> Bool

length :: Type a -> Int

elem :: Eq a => a -> Type a -> Bool

maximum :: Ord a => Type a -> a

minimum :: Ord a => Type a -> a

sum :: Num a => Type a -> a

product :: Num a => Type a -> a

Traversable Type Source 

Methods

traverse :: Applicative f => (a -> f b) -> Type a -> f (Type b)

sequenceA :: Applicative f => Type (f a) -> f (Type a)

mapM :: Monad m => (a -> m b) -> Type a -> m (Type b)

sequence :: Monad m => Type (m a) -> m (Type a)

Annotated Type Source 

Methods

ann :: Type l -> l Source

amap :: (l -> l) -> Type l -> Type l Source

ExactP Type Source 

Methods

exactP :: Type SrcSpanInfo -> EP ()

Eq l => Eq (Type l) Source 

Methods

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

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

Data l => Data (Type l) Source 

Methods

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

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

toConstr :: Type l -> Constr

dataTypeOf :: Type l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Type l) Source 

Methods

compare :: Type l -> Type l -> Ordering

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

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

(>) :: Type l -> Type l -> Bool

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

max :: Type l -> Type l -> Type l

min :: Type l -> Type l -> Type l

Show l => Show (Type l) Source 

Methods

showsPrec :: Int -> Type l -> ShowS

show :: Type l -> String

showList :: [Type l] -> ShowS

Generic (Type l) Source 

Associated Types

type Rep (Type l) :: * -> *

Methods

from :: Type l -> Rep (Type l) x

to :: Rep (Type l) x -> Type l

SrcInfo l => Pretty (Type l) Source 

Methods

pretty :: Type l -> Doc

prettyPrec :: Int -> Type l -> Doc

type Rep (Type l) Source 

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 l Source

An explicit kind annotation.

Constructors

KindStar l

*, the kind of types

KindFn l (Kind l) (Kind l)

->, the kind of a type constructor

KindParen l (Kind l)

a parenthesised kind

KindVar l (QName l)

k, a kind variable (-XPolyKinds)

KindApp l (Kind l) (Kind l)
k1 k2
KindTuple l [Kind l]

'(k1,k2,k3), a promoted tuple

KindList l (Kind l)

'[k1], a promoted list literal

Instances

Functor Kind Source 

Methods

fmap :: (a -> b) -> Kind a -> Kind b

(<$) :: a -> Kind b -> Kind a

Foldable Kind Source 

Methods

fold :: Monoid m => Kind m -> m

foldMap :: Monoid m => (a -> m) -> Kind a -> m

foldr :: (a -> b -> b) -> b -> Kind a -> b

foldr' :: (a -> b -> b) -> b -> Kind a -> b

foldl :: (b -> a -> b) -> b -> Kind a -> b

foldl' :: (b -> a -> b) -> b -> Kind a -> b

foldr1 :: (a -> a -> a) -> Kind a -> a

foldl1 :: (a -> a -> a) -> Kind a -> a

toList :: Kind a -> [a]

null :: Kind a -> Bool

length :: Kind a -> Int

elem :: Eq a => a -> Kind a -> Bool

maximum :: Ord a => Kind a -> a

minimum :: Ord a => Kind a -> a

sum :: Num a => Kind a -> a

product :: Num a => Kind a -> a

Traversable Kind Source 

Methods

traverse :: Applicative f => (a -> f b) -> Kind a -> f (Kind b)

sequenceA :: Applicative f => Kind (f a) -> f (Kind a)

mapM :: Monad m => (a -> m b) -> Kind a -> m (Kind b)

sequence :: Monad m => Kind (m a) -> m (Kind a)

Annotated Kind Source 

Methods

ann :: Kind l -> l Source

amap :: (l -> l) -> Kind l -> Kind l Source

ExactP Kind Source 

Methods

exactP :: Kind SrcSpanInfo -> EP ()

Eq l => Eq (Kind l) Source 

Methods

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

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

Data l => Data (Kind l) Source 

Methods

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

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

toConstr :: Kind l -> Constr

dataTypeOf :: Kind l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Kind l) Source 

Methods

compare :: Kind l -> Kind l -> Ordering

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

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

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

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

max :: Kind l -> Kind l -> Kind l

min :: Kind l -> Kind l -> Kind l

Show l => Show (Kind l) Source 

Methods

showsPrec :: Int -> Kind l -> ShowS

show :: Kind l -> String

showList :: [Kind l] -> ShowS

Generic (Kind l) Source 

Associated Types

type Rep (Kind l) :: * -> *

Methods

from :: Kind l -> Rep (Kind l) x

to :: Rep (Kind l) x -> Kind l

Pretty (Kind l) Source 

Methods

pretty :: Kind l -> Doc

prettyPrec :: Int -> Kind l -> Doc

type Rep (Kind l) Source 

data TyVarBind l Source

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

Constructors

KindedVar l (Name l) (Kind l)

variable binding with kind annotation

UnkindedVar l (Name l)

ordinary variable binding

Instances

Functor TyVarBind Source 

Methods

fmap :: (a -> b) -> TyVarBind a -> TyVarBind b

(<$) :: a -> TyVarBind b -> TyVarBind a

Foldable TyVarBind Source 

Methods

fold :: Monoid m => TyVarBind m -> m

foldMap :: Monoid m => (a -> m) -> TyVarBind a -> m

foldr :: (a -> b -> b) -> b -> TyVarBind a -> b

foldr' :: (a -> b -> b) -> b -> TyVarBind a -> b

foldl :: (b -> a -> b) -> b -> TyVarBind a -> b

foldl' :: (b -> a -> b) -> b -> TyVarBind a -> b

foldr1 :: (a -> a -> a) -> TyVarBind a -> a

foldl1 :: (a -> a -> a) -> TyVarBind a -> a

toList :: TyVarBind a -> [a]

null :: TyVarBind a -> Bool

length :: TyVarBind a -> Int

elem :: Eq a => a -> TyVarBind a -> Bool

maximum :: Ord a => TyVarBind a -> a

minimum :: Ord a => TyVarBind a -> a

sum :: Num a => TyVarBind a -> a

product :: Num a => TyVarBind a -> a

Traversable TyVarBind Source 

Methods

traverse :: Applicative f => (a -> f b) -> TyVarBind a -> f (TyVarBind b)

sequenceA :: Applicative f => TyVarBind (f a) -> f (TyVarBind a)

mapM :: Monad m => (a -> m b) -> TyVarBind a -> m (TyVarBind b)

sequence :: Monad m => TyVarBind (m a) -> m (TyVarBind a)

Annotated TyVarBind Source 

Methods

ann :: TyVarBind l -> l Source

amap :: (l -> l) -> TyVarBind l -> TyVarBind l Source

ExactP TyVarBind Source 

Methods

exactP :: TyVarBind SrcSpanInfo -> EP ()

Eq l => Eq (TyVarBind l) Source 

Methods

(==) :: TyVarBind l -> TyVarBind l -> Bool

(/=) :: TyVarBind l -> TyVarBind l -> Bool

Data l => Data (TyVarBind l) Source 

Methods

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

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

toConstr :: TyVarBind l -> Constr

dataTypeOf :: TyVarBind l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (TyVarBind l) Source 
Show l => Show (TyVarBind l) Source 
Generic (TyVarBind l) Source 

Associated Types

type Rep (TyVarBind l) :: * -> *

Methods

from :: TyVarBind l -> Rep (TyVarBind l) x

to :: Rep (TyVarBind l) x -> TyVarBind l

Pretty (TyVarBind l) Source 

Methods

pretty :: TyVarBind l -> Doc

prettyPrec :: Int -> TyVarBind l -> Doc

type Rep (TyVarBind l) Source 

data Promoted l Source

Bools here are True if there was a leading quote which may be left out. For example '[k1,k2] means the same thing as [k1,k2].

Constructors

PromotedInteger l Integer String

parsed value and raw string

PromotedString l String String

parsed value and raw string

PromotedCon l Bool (QName l) 
PromotedList l Bool [Type l] 
PromotedTuple l [Type l] 
PromotedUnit l 

Instances

Functor Promoted Source 

Methods

fmap :: (a -> b) -> Promoted a -> Promoted b

(<$) :: a -> Promoted b -> Promoted a

Foldable Promoted Source 

Methods

fold :: Monoid m => Promoted m -> m

foldMap :: Monoid m => (a -> m) -> Promoted a -> m

foldr :: (a -> b -> b) -> b -> Promoted a -> b

foldr' :: (a -> b -> b) -> b -> Promoted a -> b

foldl :: (b -> a -> b) -> b -> Promoted a -> b

foldl' :: (b -> a -> b) -> b -> Promoted a -> b

foldr1 :: (a -> a -> a) -> Promoted a -> a

foldl1 :: (a -> a -> a) -> Promoted a -> a

toList :: Promoted a -> [a]

null :: Promoted a -> Bool

length :: Promoted a -> Int

elem :: Eq a => a -> Promoted a -> Bool

maximum :: Ord a => Promoted a -> a

minimum :: Ord a => Promoted a -> a

sum :: Num a => Promoted a -> a

product :: Num a => Promoted a -> a

Traversable Promoted Source 

Methods

traverse :: Applicative f => (a -> f b) -> Promoted a -> f (Promoted b)

sequenceA :: Applicative f => Promoted (f a) -> f (Promoted a)

mapM :: Monad m => (a -> m b) -> Promoted a -> m (Promoted b)

sequence :: Monad m => Promoted (m a) -> m (Promoted a)

Annotated Promoted Source 

Methods

ann :: Promoted l -> l Source

amap :: (l -> l) -> Promoted l -> Promoted l Source

ExactP Promoted Source 

Methods

exactP :: Promoted SrcSpanInfo -> EP ()

Eq l => Eq (Promoted l) Source 

Methods

(==) :: Promoted l -> Promoted l -> Bool

(/=) :: Promoted l -> Promoted l -> Bool

Data l => Data (Promoted l) Source 

Methods

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

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

toConstr :: Promoted l -> Constr

dataTypeOf :: Promoted l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Promoted l) Source 

Methods

compare :: Promoted l -> Promoted l -> Ordering

(<) :: Promoted l -> Promoted l -> Bool

(<=) :: Promoted l -> Promoted l -> Bool

(>) :: Promoted l -> Promoted l -> Bool

(>=) :: Promoted l -> Promoted l -> Bool

max :: Promoted l -> Promoted l -> Promoted l

min :: Promoted l -> Promoted l -> Promoted l

Show l => Show (Promoted l) Source 

Methods

showsPrec :: Int -> Promoted l -> ShowS

show :: Promoted l -> String

showList :: [Promoted l] -> ShowS

Generic (Promoted l) Source 

Associated Types

type Rep (Promoted l) :: * -> *

Methods

from :: Promoted l -> Rep (Promoted l) x

to :: Rep (Promoted l) x -> Promoted l

type Rep (Promoted l) Source 

data TypeEqn l Source

A type equation as found in closed type families.

Constructors

TypeEqn l (Type l) (Type l) 

Instances

Functor TypeEqn Source 

Methods

fmap :: (a -> b) -> TypeEqn a -> TypeEqn b

(<$) :: a -> TypeEqn b -> TypeEqn a

Foldable TypeEqn Source 

Methods

fold :: Monoid m => TypeEqn m -> m

foldMap :: Monoid m => (a -> m) -> TypeEqn a -> m

foldr :: (a -> b -> b) -> b -> TypeEqn a -> b

foldr' :: (a -> b -> b) -> b -> TypeEqn a -> b

foldl :: (b -> a -> b) -> b -> TypeEqn a -> b

foldl' :: (b -> a -> b) -> b -> TypeEqn a -> b

foldr1 :: (a -> a -> a) -> TypeEqn a -> a

foldl1 :: (a -> a -> a) -> TypeEqn a -> a

toList :: TypeEqn a -> [a]

null :: TypeEqn a -> Bool

length :: TypeEqn a -> Int

elem :: Eq a => a -> TypeEqn a -> Bool

maximum :: Ord a => TypeEqn a -> a

minimum :: Ord a => TypeEqn a -> a

sum :: Num a => TypeEqn a -> a

product :: Num a => TypeEqn a -> a

Traversable TypeEqn Source 

Methods

traverse :: Applicative f => (a -> f b) -> TypeEqn a -> f (TypeEqn b)

sequenceA :: Applicative f => TypeEqn (f a) -> f (TypeEqn a)

mapM :: Monad m => (a -> m b) -> TypeEqn a -> m (TypeEqn b)

sequence :: Monad m => TypeEqn (m a) -> m (TypeEqn a)

Annotated TypeEqn Source 

Methods

ann :: TypeEqn l -> l Source

amap :: (l -> l) -> TypeEqn l -> TypeEqn l Source

ExactP TypeEqn Source 

Methods

exactP :: TypeEqn SrcSpanInfo -> EP ()

Eq l => Eq (TypeEqn l) Source 

Methods

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

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

Data l => Data (TypeEqn l) Source 

Methods

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

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

toConstr :: TypeEqn l -> Constr

dataTypeOf :: TypeEqn l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (TypeEqn l) Source 

Methods

compare :: TypeEqn l -> TypeEqn l -> Ordering

(<) :: TypeEqn l -> TypeEqn l -> Bool

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

(>) :: TypeEqn l -> TypeEqn l -> Bool

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

max :: TypeEqn l -> TypeEqn l -> TypeEqn l

min :: TypeEqn l -> TypeEqn l -> TypeEqn l

Show l => Show (TypeEqn l) Source 

Methods

showsPrec :: Int -> TypeEqn l -> ShowS

show :: TypeEqn l -> String

showList :: [TypeEqn l] -> ShowS

Generic (TypeEqn l) Source 

Associated Types

type Rep (TypeEqn l) :: * -> *

Methods

from :: TypeEqn l -> Rep (TypeEqn l) x

to :: Rep (TypeEqn l) x -> TypeEqn l

type Rep (TypeEqn l) Source 

Expressions

data Exp l Source

Haskell expressions.

Constructors

Var l (QName l)

variable

IPVar l (IPName l)

implicit parameter variable

Con l (QName l)

data constructor

Lit l (Literal l)

literal constant

InfixApp l (Exp l) (QOp l) (Exp l)

infix application

App l (Exp l) (Exp l)

ordinary application

NegApp l (Exp l)

negation expression -exp (unary minus)

Lambda l [Pat l] (Exp l)

lambda expression

Let l (Binds l) (Exp l)

local declarations with let ... in ...

If l (Exp l) (Exp l) (Exp l)

if exp then exp else exp

MultiIf l [GuardedRhs l]

if | stmts -> exp ...

Case l (Exp l) [Alt l]

case exp of alts

Do l [Stmt l]

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

MDo l [Stmt l]

mdo-expression

Tuple l Boxed [Exp l]

tuple expression

TupleSection l Boxed [Maybe (Exp l)]

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

List l [Exp l]

list expression

ParArray l [Exp l]

parallel array expression

Paren l (Exp l)

parenthesised expression

LeftSection l (Exp l) (QOp l)

left section (exp qop)

RightSection l (QOp l) (Exp l)

right section (qop exp)

RecConstr l (QName l) [FieldUpdate l]

record construction expression

RecUpdate l (Exp l) [FieldUpdate l]

record update expression

EnumFrom l (Exp l)

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

EnumFromTo l (Exp l) (Exp l)

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

EnumFromThen l (Exp l) (Exp l)

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

EnumFromThenTo l (Exp l) (Exp l) (Exp l)

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

ParArrayFromTo l (Exp l) (Exp l)

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

ParArrayFromThenTo l (Exp l) (Exp l) (Exp l)

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

ListComp l (Exp l) [QualStmt l]

ordinary list comprehension

ParComp l (Exp l) [[QualStmt l]]

parallel list comprehension

ParArrayComp l (Exp l) [[QualStmt l]]

parallel array comprehension

ExpTypeSig l (Exp l) (Type l)

expression with explicit type signature

VarQuote l (QName l)

'x for template haskell reifying of expressions

TypQuote l (QName l)

''T for template haskell reifying of types

BracketExp l (Bracket l)

template haskell bracket expression

SpliceExp l (Splice l)

template haskell splice expression

QuasiQuote l String String

quasi-quotaion: [$name| string |]

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

xml element, with attributes and children

XETag l (XName l) [XAttr l] (Maybe (Exp l))

empty xml element, with attributes

XPcdata l String

PCDATA child element

XExpTag l (Exp l)

escaped haskell expression inside xml

XChildTag l [Exp l]

children of an xml element

CorePragma l String (Exp l)

CORE pragma

SCCPragma l String (Exp l)

SCC pragma

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

GENERATED pragma

Proc l (Pat l) (Exp l)

arrows proc: proc pat -> exp

LeftArrApp l (Exp l) (Exp l)

arrow application (from left): exp -< exp

RightArrApp l (Exp l) (Exp l)

arrow application (from right): exp >- exp

LeftArrHighApp l (Exp l) (Exp l)

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

RightArrHighApp l (Exp l) (Exp l)

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

LCase l [Alt l]

case alts

ExprHole l

Expression hole

Instances

Functor Exp Source 

Methods

fmap :: (a -> b) -> Exp a -> Exp b

(<$) :: a -> Exp b -> Exp a

Foldable Exp Source 

Methods

fold :: Monoid m => Exp m -> m

foldMap :: Monoid m => (a -> m) -> Exp a -> m

foldr :: (a -> b -> b) -> b -> Exp a -> b

foldr' :: (a -> b -> b) -> b -> Exp a -> b

foldl :: (b -> a -> b) -> b -> Exp a -> b

foldl' :: (b -> a -> b) -> b -> Exp a -> b

foldr1 :: (a -> a -> a) -> Exp a -> a

foldl1 :: (a -> a -> a) -> Exp a -> a

toList :: Exp a -> [a]

null :: Exp a -> Bool

length :: Exp a -> Int

elem :: Eq a => a -> Exp a -> Bool

maximum :: Ord a => Exp a -> a

minimum :: Ord a => Exp a -> a

sum :: Num a => Exp a -> a

product :: Num a => Exp a -> a

Traversable Exp Source 

Methods

traverse :: Applicative f => (a -> f b) -> Exp a -> f (Exp b)

sequenceA :: Applicative f => Exp (f a) -> f (Exp a)

mapM :: Monad m => (a -> m b) -> Exp a -> m (Exp b)

sequence :: Monad m => Exp (m a) -> m (Exp a)

Annotated Exp Source 

Methods

ann :: Exp l -> l Source

amap :: (l -> l) -> Exp l -> Exp l Source

ExactP Exp Source 

Methods

exactP :: Exp SrcSpanInfo -> EP ()

AppFixity Exp Source 
Eq l => Eq (Exp l) Source 

Methods

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

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

Data l => Data (Exp l) Source 

Methods

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

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

toConstr :: Exp l -> Constr

dataTypeOf :: Exp l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Exp l) Source 

Methods

compare :: Exp l -> Exp l -> Ordering

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

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

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

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

max :: Exp l -> Exp l -> Exp l

min :: Exp l -> Exp l -> Exp l

Show l => Show (Exp l) Source 

Methods

showsPrec :: Int -> Exp l -> ShowS

show :: Exp l -> String

showList :: [Exp l] -> ShowS

Generic (Exp l) Source 

Associated Types

type Rep (Exp l) :: * -> *

Methods

from :: Exp l -> Rep (Exp l) x

to :: Rep (Exp l) x -> Exp l

SrcInfo loc => Pretty (Exp loc) Source 

Methods

pretty :: Exp loc -> Doc

prettyPrec :: Int -> Exp loc -> Doc

type Rep (Exp l) Source 

data Stmt l 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 l (Pat l) (Exp l)

a generator: pat <- exp

Qualifier l (Exp l)

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 l (Binds l)

local bindings

RecStmt l [Stmt l]

a recursive binding group for arrows

Instances

Functor Stmt Source 

Methods

fmap :: (a -> b) -> Stmt a -> Stmt b

(<$) :: a -> Stmt b -> Stmt a

Foldable Stmt Source 

Methods

fold :: Monoid m => Stmt m -> m

foldMap :: Monoid m => (a -> m) -> Stmt a -> m

foldr :: (a -> b -> b) -> b -> Stmt a -> b

foldr' :: (a -> b -> b) -> b -> Stmt a -> b

foldl :: (b -> a -> b) -> b -> Stmt a -> b

foldl' :: (b -> a -> b) -> b -> Stmt a -> b

foldr1 :: (a -> a -> a) -> Stmt a -> a

foldl1 :: (a -> a -> a) -> Stmt a -> a

toList :: Stmt a -> [a]

null :: Stmt a -> Bool

length :: Stmt a -> Int

elem :: Eq a => a -> Stmt a -> Bool

maximum :: Ord a => Stmt a -> a

minimum :: Ord a => Stmt a -> a

sum :: Num a => Stmt a -> a

product :: Num a => Stmt a -> a

Traversable Stmt Source 

Methods

traverse :: Applicative f => (a -> f b) -> Stmt a -> f (Stmt b)

sequenceA :: Applicative f => Stmt (f a) -> f (Stmt a)

mapM :: Monad m => (a -> m b) -> Stmt a -> m (Stmt b)

sequence :: Monad m => Stmt (m a) -> m (Stmt a)

Annotated Stmt Source 

Methods

ann :: Stmt l -> l Source

amap :: (l -> l) -> Stmt l -> Stmt l Source

ExactP Stmt Source 

Methods

exactP :: Stmt SrcSpanInfo -> EP ()

AppFixity Stmt Source 
Eq l => Eq (Stmt l) Source 

Methods

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

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

Data l => Data (Stmt l) Source 

Methods

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

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

toConstr :: Stmt l -> Constr

dataTypeOf :: Stmt l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Stmt l) Source 

Methods

compare :: Stmt l -> Stmt l -> Ordering

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

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

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

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

max :: Stmt l -> Stmt l -> Stmt l

min :: Stmt l -> Stmt l -> Stmt l

Show l => Show (Stmt l) Source 

Methods

showsPrec :: Int -> Stmt l -> ShowS

show :: Stmt l -> String

showList :: [Stmt l] -> ShowS

Generic (Stmt l) Source 

Associated Types

type Rep (Stmt l) :: * -> *

Methods

from :: Stmt l -> Rep (Stmt l) x

to :: Rep (Stmt l) x -> Stmt l

SrcInfo loc => Pretty (Stmt loc) Source 

Methods

pretty :: Stmt loc -> Doc

prettyPrec :: Int -> Stmt loc -> Doc

type Rep (Stmt l) Source 

data QualStmt l Source

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

Constructors

QualStmt l (Stmt l)

an ordinary statement

ThenTrans l (Exp l)

then exp

ThenBy l (Exp l) (Exp l)

then exp by exp

GroupBy l (Exp l)

then group by exp

GroupUsing l (Exp l)

then group using exp

GroupByUsing l (Exp l) (Exp l)

then group by exp using exp

Instances

Functor QualStmt Source 

Methods

fmap :: (a -> b) -> QualStmt a -> QualStmt b

(<$) :: a -> QualStmt b -> QualStmt a

Foldable QualStmt Source 

Methods

fold :: Monoid m => QualStmt m -> m

foldMap :: Monoid m => (a -> m) -> QualStmt a -> m

foldr :: (a -> b -> b) -> b -> QualStmt a -> b

foldr' :: (a -> b -> b) -> b -> QualStmt a -> b

foldl :: (b -> a -> b) -> b -> QualStmt a -> b

foldl' :: (b -> a -> b) -> b -> QualStmt a -> b

foldr1 :: (a -> a -> a) -> QualStmt a -> a

foldl1 :: (a -> a -> a) -> QualStmt a -> a

toList :: QualStmt a -> [a]

null :: QualStmt a -> Bool

length :: QualStmt a -> Int

elem :: Eq a => a -> QualStmt a -> Bool

maximum :: Ord a => QualStmt a -> a

minimum :: Ord a => QualStmt a -> a

sum :: Num a => QualStmt a -> a

product :: Num a => QualStmt a -> a

Traversable QualStmt Source 

Methods

traverse :: Applicative f => (a -> f b) -> QualStmt a -> f (QualStmt b)

sequenceA :: Applicative f => QualStmt (f a) -> f (QualStmt a)

mapM :: Monad m => (a -> m b) -> QualStmt a -> m (QualStmt b)

sequence :: Monad m => QualStmt (m a) -> m (QualStmt a)

Annotated QualStmt Source 

Methods

ann :: QualStmt l -> l Source

amap :: (l -> l) -> QualStmt l -> QualStmt l Source

ExactP QualStmt Source 

Methods

exactP :: QualStmt SrcSpanInfo -> EP ()

AppFixity QualStmt Source 
Eq l => Eq (QualStmt l) Source 

Methods

(==) :: QualStmt l -> QualStmt l -> Bool

(/=) :: QualStmt l -> QualStmt l -> Bool

Data l => Data (QualStmt l) Source 

Methods

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

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

toConstr :: QualStmt l -> Constr

dataTypeOf :: QualStmt l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (QualStmt l) Source 

Methods

compare :: QualStmt l -> QualStmt l -> Ordering

(<) :: QualStmt l -> QualStmt l -> Bool

(<=) :: QualStmt l -> QualStmt l -> Bool

(>) :: QualStmt l -> QualStmt l -> Bool

(>=) :: QualStmt l -> QualStmt l -> Bool

max :: QualStmt l -> QualStmt l -> QualStmt l

min :: QualStmt l -> QualStmt l -> QualStmt l

Show l => Show (QualStmt l) Source 

Methods

showsPrec :: Int -> QualStmt l -> ShowS

show :: QualStmt l -> String

showList :: [QualStmt l] -> ShowS

Generic (QualStmt l) Source 

Associated Types

type Rep (QualStmt l) :: * -> *

Methods

from :: QualStmt l -> Rep (QualStmt l) x

to :: Rep (QualStmt l) x -> QualStmt l

SrcInfo loc => Pretty (QualStmt loc) Source 

Methods

pretty :: QualStmt loc -> Doc

prettyPrec :: Int -> QualStmt loc -> Doc

type Rep (QualStmt l) Source 

data FieldUpdate l Source

An fbind in a labeled construction or update expression.

Constructors

FieldUpdate l (QName l) (Exp l)

ordinary label-expresion pair

FieldPun l (QName l)

record field pun

FieldWildcard l

record field wildcard

Instances

Functor FieldUpdate Source 

Methods

fmap :: (a -> b) -> FieldUpdate a -> FieldUpdate b

(<$) :: a -> FieldUpdate b -> FieldUpdate a

Foldable FieldUpdate Source 

Methods

fold :: Monoid m => FieldUpdate m -> m

foldMap :: Monoid m => (a -> m) -> FieldUpdate a -> m

foldr :: (a -> b -> b) -> b -> FieldUpdate a -> b

foldr' :: (a -> b -> b) -> b -> FieldUpdate a -> b

foldl :: (b -> a -> b) -> b -> FieldUpdate a -> b

foldl' :: (b -> a -> b) -> b -> FieldUpdate a -> b

foldr1 :: (a -> a -> a) -> FieldUpdate a -> a

foldl1 :: (a -> a -> a) -> FieldUpdate a -> a

toList :: FieldUpdate a -> [a]

null :: FieldUpdate a -> Bool

length :: FieldUpdate a -> Int

elem :: Eq a => a -> FieldUpdate a -> Bool

maximum :: Ord a => FieldUpdate a -> a

minimum :: Ord a => FieldUpdate a -> a

sum :: Num a => FieldUpdate a -> a

product :: Num a => FieldUpdate a -> a

Traversable FieldUpdate Source 

Methods

traverse :: Applicative f => (a -> f b) -> FieldUpdate a -> f (FieldUpdate b)

sequenceA :: Applicative f => FieldUpdate (f a) -> f (FieldUpdate a)

mapM :: Monad m => (a -> m b) -> FieldUpdate a -> m (FieldUpdate b)

sequence :: Monad m => FieldUpdate (m a) -> m (FieldUpdate a)

Annotated FieldUpdate Source 

Methods

ann :: FieldUpdate l -> l Source

amap :: (l -> l) -> FieldUpdate l -> FieldUpdate l Source

ExactP FieldUpdate Source 

Methods

exactP :: FieldUpdate SrcSpanInfo -> EP ()

AppFixity FieldUpdate Source 
Eq l => Eq (FieldUpdate l) Source 
Data l => Data (FieldUpdate l) Source 

Methods

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

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

toConstr :: FieldUpdate l -> Constr

dataTypeOf :: FieldUpdate l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (FieldUpdate l) Source 
Show l => Show (FieldUpdate l) Source 
Generic (FieldUpdate l) Source 

Associated Types

type Rep (FieldUpdate l) :: * -> *

Methods

from :: FieldUpdate l -> Rep (FieldUpdate l) x

to :: Rep (FieldUpdate l) x -> FieldUpdate l

SrcInfo loc => Pretty (FieldUpdate loc) Source 

Methods

pretty :: FieldUpdate loc -> Doc

prettyPrec :: Int -> FieldUpdate loc -> Doc

type Rep (FieldUpdate l) Source 

data Alt l Source

An alt alternative in a case expression.

Constructors

Alt l (Pat l) (Rhs l) (Maybe (Binds l)) 

Instances

Functor Alt Source 

Methods

fmap :: (a -> b) -> Alt a -> Alt b

(<$) :: a -> Alt b -> Alt a

Foldable Alt Source 

Methods

fold :: Monoid m => Alt m -> m

foldMap :: Monoid m => (a -> m) -> Alt a -> m

foldr :: (a -> b -> b) -> b -> Alt a -> b

foldr' :: (a -> b -> b) -> b -> Alt a -> b

foldl :: (b -> a -> b) -> b -> Alt a -> b

foldl' :: (b -> a -> b) -> b -> Alt a -> b

foldr1 :: (a -> a -> a) -> Alt a -> a

foldl1 :: (a -> a -> a) -> Alt a -> a

toList :: Alt a -> [a]

null :: Alt a -> Bool

length :: Alt a -> Int

elem :: Eq a => a -> Alt a -> Bool

maximum :: Ord a => Alt a -> a

minimum :: Ord a => Alt a -> a

sum :: Num a => Alt a -> a

product :: Num a => Alt a -> a

Traversable Alt Source 

Methods

traverse :: Applicative f => (a -> f b) -> Alt a -> f (Alt b)

sequenceA :: Applicative f => Alt (f a) -> f (Alt a)

mapM :: Monad m => (a -> m b) -> Alt a -> m (Alt b)

sequence :: Monad m => Alt (m a) -> m (Alt a)

Annotated Alt Source 

Methods

ann :: Alt l -> l Source

amap :: (l -> l) -> Alt l -> Alt l Source

ExactP Alt Source 

Methods

exactP :: Alt SrcSpanInfo -> EP ()

AppFixity Alt Source 
Eq l => Eq (Alt l) Source 

Methods

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

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

Data l => Data (Alt l) Source 

Methods

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

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

toConstr :: Alt l -> Constr

dataTypeOf :: Alt l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Alt l) Source 

Methods

compare :: Alt l -> Alt l -> Ordering

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

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

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

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

max :: Alt l -> Alt l -> Alt l

min :: Alt l -> Alt l -> Alt l

Show l => Show (Alt l) Source 

Methods

showsPrec :: Int -> Alt l -> ShowS

show :: Alt l -> String

showList :: [Alt l] -> ShowS

Generic (Alt l) Source 

Associated Types

type Rep (Alt l) :: * -> *

Methods

from :: Alt l -> Rep (Alt l) x

to :: Rep (Alt l) x -> Alt l

SrcInfo loc => Pretty (Alt loc) Source 

Methods

pretty :: Alt loc -> Doc

prettyPrec :: Int -> Alt loc -> Doc

type Rep (Alt l) Source 

data XAttr l Source

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

Constructors

XAttr l (XName l) (Exp l) 

Instances

Functor XAttr Source 

Methods

fmap :: (a -> b) -> XAttr a -> XAttr b

(<$) :: a -> XAttr b -> XAttr a

Foldable XAttr Source 

Methods

fold :: Monoid m => XAttr m -> m

foldMap :: Monoid m => (a -> m) -> XAttr a -> m

foldr :: (a -> b -> b) -> b -> XAttr a -> b

foldr' :: (a -> b -> b) -> b -> XAttr a -> b

foldl :: (b -> a -> b) -> b -> XAttr a -> b

foldl' :: (b -> a -> b) -> b -> XAttr a -> b

foldr1 :: (a -> a -> a) -> XAttr a -> a

foldl1 :: (a -> a -> a) -> XAttr a -> a

toList :: XAttr a -> [a]

null :: XAttr a -> Bool

length :: XAttr a -> Int

elem :: Eq a => a -> XAttr a -> Bool

maximum :: Ord a => XAttr a -> a

minimum :: Ord a => XAttr a -> a

sum :: Num a => XAttr a -> a

product :: Num a => XAttr a -> a

Traversable XAttr Source 

Methods

traverse :: Applicative f => (a -> f b) -> XAttr a -> f (XAttr b)

sequenceA :: Applicative f => XAttr (f a) -> f (XAttr a)

mapM :: Monad m => (a -> m b) -> XAttr a -> m (XAttr b)

sequence :: Monad m => XAttr (m a) -> m (XAttr a)

Annotated XAttr Source 

Methods

ann :: XAttr l -> l Source

amap :: (l -> l) -> XAttr l -> XAttr l Source

ExactP XAttr Source 

Methods

exactP :: XAttr SrcSpanInfo -> EP ()

AppFixity XAttr Source 
Eq l => Eq (XAttr l) Source 

Methods

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

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

Data l => Data (XAttr l) Source 

Methods

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

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

toConstr :: XAttr l -> Constr

dataTypeOf :: XAttr l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (XAttr l) Source 

Methods

compare :: XAttr l -> XAttr l -> Ordering

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

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

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

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

max :: XAttr l -> XAttr l -> XAttr l

min :: XAttr l -> XAttr l -> XAttr l

Show l => Show (XAttr l) Source 

Methods

showsPrec :: Int -> XAttr l -> ShowS

show :: XAttr l -> String

showList :: [XAttr l] -> ShowS

Generic (XAttr l) Source 

Associated Types

type Rep (XAttr l) :: * -> *

Methods

from :: XAttr l -> Rep (XAttr l) x

to :: Rep (XAttr l) x -> XAttr l

SrcInfo loc => Pretty (XAttr loc) Source 

Methods

pretty :: XAttr loc -> Doc

prettyPrec :: Int -> XAttr loc -> Doc

type Rep (XAttr l) Source 

Patterns

data Pat l Source

A pattern, to be matched against a value.

Constructors

PVar l (Name l)

variable

PLit l (Sign l) (Literal l)

literal constant

PNPlusK l (Name l) Integer

n+k pattern

PInfixApp l (Pat l) (QName l) (Pat l)

pattern with an infix data constructor

PApp l (QName l) [Pat l]

data constructor and argument patterns

PTuple l Boxed [Pat l]

tuple pattern

PList l [Pat l]

list pattern

PParen l (Pat l)

parenthesized pattern

PRec l (QName l) [PatField l]

labelled pattern, record style

PAsPat l (Name l) (Pat l)

@-pattern

PWildCard l

wildcard pattern: _

PIrrPat l (Pat l)

irrefutable pattern: ~pat

PatTypeSig l (Pat l) (Type l)

pattern with type signature

PViewPat l (Exp l) (Pat l)

view patterns of the form (exp -> pat)

PRPat l [RPat l]

regular list pattern

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

XML element pattern

PXETag l (XName l) [PXAttr l] (Maybe (Pat l))

XML singleton element pattern

PXPcdata l String

XML PCDATA pattern

PXPatTag l (Pat l)

XML embedded pattern

PXRPats l [RPat l]

XML regular list pattern

PQuasiQuote l String String

quasi quote pattern: [$name| string |]

PBangPat l (Pat l)

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

Instances

Functor Pat Source 

Methods

fmap :: (a -> b) -> Pat a -> Pat b

(<$) :: a -> Pat b -> Pat a

Foldable Pat Source 

Methods

fold :: Monoid m => Pat m -> m

foldMap :: Monoid m => (a -> m) -> Pat a -> m

foldr :: (a -> b -> b) -> b -> Pat a -> b

foldr' :: (a -> b -> b) -> b -> Pat a -> b

foldl :: (b -> a -> b) -> b -> Pat a -> b

foldl' :: (b -> a -> b) -> b -> Pat a -> b

foldr1 :: (a -> a -> a) -> Pat a -> a

foldl1 :: (a -> a -> a) -> Pat a -> a

toList :: Pat a -> [a]

null :: Pat a -> Bool

length :: Pat a -> Int

elem :: Eq a => a -> Pat a -> Bool

maximum :: Ord a => Pat a -> a

minimum :: Ord a => Pat a -> a

sum :: Num a => Pat a -> a

product :: Num a => Pat a -> a

Traversable Pat Source 

Methods

traverse :: Applicative f => (a -> f b) -> Pat a -> f (Pat b)

sequenceA :: Applicative f => Pat (f a) -> f (Pat a)

mapM :: Monad m => (a -> m b) -> Pat a -> m (Pat b)

sequence :: Monad m => Pat (m a) -> m (Pat a)

Annotated Pat Source 

Methods

ann :: Pat l -> l Source

amap :: (l -> l) -> Pat l -> Pat l Source

ExactP Pat Source 

Methods

exactP :: Pat SrcSpanInfo -> EP ()

AppFixity Pat Source 
Eq l => Eq (Pat l) Source 

Methods

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

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

Data l => Data (Pat l) Source 

Methods

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

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

toConstr :: Pat l -> Constr

dataTypeOf :: Pat l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Pat l) Source 

Methods

compare :: Pat l -> Pat l -> Ordering

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

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

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

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

max :: Pat l -> Pat l -> Pat l

min :: Pat l -> Pat l -> Pat l

Show l => Show (Pat l) Source 

Methods

showsPrec :: Int -> Pat l -> ShowS

show :: Pat l -> String

showList :: [Pat l] -> ShowS

Generic (Pat l) Source 

Associated Types

type Rep (Pat l) :: * -> *

Methods

from :: Pat l -> Rep (Pat l) x

to :: Rep (Pat l) x -> Pat l

SrcInfo loc => Pretty (Pat loc) Source 

Methods

pretty :: Pat loc -> Doc

prettyPrec :: Int -> Pat loc -> Doc

type Rep (Pat l) Source 

data PatField l Source

An fpat in a labeled record pattern.

Constructors

PFieldPat l (QName l) (Pat l)

ordinary label-pattern pair

PFieldPun l (QName l)

record field pun

PFieldWildcard l

record field wildcard

Instances

Functor PatField Source 

Methods

fmap :: (a -> b) -> PatField a -> PatField b

(<$) :: a -> PatField b -> PatField a

Foldable PatField Source 

Methods

fold :: Monoid m => PatField m -> m

foldMap :: Monoid m => (a -> m) -> PatField a -> m

foldr :: (a -> b -> b) -> b -> PatField a -> b

foldr' :: (a -> b -> b) -> b -> PatField a -> b

foldl :: (b -> a -> b) -> b -> PatField a -> b

foldl' :: (b -> a -> b) -> b -> PatField a -> b

foldr1 :: (a -> a -> a) -> PatField a -> a

foldl1 :: (a -> a -> a) -> PatField a -> a

toList :: PatField a -> [a]

null :: PatField a -> Bool

length :: PatField a -> Int

elem :: Eq a => a -> PatField a -> Bool

maximum :: Ord a => PatField a -> a

minimum :: Ord a => PatField a -> a

sum :: Num a => PatField a -> a

product :: Num a => PatField a -> a

Traversable PatField Source 

Methods

traverse :: Applicative f => (a -> f b) -> PatField a -> f (PatField b)

sequenceA :: Applicative f => PatField (f a) -> f (PatField a)

mapM :: Monad m => (a -> m b) -> PatField a -> m (PatField b)

sequence :: Monad m => PatField (m a) -> m (PatField a)

Annotated PatField Source 

Methods

ann :: PatField l -> l Source

amap :: (l -> l) -> PatField l -> PatField l Source

ExactP PatField Source 

Methods

exactP :: PatField SrcSpanInfo -> EP ()

AppFixity PatField Source 
Eq l => Eq (PatField l) Source 

Methods

(==) :: PatField l -> PatField l -> Bool

(/=) :: PatField l -> PatField l -> Bool

Data l => Data (PatField l) Source 

Methods

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

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

toConstr :: PatField l -> Constr

dataTypeOf :: PatField l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (PatField l) Source 

Methods

compare :: PatField l -> PatField l -> Ordering

(<) :: PatField l -> PatField l -> Bool

(<=) :: PatField l -> PatField l -> Bool

(>) :: PatField l -> PatField l -> Bool

(>=) :: PatField l -> PatField l -> Bool

max :: PatField l -> PatField l -> PatField l

min :: PatField l -> PatField l -> PatField l

Show l => Show (PatField l) Source 

Methods

showsPrec :: Int -> PatField l -> ShowS

show :: PatField l -> String

showList :: [PatField l] -> ShowS

Generic (PatField l) Source 

Associated Types

type Rep (PatField l) :: * -> *

Methods

from :: PatField l -> Rep (PatField l) x

to :: Rep (PatField l) x -> PatField l

SrcInfo loc => Pretty (PatField loc) Source 

Methods

pretty :: PatField loc -> Doc

prettyPrec :: Int -> PatField loc -> Doc

type Rep (PatField l) Source 

data PXAttr l Source

An XML attribute in a pattern.

Constructors

PXAttr l (XName l) (Pat l) 

Instances

Functor PXAttr Source 

Methods

fmap :: (a -> b) -> PXAttr a -> PXAttr b

(<$) :: a -> PXAttr b -> PXAttr a

Foldable PXAttr Source 

Methods

fold :: Monoid m => PXAttr m -> m

foldMap :: Monoid m => (a -> m) -> PXAttr a -> m

foldr :: (a -> b -> b) -> b -> PXAttr a -> b

foldr' :: (a -> b -> b) -> b -> PXAttr a -> b

foldl :: (b -> a -> b) -> b -> PXAttr a -> b

foldl' :: (b -> a -> b) -> b -> PXAttr a -> b

foldr1 :: (a -> a -> a) -> PXAttr a -> a

foldl1 :: (a -> a -> a) -> PXAttr a -> a

toList :: PXAttr a -> [a]

null :: PXAttr a -> Bool

length :: PXAttr a -> Int

elem :: Eq a => a -> PXAttr a -> Bool

maximum :: Ord a => PXAttr a -> a

minimum :: Ord a => PXAttr a -> a

sum :: Num a => PXAttr a -> a

product :: Num a => PXAttr a -> a

Traversable PXAttr Source 

Methods

traverse :: Applicative f => (a -> f b) -> PXAttr a -> f (PXAttr b)

sequenceA :: Applicative f => PXAttr (f a) -> f (PXAttr a)

mapM :: Monad m => (a -> m b) -> PXAttr a -> m (PXAttr b)

sequence :: Monad m => PXAttr (m a) -> m (PXAttr a)

Annotated PXAttr Source 

Methods

ann :: PXAttr l -> l Source

amap :: (l -> l) -> PXAttr l -> PXAttr l Source

ExactP PXAttr Source 

Methods

exactP :: PXAttr SrcSpanInfo -> EP ()

AppFixity PXAttr Source 
Eq l => Eq (PXAttr l) Source 

Methods

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

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

Data l => Data (PXAttr l) Source 

Methods

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

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

toConstr :: PXAttr l -> Constr

dataTypeOf :: PXAttr l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (PXAttr l) Source 

Methods

compare :: PXAttr l -> PXAttr l -> Ordering

(<) :: PXAttr l -> PXAttr l -> Bool

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

(>) :: PXAttr l -> PXAttr l -> Bool

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

max :: PXAttr l -> PXAttr l -> PXAttr l

min :: PXAttr l -> PXAttr l -> PXAttr l

Show l => Show (PXAttr l) Source 

Methods

showsPrec :: Int -> PXAttr l -> ShowS

show :: PXAttr l -> String

showList :: [PXAttr l] -> ShowS

Generic (PXAttr l) Source 

Associated Types

type Rep (PXAttr l) :: * -> *

Methods

from :: PXAttr l -> Rep (PXAttr l) x

to :: Rep (PXAttr l) x -> PXAttr l

SrcInfo loc => Pretty (PXAttr loc) Source 

Methods

pretty :: PXAttr loc -> Doc

prettyPrec :: Int -> PXAttr loc -> Doc

type Rep (PXAttr l) Source 

data RPat l Source

An entity in a regular pattern.

Constructors

RPOp l (RPat l) (RPatOp l)

operator pattern, e.g. pat*

RPEither l (RPat l) (RPat l)

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

RPSeq l [RPat l]

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

RPGuard l (Pat l) [Stmt l]

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

RPCAs l (Name l) (RPat l)

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

RPAs l (Name l) (RPat l)

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

RPParen l (RPat l)

parenthesised pattern, e.g. (2*)

RPPat l (Pat l)

an ordinary pattern

Instances

Functor RPat Source 

Methods

fmap :: (a -> b) -> RPat a -> RPat b

(<$) :: a -> RPat b -> RPat a

Foldable RPat Source 

Methods

fold :: Monoid m => RPat m -> m

foldMap :: Monoid m => (a -> m) -> RPat a -> m

foldr :: (a -> b -> b) -> b -> RPat a -> b

foldr' :: (a -> b -> b) -> b -> RPat a -> b

foldl :: (b -> a -> b) -> b -> RPat a -> b

foldl' :: (b -> a -> b) -> b -> RPat a -> b

foldr1 :: (a -> a -> a) -> RPat a -> a

foldl1 :: (a -> a -> a) -> RPat a -> a

toList :: RPat a -> [a]

null :: RPat a -> Bool

length :: RPat a -> Int

elem :: Eq a => a -> RPat a -> Bool

maximum :: Ord a => RPat a -> a

minimum :: Ord a => RPat a -> a

sum :: Num a => RPat a -> a

product :: Num a => RPat a -> a

Traversable RPat Source 

Methods

traverse :: Applicative f => (a -> f b) -> RPat a -> f (RPat b)

sequenceA :: Applicative f => RPat (f a) -> f (RPat a)

mapM :: Monad m => (a -> m b) -> RPat a -> m (RPat b)

sequence :: Monad m => RPat (m a) -> m (RPat a)

Annotated RPat Source 

Methods

ann :: RPat l -> l Source

amap :: (l -> l) -> RPat l -> RPat l Source

ExactP RPat Source 

Methods

exactP :: RPat SrcSpanInfo -> EP ()

AppFixity RPat Source 
Eq l => Eq (RPat l) Source 

Methods

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

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

Data l => Data (RPat l) Source 

Methods

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

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

toConstr :: RPat l -> Constr

dataTypeOf :: RPat l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (RPat l) Source 

Methods

compare :: RPat l -> RPat l -> Ordering

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

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

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

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

max :: RPat l -> RPat l -> RPat l

min :: RPat l -> RPat l -> RPat l

Show l => Show (RPat l) Source 

Methods

showsPrec :: Int -> RPat l -> ShowS

show :: RPat l -> String

showList :: [RPat l] -> ShowS

Generic (RPat l) Source 

Associated Types

type Rep (RPat l) :: * -> *

Methods

from :: RPat l -> Rep (RPat l) x

to :: Rep (RPat l) x -> RPat l

SrcInfo loc => Pretty (RPat loc) Source 

Methods

pretty :: RPat loc -> Doc

prettyPrec :: Int -> RPat loc -> Doc

type Rep (RPat l) Source 

data RPatOp l Source

A regular pattern operator.

Constructors

RPStar l

* = 0 or more

RPStarG l

*! = 0 or more, greedy

RPPlus l

+ = 1 or more

RPPlusG l

+! = 1 or more, greedy

RPOpt l

? = 0 or 1

RPOptG l

?! = 0 or 1, greedy

Instances

Functor RPatOp Source 

Methods

fmap :: (a -> b) -> RPatOp a -> RPatOp b

(<$) :: a -> RPatOp b -> RPatOp a

Foldable RPatOp Source 

Methods

fold :: Monoid m => RPatOp m -> m

foldMap :: Monoid m => (a -> m) -> RPatOp a -> m

foldr :: (a -> b -> b) -> b -> RPatOp a -> b

foldr' :: (a -> b -> b) -> b -> RPatOp a -> b

foldl :: (b -> a -> b) -> b -> RPatOp a -> b

foldl' :: (b -> a -> b) -> b -> RPatOp a -> b

foldr1 :: (a -> a -> a) -> RPatOp a -> a

foldl1 :: (a -> a -> a) -> RPatOp a -> a

toList :: RPatOp a -> [a]

null :: RPatOp a -> Bool

length :: RPatOp a -> Int

elem :: Eq a => a -> RPatOp a -> Bool

maximum :: Ord a => RPatOp a -> a

minimum :: Ord a => RPatOp a -> a

sum :: Num a => RPatOp a -> a

product :: Num a => RPatOp a -> a

Traversable RPatOp Source 

Methods

traverse :: Applicative f => (a -> f b) -> RPatOp a -> f (RPatOp b)

sequenceA :: Applicative f => RPatOp (f a) -> f (RPatOp a)

mapM :: Monad m => (a -> m b) -> RPatOp a -> m (RPatOp b)

sequence :: Monad m => RPatOp (m a) -> m (RPatOp a)

Annotated RPatOp Source 

Methods

ann :: RPatOp l -> l Source

amap :: (l -> l) -> RPatOp l -> RPatOp l Source

ExactP RPatOp Source 

Methods

exactP :: RPatOp SrcSpanInfo -> EP ()

Eq l => Eq (RPatOp l) Source 

Methods

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

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

Data l => Data (RPatOp l) Source 

Methods

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

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

toConstr :: RPatOp l -> Constr

dataTypeOf :: RPatOp l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (RPatOp l) Source 

Methods

compare :: RPatOp l -> RPatOp l -> Ordering

(<) :: RPatOp l -> RPatOp l -> Bool

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

(>) :: RPatOp l -> RPatOp l -> Bool

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

max :: RPatOp l -> RPatOp l -> RPatOp l

min :: RPatOp l -> RPatOp l -> RPatOp l

Show l => Show (RPatOp l) Source 

Methods

showsPrec :: Int -> RPatOp l -> ShowS

show :: RPatOp l -> String

showList :: [RPatOp l] -> ShowS

Generic (RPatOp l) Source 

Associated Types

type Rep (RPatOp l) :: * -> *

Methods

from :: RPatOp l -> Rep (RPatOp l) x

to :: Rep (RPatOp l) x -> RPatOp l

Pretty (RPatOp l) Source 

Methods

pretty :: RPatOp l -> Doc

prettyPrec :: Int -> RPatOp l -> Doc

type Rep (RPatOp l) Source 

Literals

data Literal l Source

literal Values of this type hold the abstract value of the literal, along with the precise string representation used. For example, 10, 0o12 and 0xa have the same value representation, but each carry a different string representation.

Constructors

Char l Char String

character literal

String l String String

string literal

Int l Integer String

integer literal

Frac l Rational String

floating point literal

PrimInt l Integer String

unboxed integer literal

PrimWord l Integer String

unboxed word literal

PrimFloat l Rational String

unboxed float literal

PrimDouble l Rational String

unboxed double literal

PrimChar l Char String

unboxed character literal

PrimString l String String

unboxed string literal

Instances

Functor Literal Source 

Methods

fmap :: (a -> b) -> Literal a -> Literal b

(<$) :: a -> Literal b -> Literal a

Foldable Literal Source 

Methods

fold :: Monoid m => Literal m -> m

foldMap :: Monoid m => (a -> m) -> Literal a -> m

foldr :: (a -> b -> b) -> b -> Literal a -> b

foldr' :: (a -> b -> b) -> b -> Literal a -> b

foldl :: (b -> a -> b) -> b -> Literal a -> b

foldl' :: (b -> a -> b) -> b -> Literal a -> b

foldr1 :: (a -> a -> a) -> Literal a -> a

foldl1 :: (a -> a -> a) -> Literal a -> a

toList :: Literal a -> [a]

null :: Literal a -> Bool

length :: Literal a -> Int

elem :: Eq a => a -> Literal a -> Bool

maximum :: Ord a => Literal a -> a

minimum :: Ord a => Literal a -> a

sum :: Num a => Literal a -> a

product :: Num a => Literal a -> a

Traversable Literal Source 

Methods

traverse :: Applicative f => (a -> f b) -> Literal a -> f (Literal b)

sequenceA :: Applicative f => Literal (f a) -> f (Literal a)

mapM :: Monad m => (a -> m b) -> Literal a -> m (Literal b)

sequence :: Monad m => Literal (m a) -> m (Literal a)

Annotated Literal Source 

Methods

ann :: Literal l -> l Source

amap :: (l -> l) -> Literal l -> Literal l Source

ExactP Literal Source 

Methods

exactP :: Literal SrcSpanInfo -> EP ()

Eq l => Eq (Literal l) Source 

Methods

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

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

Data l => Data (Literal l) Source 

Methods

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

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

toConstr :: Literal l -> Constr

dataTypeOf :: Literal l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Literal l) Source 

Methods

compare :: Literal l -> Literal l -> Ordering

(<) :: Literal l -> Literal l -> Bool

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

(>) :: Literal l -> Literal l -> Bool

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

max :: Literal l -> Literal l -> Literal l

min :: Literal l -> Literal l -> Literal l

Show l => Show (Literal l) Source 

Methods

showsPrec :: Int -> Literal l -> ShowS

show :: Literal l -> String

showList :: [Literal l] -> ShowS

Generic (Literal l) Source 

Associated Types

type Rep (Literal l) :: * -> *

Methods

from :: Literal l -> Rep (Literal l) x

to :: Rep (Literal l) x -> Literal l

Pretty (Literal l) Source 

Methods

pretty :: Literal l -> Doc

prettyPrec :: Int -> Literal l -> Doc

type Rep (Literal l) Source 

data Sign l Source

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

Constructors

Signless l 
Negative l 

Instances

Functor Sign Source 

Methods

fmap :: (a -> b) -> Sign a -> Sign b

(<$) :: a -> Sign b -> Sign a

Foldable Sign Source 

Methods

fold :: Monoid m => Sign m -> m

foldMap :: Monoid m => (a -> m) -> Sign a -> m

foldr :: (a -> b -> b) -> b -> Sign a -> b

foldr' :: (a -> b -> b) -> b -> Sign a -> b

foldl :: (b -> a -> b) -> b -> Sign a -> b

foldl' :: (b -> a -> b) -> b -> Sign a -> b

foldr1 :: (a -> a -> a) -> Sign a -> a

foldl1 :: (a -> a -> a) -> Sign a -> a

toList :: Sign a -> [a]

null :: Sign a -> Bool

length :: Sign a -> Int

elem :: Eq a => a -> Sign a -> Bool

maximum :: Ord a => Sign a -> a

minimum :: Ord a => Sign a -> a

sum :: Num a => Sign a -> a

product :: Num a => Sign a -> a

Traversable Sign Source 

Methods

traverse :: Applicative f => (a -> f b) -> Sign a -> f (Sign b)

sequenceA :: Applicative f => Sign (f a) -> f (Sign a)

mapM :: Monad m => (a -> m b) -> Sign a -> m (Sign b)

sequence :: Monad m => Sign (m a) -> m (Sign a)

Annotated Sign Source 

Methods

ann :: Sign l -> l Source

amap :: (l -> l) -> Sign l -> Sign l Source

ExactP Sign Source 

Methods

exactP :: Sign SrcSpanInfo -> EP ()

Eq l => Eq (Sign l) Source 

Methods

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

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

Data l => Data (Sign l) Source 

Methods

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

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

toConstr :: Sign l -> Constr

dataTypeOf :: Sign l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (Sign l) Source 

Methods

compare :: Sign l -> Sign l -> Ordering

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

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

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

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

max :: Sign l -> Sign l -> Sign l

min :: Sign l -> Sign l -> Sign l

Show l => Show (Sign l) Source 

Methods

showsPrec :: Int -> Sign l -> ShowS

show :: Sign l -> String

showList :: [Sign l] -> ShowS

Generic (Sign l) Source 

Associated Types

type Rep (Sign l) :: * -> *

Methods

from :: Sign l -> Rep (Sign l) x

to :: Rep (Sign l) x -> Sign l

type Rep (Sign l) Source 

Variables, Constructors and Operators

data ModuleName l Source

The name of a Haskell module.

Constructors

ModuleName l String 

Instances

Functor ModuleName Source 

Methods

fmap :: (a -> b) -> ModuleName a -> ModuleName b

(<$) :: a -> ModuleName b -> ModuleName a

Foldable ModuleName Source 

Methods

fold :: Monoid m => ModuleName m -> m

foldMap :: Monoid m => (a -> m) -> ModuleName a -> m

foldr :: (a -> b -> b) -> b -> ModuleName a -> b

foldr' :: (a -> b -> b) -> b -> ModuleName a -> b

foldl :: (b -> a -> b) -> b -> ModuleName a -> b

foldl' :: (b -> a -> b) -> b -> ModuleName a -> b

foldr1 :: (a -> a -> a) -> ModuleName a -> a

foldl1 :: (a -> a -> a) -> ModuleName a -> a

toList :: ModuleName a -> [a]

null :: ModuleName a -> Bool

length :: ModuleName a -> Int

elem :: Eq a => a -> ModuleName a -> Bool

maximum :: Ord a => ModuleName a -> a

minimum :: Ord a => ModuleName a -> a

sum :: Num a => ModuleName a -> a

product :: Num a => ModuleName a -> a

Traversable ModuleName Source 

Methods

traverse :: Applicative f => (a -> f b) -> ModuleName a -> f (ModuleName b)

sequenceA :: Applicative f => ModuleName (f a) -> f (ModuleName a)

mapM :: Monad m => (a -> m b) -> ModuleName a -> m (ModuleName b)

sequence :: Monad m => ModuleName (m a) -> m (ModuleName a)

Annotated ModuleName Source 

Methods

ann :: ModuleName l -> l Source

amap :: (l -> l) -> ModuleName l -> ModuleName l Source

ExactP ModuleName Source 

Methods

exactP :: ModuleName SrcSpanInfo -> EP ()

Eq l => Eq (ModuleName l) Source 

Methods

(==) :: ModuleName l -> ModuleName l -> Bool

(/=) :: ModuleName l -> ModuleName l -> Bool

Data l => Data (ModuleName l) Source 

Methods

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

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

toConstr :: ModuleName l -> Constr

dataTypeOf :: ModuleName l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ModuleName l) Source 
Show l => Show (ModuleName l) Source 
Generic (ModuleName l) Source 

Associated Types

type Rep (ModuleName l) :: * -> *

Methods

from :: ModuleName l -> Rep (ModuleName l) x

to :: Rep (ModuleName l) x -> ModuleName l

Pretty (ModuleName l) Source 

Methods

pretty :: ModuleName l -> Doc

prettyPrec :: Int -> ModuleName l -> Doc

type Rep (ModuleName l) Source 

data QName l Source

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

Constructors

Qual l (ModuleName l) (Name l)

name qualified with a module name

UnQual l (Name l)

unqualified local name

Special l (SpecialCon l)

built-in constructor with special syntax

Instances

Functor QName Source 

Methods

fmap :: (a -> b) -> QName a -> QName b

(<$) :: a -> QName b -> QName a

Foldable QName Source 

Methods

fold :: Monoid m => QName m -> m

foldMap :: Monoid m => (a -> m) -> QName a -> m

foldr :: (a -> b -> b) -> b -> QName a -> b

foldr' :: (a -> b -> b) -> b -> QName a -> b

foldl :: (b -> a -> b) -> b -> QName a -> b

foldl' :: (b -> a -> b) -> b -> QName a -> b

foldr1 :: (a -> a -> a) -> QName a -> a

foldl1 :: (a -> a -> a) -> QName a -> a

toList :: QName a -> [a]

null :: QName a -> Bool

length :: QName a -> Int

elem :: Eq a => a -> QName a -> Bool

maximum :: Ord a => QName a -> a

minimum :: Ord a => QName a -> a

sum :: Num a => QName a -> a

product :: Num a => QName a -> a

Traversable QName Source 

Methods

traverse :: Applicative f => (a -> f b) -> QName a -> f (QName b)

sequenceA :: Applicative f => QName (f a) -> f (QName a)

mapM :: Monad m => (a -> m b) -> QName a -> m (QName b)

sequence :: Monad m => QName (m a) -> m (QName a)

Annotated QName Source 

Methods

ann :: QName l -> l Source

amap :: (l -> l) -> QName l -> QName l Source

ExactP QName Source 

Methods

exactP :: QName SrcSpanInfo -> EP ()

Eq l => Eq (QName l) Source 

Methods

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

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

Data l => Data (QName l) Source 

Methods

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

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

toConstr :: QName l -> Constr

dataTypeOf :: QName l -> DataType

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (QName l) Source 

Methods

compare :: QName l -> QName l -> Ordering

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

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

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

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

max :: QName l -> QName l -> QName l

min :: QName l -> QName l -> QName l

Show l => Show (QName l) Source 

Methods

showsPrec :: Int -> QName l -> ShowS

show :: QName l -> String

showList :: [QName l] -> ShowS

Generic (QName l) Source 

Associated Types

type Rep (QName l) :: * -> *

Methods

from :: QName l -> Rep (QName l) x

to :: Rep (QName l) x -> QName l

Pretty (QName l) Source 

Methods

pretty :: QName l -> Doc

prettyPrec :: Int -> QName l -> Doc

type Rep (QName l) Source 

data Name l Source

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

Constructors

Ident l String

varid or conid.

Symbol l String

varsym or consym

Instances

Functor Name Source 

Methods

fmap :: (a -> b) -> Name a -> Name b

(<$) :: a -> Name b -> Name a

Foldable Name Source 

Methods

fold :: Monoid m => Name m -> m

foldMap :: Monoid m => (a -> m) -> Name a -> m

foldr :: (a -> b -> b) -> b -> Name a -> b

foldr' :: (a -> b -> b) -> b -> Name a -> b

foldl :: (b -> a -> b) -> b -> Name a -> b

foldl' :: (b -> a -> b) -> b -> Name a -> b

foldr1 :: (a -> a -> a) -> Name a -> a

foldl1 :: (a -> a -> a) -> Name a -> a

toList :: Name a -> [a]

null :: Name a -> Bool

length :: Name a -> Int

elem :: Eq a => a -> Name a -> Bool

maximum :: Ord a => Name a -> a

minimum :: Ord a => Name a -> a

sum :: Num a => Name a -> a

product :: Num a => Name a -> a

Traversable Name Source 

Methods

traverse :: Applicative f => (a -> f b) -> Name a -> f (Name b)

sequenceA :: Applicative f => Name (f a) -> f (Name a)

mapM :: Monad m => (a -> m b) -> Name a -> m (Name b)

sequence :: Monad m => Name (m a) -> m (Name a)

Annotated Name Source 

Methods

ann :: Name l -> l Source

amap :: (l -> l) -> Name l -> Name l Source

ExactP Name Source 

Methods

exactP :: Name SrcSpanInfo -> EP ()

Eq l => Eq (Name l) Source 

Methods

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

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

Data l => Data (Name l) Source 

Methods

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

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

toConstr :: Name l -> Constr

dataTypeOf :: Name l -> DataType

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

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

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

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

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

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

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

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

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name l -> m (Name l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name l -> m (Name l)

Ord l => Ord (Name l) Source 

Methods

compare :: Name l -> Name l -> Ordering

(<) :: Name l -> Name l -> Bool

(<=) :: Name l -> Name l -> Bool

(>) :: Name l -> Name l -> Bool

(>=) :: Name l -> Name l -> Bool

max :: Name l -> Name l -> Name l

min :: Name l -> Name l -> Name l

Show l => Show (Name l) Source 

Methods

showsPrec :: Int -> Name l -> ShowS

show :: Name l -> String

showList :: [Name l] -> ShowS

Generic (Name l) Source 

Associated Types

type Rep (Name l) :: * -> *

Methods

from :: Name l -> Rep (Name l) x

to :: Rep (Name l) x -> Name l

Pretty (Name l) Source 

Methods

pretty :: Name l -> Doc

prettyPrec :: Int -> Name l -> Doc

type Rep (Name l) Source 

data QOp l Source

Possibly qualified infix operators (qop), appearing in expressions.

Constructors

QVarOp l (QName l)

variable operator (qvarop)

QConOp l (QName l)

constructor operator (qconop)

Instances

Functor QOp Source 

Methods

fmap :: (a -> b) -> QOp a -> QOp b

(<$) :: a -> QOp b -> QOp a

Foldable QOp Source 

Methods

fold :: Monoid m => QOp m -> m

foldMap :: Monoid m => (a -> m) -> QOp a -> m

foldr :: (a -> b -> b) -> b -> QOp a -> b

foldr' :: (a -> b -> b) -> b -> QOp a -> b

foldl :: (b -> a -> b) -> b -> QOp a -> b

foldl' :: (b -> a -> b) -> b -> QOp a -> b

foldr1 :: (a -> a -> a) -> QOp a -> a

foldl1 :: (a -> a -> a) -> QOp a -> a

toList :: QOp a -> [a]

null :: QOp a -> Bool

length :: QOp a -> Int

elem :: Eq a => a -> QOp a -> Bool

maximum :: Ord a => QOp a -> a

minimum :: Ord a => QOp a -> a

sum :: Num a => QOp a -> a

product :: Num a => QOp a -> a

Traversable QOp Source 

Methods

traverse :: Applicative f => (a -> f b) -> QOp a -> f (QOp b)

sequenceA :: Applicative f => QOp (f a) -> f (QOp a)

mapM :: Monad m => (a -> m b) -> QOp a -> m (QOp b)

sequence :: Monad m => QOp (m a) -> m (QOp a)

Annotated QOp Source 

Methods

ann :: QOp l -> l Source

amap :: (l -> l) -> QOp l -> QOp l Source

ExactP QOp Source 

Methods

exactP :: QOp SrcSpanInfo -> EP ()

Eq l => Eq (QOp l) Source 

Methods

(==) :: QOp l -> QOp l -> Bool

(/=) :: QOp l -> QOp l -> Bool

Data l => Data (QOp l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QOp l -> c (QOp l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (QOp l)

toConstr :: QOp l -> Constr

dataTypeOf :: QOp l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (QOp l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (QOp l))

gmapT :: (forall b. Data b => b -> b) -> QOp l -> QOp l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QOp l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QOp l -> r

gmapQ :: (forall d. Data d => d -> u) -> QOp l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QOp l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QOp l -> m (QOp l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QOp l -> m (QOp l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QOp l -> m (QOp l)

Ord l => Ord (QOp l) Source 

Methods

compare :: QOp l -> QOp l -> Ordering

(<) :: QOp l -> QOp l -> Bool

(<=) :: QOp l -> QOp l -> Bool

(>) :: QOp l -> QOp l -> Bool

(>=) :: QOp l -> QOp l -> Bool

max :: QOp l -> QOp l -> QOp l

min :: QOp l -> QOp l -> QOp l

Show l => Show (QOp l) Source 

Methods

showsPrec :: Int -> QOp l -> ShowS

show :: QOp l -> String

showList :: [QOp l] -> ShowS

Generic (QOp l) Source 

Associated Types

type Rep (QOp l) :: * -> *

Methods

from :: QOp l -> Rep (QOp l) x

to :: Rep (QOp l) x -> QOp l

Pretty (QOp l) Source 

Methods

pretty :: QOp l -> Doc

prettyPrec :: Int -> QOp l -> Doc

type Rep (QOp l) Source 

data Op l Source

Operators appearing in infix declarations are never qualified.

Constructors

VarOp l (Name l)

variable operator (varop)

ConOp l (Name l)

constructor operator (conop)

Instances

Functor Op Source 

Methods

fmap :: (a -> b) -> Op a -> Op b

(<$) :: a -> Op b -> Op a

Foldable Op Source 

Methods

fold :: Monoid m => Op m -> m

foldMap :: Monoid m => (a -> m) -> Op a -> m

foldr :: (a -> b -> b) -> b -> Op a -> b

foldr' :: (a -> b -> b) -> b -> Op a -> b

foldl :: (b -> a -> b) -> b -> Op a -> b

foldl' :: (b -> a -> b) -> b -> Op a -> b

foldr1 :: (a -> a -> a) -> Op a -> a

foldl1 :: (a -> a -> a) -> Op a -> a

toList :: Op a -> [a]

null :: Op a -> Bool

length :: Op a -> Int

elem :: Eq a => a -> Op a -> Bool

maximum :: Ord a => Op a -> a

minimum :: Ord a => Op a -> a

sum :: Num a => Op a -> a

product :: Num a => Op a -> a

Traversable Op Source 

Methods

traverse :: Applicative f => (a -> f b) -> Op a -> f (Op b)

sequenceA :: Applicative f => Op (f a) -> f (Op a)

mapM :: Monad m => (a -> m b) -> Op a -> m (Op b)

sequence :: Monad m => Op (m a) -> m (Op a)

Annotated Op Source 

Methods

ann :: Op l -> l Source

amap :: (l -> l) -> Op l -> Op l Source

ExactP Op Source 

Methods

exactP :: Op SrcSpanInfo -> EP ()

Eq l => Eq (Op l) Source 

Methods

(==) :: Op l -> Op l -> Bool

(/=) :: Op l -> Op l -> Bool

Data l => Data (Op l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op l -> c (Op l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Op l)

toConstr :: Op l -> Constr

dataTypeOf :: Op l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Op l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Op l))

gmapT :: (forall b. Data b => b -> b) -> Op l -> Op l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op l -> r

gmapQ :: (forall d. Data d => d -> u) -> Op l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op l -> m (Op l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op l -> m (Op l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op l -> m (Op l)

Ord l => Ord (Op l) Source 

Methods

compare :: Op l -> Op l -> Ordering

(<) :: Op l -> Op l -> Bool

(<=) :: Op l -> Op l -> Bool

(>) :: Op l -> Op l -> Bool

(>=) :: Op l -> Op l -> Bool

max :: Op l -> Op l -> Op l

min :: Op l -> Op l -> Op l

Show l => Show (Op l) Source 

Methods

showsPrec :: Int -> Op l -> ShowS

show :: Op l -> String

showList :: [Op l] -> ShowS

Generic (Op l) Source 

Associated Types

type Rep (Op l) :: * -> *

Methods

from :: Op l -> Rep (Op l) x

to :: Rep (Op l) x -> Op l

Pretty (Op l) Source 

Methods

pretty :: Op l -> Doc

prettyPrec :: Int -> Op l -> Doc

type Rep (Op l) Source 

data SpecialCon l Source

Constructors with special syntax. These names are never qualified, and always refer to builtin type or data constructors.

Constructors

UnitCon l

unit type and data constructor ()

ListCon l

list type constructor []

FunCon l

function type constructor ->

TupleCon l Boxed Int

n-ary tuple type and data constructors (,) etc, possibly boxed (#,#)

Cons l

list data constructor (:)

UnboxedSingleCon l

unboxed singleton tuple constructor (# #)

Instances

Functor SpecialCon Source 

Methods

fmap :: (a -> b) -> SpecialCon a -> SpecialCon b

(<$) :: a -> SpecialCon b -> SpecialCon a

Foldable SpecialCon Source 

Methods

fold :: Monoid m => SpecialCon m -> m

foldMap :: Monoid m => (a -> m) -> SpecialCon a -> m

foldr :: (a -> b -> b) -> b -> SpecialCon a -> b

foldr' :: (a -> b -> b) -> b -> SpecialCon a -> b

foldl :: (b -> a -> b) -> b -> SpecialCon a -> b

foldl' :: (b -> a -> b) -> b -> SpecialCon a -> b

foldr1 :: (a -> a -> a) -> SpecialCon a -> a

foldl1 :: (a -> a -> a) -> SpecialCon a -> a

toList :: SpecialCon a -> [a]

null :: SpecialCon a -> Bool

length :: SpecialCon a -> Int

elem :: Eq a => a -> SpecialCon a -> Bool

maximum :: Ord a => SpecialCon a -> a

minimum :: Ord a => SpecialCon a -> a

sum :: Num a => SpecialCon a -> a

product :: Num a => SpecialCon a -> a

Traversable SpecialCon Source 

Methods

traverse :: Applicative f => (a -> f b) -> SpecialCon a -> f (SpecialCon b)

sequenceA :: Applicative f => SpecialCon (f a) -> f (SpecialCon a)

mapM :: Monad m => (a -> m b) -> SpecialCon a -> m (SpecialCon b)

sequence :: Monad m => SpecialCon (m a) -> m (SpecialCon a)

Annotated SpecialCon Source 

Methods

ann :: SpecialCon l -> l Source

amap :: (l -> l) -> SpecialCon l -> SpecialCon l Source

ExactP SpecialCon Source 

Methods

exactP :: SpecialCon SrcSpanInfo -> EP ()

Eq l => Eq (SpecialCon l) Source 

Methods

(==) :: SpecialCon l -> SpecialCon l -> Bool

(/=) :: SpecialCon l -> SpecialCon l -> Bool

Data l => Data (SpecialCon l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpecialCon l -> c (SpecialCon l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpecialCon l)

toConstr :: SpecialCon l -> Constr

dataTypeOf :: SpecialCon l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SpecialCon l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpecialCon l))

gmapT :: (forall b. Data b => b -> b) -> SpecialCon l -> SpecialCon l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpecialCon l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpecialCon l -> r

gmapQ :: (forall d. Data d => d -> u) -> SpecialCon l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpecialCon l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpecialCon l -> m (SpecialCon l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecialCon l -> m (SpecialCon l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecialCon l -> m (SpecialCon l)

Ord l => Ord (SpecialCon l) Source 
Show l => Show (SpecialCon l) Source 
Generic (SpecialCon l) Source 

Associated Types

type Rep (SpecialCon l) :: * -> *

Methods

from :: SpecialCon l -> Rep (SpecialCon l) x

to :: Rep (SpecialCon l) x -> SpecialCon l

type Rep (SpecialCon l) Source 

data CName l Source

A name (cname) of a component of a class or data type in an import or export specification.

Constructors

VarName l (Name l)

name of a method or field

ConName l (Name l)

name of a data constructor

Instances

Functor CName Source 

Methods

fmap :: (a -> b) -> CName a -> CName b

(<$) :: a -> CName b -> CName a

Foldable CName Source 

Methods

fold :: Monoid m => CName m -> m

foldMap :: Monoid m => (a -> m) -> CName a -> m

foldr :: (a -> b -> b) -> b -> CName a -> b

foldr' :: (a -> b -> b) -> b -> CName a -> b

foldl :: (b -> a -> b) -> b -> CName a -> b

foldl' :: (b -> a -> b) -> b -> CName a -> b

foldr1 :: (a -> a -> a) -> CName a -> a

foldl1 :: (a -> a -> a) -> CName a -> a

toList :: CName a -> [a]

null :: CName a -> Bool

length :: CName a -> Int

elem :: Eq a => a -> CName a -> Bool

maximum :: Ord a => CName a -> a

minimum :: Ord a => CName a -> a

sum :: Num a => CName a -> a

product :: Num a => CName a -> a

Traversable CName Source 

Methods

traverse :: Applicative f => (a -> f b) -> CName a -> f (CName b)

sequenceA :: Applicative f => CName (f a) -> f (CName a)

mapM :: Monad m => (a -> m b) -> CName a -> m (CName b)

sequence :: Monad m => CName (m a) -> m (CName a)

Annotated CName Source 

Methods

ann :: CName l -> l Source

amap :: (l -> l) -> CName l -> CName l Source

ExactP CName Source 

Methods

exactP :: CName SrcSpanInfo -> EP ()

Eq l => Eq (CName l) Source 

Methods

(==) :: CName l -> CName l -> Bool

(/=) :: CName l -> CName l -> Bool

Data l => Data (CName l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CName l -> c (CName l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CName l)

toConstr :: CName l -> Constr

dataTypeOf :: CName l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CName l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CName l))

gmapT :: (forall b. Data b => b -> b) -> CName l -> CName l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CName l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CName l -> r

gmapQ :: (forall d. Data d => d -> u) -> CName l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CName l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CName l -> m (CName l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CName l -> m (CName l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CName l -> m (CName l)

Ord l => Ord (CName l) Source 

Methods

compare :: CName l -> CName l -> Ordering

(<) :: CName l -> CName l -> Bool

(<=) :: CName l -> CName l -> Bool

(>) :: CName l -> CName l -> Bool

(>=) :: CName l -> CName l -> Bool

max :: CName l -> CName l -> CName l

min :: CName l -> CName l -> CName l

Show l => Show (CName l) Source 

Methods

showsPrec :: Int -> CName l -> ShowS

show :: CName l -> String

showList :: [CName l] -> ShowS

Generic (CName l) Source 

Associated Types

type Rep (CName l) :: * -> *

Methods

from :: CName l -> Rep (CName l) x

to :: Rep (CName l) x -> CName l

Pretty (CName l) Source 

Methods

pretty :: CName l -> Doc

prettyPrec :: Int -> CName l -> Doc

type Rep (CName l) Source 

data IPName l Source

An implicit parameter name.

Constructors

IPDup l String

?ident, non-linear implicit parameter

IPLin l String

%ident, linear implicit parameter

Instances

Functor IPName Source 

Methods

fmap :: (a -> b) -> IPName a -> IPName b

(<$) :: a -> IPName b -> IPName a

Foldable IPName Source 

Methods

fold :: Monoid m => IPName m -> m

foldMap :: Monoid m => (a -> m) -> IPName a -> m

foldr :: (a -> b -> b) -> b -> IPName a -> b

foldr' :: (a -> b -> b) -> b -> IPName a -> b

foldl :: (b -> a -> b) -> b -> IPName a -> b

foldl' :: (b -> a -> b) -> b -> IPName a -> b

foldr1 :: (a -> a -> a) -> IPName a -> a

foldl1 :: (a -> a -> a) -> IPName a -> a

toList :: IPName a -> [a]

null :: IPName a -> Bool

length :: IPName a -> Int

elem :: Eq a => a -> IPName a -> Bool

maximum :: Ord a => IPName a -> a

minimum :: Ord a => IPName a -> a

sum :: Num a => IPName a -> a

product :: Num a => IPName a -> a

Traversable IPName Source 

Methods

traverse :: Applicative f => (a -> f b) -> IPName a -> f (IPName b)

sequenceA :: Applicative f => IPName (f a) -> f (IPName a)

mapM :: Monad m => (a -> m b) -> IPName a -> m (IPName b)

sequence :: Monad m => IPName (m a) -> m (IPName a)

Annotated IPName Source 

Methods

ann :: IPName l -> l Source

amap :: (l -> l) -> IPName l -> IPName l Source

ExactP IPName Source 

Methods

exactP :: IPName SrcSpanInfo -> EP ()

Eq l => Eq (IPName l) Source 

Methods

(==) :: IPName l -> IPName l -> Bool

(/=) :: IPName l -> IPName l -> Bool

Data l => Data (IPName l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPName l -> c (IPName l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPName l)

toConstr :: IPName l -> Constr

dataTypeOf :: IPName l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (IPName l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPName l))

gmapT :: (forall b. Data b => b -> b) -> IPName l -> IPName l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPName l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPName l -> r

gmapQ :: (forall d. Data d => d -> u) -> IPName l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPName l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPName l -> m (IPName l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPName l -> m (IPName l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPName l -> m (IPName l)

Ord l => Ord (IPName l) Source 

Methods

compare :: IPName l -> IPName l -> Ordering

(<) :: IPName l -> IPName l -> Bool

(<=) :: IPName l -> IPName l -> Bool

(>) :: IPName l -> IPName l -> Bool

(>=) :: IPName l -> IPName l -> Bool

max :: IPName l -> IPName l -> IPName l

min :: IPName l -> IPName l -> IPName l

Show l => Show (IPName l) Source 

Methods

showsPrec :: Int -> IPName l -> ShowS

show :: IPName l -> String

showList :: [IPName l] -> ShowS

Generic (IPName l) Source 

Associated Types

type Rep (IPName l) :: * -> *

Methods

from :: IPName l -> Rep (IPName l) x

to :: Rep (IPName l) x -> IPName l

Pretty (IPName l) Source 

Methods

pretty :: IPName l -> Doc

prettyPrec :: Int -> IPName l -> Doc

type Rep (IPName l) Source 

data XName l Source

The name of an xml element or attribute, possibly qualified with a namespace.

Constructors

XName l String 
XDomName l String String 

Instances

Functor XName Source 

Methods

fmap :: (a -> b) -> XName a -> XName b

(<$) :: a -> XName b -> XName a

Foldable XName Source 

Methods

fold :: Monoid m => XName m -> m

foldMap :: Monoid m => (a -> m) -> XName a -> m

foldr :: (a -> b -> b) -> b -> XName a -> b

foldr' :: (a -> b -> b) -> b -> XName a -> b

foldl :: (b -> a -> b) -> b -> XName a -> b

foldl' :: (b -> a -> b) -> b -> XName a -> b

foldr1 :: (a -> a -> a) -> XName a -> a

foldl1 :: (a -> a -> a) -> XName a -> a

toList :: XName a -> [a]

null :: XName a -> Bool

length :: XName a -> Int

elem :: Eq a => a -> XName a -> Bool

maximum :: Ord a => XName a -> a

minimum :: Ord a => XName a -> a

sum :: Num a => XName a -> a

product :: Num a => XName a -> a

Traversable XName Source 

Methods

traverse :: Applicative f => (a -> f b) -> XName a -> f (XName b)

sequenceA :: Applicative f => XName (f a) -> f (XName a)

mapM :: Monad m => (a -> m b) -> XName a -> m (XName b)

sequence :: Monad m => XName (m a) -> m (XName a)

Annotated XName Source 

Methods

ann :: XName l -> l Source

amap :: (l -> l) -> XName l -> XName l Source

ExactP XName Source 

Methods

exactP :: XName SrcSpanInfo -> EP ()

Eq l => Eq (XName l) Source 

Methods

(==) :: XName l -> XName l -> Bool

(/=) :: XName l -> XName l -> Bool

Data l => Data (XName l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XName l -> c (XName l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (XName l)

toConstr :: XName l -> Constr

dataTypeOf :: XName l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (XName l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (XName l))

gmapT :: (forall b. Data b => b -> b) -> XName l -> XName l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XName l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XName l -> r

gmapQ :: (forall d. Data d => d -> u) -> XName l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> XName l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XName l -> m (XName l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XName l -> m (XName l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XName l -> m (XName l)

Ord l => Ord (XName l) Source 

Methods

compare :: XName l -> XName l -> Ordering

(<) :: XName l -> XName l -> Bool

(<=) :: XName l -> XName l -> Bool

(>) :: XName l -> XName l -> Bool

(>=) :: XName l -> XName l -> Bool

max :: XName l -> XName l -> XName l

min :: XName l -> XName l -> XName l

Show l => Show (XName l) Source 

Methods

showsPrec :: Int -> XName l -> ShowS

show :: XName l -> String

showList :: [XName l] -> ShowS

Generic (XName l) Source 

Associated Types

type Rep (XName l) :: * -> *

Methods

from :: XName l -> Rep (XName l) x

to :: Rep (XName l) x -> XName l

Pretty (XName l) Source 

Methods

pretty :: XName l -> Doc

prettyPrec :: Int -> XName l -> Doc

type Rep (XName l) Source 

data Role l Source

Constructors

Nominal l 
Representational l 
Phantom l 
RoleWildcard l 

Instances

Functor Role Source 

Methods

fmap :: (a -> b) -> Role a -> Role b

(<$) :: a -> Role b -> Role a

Foldable Role Source 

Methods

fold :: Monoid m => Role m -> m

foldMap :: Monoid m => (a -> m) -> Role a -> m

foldr :: (a -> b -> b) -> b -> Role a -> b

foldr' :: (a -> b -> b) -> b -> Role a -> b

foldl :: (b -> a -> b) -> b -> Role a -> b

foldl' :: (b -> a -> b) -> b -> Role a -> b

foldr1 :: (a -> a -> a) -> Role a -> a

foldl1 :: (a -> a -> a) -> Role a -> a

toList :: Role a -> [a]

null :: Role a -> Bool

length :: Role a -> Int

elem :: Eq a => a -> Role a -> Bool

maximum :: Ord a => Role a -> a

minimum :: Ord a => Role a -> a

sum :: Num a => Role a -> a

product :: Num a => Role a -> a

Traversable Role Source 

Methods

traverse :: Applicative f => (a -> f b) -> Role a -> f (Role b)

sequenceA :: Applicative f => Role (f a) -> f (Role a)

mapM :: Monad m => (a -> m b) -> Role a -> m (Role b)

sequence :: Monad m => Role (m a) -> m (Role a)

Annotated Role Source 

Methods

ann :: Role l -> l Source

amap :: (l -> l) -> Role l -> Role l Source

ExactP Role Source 

Methods

exactP :: Role SrcSpanInfo -> EP ()

Eq l => Eq (Role l) Source 

Methods

(==) :: Role l -> Role l -> Bool

(/=) :: Role l -> Role l -> Bool

Data l => Data (Role l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role l -> c (Role l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Role l)

toConstr :: Role l -> Constr

dataTypeOf :: Role l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Role l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Role l))

gmapT :: (forall b. Data b => b -> b) -> Role l -> Role l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role l -> r

gmapQ :: (forall d. Data d => d -> u) -> Role l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role l -> m (Role l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role l -> m (Role l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role l -> m (Role l)

Ord l => Ord (Role l) Source 

Methods

compare :: Role l -> Role l -> Ordering

(<) :: Role l -> Role l -> Bool

(<=) :: Role l -> Role l -> Bool

(>) :: Role l -> Role l -> Bool

(>=) :: Role l -> Role l -> Bool

max :: Role l -> Role l -> Role l

min :: Role l -> Role l -> Role l

Show l => Show (Role l) Source 

Methods

showsPrec :: Int -> Role l -> ShowS

show :: Role l -> String

showList :: [Role l] -> ShowS

Generic (Role l) Source 

Associated Types

type Rep (Role l) :: * -> *

Methods

from :: Role l -> Rep (Role l) x

to :: Rep (Role l) x -> Role l

type Rep (Role l) Source 

Template Haskell

data Bracket l Source

A template haskell bracket expression.

Constructors

ExpBracket l (Exp l)

expression bracket: [| ... |]

PatBracket l (Pat l)

pattern bracket: [p| ... |]

TypeBracket l (Type l)

type bracket: [t| ... |]

DeclBracket l [Decl l]

declaration bracket: [d| ... |]

Instances

Functor Bracket Source 

Methods

fmap :: (a -> b) -> Bracket a -> Bracket b

(<$) :: a -> Bracket b -> Bracket a

Foldable Bracket Source 

Methods

fold :: Monoid m => Bracket m -> m

foldMap :: Monoid m => (a -> m) -> Bracket a -> m

foldr :: (a -> b -> b) -> b -> Bracket a -> b

foldr' :: (a -> b -> b) -> b -> Bracket a -> b

foldl :: (b -> a -> b) -> b -> Bracket a -> b

foldl' :: (b -> a -> b) -> b -> Bracket a -> b

foldr1 :: (a -> a -> a) -> Bracket a -> a

foldl1 :: (a -> a -> a) -> Bracket a -> a

toList :: Bracket a -> [a]

null :: Bracket a -> Bool

length :: Bracket a -> Int

elem :: Eq a => a -> Bracket a -> Bool

maximum :: Ord a => Bracket a -> a

minimum :: Ord a => Bracket a -> a

sum :: Num a => Bracket a -> a

product :: Num a => Bracket a -> a

Traversable Bracket Source 

Methods

traverse :: Applicative f => (a -> f b) -> Bracket a -> f (Bracket b)

sequenceA :: Applicative f => Bracket (f a) -> f (Bracket a)

mapM :: Monad m => (a -> m b) -> Bracket a -> m (Bracket b)

sequence :: Monad m => Bracket (m a) -> m (Bracket a)

Annotated Bracket Source 

Methods

ann :: Bracket l -> l Source

amap :: (l -> l) -> Bracket l -> Bracket l Source

ExactP Bracket Source 

Methods

exactP :: Bracket SrcSpanInfo -> EP ()

AppFixity Bracket Source 
Eq l => Eq (Bracket l) Source 

Methods

(==) :: Bracket l -> Bracket l -> Bool

(/=) :: Bracket l -> Bracket l -> Bool

Data l => Data (Bracket l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bracket l -> c (Bracket l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bracket l)

toConstr :: Bracket l -> Constr

dataTypeOf :: Bracket l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Bracket l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bracket l))

gmapT :: (forall b. Data b => b -> b) -> Bracket l -> Bracket l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bracket l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bracket l -> r

gmapQ :: (forall d. Data d => d -> u) -> Bracket l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bracket l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bracket l -> m (Bracket l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bracket l -> m (Bracket l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bracket l -> m (Bracket l)

Ord l => Ord (Bracket l) Source 

Methods

compare :: Bracket l -> Bracket l -> Ordering

(<) :: Bracket l -> Bracket l -> Bool

(<=) :: Bracket l -> Bracket l -> Bool

(>) :: Bracket l -> Bracket l -> Bool

(>=) :: Bracket l -> Bracket l -> Bool

max :: Bracket l -> Bracket l -> Bracket l

min :: Bracket l -> Bracket l -> Bracket l

Show l => Show (Bracket l) Source 

Methods

showsPrec :: Int -> Bracket l -> ShowS

show :: Bracket l -> String

showList :: [Bracket l] -> ShowS

Generic (Bracket l) Source 

Associated Types

type Rep (Bracket l) :: * -> *

Methods

from :: Bracket l -> Rep (Bracket l) x

to :: Rep (Bracket l) x -> Bracket l

SrcInfo loc => Pretty (Bracket loc) Source 

Methods

pretty :: Bracket loc -> Doc

prettyPrec :: Int -> Bracket loc -> Doc

type Rep (Bracket l) Source 

data Splice l Source

A template haskell splice expression

Constructors

IdSplice l String

variable splice: $var

ParenSplice l (Exp l)

parenthesised expression splice: $(exp)

Instances

Functor Splice Source 

Methods

fmap :: (a -> b) -> Splice a -> Splice b

(<$) :: a -> Splice b -> Splice a

Foldable Splice Source 

Methods

fold :: Monoid m => Splice m -> m

foldMap :: Monoid m => (a -> m) -> Splice a -> m

foldr :: (a -> b -> b) -> b -> Splice a -> b

foldr' :: (a -> b -> b) -> b -> Splice a -> b

foldl :: (b -> a -> b) -> b -> Splice a -> b

foldl' :: (b -> a -> b) -> b -> Splice a -> b

foldr1 :: (a -> a -> a) -> Splice a -> a

foldl1 :: (a -> a -> a) -> Splice a -> a

toList :: Splice a -> [a]

null :: Splice a -> Bool

length :: Splice a -> Int

elem :: Eq a => a -> Splice a -> Bool

maximum :: Ord a => Splice a -> a

minimum :: Ord a => Splice a -> a

sum :: Num a => Splice a -> a

product :: Num a => Splice a -> a

Traversable Splice Source 

Methods

traverse :: Applicative f => (a -> f b) -> Splice a -> f (Splice b)

sequenceA :: Applicative f => Splice (f a) -> f (Splice a)

mapM :: Monad m => (a -> m b) -> Splice a -> m (Splice b)

sequence :: Monad m => Splice (m a) -> m (Splice a)

Annotated Splice Source 

Methods

ann :: Splice l -> l Source

amap :: (l -> l) -> Splice l -> Splice l Source

ExactP Splice Source 

Methods

exactP :: Splice SrcSpanInfo -> EP ()

AppFixity Splice Source 
Eq l => Eq (Splice l) Source 

Methods

(==) :: Splice l -> Splice l -> Bool

(/=) :: Splice l -> Splice l -> Bool

Data l => Data (Splice l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Splice l -> c (Splice l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Splice l)

toConstr :: Splice l -> Constr

dataTypeOf :: Splice l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Splice l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Splice l))

gmapT :: (forall b. Data b => b -> b) -> Splice l -> Splice l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Splice l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Splice l -> r

gmapQ :: (forall d. Data d => d -> u) -> Splice l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Splice l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Splice l -> m (Splice l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Splice l -> m (Splice l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Splice l -> m (Splice l)

Ord l => Ord (Splice l) Source 

Methods

compare :: Splice l -> Splice l -> Ordering

(<) :: Splice l -> Splice l -> Bool

(<=) :: Splice l -> Splice l -> Bool

(>) :: Splice l -> Splice l -> Bool

(>=) :: Splice l -> Splice l -> Bool

max :: Splice l -> Splice l -> Splice l

min :: Splice l -> Splice l -> Splice l

Show l => Show (Splice l) Source 

Methods

showsPrec :: Int -> Splice l -> ShowS

show :: Splice l -> String

showList :: [Splice l] -> ShowS

Generic (Splice l) Source 

Associated Types

type Rep (Splice l) :: * -> *

Methods

from :: Splice l -> Rep (Splice l) x

to :: Rep (Splice l) x -> Splice l

SrcInfo loc => Pretty (Splice loc) Source 

Methods

pretty :: Splice loc -> Doc

prettyPrec :: Int -> Splice loc -> Doc

type Rep (Splice l) Source 

FFI

data Safety l Source

The safety of a foreign function call.

Constructors

PlayRisky l

unsafe

PlaySafe l Bool

safe (False) or threadsafe (True)

PlayInterruptible l

interruptible

Instances

Functor Safety Source 

Methods

fmap :: (a -> b) -> Safety a -> Safety b

(<$) :: a -> Safety b -> Safety a

Foldable Safety Source 

Methods

fold :: Monoid m => Safety m -> m

foldMap :: Monoid m => (a -> m) -> Safety a -> m

foldr :: (a -> b -> b) -> b -> Safety a -> b

foldr' :: (a -> b -> b) -> b -> Safety a -> b

foldl :: (b -> a -> b) -> b -> Safety a -> b

foldl' :: (b -> a -> b) -> b -> Safety a -> b

foldr1 :: (a -> a -> a) -> Safety a -> a

foldl1 :: (a -> a -> a) -> Safety a -> a

toList :: Safety a -> [a]

null :: Safety a -> Bool

length :: Safety a -> Int

elem :: Eq a => a -> Safety a -> Bool

maximum :: Ord a => Safety a -> a

minimum :: Ord a => Safety a -> a

sum :: Num a => Safety a -> a

product :: Num a => Safety a -> a

Traversable Safety Source 

Methods

traverse :: Applicative f => (a -> f b) -> Safety a -> f (Safety b)

sequenceA :: Applicative f => Safety (f a) -> f (Safety a)

mapM :: Monad m => (a -> m b) -> Safety a -> m (Safety b)

sequence :: Monad m => Safety (m a) -> m (Safety a)

Annotated Safety Source 

Methods

ann :: Safety l -> l Source

amap :: (l -> l) -> Safety l -> Safety l Source

ExactP Safety Source 

Methods

exactP :: Safety SrcSpanInfo -> EP ()

Eq l => Eq (Safety l) Source 

Methods

(==) :: Safety l -> Safety l -> Bool

(/=) :: Safety l -> Safety l -> Bool

Data l => Data (Safety l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety l -> c (Safety l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Safety l)

toConstr :: Safety l -> Constr

dataTypeOf :: Safety l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Safety l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Safety l))

gmapT :: (forall b. Data b => b -> b) -> Safety l -> Safety l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety l -> r

gmapQ :: (forall d. Data d => d -> u) -> Safety l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety l -> m (Safety l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety l -> m (Safety l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety l -> m (Safety l)

Ord l => Ord (Safety l) Source 

Methods

compare :: Safety l -> Safety l -> Ordering

(<) :: Safety l -> Safety l -> Bool

(<=) :: Safety l -> Safety l -> Bool

(>) :: Safety l -> Safety l -> Bool

(>=) :: Safety l -> Safety l -> Bool

max :: Safety l -> Safety l -> Safety l

min :: Safety l -> Safety l -> Safety l

Show l => Show (Safety l) Source 

Methods

showsPrec :: Int -> Safety l -> ShowS

show :: Safety l -> String

showList :: [Safety l] -> ShowS

Generic (Safety l) Source 

Associated Types

type Rep (Safety l) :: * -> *

Methods

from :: Safety l -> Rep (Safety l) x

to :: Rep (Safety l) x -> Safety l

Pretty (Safety l) Source 

Methods

pretty :: Safety l -> Doc

prettyPrec :: Int -> Safety l -> Doc

type Rep (Safety l) Source 

data CallConv l Source

The calling convention of a foreign function call.

Constructors

StdCall l 
CCall l 
CPlusPlus l 
DotNet l 
Jvm l 
Js l 
JavaScript l 
CApi l 

Instances

Functor CallConv Source 

Methods

fmap :: (a -> b) -> CallConv a -> CallConv b

(<$) :: a -> CallConv b -> CallConv a

Foldable CallConv Source 

Methods

fold :: Monoid m => CallConv m -> m

foldMap :: Monoid m => (a -> m) -> CallConv a -> m

foldr :: (a -> b -> b) -> b -> CallConv a -> b

foldr' :: (a -> b -> b) -> b -> CallConv a -> b

foldl :: (b -> a -> b) -> b -> CallConv a -> b

foldl' :: (b -> a -> b) -> b -> CallConv a -> b

foldr1 :: (a -> a -> a) -> CallConv a -> a

foldl1 :: (a -> a -> a) -> CallConv a -> a

toList :: CallConv a -> [a]

null :: CallConv a -> Bool

length :: CallConv a -> Int

elem :: Eq a => a -> CallConv a -> Bool

maximum :: Ord a => CallConv a -> a

minimum :: Ord a => CallConv a -> a

sum :: Num a => CallConv a -> a

product :: Num a => CallConv a -> a

Traversable CallConv Source 

Methods

traverse :: Applicative f => (a -> f b) -> CallConv a -> f (CallConv b)

sequenceA :: Applicative f => CallConv (f a) -> f (CallConv a)

mapM :: Monad m => (a -> m b) -> CallConv a -> m (CallConv b)

sequence :: Monad m => CallConv (m a) -> m (CallConv a)

Annotated CallConv Source 

Methods

ann :: CallConv l -> l Source

amap :: (l -> l) -> CallConv l -> CallConv l Source

ExactP CallConv Source 

Methods

exactP :: CallConv SrcSpanInfo -> EP ()

Eq l => Eq (CallConv l) Source 

Methods

(==) :: CallConv l -> CallConv l -> Bool

(/=) :: CallConv l -> CallConv l -> Bool

Data l => Data (CallConv l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CallConv l -> c (CallConv l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CallConv l)

toConstr :: CallConv l -> Constr

dataTypeOf :: CallConv l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CallConv l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CallConv l))

gmapT :: (forall b. Data b => b -> b) -> CallConv l -> CallConv l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CallConv l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CallConv l -> r

gmapQ :: (forall d. Data d => d -> u) -> CallConv l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CallConv l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CallConv l -> m (CallConv l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CallConv l -> m (CallConv l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CallConv l -> m (CallConv l)

Ord l => Ord (CallConv l) Source 

Methods

compare :: CallConv l -> CallConv l -> Ordering

(<) :: CallConv l -> CallConv l -> Bool

(<=) :: CallConv l -> CallConv l -> Bool

(>) :: CallConv l -> CallConv l -> Bool

(>=) :: CallConv l -> CallConv l -> Bool

max :: CallConv l -> CallConv l -> CallConv l

min :: CallConv l -> CallConv l -> CallConv l

Show l => Show (CallConv l) Source 

Methods

showsPrec :: Int -> CallConv l -> ShowS

show :: CallConv l -> String

showList :: [CallConv l] -> ShowS

Generic (CallConv l) Source 

Associated Types

type Rep (CallConv l) :: * -> *

Methods

from :: CallConv l -> Rep (CallConv l) x

to :: Rep (CallConv l) x -> CallConv l

Pretty (CallConv l) Source 

Methods

pretty :: CallConv l -> Doc

prettyPrec :: Int -> CallConv l -> Doc

type Rep (CallConv l) Source 

Pragmas

data ModulePragma l Source

A top level options pragma, preceding the module header.

Constructors

LanguagePragma l [Name l]

LANGUAGE pragma

OptionsPragma l (Maybe Tool) String

OPTIONS pragma, possibly qualified with a tool, e.g. OPTIONS_GHC

AnnModulePragma l (Annotation l)

ANN pragma with module scope

Instances

Functor ModulePragma Source 

Methods

fmap :: (a -> b) -> ModulePragma a -> ModulePragma b

(<$) :: a -> ModulePragma b -> ModulePragma a

Foldable ModulePragma Source 

Methods

fold :: Monoid m => ModulePragma m -> m

foldMap :: Monoid m => (a -> m) -> ModulePragma a -> m

foldr :: (a -> b -> b) -> b -> ModulePragma a -> b

foldr' :: (a -> b -> b) -> b -> ModulePragma a -> b

foldl :: (b -> a -> b) -> b -> ModulePragma a -> b

foldl' :: (b -> a -> b) -> b -> ModulePragma a -> b

foldr1 :: (a -> a -> a) -> ModulePragma a -> a

foldl1 :: (a -> a -> a) -> ModulePragma a -> a

toList :: ModulePragma a -> [a]

null :: ModulePragma a -> Bool

length :: ModulePragma a -> Int

elem :: Eq a => a -> ModulePragma a -> Bool

maximum :: Ord a => ModulePragma a -> a

minimum :: Ord a => ModulePragma a -> a

sum :: Num a => ModulePragma a -> a

product :: Num a => ModulePragma a -> a

Traversable ModulePragma Source 

Methods

traverse :: Applicative f => (a -> f b) -> ModulePragma a -> f (ModulePragma b)

sequenceA :: Applicative f => ModulePragma (f a) -> f (ModulePragma a)

mapM :: Monad m => (a -> m b) -> ModulePragma a -> m (ModulePragma b)

sequence :: Monad m => ModulePragma (m a) -> m (ModulePragma a)

Annotated ModulePragma Source 

Methods

ann :: ModulePragma l -> l Source

amap :: (l -> l) -> ModulePragma l -> ModulePragma l Source

ExactP ModulePragma Source 

Methods

exactP :: ModulePragma SrcSpanInfo -> EP ()

Eq l => Eq (ModulePragma l) Source 
Data l => Data (ModulePragma l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModulePragma l -> c (ModulePragma l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ModulePragma l)

toConstr :: ModulePragma l -> Constr

dataTypeOf :: ModulePragma l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ModulePragma l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ModulePragma l))

gmapT :: (forall b. Data b => b -> b) -> ModulePragma l -> ModulePragma l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModulePragma l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModulePragma l -> r

gmapQ :: (forall d. Data d => d -> u) -> ModulePragma l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModulePragma l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModulePragma l -> m (ModulePragma l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModulePragma l -> m (ModulePragma l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModulePragma l -> m (ModulePragma l)

Ord l => Ord (ModulePragma l) Source 
Show l => Show (ModulePragma l) Source 
Generic (ModulePragma l) Source 

Associated Types

type Rep (ModulePragma l) :: * -> *

Methods

from :: ModulePragma l -> Rep (ModulePragma l) x

to :: Rep (ModulePragma l) x -> ModulePragma l

Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) Source 
SrcInfo loc => Pretty (ModulePragma loc) Source 

Methods

pretty :: ModulePragma loc -> Doc

prettyPrec :: Int -> ModulePragma loc -> Doc

type Rep (ModulePragma l) 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 l Source

Recognised overlaps for overlap pragmas.

Constructors

NoOverlap l

NO_OVERLAP pragma

Overlap l

OVERLAP pragma

Incoherent l

INCOHERENT pragma

Instances

Functor Overlap Source 

Methods

fmap :: (a -> b) -> Overlap a -> Overlap b

(<$) :: a -> Overlap b -> Overlap a

Foldable Overlap Source 

Methods

fold :: Monoid m => Overlap m -> m

foldMap :: Monoid m => (a -> m) -> Overlap a -> m

foldr :: (a -> b -> b) -> b -> Overlap a -> b

foldr' :: (a -> b -> b) -> b -> Overlap a -> b

foldl :: (b -> a -> b) -> b -> Overlap a -> b

foldl' :: (b -> a -> b) -> b -> Overlap a -> b

foldr1 :: (a -> a -> a) -> Overlap a -> a

foldl1 :: (a -> a -> a) -> Overlap a -> a

toList :: Overlap a -> [a]

null :: Overlap a -> Bool

length :: Overlap a -> Int

elem :: Eq a => a -> Overlap a -> Bool

maximum :: Ord a => Overlap a -> a

minimum :: Ord a => Overlap a -> a

sum :: Num a => Overlap a -> a

product :: Num a => Overlap a -> a

Traversable Overlap Source 

Methods

traverse :: Applicative f => (a -> f b) -> Overlap a -> f (Overlap b)

sequenceA :: Applicative f => Overlap (f a) -> f (Overlap a)

mapM :: Monad m => (a -> m b) -> Overlap a -> m (Overlap b)

sequence :: Monad m => Overlap (m a) -> m (Overlap a)

Annotated Overlap Source 

Methods

ann :: Overlap l -> l Source

amap :: (l -> l) -> Overlap l -> Overlap l Source

ExactP Overlap Source 

Methods

exactP :: Overlap SrcSpanInfo -> EP ()

Eq l => Eq (Overlap l) Source 

Methods

(==) :: Overlap l -> Overlap l -> Bool

(/=) :: Overlap l -> Overlap l -> Bool

Data l => Data (Overlap l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Overlap l -> c (Overlap l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Overlap l)

toConstr :: Overlap l -> Constr

dataTypeOf :: Overlap l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Overlap l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Overlap l))

gmapT :: (forall b. Data b => b -> b) -> Overlap l -> Overlap l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Overlap l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Overlap l -> r

gmapQ :: (forall d. Data d => d -> u) -> Overlap l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Overlap l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Overlap l -> m (Overlap l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap l -> m (Overlap l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap l -> m (Overlap l)

Ord l => Ord (Overlap l) Source 

Methods

compare :: Overlap l -> Overlap l -> Ordering

(<) :: Overlap l -> Overlap l -> Bool

(<=) :: Overlap l -> Overlap l -> Bool

(>) :: Overlap l -> Overlap l -> Bool

(>=) :: Overlap l -> Overlap l -> Bool

max :: Overlap l -> Overlap l -> Overlap l

min :: Overlap l -> Overlap l -> Overlap l

Show l => Show (Overlap l) Source 

Methods

showsPrec :: Int -> Overlap l -> ShowS

show :: Overlap l -> String

showList :: [Overlap l] -> ShowS

Generic (Overlap l) Source 

Associated Types

type Rep (Overlap l) :: * -> *

Methods

from :: Overlap l -> Rep (Overlap l) x

to :: Rep (Overlap l) x -> Overlap l

type Rep (Overlap l) Source 

data Rule l Source

The body of a RULES pragma.

Constructors

Rule l String (Maybe (Activation l)) (Maybe [RuleVar l]) (Exp l) (Exp l) 

Instances

Functor Rule Source 

Methods

fmap :: (a -> b) -> Rule a -> Rule b

(<$) :: a -> Rule b -> Rule a

Foldable Rule Source 

Methods

fold :: Monoid m => Rule m -> m

foldMap :: Monoid m => (a -> m) -> Rule a -> m

foldr :: (a -> b -> b) -> b -> Rule a -> b

foldr' :: (a -> b -> b) -> b -> Rule a -> b

foldl :: (b -> a -> b) -> b -> Rule a -> b

foldl' :: (b -> a -> b) -> b -> Rule a -> b

foldr1 :: (a -> a -> a) -> Rule a -> a

foldl1 :: (a -> a -> a) -> Rule a -> a

toList :: Rule a -> [a]

null :: Rule a -> Bool

length :: Rule a -> Int

elem :: Eq a => a -> Rule a -> Bool

maximum :: Ord a => Rule a -> a

minimum :: Ord a => Rule a -> a

sum :: Num a => Rule a -> a

product :: Num a => Rule a -> a

Traversable Rule Source 

Methods

traverse :: Applicative f => (a -> f b) -> Rule a -> f (Rule b)

sequenceA :: Applicative f => Rule (f a) -> f (Rule a)

mapM :: Monad m => (a -> m b) -> Rule a -> m (Rule b)

sequence :: Monad m => Rule (m a) -> m (Rule a)

Annotated Rule Source 

Methods

ann :: Rule l -> l Source

amap :: (l -> l) -> Rule l -> Rule l Source

ExactP Rule Source 

Methods

exactP :: Rule SrcSpanInfo -> EP ()

Eq l => Eq (Rule l) Source 

Methods

(==) :: Rule l -> Rule l -> Bool

(/=) :: Rule l -> Rule l -> Bool

Data l => Data (Rule l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rule l -> c (Rule l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rule l)

toConstr :: Rule l -> Constr

dataTypeOf :: Rule l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Rule l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rule l))

gmapT :: (forall b. Data b => b -> b) -> Rule l -> Rule l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule l -> r

gmapQ :: (forall d. Data d => d -> u) -> Rule l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule l -> m (Rule l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule l -> m (Rule l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule l -> m (Rule l)

Ord l => Ord (Rule l) Source 

Methods

compare :: Rule l -> Rule l -> Ordering

(<) :: Rule l -> Rule l -> Bool

(<=) :: Rule l -> Rule l -> Bool

(>) :: Rule l -> Rule l -> Bool

(>=) :: Rule l -> Rule l -> Bool

max :: Rule l -> Rule l -> Rule l

min :: Rule l -> Rule l -> Rule l

Show l => Show (Rule l) Source 

Methods

showsPrec :: Int -> Rule l -> ShowS

show :: Rule l -> String

showList :: [Rule l] -> ShowS

Generic (Rule l) Source 

Associated Types

type Rep (Rule l) :: * -> *

Methods

from :: Rule l -> Rep (Rule l) x

to :: Rep (Rule l) x -> Rule l

SrcInfo loc => Pretty (Rule loc) Source 

Methods

pretty :: Rule loc -> Doc

prettyPrec :: Int -> Rule loc -> Doc

type Rep (Rule l) Source 

data RuleVar l Source

Variables used in a RULES pragma, optionally annotated with types

Constructors

RuleVar l (Name l) 
TypedRuleVar l (Name l) (Type l) 

Instances

Functor RuleVar Source 

Methods

fmap :: (a -> b) -> RuleVar a -> RuleVar b

(<$) :: a -> RuleVar b -> RuleVar a

Foldable RuleVar Source 

Methods

fold :: Monoid m => RuleVar m -> m

foldMap :: Monoid m => (a -> m) -> RuleVar a -> m

foldr :: (a -> b -> b) -> b -> RuleVar a -> b

foldr' :: (a -> b -> b) -> b -> RuleVar a -> b

foldl :: (b -> a -> b) -> b -> RuleVar a -> b

foldl' :: (b -> a -> b) -> b -> RuleVar a -> b

foldr1 :: (a -> a -> a) -> RuleVar a -> a

foldl1 :: (a -> a -> a) -> RuleVar a -> a

toList :: RuleVar a -> [a]

null :: RuleVar a -> Bool

length :: RuleVar a -> Int

elem :: Eq a => a -> RuleVar a -> Bool

maximum :: Ord a => RuleVar a -> a

minimum :: Ord a => RuleVar a -> a

sum :: Num a => RuleVar a -> a

product :: Num a => RuleVar a -> a

Traversable RuleVar Source 

Methods

traverse :: Applicative f => (a -> f b) -> RuleVar a -> f (RuleVar b)

sequenceA :: Applicative f => RuleVar (f a) -> f (RuleVar a)

mapM :: Monad m => (a -> m b) -> RuleVar a -> m (RuleVar b)

sequence :: Monad m => RuleVar (m a) -> m (RuleVar a)

Annotated RuleVar Source 

Methods

ann :: RuleVar l -> l Source

amap :: (l -> l) -> RuleVar l -> RuleVar l Source

ExactP RuleVar Source 

Methods

exactP :: RuleVar SrcSpanInfo -> EP ()

Eq l => Eq (RuleVar l) Source 

Methods

(==) :: RuleVar l -> RuleVar l -> Bool

(/=) :: RuleVar l -> RuleVar l -> Bool

Data l => Data (RuleVar l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleVar l -> c (RuleVar l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleVar l)

toConstr :: RuleVar l -> Constr

dataTypeOf :: RuleVar l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RuleVar l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleVar l))

gmapT :: (forall b. Data b => b -> b) -> RuleVar l -> RuleVar l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleVar l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleVar l -> r

gmapQ :: (forall d. Data d => d -> u) -> RuleVar l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleVar l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleVar l -> m (RuleVar l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleVar l -> m (RuleVar l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleVar l -> m (RuleVar l)

Ord l => Ord (RuleVar l) Source 

Methods

compare :: RuleVar l -> RuleVar l -> Ordering

(<) :: RuleVar l -> RuleVar l -> Bool

(<=) :: RuleVar l -> RuleVar l -> Bool

(>) :: RuleVar l -> RuleVar l -> Bool

(>=) :: RuleVar l -> RuleVar l -> Bool

max :: RuleVar l -> RuleVar l -> RuleVar l

min :: RuleVar l -> RuleVar l -> RuleVar l

Show l => Show (RuleVar l) Source 

Methods

showsPrec :: Int -> RuleVar l -> ShowS

show :: RuleVar l -> String

showList :: [RuleVar l] -> ShowS

Generic (RuleVar l) Source 

Associated Types

type Rep (RuleVar l) :: * -> *

Methods

from :: RuleVar l -> Rep (RuleVar l) x

to :: Rep (RuleVar l) x -> RuleVar l

SrcInfo l => Pretty (RuleVar l) Source 

Methods

pretty :: RuleVar l -> Doc

prettyPrec :: Int -> RuleVar l -> Doc

type Rep (RuleVar l) Source 

data Activation l Source

Activation clause of a RULES pragma.

Constructors

ActiveFrom l Int 
ActiveUntil l Int 

Instances

Functor Activation Source 

Methods

fmap :: (a -> b) -> Activation a -> Activation b

(<$) :: a -> Activation b -> Activation a

Foldable Activation Source 

Methods

fold :: Monoid m => Activation m -> m

foldMap :: Monoid m => (a -> m) -> Activation a -> m

foldr :: (a -> b -> b) -> b -> Activation a -> b

foldr' :: (a -> b -> b) -> b -> Activation a -> b

foldl :: (b -> a -> b) -> b -> Activation a -> b

foldl' :: (b -> a -> b) -> b -> Activation a -> b

foldr1 :: (a -> a -> a) -> Activation a -> a

foldl1 :: (a -> a -> a) -> Activation a -> a

toList :: Activation a -> [a]

null :: Activation a -> Bool

length :: Activation a -> Int

elem :: Eq a => a -> Activation a -> Bool

maximum :: Ord a => Activation a -> a

minimum :: Ord a => Activation a -> a

sum :: Num a => Activation a -> a

product :: Num a => Activation a -> a

Traversable Activation Source 

Methods

traverse :: Applicative f => (a -> f b) -> Activation a -> f (Activation b)

sequenceA :: Applicative f => Activation (f a) -> f (Activation a)

mapM :: Monad m => (a -> m b) -> Activation a -> m (Activation b)

sequence :: Monad m => Activation (m a) -> m (Activation a)

Annotated Activation Source 

Methods

ann :: Activation l -> l Source

amap :: (l -> l) -> Activation l -> Activation l Source

ExactP Activation Source 

Methods

exactP :: Activation SrcSpanInfo -> EP ()

Eq l => Eq (Activation l) Source 

Methods

(==) :: Activation l -> Activation l -> Bool

(/=) :: Activation l -> Activation l -> Bool

Data l => Data (Activation l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation l -> c (Activation l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Activation l)

toConstr :: Activation l -> Constr

dataTypeOf :: Activation l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Activation l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Activation l))

gmapT :: (forall b. Data b => b -> b) -> Activation l -> Activation l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation l -> r

gmapQ :: (forall d. Data d => d -> u) -> Activation l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation l -> m (Activation l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation l -> m (Activation l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation l -> m (Activation l)

Ord l => Ord (Activation l) Source 
Show l => Show (Activation l) Source 
Generic (Activation l) Source 

Associated Types

type Rep (Activation l) :: * -> *

Methods

from :: Activation l -> Rep (Activation l) x

to :: Rep (Activation l) x -> Activation l

Pretty (Activation l) Source 

Methods

pretty :: Activation l -> Doc

prettyPrec :: Int -> Activation l -> Doc

type Rep (Activation l) Source 

data Annotation l Source

An annotation through an ANN pragma.

Constructors

Ann l (Name l) (Exp l)

An annotation for a declared name.

TypeAnn l (Name l) (Exp l)

An annotation for a declared type.

ModuleAnn l (Exp l)

An annotation for the defining module.

Instances

Functor Annotation Source 

Methods

fmap :: (a -> b) -> Annotation a -> Annotation b

(<$) :: a -> Annotation b -> Annotation a

Foldable Annotation Source 

Methods

fold :: Monoid m => Annotation m -> m

foldMap :: Monoid m => (a -> m) -> Annotation a -> m

foldr :: (a -> b -> b) -> b -> Annotation a -> b

foldr' :: (a -> b -> b) -> b -> Annotation a -> b

foldl :: (b -> a -> b) -> b -> Annotation a -> b

foldl' :: (b -> a -> b) -> b -> Annotation a -> b

foldr1 :: (a -> a -> a) -> Annotation a -> a

foldl1 :: (a -> a -> a) -> Annotation a -> a

toList :: Annotation a -> [a]

null :: Annotation a -> Bool

length :: Annotation a -> Int

elem :: Eq a => a -> Annotation a -> Bool

maximum :: Ord a => Annotation a -> a

minimum :: Ord a => Annotation a -> a

sum :: Num a => Annotation a -> a

product :: Num a => Annotation a -> a

Traversable Annotation Source 

Methods

traverse :: Applicative f => (a -> f b) -> Annotation a -> f (Annotation b)

sequenceA :: Applicative f => Annotation (f a) -> f (Annotation a)

mapM :: Monad m => (a -> m b) -> Annotation a -> m (Annotation b)

sequence :: Monad m => Annotation (m a) -> m (Annotation a)

Annotated Annotation Source 

Methods

ann :: Annotation l -> l Source

amap :: (l -> l) -> Annotation l -> Annotation l Source

ExactP Annotation Source 

Methods

exactP :: Annotation SrcSpanInfo -> EP ()

AppFixity Annotation Source 
Eq l => Eq (Annotation l) Source 

Methods

(==) :: Annotation l -> Annotation l -> Bool

(/=) :: Annotation l -> Annotation l -> Bool

Data l => Data (Annotation l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation l -> c (Annotation l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Annotation l)

toConstr :: Annotation l -> Constr

dataTypeOf :: Annotation l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Annotation l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Annotation l))

gmapT :: (forall b. Data b => b -> b) -> Annotation l -> Annotation l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation l -> r

gmapQ :: (forall d. Data d => d -> u) -> Annotation l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation l -> m (Annotation l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation l -> m (Annotation l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation l -> m (Annotation l)

Ord l => Ord (Annotation l) Source 
Show l => Show (Annotation l) Source 
Generic (Annotation l) Source 

Associated Types

type Rep (Annotation l) :: * -> *

Methods

from :: Annotation l -> Rep (Annotation l) x

to :: Rep (Annotation l) x -> Annotation l

SrcInfo loc => Pretty (Annotation loc) Source 

Methods

pretty :: Annotation loc -> Doc

prettyPrec :: Int -> Annotation loc -> Doc

type Rep (Annotation l) Source 

data BooleanFormula l Source

A boolean formula for MINIMAL pragmas.

Constructors

VarFormula l (Name l)

A variable.

AndFormula l [BooleanFormula l]

And boolean formulas.

OrFormula l [BooleanFormula l]

Or boolean formulas.

ParenFormula l (BooleanFormula l)

Parenthesized boolean formulas.

Instances

Functor BooleanFormula Source 

Methods

fmap :: (a -> b) -> BooleanFormula a -> BooleanFormula b

(<$) :: a -> BooleanFormula b -> BooleanFormula a

Foldable BooleanFormula Source 

Methods

fold :: Monoid m => BooleanFormula m -> m

foldMap :: Monoid m => (a -> m) -> BooleanFormula a -> m

foldr :: (a -> b -> b) -> b -> BooleanFormula a -> b

foldr' :: (a -> b -> b) -> b -> BooleanFormula a -> b

foldl :: (b -> a -> b) -> b -> BooleanFormula a -> b

foldl' :: (b -> a -> b) -> b -> BooleanFormula a -> b

foldr1 :: (a -> a -> a) -> BooleanFormula a -> a

foldl1 :: (a -> a -> a) -> BooleanFormula a -> a

toList :: BooleanFormula a -> [a]

null :: BooleanFormula a -> Bool

length :: BooleanFormula a -> Int

elem :: Eq a => a -> BooleanFormula a -> Bool

maximum :: Ord a => BooleanFormula a -> a

minimum :: Ord a => BooleanFormula a -> a

sum :: Num a => BooleanFormula a -> a

product :: Num a => BooleanFormula a -> a

Traversable BooleanFormula Source 

Methods

traverse :: Applicative f => (a -> f b) -> BooleanFormula a -> f (BooleanFormula b)

sequenceA :: Applicative f => BooleanFormula (f a) -> f (BooleanFormula a)

mapM :: Monad m => (a -> m b) -> BooleanFormula a -> m (BooleanFormula b)

sequence :: Monad m => BooleanFormula (m a) -> m (BooleanFormula a)

Annotated BooleanFormula Source 

Methods

ann :: BooleanFormula l -> l Source

amap :: (l -> l) -> BooleanFormula l -> BooleanFormula l Source

ExactP BooleanFormula Source 

Methods

exactP :: BooleanFormula SrcSpanInfo -> EP ()

Eq l => Eq (BooleanFormula l) Source 
Data l => Data (BooleanFormula l) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BooleanFormula l -> c (BooleanFormula l)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BooleanFormula l)

toConstr :: BooleanFormula l -> Constr

dataTypeOf :: BooleanFormula l -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (BooleanFormula l))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BooleanFormula l))

gmapT :: (forall b. Data b => b -> b) -> BooleanFormula l -> BooleanFormula l

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BooleanFormula l -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BooleanFormula l -> r

gmapQ :: (forall d. Data d => d -> u) -> BooleanFormula l -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> BooleanFormula l -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BooleanFormula l -> m (BooleanFormula l)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanFormula l -> m (BooleanFormula l)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanFormula l -> m (BooleanFormula l)

Ord l => Ord (BooleanFormula l) Source 
Show l => Show (BooleanFormula l) Source 
Generic (BooleanFormula l) Source 

Associated Types

type Rep (BooleanFormula l) :: * -> *

type Rep (BooleanFormula l) Source 

Builtin names

Modules

Main function of a program

Constructors

unit_con :: l -> Exp l Source

tuple_con :: l -> Boxed -> Int -> Exp l Source

Special identifiers

as_name :: l -> Name l Source

dot_name :: l -> Name l Source

jvm_name :: l -> Name l Source

js_name :: l -> Name l Source

Type constructors

tuple_tycon :: l -> Boxed -> Int -> Type l Source

Source coordinates

Annotated trees

class Functor ast => Annotated ast where Source

AST nodes are annotated, and this class allows manipulation of the annotations.

Methods

ann :: ast l -> l Source

Retrieve the annotation of an AST node.

amap :: (l -> l) -> ast l -> ast l Source

Change the annotation of an AST node. Note that only the annotation of the node itself is affected, and not the annotations of any child nodes. if all nodes in the AST tree are to be affected, use fmap.

Instances

Annotated Alt Source 

Methods

ann :: Alt l -> l Source

amap :: (l -> l) -> Alt l -> Alt l Source

Annotated FieldUpdate Source 

Methods

ann :: FieldUpdate l -> l Source

amap :: (l -> l) -> FieldUpdate l -> FieldUpdate l Source

Annotated QualStmt Source 

Methods

ann :: QualStmt l -> l Source

amap :: (l -> l) -> QualStmt l -> QualStmt l Source

Annotated Stmt Source 

Methods

ann :: Stmt l -> l Source

amap :: (l -> l) -> Stmt l -> Stmt l Source

Annotated PatField Source 

Methods

ann :: PatField l -> l Source

amap :: (l -> l) -> PatField l -> PatField l Source

Annotated RPat Source 

Methods

ann :: RPat l -> l Source

amap :: (l -> l) -> RPat l -> RPat l Source

Annotated RPatOp Source 

Methods

ann :: RPatOp l -> l Source

amap :: (l -> l) -> RPatOp l -> RPatOp l Source

Annotated PXAttr Source 

Methods

ann :: PXAttr l -> l Source

amap :: (l -> l) -> PXAttr l -> PXAttr l Source

Annotated Pat Source 

Methods

ann :: Pat l -> l Source

amap :: (l -> l) -> Pat l -> Pat l Source

Annotated WarningText Source 

Methods

ann :: WarningText l -> l Source

amap :: (l -> l) -> WarningText l -> WarningText l Source

Annotated RuleVar Source 

Methods

ann :: RuleVar l -> l Source

amap :: (l -> l) -> RuleVar l -> RuleVar l Source

Annotated Rule Source 

Methods

ann :: Rule l -> l Source

amap :: (l -> l) -> Rule l -> Rule l Source

Annotated Activation Source 

Methods

ann :: Activation l -> l Source

amap :: (l -> l) -> Activation l -> Activation l Source

Annotated Overlap Source 

Methods

ann :: Overlap l -> l Source

amap :: (l -> l) -> Overlap l -> Overlap l Source

Annotated ModulePragma Source 

Methods

ann :: ModulePragma l -> l Source

amap :: (l -> l) -> ModulePragma l -> ModulePragma l Source

Annotated CallConv Source 

Methods

ann :: CallConv l -> l Source

amap :: (l -> l) -> CallConv l -> CallConv l Source

Annotated Safety Source 

Methods

ann :: Safety l -> l Source

amap :: (l -> l) -> Safety l -> Safety l Source

Annotated Splice Source 

Methods

ann :: Splice l -> l Source

amap :: (l -> l) -> Splice l -> Splice l Source

Annotated Bracket Source 

Methods

ann :: Bracket l -> l Source

amap :: (l -> l) -> Bracket l -> Bracket l Source

Annotated XAttr Source 

Methods

ann :: XAttr l -> l Source

amap :: (l -> l) -> XAttr l -> XAttr l Source

Annotated XName Source 

Methods

ann :: XName l -> l Source

amap :: (l -> l) -> XName l -> XName l Source

Annotated Exp Source 

Methods

ann :: Exp l -> l Source

amap :: (l -> l) -> Exp l -> Exp l Source

Annotated Sign Source 

Methods

ann :: Sign l -> l Source

amap :: (l -> l) -> Sign l -> Sign l Source

Annotated Literal Source 

Methods

ann :: Literal l -> l Source

amap :: (l -> l) -> Literal l -> Literal l Source

Annotated Asst Source 

Methods

ann :: Asst l -> l Source

amap :: (l -> l) -> Asst l -> Asst l Source

Annotated Context Source 

Methods

ann :: Context l -> l Source

amap :: (l -> l) -> Context l -> Context l Source

Annotated FunDep Source 

Methods

ann :: FunDep l -> l Source

amap :: (l -> l) -> FunDep l -> FunDep l Source

Annotated Kind Source 

Methods

ann :: Kind l -> l Source

amap :: (l -> l) -> Kind l -> Kind l Source

Annotated TyVarBind Source 

Methods

ann :: TyVarBind l -> l Source

amap :: (l -> l) -> TyVarBind l -> TyVarBind l Source

Annotated Promoted Source 

Methods

ann :: Promoted l -> l Source

amap :: (l -> l) -> Promoted l -> Promoted l Source

Annotated Type Source 

Methods

ann :: Type l -> l Source

amap :: (l -> l) -> Type l -> Type l Source

Annotated GuardedRhs Source 

Methods

ann :: GuardedRhs l -> l Source

amap :: (l -> l) -> GuardedRhs l -> GuardedRhs l Source

Annotated Rhs Source 

Methods

ann :: Rhs l -> l Source

amap :: (l -> l) -> Rhs l -> Rhs l Source

Annotated BangType Source 

Methods

ann :: BangType l -> l Source

amap :: (l -> l) -> BangType l -> BangType l Source

Annotated InstDecl Source 

Methods

ann :: InstDecl l -> l Source

amap :: (l -> l) -> InstDecl l -> InstDecl l Source

Annotated ClassDecl Source 

Methods

ann :: ClassDecl l -> l Source

amap :: (l -> l) -> ClassDecl l -> ClassDecl l Source

Annotated GadtDecl Source 

Methods

ann :: GadtDecl l -> l Source

amap :: (l -> l) -> GadtDecl l -> GadtDecl l Source

Annotated FieldDecl Source 

Methods

ann :: FieldDecl l -> l Source

amap :: (l -> l) -> FieldDecl l -> FieldDecl l Source

Annotated ConDecl Source 

Methods

ann :: ConDecl l -> l Source

amap :: (l -> l) -> ConDecl l -> ConDecl l Source

Annotated QualConDecl Source 

Methods

ann :: QualConDecl l -> l Source

amap :: (l -> l) -> QualConDecl l -> QualConDecl l Source

Annotated Match Source 

Methods

ann :: Match l -> l Source

amap :: (l -> l) -> Match l -> Match l Source

Annotated IPBind Source 

Methods

ann :: IPBind l -> l Source

amap :: (l -> l) -> IPBind l -> IPBind l Source

Annotated Binds Source 

Methods

ann :: Binds l -> l Source

amap :: (l -> l) -> Binds l -> Binds l Source

Annotated Deriving Source 

Methods

ann :: Deriving l -> l Source

amap :: (l -> l) -> Deriving l -> Deriving l Source

Annotated InstHead Source 

Methods

ann :: InstHead l -> l Source

amap :: (l -> l) -> InstHead l -> InstHead l Source

Annotated InstRule Source 

Methods

ann :: InstRule l -> l Source

amap :: (l -> l) -> InstRule l -> InstRule l Source

Annotated DeclHead Source 

Methods

ann :: DeclHead l -> l Source

amap :: (l -> l) -> DeclHead l -> DeclHead l Source

Annotated DataOrNew Source 

Methods

ann :: DataOrNew l -> l Source

amap :: (l -> l) -> DataOrNew l -> DataOrNew l Source

Annotated Role Source 

Methods

ann :: Role l -> l Source

amap :: (l -> l) -> Role l -> Role l Source

Annotated BooleanFormula Source 

Methods

ann :: BooleanFormula l -> l Source

amap :: (l -> l) -> BooleanFormula l -> BooleanFormula l Source

Annotated Annotation Source 

Methods

ann :: Annotation l -> l Source

amap :: (l -> l) -> Annotation l -> Annotation l Source

Annotated TypeEqn Source 

Methods

ann :: TypeEqn l -> l Source

amap :: (l -> l) -> TypeEqn l -> TypeEqn l Source

Annotated Decl Source 

Methods

ann :: Decl l -> l Source

amap :: (l -> l) -> Decl l -> Decl l Source

Annotated Assoc Source 

Methods

ann :: Assoc l -> l Source

amap :: (l -> l) -> Assoc l -> Assoc l Source

Annotated ImportSpec Source 

Methods

ann :: ImportSpec l -> l Source

amap :: (l -> l) -> ImportSpec l -> ImportSpec l Source

Annotated ImportSpecList Source 

Methods

ann :: ImportSpecList l -> l Source

amap :: (l -> l) -> ImportSpecList l -> ImportSpecList l Source

Annotated ImportDecl Source 

Methods

ann :: ImportDecl l -> l Source

amap :: (l -> l) -> ImportDecl l -> ImportDecl l Source

Annotated Namespace Source 

Methods

ann :: Namespace l -> l Source

amap :: (l -> l) -> Namespace l -> Namespace l Source

Annotated ExportSpec Source 

Methods

ann :: ExportSpec l -> l Source

amap :: (l -> l) -> ExportSpec l -> ExportSpec l Source

Annotated ExportSpecList Source 

Methods

ann :: ExportSpecList l -> l Source

amap :: (l -> l) -> ExportSpecList l -> ExportSpecList l Source

Annotated ModuleHead Source 

Methods

ann :: ModuleHead l -> l Source

amap :: (l -> l) -> ModuleHead l -> ModuleHead l Source

Annotated Module Source 

Methods

ann :: Module l -> l Source

amap :: (l -> l) -> Module l -> Module l Source

Annotated CName Source 

Methods

ann :: CName l -> l Source

amap :: (l -> l) -> CName l -> CName l Source

Annotated Op Source 

Methods

ann :: Op l -> l Source

amap :: (l -> l) -> Op l -> Op l Source

Annotated QOp Source 

Methods

ann :: QOp l -> l Source

amap :: (l -> l) -> QOp l -> QOp l Source

Annotated IPName Source 

Methods

ann :: IPName l -> l Source

amap :: (l -> l) -> IPName l -> IPName l Source

Annotated Name Source 

Methods

ann :: Name l -> l Source

amap :: (l -> l) -> Name l -> Name l Source

Annotated QName Source 

Methods

ann :: QName l -> l Source

amap :: (l -> l) -> QName l -> QName l Source

Annotated SpecialCon Source 

Methods

ann :: SpecialCon l -> l Source

amap :: (l -> l) -> SpecialCon l -> SpecialCon l Source

Annotated ModuleName Source 

Methods

ann :: ModuleName l -> l Source

amap :: (l -> l) -> ModuleName l -> ModuleName l Source

(=~=) :: (Annotated a, Eq (a ())) => a l1 -> a l2 -> Bool Source

Test if two AST elements are equal modulo annotations.