haskell-src-exts-1.23.1: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer
Copyright (c) Niklas Broberg 2004-2009
(c) The GHC Team 1997-2000
License BSD-style (see the file LICENSE.txt)
Maintainer Niklas Broberg, d00nibro@chalmers.se
Stability stable
Portability portable
Safe Haskell Safe-Inferred
Language Haskell98

Language.Haskell.Exts.Syntax

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

Instances details
Functor Module Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Module Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Module Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Module Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Module Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Module Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Module l -> Constr Source #

dataTypeOf :: Module l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Module l) :: Type -> Type Source #

Pretty ( Module pos) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Module pos -> Doc

prettyPrec :: Int -> Module pos -> Doc

Parseable ( Module SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Module l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Module l) = D1 (' MetaData "Module" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ( C1 (' MetaCons "Module" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ModuleHead l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ ModulePragma l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ ImportDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Decl l])))) :+: ( C1 (' MetaCons "XmlPage" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( ModuleName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ ModulePragma l]))) :*: (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ XAttr l])) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Exp l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l])))) :+: C1 (' MetaCons "XmlHybrid" ' PrefixI ' False ) ((( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ModuleHead l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ ModulePragma l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ ImportDecl l]))) :*: (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Decl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ XAttr l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Exp l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l])))))))

data ModuleHead l Source #

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

Instances

Instances details
Functor ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ModuleHead l -> Constr Source #

dataTypeOf :: ModuleHead l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ModuleHead l) :: Type -> Type Source #

Pretty ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ModuleHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data WarningText l Source #

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

Instances

Instances details
Functor WarningText Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable WarningText Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable WarningText Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated WarningText Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP WarningText Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: WarningText l -> Constr Source #

dataTypeOf :: WarningText l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( WarningText l) :: Type -> Type Source #

type Rep ( WarningText l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data ExportSpecList l Source #

An explicit export specification.

Constructors

ExportSpecList l [ ExportSpec l]

Instances

Instances details
Functor ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ExportSpecList l -> Constr Source #

dataTypeOf :: ExportSpecList l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ExportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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.

EThingWith l ( EWildcard 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

Instances details
Functor ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ExportSpec l -> Constr Source #

dataTypeOf :: ExportSpec l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ExportSpec l) :: Type -> Type Source #

Pretty ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ExportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( ExportSpec l) = D1 (' MetaData "ExportSpec" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "EVar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: C1 (' MetaCons "EAbs" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Namespace l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))))) :+: ( C1 (' MetaCons "EThingWith" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( EWildcard l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ CName l]))) :+: C1 (' MetaCons "EModuleContents" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( ModuleName l)))))

data EWildcard l Source #

Indicates the position of the wildcard in an export list

Instances

Instances details
Functor EWildcard Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable EWildcard Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable EWildcard Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated EWildcard Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Eq l => Eq ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> EWildcard l -> c ( EWildcard l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( EWildcard l) Source #

toConstr :: EWildcard l -> Constr Source #

dataTypeOf :: EWildcard l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( EWildcard l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( EWildcard l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> EWildcard l -> EWildcard l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> EWildcard l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> EWildcard l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> EWildcard l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> EWildcard l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> EWildcard l -> m ( EWildcard l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> EWildcard l -> m ( EWildcard l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> EWildcard l -> m ( EWildcard l) Source #

Ord l => Ord ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( EWildcard l) :: Type -> Type Source #

type Rep ( EWildcard l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data ImportDecl l Source #

An import declaration.

Constructors

ImportDecl

Fields

Instances

Instances details
Functor ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ImportDecl l -> Constr Source #

dataTypeOf :: ImportDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ImportDecl l) :: Type -> Type Source #

Pretty ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Parseable ( ImportDecl SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( ImportDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data ImportSpecList l Source #

An explicit import specification list.

Constructors

ImportSpecList l Bool [ ImportSpec l]

A list of import specifications. The Bool is True if the names are excluded by hiding .

Instances

Instances details
Functor ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ImportSpecList l -> Constr Source #

dataTypeOf :: ImportSpecList l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ImportSpecList l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ImportSpec l -> Constr Source #

dataTypeOf :: ImportSpec l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ImportSpec l) :: Type -> Type Source #

Pretty ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ImportSpec l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( ImportSpec l) = D1 (' MetaData "ImportSpec" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "IVar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))) :+: C1 (' MetaCons "IAbs" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Namespace l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))))) :+: ( C1 (' MetaCons "IThingAll" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))) :+: C1 (' MetaCons "IThingWith" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ CName l])))))

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

Instances details
Functor Assoc Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Assoc Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Assoc Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Assoc Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Assoc Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Assoc l -> Constr Source #

dataTypeOf :: Assoc l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Assoc l) :: Type -> Type Source #

Pretty ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Assoc l -> Doc

prettyPrec :: Int -> Assoc l -> Doc

type Rep ( Assoc l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Namespace l Source #

Namespaces for imports/exports.

Instances

Instances details
Functor Namespace Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Namespace Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Namespace Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Namespace Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Namespace Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Namespace l -> Constr Source #

dataTypeOf :: Namespace l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Namespace l) :: Type -> Type Source #

