ghc-lib-parser-9.2.3.20220527: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Parser.Annotation

Synopsis

Core Exact Print Annotation types

data AnnKeywordId Source #

Exact print annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not otherwise captured in the AST.

The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/in-tree-api-annotations

Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [exact print annotations] above for details of the usage

Constructors

AnnAnyclass 
AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseB

'|)'

AnnCloseBU

'|)', unicode variant

AnnCloseC

'}'

AnnCloseQ

'|]'

AnnCloseQU

'|]', unicode variant

AnnCloseP

')'

AnnClosePH

'#)'

AnnCloseS

']'

AnnColon 
AnnComma

as a list separator

AnnCommaTuple

in a RdrName for a tuple

AnnDarrow

'=>'

AnnDarrowU

'=>', unicode variant

AnnData 
AnnDcolon

'::'

AnnDcolonU

'::', unicode variant

AnnDefault 
AnnDeriving 
AnnDo 
AnnDot

.

AnnDotdot

'..'

AnnElse 
AnnEqual 
AnnExport 
AnnFamily 
AnnForall 
AnnForallU

Unicode variant

AnnForeign 
AnnFunId

for function name in matches where there are multiple equations for the function.

AnnGroup 
AnnHeader

for CType

AnnHiding 
AnnIf 
AnnImport 
AnnIn 
AnnInfix

'infix' or 'infixl' or 'infixr'

AnnInstance 
AnnLam 
AnnLarrow

'<-'

AnnLarrowU

'<-', unicode variant

AnnLet 
AnnLollyU

The unicode arrow

AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnName

where a name loses its location in the AST, this carries it

AnnOf 
AnnOpen

'{-# DEPRECATED' etc. Opening of pragmas where the capitalisation of the string can be changed by the user. The actual text used is stored in a SourceText on the relevant pragma item.

AnnOpenB

'(|'

AnnOpenBU

'(|', unicode variant

AnnOpenC

'{'

AnnOpenE

'[e|' or '[e||'

AnnOpenEQ

'[|'

AnnOpenEQU

'[|', unicode variant

AnnOpenP

'('

AnnOpenS

'['

AnnOpenPH

'(#'

AnnDollar

prefix $ -- TemplateHaskell

AnnDollarDollar

prefix $$ -- TemplateHaskell

AnnPackageName 
AnnPattern 
AnnPercent

% -- for HsExplicitMult

AnnPercentOne

'%1' -- for HsLinearArrow

AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThTyQuote

double '''

AnnTilde

'~'

AnnType 
AnnUnit

() for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnVia

via

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

->

AnnrarrowtailU

->, unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

Instances

Instances details
Eq AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnKeywordId -> Constr #

dataTypeOf :: AnnKeywordId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Show AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

data EpaComment Source #

Constructors

EpaComment 

Fields

Instances

Instances details
Eq EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Data EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: EpaComment -> Constr #

dataTypeOf :: EpaComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Show EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc Source #

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

data EpaCommentTok Source #

Constructors

EpaDocCommentNext String

something beginning '-- |'

EpaDocCommentPrev String

something beginning '-- ^'

EpaDocCommentNamed String

something beginning '-- $'

EpaDocSection Int String

a section heading

EpaDocOptions String

doc options (prune, ignore-exports, etc)

EpaLineComment String

comment starting by "--"

EpaBlockComment String

comment in {- -}

EpaEofComment

empty comment, capturing location of EOF

Instances

Instances details
Eq EpaCommentTok Source # 
Instance details

Defined in GHC.Parser.Annotation

Data EpaCommentTok Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: EpaCommentTok -> Constr #

dataTypeOf :: EpaCommentTok -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EpaCommentTok Source # 
Instance details

Defined in GHC.Parser.Annotation

Show EpaCommentTok Source # 
Instance details

Defined in GHC.Parser.Annotation

data IsUnicodeSyntax Source #

Certain tokens can have alternate representations when unicode syntax is enabled. This flag is attached to those tokens in the lexer so that the original source representation can be reproduced in the corresponding EpAnnotation

Instances

Instances details
Eq IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Data IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: IsUnicodeSyntax -> Constr #

dataTypeOf :: IsUnicodeSyntax -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Show IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

unicodeAnn :: AnnKeywordId -> AnnKeywordId Source #

Convert a normal annotation into its unicode equivalent one

data HasE Source #

Some template haskell tokens have two variants, one with an e the other not:

 [| or [e|
 [|| or [e||

This type indicates whether the e is present or not.

Constructors

HasE 
NoE 

Instances

Instances details
Eq HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Data HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: HasE -> Constr #

dataTypeOf :: HasE -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

compare :: HasE -> HasE -> Ordering #

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

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

(>) :: HasE -> HasE -> Bool #

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

max :: HasE -> HasE -> HasE #

min :: HasE -> HasE -> HasE #

Show HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

showsPrec :: Int -> HasE -> ShowS #

show :: HasE -> String #

showList :: [HasE] -> ShowS #

In-tree Exact Print Annotations

data AddEpAnn Source #

Captures an annotation, storing the AnnKeywordId and its location. The parser only ever inserts EpaLocation fields with a RealSrcSpan being the original location of the annotation in the source file. The EpaLocation can also store a delta position if the AST has been modified and needs to be pretty printed again. The usual way an AddEpAnn is created is using the mj ("make jump") function, and then it can be inserted into the appropriate annotation.

Instances

Instances details
Eq AddEpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AddEpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AddEpAnn -> Constr #

dataTypeOf :: AddEpAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddEpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AddEpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AddEpAnn -> SDoc Source #

data EpaLocation Source #

The anchor for an AnnKeywordId. The Parser inserts the EpaSpan variant, giving the exact location of the original item in the parsed source. This can be replaced by the EpaDelta version, to provide a position for the item relative to the end of the previous item in the source. This is useful when editing an AST prior to exact printing the changed one. The list of comments in the EpaDelta variant captures any comments between the prior output and the thing being marked here, since we cannot otherwise sort the relative order.

Instances

Instances details
Eq EpaLocation Source # 
Instance details

Defined in GHC.Parser.Annotation

Data EpaLocation Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: EpaLocation -> Constr #

dataTypeOf :: EpaLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EpaLocation Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpaLocation Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaLocation -> SDoc Source #

epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan Source #

Used in the parser only, extract the RealSrcSpan from an EpaLocation. The parser will never insert a DeltaPos, so the partial function is safe.

data DeltaPos Source #

Spacing between output items when exact printing. It captures the spacing from the current print position on the page to the position required for the thing about to be printed. This is either on the same line in which case is is simply the number of spaces to emit, or it is some number of lines down, with a given column offset. The exact printing algorithm keeps track of the column offset pertaining to the current anchor position, so the deltaColumn is the additional spaces to add in this case. See https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations for details.

Constructors

SameLine 

Fields

DifferentLine 

Fields

Instances

Instances details
Eq DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Data DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: DeltaPos -> Constr #

dataTypeOf :: DeltaPos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Show DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable DeltaPos Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc Source #

deltaPos :: Int -> Int -> DeltaPos Source #

Smart constructor for a DeltaPos. It preserves the invariant that for the DifferentLine constructor deltaLine is always > 0.

data EpAnn ann Source #

The exact print annotations (EPAs) are kept in the HsSyn AST for the GhcPs phase. We do not always have EPAs though, only for code that has been parsed as they do not exist for generated code. This type captures that they may be missing.

A goal of the annotations is that an AST can be edited, including moving subtrees from one place to another, duplicating them, and so on. This means that each fragment must be self-contained. To this end, each annotated fragment keeps track of the anchor position it was originally captured at, being simply the start span of the topmost element of the ast fragment. This gives us a way to later re-calculate all Located items in this layer of the AST, as well as any annotations captured. The comments associated with the AST fragment are also captured here.

The ann type parameter allows this general structure to be specialised to the specific set of locations of original exact print annotation elements. So for HsLet we have

type instance XLet GhcPs = EpAnn AnnsLet data AnnsLet = AnnsLet { alLet :: EpaLocation, alIn :: EpaLocation } deriving Data

The spacing between the items under the scope of a given EpAnn is normally derived from the original Anchor. But if a sub-element is not in its original position, the required spacing can be directly captured in the anchor_op field of the entry Anchor. This allows us to freely move elements around, and stitch together new AST fragments out of old ones, and have them still printed out in a precise way.

Constructors

EpAnn 

Fields

  • entry :: !Anchor

    Base location for the start of the syntactic element holding the annotations.

  • anns :: !ann

    Annotations added by the Parser

  • comments :: !EpAnnComments

    Comments enclosed in the SrcSpan of the element this EpAnn is attached to

EpAnnNotUsed

No Annotation for generated code, e.g. from TH, deriving, etc.

Instances

Instances details
Functor EpAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

fmap :: (a -> b) -> EpAnn a -> EpAnn b #

(<$) :: a -> EpAnn b -> EpAnn a #

Eq ann => Eq (EpAnn ann) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

(==) :: EpAnn ann -> EpAnn ann -> Bool #

(/=) :: EpAnn ann -> EpAnn ann -> Bool #

Data ann => Data (EpAnn ann) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnn ann -> c (EpAnn ann) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EpAnn ann) #

toConstr :: EpAnn ann -> Constr #

dataTypeOf :: EpAnn ann -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> EpAnn ann -> EpAnn ann #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnn ann -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnn ann -> r #

gmapQ :: (forall d. Data d => d -> u) -> EpAnn ann -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnn ann -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnn ann -> m (EpAnn ann) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnn ann -> m (EpAnn ann) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnn ann -> m (EpAnn ann) #

Semigroup a => Semigroup (EpAnn a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

(<>) :: EpAnn a -> EpAnn a -> EpAnn a #

sconcat :: NonEmpty (EpAnn a) -> EpAnn a #

stimes :: Integral b => b -> EpAnn a -> EpAnn a #

Monoid a => Monoid (EpAnn a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

mempty :: EpAnn a #

mappend :: EpAnn a -> EpAnn a -> EpAnn a #

mconcat :: [EpAnn a] -> EpAnn a #

Outputable a => Outputable (EpAnn a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnn a -> SDoc Source #

Binary a => Binary (LocatedL a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Data (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

Data (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

Data (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

Data (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

Data (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

Data (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

Data (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

Data (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

Data (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

Data (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

Data (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

Data (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

Data (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

Data (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

NamedThing (Located a) => NamedThing (LocatedAn an a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Data (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

Data (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

data Anchor Source #

An Anchor records the base location for the start of the syntactic element holding the annotations, and is used as the point of reference for calculating delta positions for contained annotations. It is also normally used as the reference point for the spacing of the element relative to its container. If it is moved, that relationship is tracked in the anchor_op instead.

Constructors

Anchor 

Fields

Instances

Instances details
Eq Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Data Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: Anchor -> Constr #

dataTypeOf :: Anchor -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Show Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Semigroup Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable Anchor Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: Anchor -> SDoc Source #

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

data AnchorOperation Source #

If tools modify the parsed source, the MovedAnchor variant can directly provide the spacing for this item relative to the previous one when printing. This allows AST fragments with a particular anchor to be freely moved, without worrying about recalculating the appropriate anchor span.

Instances

Instances details
Eq AnchorOperation Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AnchorOperation Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnchorOperation -> Constr #

dataTypeOf :: AnchorOperation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnchorOperation Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnchorOperation Source # 
Instance details

Defined in GHC.Parser.Annotation

noAnn :: EpAnn a Source #

Short form for EpAnnNotUsed

Comments in Annotations

data EpAnnComments Source #

When we are parsing we add comments that belong a particular AST element, and print them together with the element, interleaving them into the output stream. But when editing the AST to move fragments around it is useful to be able to first separate the comments into those occuring before the AST element and those following it. The EpaCommentsBalanced constructor is used to do this. The GHC parser will only insert the EpaComments form.

Instances

Instances details
Eq EpAnnComments Source # 
Instance details

Defined in GHC.Parser.Annotation

Data EpAnnComments Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: EpAnnComments -> Constr #

dataTypeOf :: EpAnnComments -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup EpAnnComments Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable EpAnnComments Source # 
Instance details

Defined in GHC.Parser.Annotation

type EpAnnCO Source #

Arguments

 = EpAnn NoEpAnns

Api Annotations for comments only

Annotations in GenLocated

type LocatedAn an = GenLocated (SrcAnn an) Source #

General representation of a GenLocated type carrying a parameterised annotation type.

data SrcSpanAnn' a Source #

The 'SrcSpanAnn'' type wraps a normal SrcSpan, together with an extra annotation type. This is mapped to a specific GenLocated usage in the AST through the XRec and Anno type families.

Constructors

SrcSpanAnn 

Fields

Instances

Instances details
Eq a => Eq (SrcSpanAnn' a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Data a => Data (SrcSpanAnn' a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpanAnn' a -> c (SrcSpanAnn' a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SrcSpanAnn' a) #

toConstr :: SrcSpanAnn' a -> Constr #

dataTypeOf :: SrcSpanAnn' a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SrcSpanAnn' a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SrcSpanAnn' a)) #

gmapT :: (forall b. Data b => b -> b) -> SrcSpanAnn' a -> SrcSpanAnn' a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpanAnn' a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpanAnn' a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcSpanAnn' a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpanAnn' a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpanAnn' a -> m (SrcSpanAnn' a) #

Semigroup an => Semigroup (SrcSpanAnn' an) Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable a => Outputable (SrcSpanAnn' a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc Source #

Binary a => Binary (LocatedL a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Data (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

Data (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

Data (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

Data (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

Data (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

Data (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

Data (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

Data (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

Data (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

Data (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

Data (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

Data (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

Data (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

Data (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc Source #

NamedThing (Located a) => NamedThing (LocatedAn an a) Source # 
Instance details

Defined in GHC.Parser.Annotation

Data (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

Data (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type SrcAnn ann = SrcSpanAnn' (EpAnn ann) Source #

We mostly use 'SrcSpanAnn'' with an 'EpAnn''

Annotation data types used in GenLocated

data AnnListItem Source #

Annotation for items appearing in a list. They can have one or more trailing punctuations items, such as commas or semicolons.

Constructors

AnnListItem 

Instances

Instances details
Eq AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnListItem -> Constr #

dataTypeOf :: AnnListItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Monoid AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnListItem Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnListItem -> SDoc Source #

Data (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) #

Data (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) #

Data (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) #

Data (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) #

Data (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) #

Data (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) #

Data (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) #

Data (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) #

Data (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) #

Data (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) #

Data (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) #

Data (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) #

Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) #

Data (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) #

Data (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) #

Data (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) #

Data (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) #

Data (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) #

Data (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) #

Data (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) #

Data (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) #

Data (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) #

Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) #

type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnList Source #

Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.

Constructors

AnnList 

Fields

Instances

Instances details
Eq AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Data AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnList -> Constr #

dataTypeOf :: AnnList -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Monoid AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnList Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnList -> SDoc Source #

Binary a => Binary (LocatedL a) Source # 
Instance details

Defined in GHC.Parser.Annotation

data AnnParen Source #

exact print annotation for an item having surrounding "brackets", such as tuples or lists

Instances

Instances details
Data AnnParen Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnParen -> Constr #

dataTypeOf :: AnnParen -> DataType #

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

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

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

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

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

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

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

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

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

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

data ParenType Source #

Detail of the "brackets" used in an AnnParen exact print annotation.

Constructors

AnnParens

'(', ')'

AnnParensHash

'()'

AnnParensSquare

'[', ']'

Instances

Instances details
Eq ParenType Source # 
Instance details

Defined in GHC.Parser.Annotation

Data ParenType Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: ParenType -> Constr #

dataTypeOf :: ParenType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ParenType Source # 
Instance details

Defined in GHC.Parser.Annotation

parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) Source #

Maps the ParenType to the related opening and closing AnnKeywordId. Used when actually printing the item.

data AnnPragma Source #

exact print annotation used for capturing the locations of annotations in pragmas.

Constructors

AnnPragma 

Instances

Instances details
Eq AnnPragma Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AnnPragma Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnPragma -> Constr #

dataTypeOf :: AnnPragma -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AnnPragma Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnPragma -> SDoc Source #

data AnnContext Source #

Exact print annotation for the Context data type.

Constructors

AnnContext 

Fields

Instances

Instances details
Data AnnContext Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnContext -> Constr #

dataTypeOf :: AnnContext -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AnnContext Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnContext -> SDoc Source #

data NameAnn Source #

exact print annotations for a RdrName. There are many kinds of adornment that can be attached to a given RdrName. This type captures them, as detailed on the individual constructors.

Constructors

NameAnn

Used for a name with an adornment, so `foo`, (bar)

NameAnnCommas

Used for (,,,), or @()#

NameAnnOnly

Used for (), (##), []

NameAnnRArrow

Used for ->, as an identifier

NameAnnQuote

Used for an item with a leading '. The annotation for unquoted item is stored in nann_quoted.

NameAnnTrailing

Used when adding a TrailingAnn to an existing LocatedN which has no Api Annotation (via the EpAnnNotUsed constructor.

Instances

Instances details
Eq NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

Data NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: NameAnn -> Constr #

dataTypeOf :: NameAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Monoid NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAnn -> SDoc Source #

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

data NameAdornment Source #

A NameAnn can capture the locations of surrounding adornments, such as parens or backquotes. This data type identifies what particular pair are being used.

Constructors

NameParens

'(' ')'

NameParensHash

'()'

NameBackquotes

'`'

NameSquare

'[' ']'

Instances

Instances details
Eq NameAdornment Source # 
Instance details

Defined in GHC.Parser.Annotation

Data NameAdornment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: NameAdornment -> Constr #

dataTypeOf :: NameAdornment -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NameAdornment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable NameAdornment Source # 
Instance details

Defined in GHC.Parser.Annotation

data NoEpAnns Source #

Constructors

NoEpAnns 

Instances

Instances details
Eq NoEpAnns Source # 
Instance details

Defined in GHC.Parser.Annotation

Data NoEpAnns Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: NoEpAnns -> Constr #

dataTypeOf :: NoEpAnns -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NoEpAnns Source # 
Instance details

Defined in GHC.Parser.Annotation

data AnnSortKey Source #

Captures the sort order of sub elements. This is needed when the sub-elements have been split (as in a HsLocalBind which holds separate binds and sigs) or for infix patterns where the order has been re-arranged. It is captured explicitly so that after the Delta phase a SrcSpan is used purely as an index into the annotations, allowing transformations of the AST including the introduction of new Located items or re-arranging existing ones.

Instances

Instances details
Eq AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Data AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: AnnSortKey -> Constr #

dataTypeOf :: AnnSortKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Monoid AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnSortKey Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnSortKey -> SDoc Source #

Trailing annotations in lists

data TrailingAnn Source #

Captures the location of punctuation occuring between items, normally in a list. It is captured as a trailing annotation.

Constructors

AddSemiAnn EpaLocation

Trailing ';'

AddCommaAnn EpaLocation

Trailing ','

AddVbarAnn EpaLocation

Trailing '|'

AddRarrowAnn EpaLocation

Trailing ->

AddRarrowAnnU EpaLocation

Trailing ->, unicode variant

AddLollyAnnU EpaLocation

Trailing

Instances

Instances details
Eq TrailingAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Data TrailingAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

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

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

toConstr :: TrailingAnn -> Constr #

dataTypeOf :: TrailingAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrailingAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable TrailingAnn Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: TrailingAnn -> SDoc Source #

addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnListItem -> EpAnn AnnListItem Source #

Helper function used in the parser to add a TrailingAnn items to an existing annotation.

addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn AnnList -> EpAnn AnnList Source #

Helper function used in the parser to add a TrailingAnn items to an existing annotation.

addTrailingCommaToN :: SrcSpan -> EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn Source #

Helper function used in the parser to add a comma location to an existing annotation.

Utilities for converting between different GenLocated when

we do not care about the annotations.

la2na :: SrcSpanAnn' a -> SrcSpanAnnN Source #

Helper function (temporary) during transition of names Discards any annotations

na2la :: SrcSpanAnn' a -> SrcAnn ann Source #

Helper function (temporary) during transition of names Discards any annotations

l2n :: LocatedAn a1 a2 -> LocatedN a2 Source #

Helper function (temporary) during transition of names Discards any annotations

la2la :: LocatedAn ann1 a2 -> LocatedAn ann2 a2 Source #

Helper function (temporary) during transition of names Discards any annotations

Building up annotations

widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan Source #

The annotations need to all come after the anchor. Make sure this is the case.

Querying annotations

epAnnAnnsL :: EpAnn a -> [a] Source #

Working with locations of annotations

mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b Source #

addCLocA :: GenLocated (SrcSpanAnn' a) e1 -> GenLocated SrcSpan e2 -> e3 -> GenLocated (SrcAnn ann) e3 Source #

Combine locations from two Located things and add them to a third thing

Constructing GenLocated annotation types when we do not care

noLocA :: a -> LocatedAn an a Source #

Working with comments in annotations

addCommentsToSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann Source #

Add additional comments to a SrcAnn, used for manipulating the AST prior to exact printing the changed one.

setCommentsSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann Source #

Replace any existing comments on a SrcAnn, used for manipulating the AST prior to exact printing the changed one.

addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a Source #

Add additional comments, used for manipulating the AST prior to exact printing the changed one.

setCommentsEpAnn :: Monoid a => SrcSpan -> EpAnn a -> EpAnnComments -> EpAnn a Source #

Replace any existing comments, used for manipulating the AST prior to exact printing the changed one.

transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) Source #

Transfer comments and trailing items from the annotations in the first SrcSpanAnnA argument to those in the second.

commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann Source #

Remove the exact print annotations payload, leaving only the anchor and comments.

removeCommentsA :: SrcAnn ann -> SrcAnn ann Source #

Remove the comments, leaving the exact print annotations payload