Pretty ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( Namespace l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Declarations

data Decl l Source #

A top-level declaration.

Constructors

TypeDecl l ( DeclHead l) ( Type l)

A type declaration

TypeFamDecl l ( DeclHead l) ( Maybe ( ResultSig l)) ( Maybe ( InjectivityInfo l))

A type family declaration

ClosedTypeFamDecl l ( DeclHead l) ( Maybe ( ResultSig l)) ( Maybe ( InjectivityInfo l)) [ TypeEqn l]

A closed type family declaration

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

A data OR newtype declaration

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

A data OR newtype declaration, GADT style

DataFamDecl l ( Maybe ( Context l)) ( DeclHead l) ( Maybe ( ResultSig l))

A data family declaration

TypeInsDecl l ( Type l) ( Type l)

A type family instance declaration

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

A data family instance declaration

GDataInsDecl l ( DataOrNew l) ( Type l) ( Maybe ( Kind l)) [ GadtDecl l] [ 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 ( DerivStrategy 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

TSpliceDecl l ( Exp l)

A typed 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 [ TyVarBind 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

CompletePragma l [ Name l] ( Maybe ( QName l))

A COMPLETE pragma

Instances

Instances details
Functor Decl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Decl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Decl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Decl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Decl Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Decl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Decl SrcSpanInfo -> EP ()

Eq l => Eq ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Decl l -> Constr Source #

dataTypeOf :: Decl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Decl l) :: Type -> Type Source #

Pretty ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Decl l -> Doc

prettyPrec :: Int -> Decl l -> Doc

Parseable ( Decl SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Decl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Decl l) = D1 (' MetaData "Decl" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ((((( C1 (' MetaCons "TypeDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "TypeFamDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ResultSig l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( InjectivityInfo l)))))) :+: ( C1 (' MetaCons "ClosedTypeFamDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ResultSig l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( InjectivityInfo l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ TypeEqn l])))) :+: C1 (' MetaCons "DataDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l))))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ QualConDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l])))))) :+: (( C1 (' MetaCons "GDataDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l))))) :*: (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Kind l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ GadtDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l])))) :+: C1 (' MetaCons "DataFamDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ResultSig l)))))) :+: ( C1 (' MetaCons "TypeInsDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "DataInsDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ QualConDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l]))))))) :+: ((( C1 (' MetaCons "GDataInsDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Kind l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ GadtDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l])))) :+: C1 (' MetaCons "ClassDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ FunDep l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe [ ClassDecl l])))))) :+: ( C1 (' MetaCons "InstDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Overlap l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( InstRule l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe [ InstDecl l])))) :+: C1 (' MetaCons "DerivDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( DerivStrategy l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Overlap l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( InstRule l)))))) :+: (( C1 (' MetaCons "InfixDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Assoc l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe Int )) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Op l]))) :+: C1 (' MetaCons "DefaultDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l]))) :+: ( C1 (' MetaCons "SpliceDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: ( C1 (' MetaCons "TSpliceDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: C1 (' MetaCons "TypeSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Name l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))))))) :+: (((( C1 (' MetaCons "PatSynSig" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Name l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe [ TyVarBind l])))) :*: (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe [ TyVarBind l]))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))) :+: C1 (' MetaCons "FunBind" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Match l]))) :+: ( C1 (' MetaCons "PatBind" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Rhs l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Binds l))))) :+: C1 (' MetaCons "PatSyn" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( PatternSynDirection l)))))) :+: (( C1 (' MetaCons "ForImp" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( CallConv l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Safety l))))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe String )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))) :+: C1 (' MetaCons "ForExp" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( CallConv l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe String )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))))) :+: ( C1 (' MetaCons "RulePragmaDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Rule l])) :+: ( C1 (' MetaCons "DeprPragmaDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [([ Name l], String )])) :+: C1 (' MetaCons "WarnPragmaDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [([ Name l], String )])))))) :+: ((( C1 (' MetaCons "InlineSig" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Bool )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Activation l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)))) :+: C1 (' MetaCons "InlineConlikeSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Activation l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))))) :+: ( C1 (' MetaCons "SpecSig" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Activation l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l]))) :+: C1 (' MetaCons "SpecInlineSig" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Bool )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Activation l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l])))))) :+: (( C1 (' MetaCons "InstSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( InstRule l))) :+: C1 (' MetaCons "AnnPragma" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Annotation l)))) :+: ( C1 (' MetaCons "MinimalPragma" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( BooleanFormula l)))) :+: ( C1 (' MetaCons "RoleAnnotDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Role l]))) :+: C1 (' MetaCons "CompletePragma" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Name l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( QName l)))))))))))

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

Instances details
Functor DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: DeclHead l -> Constr Source #

dataTypeOf :: DeclHead l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( DeclHead l) :: Type -> Type Source #

Pretty ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: DeclHead l -> Doc

prettyPrec :: Int -> DeclHead l -> Doc

type Rep ( DeclHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( DeclHead l) = D1 (' MetaData "DeclHead" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "DHead" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))) :+: C1 (' MetaCons "DHInfix" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( TyVarBind l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))))) :+: ( C1 (' MetaCons "DHParen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l))) :+: C1 (' MetaCons "DHApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( TyVarBind l))))))

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") ])
   ...

Instances

Instances details
Functor InstRule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable InstRule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable InstRule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstRule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP InstRule Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: InstRule l -> Constr Source #

dataTypeOf :: InstRule l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( InstRule l) :: Type -> Type Source #

Pretty ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstRule l -> Doc

prettyPrec :: Int -> InstRule l -> Doc

type Rep ( InstRule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor InstHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable InstHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable InstHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP InstHead Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: InstHead l -> Constr Source #

dataTypeOf :: InstHead l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( InstHead l) :: Type -> Type Source #

Pretty ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstHead l -> Doc

prettyPrec :: Int -> InstHead l -> Doc

type Rep ( InstHead l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( InstHead l) = D1 (' MetaData "InstHead" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "IHCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: C1 (' MetaCons "IHInfix" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))))) :+: ( C1 (' MetaCons "IHParen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( InstHead l))) :+: C1 (' MetaCons "IHApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( InstHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))))

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

Instances details
Functor Binds Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Binds Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Binds Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Binds Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Binds Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Binds Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Binds l -> Constr Source #

dataTypeOf :: Binds l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Binds l) :: Type -> Type Source #

type Rep ( Binds l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data IPBind l Source #

A binding of an implicit parameter.

Constructors

IPBind l ( IPName l) ( Exp l)

Instances

Instances details
Functor IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP IPBind Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: IPBind l -> Constr Source #

dataTypeOf :: IPBind l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( IPBind l) :: Type -> Type Source #

Pretty ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: IPBind l -> Doc

prettyPrec :: Int -> IPBind l -> Doc

type Rep ( IPBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor PatternSynDirection Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable PatternSynDirection Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable PatternSynDirection Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity PatternSynDirection Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

Eq l => Eq ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: PatternSynDirection l -> Constr Source #

dataTypeOf :: PatternSynDirection l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( PatternSynDirection l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data InjectivityInfo l Source #

Injectivity info for injective type families

Constructors

InjectivityInfo l ( Name l) [ Name l]

Instances

Instances details
Functor InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> InjectivityInfo l -> c ( InjectivityInfo l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( InjectivityInfo l) Source #

toConstr :: InjectivityInfo l -> Constr Source #

dataTypeOf :: InjectivityInfo l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( InjectivityInfo l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( InjectivityInfo l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> InjectivityInfo l -> InjectivityInfo l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> InjectivityInfo l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> InjectivityInfo l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> InjectivityInfo l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> InjectivityInfo l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> InjectivityInfo l -> m ( InjectivityInfo l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> InjectivityInfo l -> m ( InjectivityInfo l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> InjectivityInfo l -> m ( InjectivityInfo l) Source #

Ord l => Ord ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( InjectivityInfo l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data ResultSig l Source #

Constructors

KindSig l ( Kind l)
TyVarSig l ( TyVarBind l)

Instances

Instances details
Functor ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> ResultSig l -> c ( ResultSig l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( ResultSig l) Source #

toConstr :: ResultSig l -> Constr Source #

dataTypeOf :: ResultSig l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( ResultSig l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( ResultSig l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> ResultSig l -> ResultSig l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> ResultSig l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> ResultSig l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> ResultSig l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> ResultSig l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> ResultSig l -> m ( ResultSig l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> ResultSig l -> m ( ResultSig l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> ResultSig l -> m ( ResultSig l) Source #

Ord l => Ord ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ResultSig l) :: Type -> Type Source #

Pretty ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ResultSig l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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 ( ResultSig l))

declaration of an associated data type

ClsTyFam l ( DeclHead l) ( Maybe ( ResultSig l)) ( Maybe ( InjectivityInfo l))

declaration of an associated type synonym

ClsTyDef l ( TypeEqn l)

default choice for an associated type synonym

ClsDefSig l ( Name l) ( Type l)

default signature

Instances

Instances details
Functor ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ClassDecl l -> Constr Source #

dataTypeOf :: ClassDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ClassDecl l) :: Type -> Type Source #

Pretty ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ClassDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( ClassDecl l) = D1 (' MetaData "ClassDecl" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "ClsDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Decl l))) :+: C1 (' MetaCons "ClsDataFam" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ResultSig l)))))) :+: ( C1 (' MetaCons "ClsTyFam" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DeclHead l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( ResultSig l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( InjectivityInfo l))))) :+: ( C1 (' MetaCons "ClsTyDef" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( TypeEqn l))) :+: C1 (' MetaCons "ClsDefSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))))))

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] [ Deriving l]

an associated data type implementation

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

an associated data type implemented using GADT style

Instances

Instances details
Functor InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: InstDecl l -> Constr Source #

dataTypeOf :: InstDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( InstDecl l) :: Type -> Type Source #

Pretty ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstDecl l -> Doc

prettyPrec :: Int -> InstDecl l -> Doc

type Rep ( InstDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( InstDecl l) = D1 (' MetaData "InstDecl" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "InsDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Decl l))) :+: C1 (' MetaCons "InsType" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))) :+: ( C1 (' MetaCons "InsData" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ QualConDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l])))) :+: C1 (' MetaCons "InsGData" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( DataOrNew l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Kind l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ GadtDecl l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Deriving l]))))))

data Deriving l Source #

A deriving clause following a data type declaration.

Instances

Instances details
Functor Deriving Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Deriving Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Deriving Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Deriving Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Deriving Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Deriving l -> c ( Deriving l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Deriving l) Source #

toConstr :: Deriving l -> Constr Source #

dataTypeOf :: Deriving l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Deriving l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Deriving l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Deriving l -> Deriving l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Deriving l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Deriving l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Deriving l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Deriving l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Deriving l -> m ( Deriving l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Deriving l -> m ( Deriving l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Deriving l -> m ( Deriving l) Source #

Ord l => Ord ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Deriving l) :: Type -> Type Source #

Pretty ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Deriving l -> Doc

prettyPrec :: Int -> Deriving l -> Doc

type Rep ( Deriving l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data DerivStrategy l Source #

Which technique the user explicitly requested when deriving an instance.

Constructors

DerivStock l

GHC's "standard" strategy, which is to implement a custom instance for the data type. This only works for certain types that GHC knows about (e.g., Eq , Show , Functor when -XDeriveFunctor is enabled, etc.)

DerivAnyclass l
-XDeriveAnyClass
DerivNewtype l
-XGeneralizedNewtypeDeriving
DerivVia l ( Type l)
-XDerivingVia

Instances

Instances details
Functor DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> DerivStrategy l -> c ( DerivStrategy l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( DerivStrategy l) Source #

toConstr :: DerivStrategy l -> Constr Source #

dataTypeOf :: DerivStrategy l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( DerivStrategy l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( DerivStrategy l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> DerivStrategy l -> DerivStrategy l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> DerivStrategy l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> DerivStrategy l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> DerivStrategy l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> DerivStrategy l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> DerivStrategy l -> m ( DerivStrategy l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> DerivStrategy l -> m ( DerivStrategy l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> DerivStrategy l -> m ( DerivStrategy l) Source #

Ord l => Ord ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( DerivStrategy l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: DataOrNew l -> Constr Source #

dataTypeOf :: DataOrNew l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( DataOrNew l) :: Type -> Type Source #

Pretty ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( DataOrNew l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ConDecl l -> Constr Source #

dataTypeOf :: ConDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ConDecl l) :: Type -> Type Source #

Pretty ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ConDecl l -> Doc

prettyPrec :: Int -> ConDecl l -> Doc

type Rep ( ConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( ConDecl l) = D1 (' MetaData "ConDecl" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ( C1 (' MetaCons "ConDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l]))) :+: ( C1 (' MetaCons "InfixConDecl" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "RecDecl" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ FieldDecl l])))))

data FieldDecl l Source #

Declaration of a (list of) named field(s).

Constructors

FieldDecl l [ Name l] ( Type l)

Instances

Instances details
Functor FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> FieldDecl l -> c ( FieldDecl l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( FieldDecl l) Source #

toConstr :: FieldDecl l -> Constr Source #

dataTypeOf :: FieldDecl l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( FieldDecl l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( FieldDecl l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> FieldDecl l -> FieldDecl l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> FieldDecl l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> FieldDecl l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> FieldDecl l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> FieldDecl l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> FieldDecl l -> m ( FieldDecl l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> FieldDecl l -> m ( FieldDecl l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> FieldDecl l -> m ( FieldDecl l) Source #

Ord l => Ord ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( FieldDecl l) :: Type -> Type Source #

Pretty ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( FieldDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data QualConDecl l Source #

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

Instances

Instances details
Functor QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: QualConDecl l -> Constr Source #

dataTypeOf :: QualConDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( QualConDecl l) :: Type -> Type Source #

Pretty ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( QualConDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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 FieldDecl s, 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.

Instances

Instances details
Functor GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: GadtDecl l -> Constr Source #

dataTypeOf :: GadtDecl l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( GadtDecl l) :: Type -> Type Source #

Pretty ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: GadtDecl l -> Doc

prettyPrec :: Int -> GadtDecl l -> Doc

type Rep ( GadtDecl l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data BangType l Source #

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

Constructors

BangedTy l

strict component, marked with " ! "

LazyTy l

lazy component, marked with " ~ "

NoStrictAnnot l

No strictness information

Instances

Instances details
Functor BangType Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable BangType Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable BangType Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated BangType Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP BangType Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: BangType l -> Constr Source #

dataTypeOf :: BangType l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( BangType l) :: Type -> Type Source #

Pretty ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: BangType l -> Doc

prettyPrec :: Int -> BangType l -> Doc

type Rep ( BangType l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Unpackedness l Source #

Constructors

Unpack l

" {-# UNPACK #-} "

NoUnpack l

" {-# NOUNPACK #-} "

NoUnpackPragma l

No unpack pragma

Instances

Instances details
Functor Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Unpackedness l -> c ( Unpackedness l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Unpackedness l) Source #

toConstr :: Unpackedness l -> Constr Source #

dataTypeOf :: Unpackedness l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Unpackedness l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Unpackedness l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Unpackedness l -> Unpackedness l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Unpackedness l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Unpackedness l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Unpackedness l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Unpackedness l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Unpackedness l -> m ( Unpackedness l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Unpackedness l -> m ( Unpackedness l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Unpackedness l -> m ( Unpackedness l) Source #

Ord l => Ord ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Unpackedness l) :: Type -> Type Source #

Pretty ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( Unpackedness l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Match Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Match Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Match Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Match Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Match Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Match Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Match l -> Constr Source #

dataTypeOf :: Match l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Match l) :: Type -> Type Source #

Pretty ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Match l -> Doc

prettyPrec :: Int -> Match l -> Doc

type Rep ( Match l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Match l) = D1 (' MetaData "Match" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ( C1 (' MetaCons "Match" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Rhs l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Binds l)))))) :+: C1 (' MetaCons "InfixMatch" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Rhs l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Binds l)))))))

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

Instances details
Functor Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> Rhs a -> Rhs b Source #

(<$) :: a -> Rhs b -> Rhs a Source #

Foldable Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Rhs l -> l Source #

amap :: (l -> l) -> Rhs l -> Rhs l Source #

AppFixity Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Rhs Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Rhs SrcSpanInfo -> EP ()

Eq l => Eq ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Rhs l -> Constr Source #

dataTypeOf :: Rhs l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Rhs l) :: Type -> Type Source #

Pretty ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Rhs l -> Doc

prettyPrec :: Int -> Rhs l -> Doc

type Rep ( Rhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: GuardedRhs l -> Constr Source #

dataTypeOf :: GuardedRhs l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( GuardedRhs l) :: Type -> Type Source #

Pretty ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( GuardedRhs l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Class Assertions and Contexts

data Context l Source #

A context is a set of assertions

Instances

Instances details
Functor Context Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Context Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Context Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Context Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Context Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Context l -> c ( Context l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Context l) Source #

toConstr :: Context l -> Constr Source #

dataTypeOf :: Context l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Context l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Context l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Context l -> Context l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Context l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Context l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Context l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Context l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Context l -> m ( Context l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Context l -> m ( Context l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Context l -> m ( Context l) Source #

Ord l => Ord ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Context l) :: Type -> Type Source #

Pretty ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Context l -> Doc

prettyPrec :: Int -> Context l -> Doc

type Rep ( Context l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor FunDep Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable FunDep Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable FunDep Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated FunDep Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP FunDep Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: FunDep l -> Constr Source #

dataTypeOf :: FunDep l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( FunDep l) :: Type -> Type Source #

Pretty ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: FunDep l -> Doc

prettyPrec :: Int -> FunDep l -> Doc

type Rep ( FunDep l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Asst l Source #

Class assertions.

Constructors

TypeA l ( Type l)

type assertion

IParam l ( IPName l) ( Type l)

implicit parameter assertion

ParenA l ( Asst l)

parenthesised class assertion

Instances

Instances details
Functor Asst Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Asst Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Asst Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Asst Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Asst Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Asst SrcSpanInfo -> EP ()

Eq l => Eq ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Asst l -> Constr Source #

dataTypeOf :: Asst l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Asst l) :: Type -> Type Source #

Pretty ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Asst l -> Doc

prettyPrec :: Int -> Asst l -> Doc

type Rep ( Asst l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

TyStar l

* , the type of types

TyFun l ( Type l) ( Type l)

function type

TyTuple l Boxed [ Type l]

tuple type, possibly boxed

TyUnboxedSum l [ Type l]

unboxed tuple type

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) ( MaybePromotedName 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) ( Unpackedness 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

TyQuasiQuote l String String
[$name| string |]

Instances

Instances details
Functor Type Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Type Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Type Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Type Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Type Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Type SrcSpanInfo -> EP ()

Eq l => Eq ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Type l -> Constr Source #

dataTypeOf :: Type l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Type l) :: Type -> Type Source #

Pretty ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Type l -> Doc

prettyPrec :: Int -> Type l -> Doc

Parseable ( Type SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Type l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Type l) = D1 (' MetaData "Type" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (((( C1 (' MetaCons "TyForall" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe [ TyVarBind l]))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Context l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "TyStar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l))) :+: ( C1 (' MetaCons "TyFun" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "TyTuple" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Boxed ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l]))))) :+: (( C1 (' MetaCons "TyUnboxedSum" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l])) :+: C1 (' MetaCons "TyList" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: ( C1 (' MetaCons "TyParArray" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))) :+: ( C1 (' MetaCons "TyApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "TyVar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))))))) :+: ((( C1 (' MetaCons "TyCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: C1 (' MetaCons "TyParen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: ( C1 (' MetaCons "TyInfix" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( MaybePromotedName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: ( C1 (' MetaCons "TyKind" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Kind l)))) :+: C1 (' MetaCons "TyPromoted" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Promoted l)))))) :+: (( C1 (' MetaCons "TyEquals" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "TySplice" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Splice l)))) :+: ( C1 (' MetaCons "TyBang" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( BangType l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Unpackedness l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: ( C1 (' MetaCons "TyWildCard" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Name l)))) :+: C1 (' MetaCons "TyQuasiQuote" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))))))))

data Boxed Source #

Flag denoting whether a tuple is boxed or unboxed.

Constructors

Boxed
Unboxed

Instances

Instances details
Eq Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Boxed -> Constr Source #

dataTypeOf :: Boxed -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep Boxed Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep Boxed = D1 (' MetaData "Boxed" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ( C1 (' MetaCons "Boxed" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "Unboxed" ' PrefixI ' False ) ( U1 :: Type -> Type ))

type Kind = Type Source #

An explicit kind annotation.

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

Instances details
Functor TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: TyVarBind l -> Constr Source #

dataTypeOf :: TyVarBind l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( TyVarBind l) :: Type -> Type Source #

Pretty ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( TyVarBind l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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] .

Instances

Instances details
Functor Promoted Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Promoted Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Promoted Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Promoted Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Promoted Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Promoted l -> Constr Source #

dataTypeOf :: Promoted l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Promoted l) :: Type -> Type Source #

Pretty ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Promoted l -> Doc

prettyPrec :: Int -> Promoted l -> Doc

type Rep ( Promoted l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Promoted l) = D1 (' MetaData "Promoted" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "PromotedInteger" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Integer ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: ( C1 (' MetaCons "PromotedString" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "PromotedCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Bool ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)))))) :+: ( C1 (' MetaCons "PromotedList" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Bool ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l]))) :+: ( C1 (' MetaCons "PromotedTuple" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Type l])) :+: C1 (' MetaCons "PromotedUnit" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)))))

data TypeEqn l Source #

A type equation as found in closed type families.

Constructors

TypeEqn l ( Type l) ( Type l)

Instances

Instances details
Functor TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: TypeEqn l -> Constr Source #

dataTypeOf :: TypeEqn l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( TypeEqn l) :: Type -> Type Source #

Pretty ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: TypeEqn l -> Doc

prettyPrec :: Int -> TypeEqn l -> Doc

type Rep ( TypeEqn l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Expressions

data Exp l Source #

Haskell expressions.

Constructors

Var l ( QName l)

variable

OverloadedLabel l String

Overloaded label #foo

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

UnboxedSum l Int Int ( Exp l)

unboxed sum

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 |]

TypeApp l ( Type l)

Visible type application

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

ArrOp l ( Exp l)

arrow control operators: (| exp |)

LCase l [ Alt l]

case alts

Instances

Instances details
Functor Exp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> Exp a -> Exp b Source #

(<$) :: a -> Exp b -> Exp a Source #

Foldable Exp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Exp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Exp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Exp l -> l Source #

amap :: (l -> l) -> Exp l -> Exp l Source #

AppFixity Exp Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Exp Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Exp SrcSpanInfo -> EP ()

Eq l => Eq ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Exp l -> Constr Source #

dataTypeOf :: Exp l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Exp l) :: Type -> Type Source #

Pretty ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Exp l -> Doc

prettyPrec :: Int -> Exp l -> Doc

Parseable ( Exp SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Exp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Exp l) = D1 (' MetaData "Exp" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ((((( C1 (' MetaCons "Var" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: ( C1 (' MetaCons "OverloadedLabel" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )) :+: C1 (' MetaCons "IPVar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( IPName l))))) :+: (( C1 (' MetaCons "Con" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: C1 (' MetaCons "Lit" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Literal l)))) :+: ( C1 (' MetaCons "InfixApp" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QOp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "App" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))))))) :+: (( C1 (' MetaCons "NegApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: ( C1 (' MetaCons "Lambda" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "Let" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Binds l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: (( C1 (' MetaCons "If" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "MultiIf" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ GuardedRhs l]))) :+: ( C1 (' MetaCons "Case" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Alt l]))) :+: C1 (' MetaCons "Do" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Stmt l])))))) :+: ((( C1 (' MetaCons "MDo" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Stmt l])) :+: ( C1 (' MetaCons "Tuple" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Boxed ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l]))) :+: C1 (' MetaCons "UnboxedSum" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Int )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Int ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: (( C1 (' MetaCons "TupleSection" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Boxed ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Maybe ( Exp l)]))) :+: C1 (' MetaCons "List" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l]))) :+: ( C1 (' MetaCons "ParArray" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l])) :+: C1 (' MetaCons "Paren" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: (( C1 (' MetaCons "LeftSection" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QOp l)))) :+: ( C1 (' MetaCons "RightSection" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QOp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "RecConstr" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ FieldUpdate l]))))) :+: (( C1 (' MetaCons "RecUpdate" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ FieldUpdate l]))) :+: C1 (' MetaCons "EnumFrom" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: ( C1 (' MetaCons "EnumFromTo" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "EnumFromThen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))))))))) :+: (((( C1 (' MetaCons "EnumFromThenTo" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: ( C1 (' MetaCons "ParArrayFromTo" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "ParArrayFromThenTo" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: (( C1 (' MetaCons "ListComp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ QualStmt l]))) :+: C1 (' MetaCons "ParComp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [[ QualStmt l]])))) :+: ( C1 (' MetaCons "ParArrayComp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [[ QualStmt l]]))) :+: C1 (' MetaCons "ExpTypeSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))))))) :+: (( C1 (' MetaCons "VarQuote" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: ( C1 (' MetaCons "TypQuote" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l))) :+: C1 (' MetaCons "BracketExp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Bracket l))))) :+: (( C1 (' MetaCons "SpliceExp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Splice l))) :+: C1 (' MetaCons "QuasiQuote" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )))) :+: ( C1 (' MetaCons "TypeApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))) :+: C1 (' MetaCons "XTag" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ XAttr l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Exp l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l])))))))) :+: ((( C1 (' MetaCons "XETag" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ XAttr l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Exp l))))) :+: ( C1 (' MetaCons "XPcdata" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )) :+: C1 (' MetaCons "XExpTag" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))))) :+: (( C1 (' MetaCons "XChildTag" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Exp l])) :+: C1 (' MetaCons "CorePragma" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))))) :+: ( C1 (' MetaCons "SCCPragma" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "GenPragma" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Int , Int )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Int , Int )) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))))) :+: (( C1 (' MetaCons "Proc" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: ( C1 (' MetaCons "LeftArrApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "RightArrApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: (( C1 (' MetaCons "LeftArrHighApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: C1 (' MetaCons "RightArrHighApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))))) :+: ( C1 (' MetaCons "ArrOp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: C1 (' MetaCons "LCase" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Alt l]))))))))

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

Instances details
Functor Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Stmt Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Stmt SrcSpanInfo -> EP ()

Eq l => Eq ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Stmt l -> Constr Source #

dataTypeOf :: Stmt l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Stmt l) :: Type -> Type Source #

Pretty ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Stmt l -> Doc

prettyPrec :: Int -> Stmt l -> Doc

Parseable ( Stmt SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Stmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: QualStmt l -> Constr Source #

dataTypeOf :: QualStmt l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( QualStmt l) :: Type -> Type Source #

Pretty ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QualStmt l -> Doc

prettyPrec :: Int -> QualStmt l -> Doc

type Rep ( QualStmt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( QualStmt l) = D1 (' MetaData "QualStmt" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "QualStmt" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Stmt l))) :+: ( C1 (' MetaCons "ThenTrans" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: C1 (' MetaCons "ThenBy" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))) :+: ( C1 (' MetaCons "GroupBy" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: ( C1 (' MetaCons "GroupUsing" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: C1 (' MetaCons "GroupByUsing" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))))))

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

Instances details
Functor FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: FieldUpdate l -> Constr Source #

dataTypeOf :: FieldUpdate l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( FieldUpdate l) :: Type -> Type Source #

Pretty ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( FieldUpdate l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Alt l Source #

An alt alternative in a case expression.

Constructors

Alt l ( Pat l) ( Rhs l) ( Maybe ( Binds l))

Instances

Instances details
Functor Alt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> Alt a -> Alt b Source #

(<$) :: a -> Alt b -> Alt a Source #

Foldable Alt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Alt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Alt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Alt l -> l Source #

amap :: (l -> l) -> Alt l -> Alt l Source #

AppFixity Alt Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Alt Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Alt SrcSpanInfo -> EP ()

Eq l => Eq ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Alt l -> Constr Source #

dataTypeOf :: Alt l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Alt l) :: Type -> Type Source #

Pretty ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Alt l -> Doc

prettyPrec :: Int -> Alt l -> Doc

type Rep ( Alt l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data XAttr l Source #

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

Constructors

XAttr l ( XName l) ( Exp l)

Instances

Instances details
Functor XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP XAttr Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: XAttr l -> Constr Source #

dataTypeOf :: XAttr l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( XAttr l) :: Type -> Type Source #

Pretty ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: XAttr l -> Doc

prettyPrec :: Int -> XAttr l -> Doc

type Rep ( XAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

PUnboxedSum l Int Int ( Pat l)

unboxed sum

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

PSplice l ( Splice l)

template haskell splice pattern

PQuasiQuote l String String

quasi quote pattern: [$ name | string |]

PBangPat l ( Pat l)

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

Instances

Instances details
Functor Pat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> Pat a -> Pat b Source #

(<$) :: a -> Pat b -> Pat a Source #

Foldable Pat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Pat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Pat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Pat l -> l Source #

amap :: (l -> l) -> Pat l -> Pat l Source #

AppFixity Pat Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Pat Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Pat SrcSpanInfo -> EP ()

Eq l => Eq ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Pat l -> Constr Source #

dataTypeOf :: Pat l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Pat l) :: Type -> Type Source #

Pretty ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Pat l -> Doc

prettyPrec :: Int -> Pat l -> Doc

Parseable ( Pat SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( Pat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Pat l) = D1 (' MetaData "Pat" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (((( C1 (' MetaCons "PVar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l))) :+: ( C1 (' MetaCons "PLit" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Sign l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Literal l)))) :+: C1 (' MetaCons "PNPlusK" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Integer ))))) :+: ( C1 (' MetaCons "PInfixApp" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)))) :+: ( C1 (' MetaCons "PApp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l]))) :+: C1 (' MetaCons "PTuple" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Boxed ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l])))))) :+: (( C1 (' MetaCons "PUnboxedSum" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Int )) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Int ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)))) :+: ( C1 (' MetaCons "PList" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l])) :+: C1 (' MetaCons "PParen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))))) :+: ( C1 (' MetaCons "PRec" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( QName l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ PatField l]))) :+: ( C1 (' MetaCons "PAsPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)))) :+: C1 (' MetaCons "PWildCard" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)))))) :+: ((( C1 (' MetaCons "PIrrPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :+: ( C1 (' MetaCons "PatTypeSig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l)))) :+: C1 (' MetaCons "PViewPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)))))) :+: ( C1 (' MetaCons "PRPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ RPat l])) :+: ( C1 (' MetaCons "PXTag" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ PXAttr l]) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Pat l))) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Pat l])))) :+: C1 (' MetaCons "PXETag" ' PrefixI ' False ) (( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( XName l))) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ PXAttr l]) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe ( Pat l)))))))) :+: (( C1 (' MetaCons "PXPcdata" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )) :+: ( C1 (' MetaCons "PXPatTag" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :+: C1 (' MetaCons "PXRPats" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ RPat l])))) :+: ( C1 (' MetaCons "PSplice" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Splice l))) :+: ( C1 (' MetaCons "PQuasiQuote" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "PBangPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))))))))

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

Instances details
Functor PatField Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable PatField Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable PatField Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated PatField Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity PatField Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP PatField Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: PatField l -> Constr Source #

dataTypeOf :: PatField l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( PatField l) :: Type -> Type Source #

Pretty ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: PatField l -> Doc

prettyPrec :: Int -> PatField l -> Doc

type Rep ( PatField l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data PXAttr l Source #

An XML attribute in a pattern.

Constructors

PXAttr l ( XName l) ( Pat l)

Instances

Instances details
Functor PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: PXAttr l -> Constr Source #

dataTypeOf :: PXAttr l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( PXAttr l) :: Type -> Type Source #

Pretty ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: PXAttr l -> Doc

prettyPrec :: Int -> PXAttr l -> Doc

type Rep ( PXAttr l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor RPat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable RPat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable RPat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RPat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity RPat Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP RPat Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: RPat SrcSpanInfo -> EP ()

Eq l => Eq ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: RPat l -> Constr Source #

dataTypeOf :: RPat l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( RPat l) :: Type -> Type Source #

Pretty ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RPat l -> Doc

prettyPrec :: Int -> RPat l -> Doc

type Rep ( RPat l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( RPat l) = D1 (' MetaData "RPat" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ((( C1 (' MetaCons "RPOp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPatOp l)))) :+: C1 (' MetaCons "RPEither" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l))))) :+: ( C1 (' MetaCons "RPSeq" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ RPat l])) :+: C1 (' MetaCons "RPGuard" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Stmt l]))))) :+: (( C1 (' MetaCons "RPCAs" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l)))) :+: C1 (' MetaCons "RPAs" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Name l)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l))))) :+: ( C1 (' MetaCons "RPParen" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( RPat l))) :+: C1 (' MetaCons "RPPat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))))))

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

Instances details
Functor RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: RPatOp l -> Constr Source #

dataTypeOf :: RPatOp l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( RPatOp l) :: Type -> Type Source #

Pretty ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RPatOp l -> Doc

prettyPrec :: Int -> RPatOp l -> Doc

type Rep ( RPatOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Literal Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Literal Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Literal Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Literal Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Literal Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Literal l -> Constr Source #

dataTypeOf :: Literal l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Literal l) :: Type -> Type Source #

Pretty ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Literal l -> Doc

prettyPrec :: Int -> Literal l -> Doc

type Rep ( Literal l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Literal l) = D1 (' MetaData "Literal" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ((( C1 (' MetaCons "Char" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Char ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "String" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )))) :+: ( C1 (' MetaCons "Int" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Integer ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: ( C1 (' MetaCons "Frac" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Rational ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "PrimInt" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Integer ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )))))) :+: (( C1 (' MetaCons "PrimWord" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Integer ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "PrimFloat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Rational ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )))) :+: ( C1 (' MetaCons "PrimDouble" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Rational ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: ( C1 (' MetaCons "PrimChar" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Char ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ))) :+: C1 (' MetaCons "PrimString" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 String )))))))

data Sign l Source #

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

Constructors

Signless l
Negative l

Instances

Instances details
Functor Sign Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Sign Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Sign Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Sign Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Sign Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Sign SrcSpanInfo -> EP ()

Eq l => Eq ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Sign l -> Constr Source #

dataTypeOf :: Sign l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Sign l) :: Type -> Type Source #

type Rep ( Sign l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Variables, Constructors and Operators

data ModuleName l Source #

The name of a Haskell module.

Constructors

ModuleName l String

Instances

Instances details
Functor ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ModuleName l -> Constr Source #

dataTypeOf :: ModuleName l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ModuleName l) :: Type -> Type Source #

Pretty ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( ModuleName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor QName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable QName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable QName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP QName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: QName l -> Constr Source #

dataTypeOf :: QName l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( QName l) :: Type -> Type Source #

Pretty ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QName l -> Doc

prettyPrec :: Int -> QName l -> Doc

type Rep ( QName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Name Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Name Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Name Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Name Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Name Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Name SrcSpanInfo -> EP ()

Eq l => Eq ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Name l -> Constr Source #

dataTypeOf :: Name l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Name l) :: Type -> Type Source #

Pretty ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Name l -> Doc

prettyPrec :: Int -> Name l -> Doc

type Rep ( Name l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor QOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> QOp a -> QOp b Source #

(<$) :: a -> QOp b -> QOp a Source #

Foldable QOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable QOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: QOp l -> l Source #

amap :: (l -> l) -> QOp l -> QOp l Source #

ExactP QOp Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: QOp SrcSpanInfo -> EP ()

Eq l => Eq ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: QOp l -> Constr Source #

dataTypeOf :: QOp l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( QOp l) :: Type -> Type Source #

Pretty ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QOp l -> Doc

prettyPrec :: Int -> QOp l -> Doc

type Rep ( QOp l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Op Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> Op a -> Op b Source #

(<$) :: a -> Op b -> Op a Source #

Foldable Op Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Op Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Op Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Op l -> l Source #

amap :: (l -> l) -> Op l -> Op l Source #

ExactP Op Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Op SrcSpanInfo -> EP ()

Eq l => Eq ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: Op l -> Constr Source #

dataTypeOf :: Op l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Op l) :: Type -> Type Source #

Pretty ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Op l -> Doc

prettyPrec :: Int -> Op l -> Doc

type Rep ( Op l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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 and data 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 (# #)

ExprHole l

An expression hole _

Instances

Instances details
Functor SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: SpecialCon l -> Constr Source #

dataTypeOf :: SpecialCon l -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( SpecialCon l) :: Type -> Type Source #

Pretty ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( SpecialCon l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( SpecialCon l) = D1 (' MetaData "SpecialCon" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "UnitCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)) :+: ( C1 (' MetaCons "ListCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)) :+: C1 (' MetaCons "FunCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)))) :+: (( C1 (' MetaCons "TupleCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Boxed ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Int ))) :+: C1 (' MetaCons "Cons" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l))) :+: ( C1 (' MetaCons "UnboxedSingleCon" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)) :+: C1 (' MetaCons "ExprHole" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l)))))

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

Instances details
Functor CName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable CName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable CName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated CName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP CName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: CName l -> Constr Source #

dataTypeOf :: CName l -> DataType Source #

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

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

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

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

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

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

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

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

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> CName l -> m ( CName l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> CName l -> m ( CName l) Source #

Ord l => Ord ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( CName l) :: Type -> Type Source #

Pretty ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: CName l -> Doc

prettyPrec :: Int -> CName l -> Doc

type Rep ( CName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor IPName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable IPName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable IPName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated IPName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP IPName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> IPName l -> c ( IPName l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( IPName l) Source #

toConstr :: IPName l -> Constr Source #

dataTypeOf :: IPName l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( IPName l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( IPName l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> IPName l -> IPName l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> IPName l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> IPName l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> IPName l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> IPName l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> IPName l -> m ( IPName l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> IPName l -> m ( IPName l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> IPName l -> m ( IPName l) Source #

Ord l => Ord ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( IPName l) :: Type -> Type Source #

Pretty ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: IPName l -> Doc

prettyPrec :: Int -> IPName l -> Doc

type Rep ( IPName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data XName l Source #

The name of an xml element or attribute, possibly qualified with a namespace.

Instances

Instances details
Functor XName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable XName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable XName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated XName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP XName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> XName l -> c ( XName l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( XName l) Source #

toConstr :: XName l -> Constr Source #

dataTypeOf :: XName l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( XName l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( XName l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> XName l -> XName l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> XName l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> XName l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> XName l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> XName l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> XName l -> m ( XName l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> XName l -> m ( XName l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> XName l -> m ( XName l) Source #

Ord l => Ord ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( XName l) :: Type -> Type Source #

Pretty ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: XName l -> Doc

prettyPrec :: Int -> XName l -> Doc

type Rep ( XName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Role l Source #

Instances

Instances details
Functor Role Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Role Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Role Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Role Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Role Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Role SrcSpanInfo -> EP ()

Eq l => Eq ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Role l -> c ( Role l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Role l) Source #

toConstr :: Role l -> Constr Source #

dataTypeOf :: Role l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Role l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Role l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Role l -> Role l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Role l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Role l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Role l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Role l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Role l -> m ( Role l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Role l -> m ( Role l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Role l -> m ( Role l) Source #

Ord l => Ord ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Role l) :: Type -> Type Source #

Pretty ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Role l -> Doc

prettyPrec :: Int -> Role l -> Doc

type Rep ( Role l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data MaybePromotedName l Source #

Instances

Instances details
Functor MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> MaybePromotedName l -> c ( MaybePromotedName l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( MaybePromotedName l) Source #

toConstr :: MaybePromotedName l -> Constr Source #

dataTypeOf :: MaybePromotedName l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( MaybePromotedName l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( MaybePromotedName l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> MaybePromotedName l -> MaybePromotedName l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> MaybePromotedName l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> MaybePromotedName l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> MaybePromotedName l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> MaybePromotedName l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> MaybePromotedName l -> m ( MaybePromotedName l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> MaybePromotedName l -> m ( MaybePromotedName l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> MaybePromotedName l -> m ( MaybePromotedName l) Source #

Ord l => Ord ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( MaybePromotedName l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Template Haskell

data Bracket l Source #

A template haskell bracket expression.

Constructors

ExpBracket l ( Exp l)

expression bracket: [| ... |]

TExpBracket l ( Exp l)

typed expression bracket: [|| ... ||]

PatBracket l ( Pat l)

pattern bracket: [p| ... |]

TypeBracket l ( Type l)

type bracket: [t| ... |]

DeclBracket l [ Decl l]

declaration bracket: [d| ... |]

Instances

Instances details
Functor Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Bracket Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Bracket l -> c ( Bracket l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Bracket l) Source #

toConstr :: Bracket l -> Constr Source #

dataTypeOf :: Bracket l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Bracket l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Bracket l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Bracket l -> Bracket l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Bracket l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Bracket l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Bracket l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Bracket l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Bracket l -> m ( Bracket l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Bracket l -> m ( Bracket l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Bracket l -> m ( Bracket l) Source #

Ord l => Ord ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Bracket l) :: Type -> Type Source #

Pretty ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Bracket l -> Doc

prettyPrec :: Int -> Bracket l -> Doc

type Rep ( Bracket l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep ( Bracket l) = D1 (' MetaData "Bracket" "Language.Haskell.Exts.Syntax" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) (( C1 (' MetaCons "ExpBracket" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l))) :+: C1 (' MetaCons "TExpBracket" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Exp l)))) :+: ( C1 (' MetaCons "PatBracket" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Pat l))) :+: ( C1 (' MetaCons "TypeBracket" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Type l))) :+: C1 (' MetaCons "DeclBracket" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 l) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ Decl l])))))

data Splice l Source #

A template haskell splice expression

Constructors

IdSplice l String

variable splice: $var

TIdSplice l String

typed variable splice: $$var

ParenSplice l ( Exp l)

parenthesised expression splice: $( exp )

TParenSplice l ( Exp l)

parenthesised typed expression splice: $$( exp )

Instances

Instances details
Functor Splice Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Splice Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Splice Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Splice Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Splice Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Splice Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Splice l -> c ( Splice l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Splice l) Source #

toConstr :: Splice l -> Constr Source #

dataTypeOf :: Splice l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Splice l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Splice l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Splice l -> Splice l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Splice l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Splice l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Splice l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Splice l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Splice l -> m ( Splice l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Splice l -> m ( Splice l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Splice l -> m ( Splice l) Source #

Ord l => Ord ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Splice l) :: Type -> Type Source #

Pretty ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Splice l -> Doc

prettyPrec :: Int -> Splice l -> Doc

type Rep ( Splice l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Safety Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Safety Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Safety Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Safety Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Safety Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Safety l -> c ( Safety l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Safety l) Source #

toConstr :: Safety l -> Constr Source #

dataTypeOf :: Safety l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Safety l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Safety l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Safety l -> Safety l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Safety l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Safety l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Safety l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Safety l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Safety l -> m ( Safety l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Safety l -> m ( Safety l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Safety l -> m ( Safety l) Source #

Ord l => Ord ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Safety l) :: Type -> Type Source #

Pretty ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Safety l -> Doc

prettyPrec :: Int -> Safety l -> Doc

type Rep ( Safety l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data CallConv l Source #

The calling convention of a foreign function call.

Instances

Instances details
Functor CallConv Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable CallConv Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable CallConv Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated CallConv Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP CallConv Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> CallConv l -> c ( CallConv l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( CallConv l) Source #

toConstr :: CallConv l -> Constr Source #

dataTypeOf :: CallConv l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( CallConv l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( CallConv l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> CallConv l -> CallConv l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> CallConv l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> CallConv l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> CallConv l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> CallConv l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> CallConv l -> m ( CallConv l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> CallConv l -> m ( CallConv l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> CallConv l -> m ( CallConv l) Source #

Ord l => Ord ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( CallConv l) :: Type -> Type Source #

Pretty ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: CallConv l -> Doc

prettyPrec :: Int -> CallConv l -> Doc

type Rep ( CallConv l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> ModulePragma l -> c ( ModulePragma l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( ModulePragma l) Source #

toConstr :: ModulePragma l -> Constr Source #

dataTypeOf :: ModulePragma l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( ModulePragma l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( ModulePragma l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> ModulePragma l -> ModulePragma l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> ModulePragma l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> ModulePragma l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> ModulePragma l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> ModulePragma l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> ModulePragma l -> m ( ModulePragma l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> ModulePragma l -> m ( ModulePragma l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> ModulePragma l -> m ( ModulePragma l) Source #

Ord l => Ord ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( ModulePragma l) :: Type -> Type Source #

Pretty ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Parseable ( NonGreedy ( ListOf ( ModulePragma SrcSpanInfo ))) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep ( ModulePragma l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Tool Source #

Recognised tools for OPTIONS pragmas.

Instances

Instances details
Eq Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Tool -> c Tool Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Tool Source #

toConstr :: Tool -> Constr Source #

dataTypeOf :: Tool -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Tool ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Tool ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Tool -> Tool Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Tool -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Tool -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Tool -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Tool -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Tool -> m Tool Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tool -> m Tool Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tool -> m Tool Source #

Ord Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Tool :: Type -> Type Source #

Pretty Tool Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Tool -> Doc

prettyPrec :: Int -> Tool -> Doc

type Rep Tool Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Overlap l Source #

Recognised overlaps for overlap pragmas.

Constructors

NoOverlap l

NO_OVERLAP pragma

Overlap l

OVERLAP pragma

Overlapping l
Overlaps l
Overlappable l
Incoherent l

INCOHERENT pragma

Instances

Instances details
Functor Overlap Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Overlap Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Overlap Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Overlap Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Overlap Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Overlap l -> c ( Overlap l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Overlap l) Source #

toConstr :: Overlap l -> Constr Source #

dataTypeOf :: Overlap l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Overlap l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Overlap l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Overlap l -> Overlap l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Overlap l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Overlap l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Overlap l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Overlap l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Overlap l -> m ( Overlap l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Overlap l -> m ( Overlap l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Overlap l -> m ( Overlap l) Source #

Ord l => Ord ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Overlap l) :: Type -> Type Source #

Pretty ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Overlap l -> Doc

prettyPrec :: Int -> Overlap l -> Doc

type Rep ( Overlap l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Rule l Source #

The body of a RULES pragma.

Instances

Instances details
Functor Rule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Rule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Rule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Rule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Rule Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Methods

exactP :: Rule SrcSpanInfo -> EP ()

Eq l => Eq ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Rule l -> c ( Rule l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Rule l) Source #

toConstr :: Rule l -> Constr Source #

dataTypeOf :: Rule l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Rule l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Rule l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Rule l -> Rule l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Rule l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Rule l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Rule l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Rule l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Rule l -> m ( Rule l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Rule l -> m ( Rule l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Rule l -> m ( Rule l) Source #

Ord l => Ord ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Rule l) :: Type -> Type Source #

Pretty ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Rule l -> Doc

prettyPrec :: Int -> Rule l -> Doc

type Rep ( Rule l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> RuleVar l -> c ( RuleVar l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( RuleVar l) Source #

toConstr :: RuleVar l -> Constr Source #

dataTypeOf :: RuleVar l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( RuleVar l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( RuleVar l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> RuleVar l -> RuleVar l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> RuleVar l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> RuleVar l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> RuleVar l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> RuleVar l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> RuleVar l -> m ( RuleVar l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> RuleVar l -> m ( RuleVar l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> RuleVar l -> m ( RuleVar l) Source #

Ord l => Ord ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( RuleVar l) :: Type -> Type Source #

Pretty ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RuleVar l -> Doc

prettyPrec :: Int -> RuleVar l -> Doc

type Rep ( RuleVar l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

data Activation l Source #

Activation clause of a RULES pragma.

Instances

Instances details
Functor Activation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Activation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Activation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Activation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP Activation Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Activation l -> c ( Activation l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Activation l) Source #

toConstr :: Activation l -> Constr Source #

dataTypeOf :: Activation l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Activation l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Activation l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Activation l -> Activation l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Activation l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Activation l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Activation l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Activation l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Activation l -> m ( Activation l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Activation l -> m ( Activation l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Activation l -> m ( Activation l) Source #

Ord l => Ord ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Activation l) :: Type -> Type Source #

Pretty ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( Activation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

AppFixity Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Fixity

ExactP Annotation Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Annotation l -> c ( Annotation l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Annotation l) Source #

toConstr :: Annotation l -> Constr Source #

dataTypeOf :: Annotation l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Annotation l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Annotation l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Annotation l -> Annotation l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Annotation l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Annotation l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Annotation l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Annotation l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Annotation l -> m ( Annotation l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Annotation l -> m ( Annotation l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Annotation l -> m ( Annotation l) Source #

Ord l => Ord ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep ( Annotation l) :: Type -> Type Source #

Pretty ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( Annotation l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

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

Instances details
Functor BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Foldable BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Traversable BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

ExactP BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.ExactPrint

Eq l => Eq ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Data l => Data ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> BooleanFormula l -> c ( BooleanFormula l) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( BooleanFormula l) Source #

toConstr :: BooleanFormula l -> Constr Source #

dataTypeOf :: BooleanFormula l -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( BooleanFormula l)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( BooleanFormula l)) Source #

gmapT :: ( forall b. Data b => b -> b) -> BooleanFormula l -> BooleanFormula l Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> BooleanFormula l -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> BooleanFormula l -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> BooleanFormula l -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> BooleanFormula l -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> BooleanFormula l -> m ( BooleanFormula l) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> BooleanFormula l -> m ( BooleanFormula l) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> BooleanFormula l -> m ( BooleanFormula l) Source #

Ord l => Ord ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Pretty ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep ( BooleanFormula l) Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Builtin names

Modules

Main function of a program

Constructors

Special identifiers

Type constructors

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

Instances details
Annotated Alt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Alt l -> l Source #

amap :: (l -> l) -> Alt l -> Alt l Source #

Annotated FieldUpdate Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QualStmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Stmt Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated PatField Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RPat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RPatOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated PXAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Pat Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Pat l -> l Source #

amap :: (l -> l) -> Pat l -> Pat l Source #

Annotated WarningText Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated RuleVar Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Rule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Activation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Overlap Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModulePragma Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated CallConv Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Safety Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Splice Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Bracket Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated XAttr Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated XName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Exp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Exp l -> l Source #

amap :: (l -> l) -> Exp l -> Exp l Source #

Annotated Sign Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Literal Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Asst Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Context Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated FunDep Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated TyVarBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Promoted Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated MaybePromotedName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Type Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated GuardedRhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Rhs Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Rhs l -> l Source #

amap :: (l -> l) -> Rhs l -> Rhs l Source #

Annotated Unpackedness Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated BangType Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ClassDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated GadtDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated FieldDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QualConDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Match Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated IPBind Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Binds Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DerivStrategy Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Deriving Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InstRule Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DeclHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ResultSig Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated InjectivityInfo Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated DataOrNew Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Role Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated BooleanFormula Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Annotation Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated TypeEqn Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Decl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Assoc Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ImportDecl Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Namespace Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated EWildcard Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ExportSpec Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ExportSpecList Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModuleHead Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Module Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated CName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Op Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: Op l -> l Source #

amap :: (l -> l) -> Op l -> Op l Source #

Annotated QOp Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: QOp l -> l Source #

amap :: (l -> l) -> QOp l -> QOp l Source #

Annotated IPName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated Name Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated QName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated SpecialCon Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

Annotated ModuleName Source #
Instance details

Defined in Language.Haskell.Exts.Syntax

(=~=) :: ( Annotated a, Eq (a ())) => a l1 -> a l2 -> Bool Source #

Test if two AST elements are equal modulo annotations.