Safe Haskell | Ignore |
---|---|
Language | GHC2021 |
GHC.Parser.Annotation
Contents
- Core Exact Print Annotation types
- In-tree Exact Print Annotations
- Comments in Annotations
- Annotations in
GenLocated
- Annotation data types used in
GenLocated
- Trailing annotations in lists
- Utilities for converting between different
GenLocated
when - we do not care about the annotations.
- Building up annotations
- Querying annotations
- Working with locations of annotations
- Constructing
GenLocated
annotation types when we do not care - Working with comments in annotations
Synopsis
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnCases
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- data EpToken (tok :: Symbol)
- = NoEpTok
- | EpTok !EpaLocation
- data EpUniToken (tok :: Symbol) (utok :: Symbol)
- getEpTokenSrcSpan :: forall (tok :: Symbol). EpToken tok -> SrcSpan
- data EpLayout
- = EpExplicitBraces !(EpToken "{") !(EpToken "}")
- | EpVirtualBraces !Int
- | EpNoLayout
- data EpaComment = EpaComment {}
- data EpaCommentTok
- data IsUnicodeSyntax
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- data HasE
- data AddEpAnn = AddEpAnn AnnKeywordId EpaLocation
- type EpaLocation = EpaLocation' [LEpaComment]
- data EpaLocation' a
- epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
- data TokenLocation
- data DeltaPos
- = SameLine {
- deltaColumn :: !Int
- | DifferentLine {
- deltaLine :: !Int
- deltaColumn :: !Int
- = SameLine {
- deltaPos :: Int -> Int -> DeltaPos
- getDeltaLine :: DeltaPos -> Int
- data EpAnn ann = EpAnn {
- entry :: !Anchor
- anns :: !ann
- comments :: !EpAnnComments
- type Anchor = EpaLocation
- anchor :: EpaLocation' a -> RealSrcSpan
- spanAsAnchor :: SrcSpan -> EpaLocation' a
- realSpanAsAnchor :: RealSrcSpan -> EpaLocation' a
- noSpanAnchor :: NoAnn a => EpaLocation' a
- class NoAnn a where
- noAnn :: a
- data EpAnnComments
- = EpaComments {
- priorComments :: ![LEpaComment]
- | EpaCommentsBalanced {
- priorComments :: ![LEpaComment]
- followingComments :: ![LEpaComment]
- = EpaComments {
- type LEpaComment = GenLocated NoCommentsLocation EpaComment
- type NoCommentsLocation = EpaLocation' NoComments
- data NoComments = NoComments
- emptyComments :: EpAnnComments
- epaToNoCommentsLocation :: EpaLocation -> NoCommentsLocation
- noCommentsToEpaLocation :: NoCommentsLocation -> EpaLocation
- getFollowingComments :: EpAnnComments -> [LEpaComment]
- setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- type EpAnnCO = EpAnn NoEpAnns
- type LocatedA = GenLocated SrcSpanAnnA
- type LocatedL = GenLocated SrcSpanAnnL
- type LocatedC = GenLocated SrcSpanAnnC
- type LocatedN = GenLocated SrcSpanAnnN
- type LocatedAn an = GenLocated (EpAnn an)
- type LocatedP = GenLocated SrcSpanAnnP
- type SrcSpanAnnA = EpAnn AnnListItem
- type SrcSpanAnnL = EpAnn AnnList
- type SrcSpanAnnP = EpAnn AnnPragma
- type SrcSpanAnnC = EpAnn AnnContext
- type SrcSpanAnnN = EpAnn NameAnn
- type LocatedE = GenLocated EpaLocation
- data AnnListItem = AnnListItem {
- lann_trailing :: [TrailingAnn]
- data AnnList = AnnList {}
- data AnnParen = AnnParen {}
- data ParenType
- parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId)
- data AnnPragma = AnnPragma {}
- data AnnContext = AnnContext {
- ac_darrow :: Maybe (IsUnicodeSyntax, EpaLocation)
- ac_open :: [EpaLocation]
- ac_close :: [EpaLocation]
- data NameAnn
- = NameAnn { }
- | NameAnnCommas { }
- | NameAnnBars { }
- | NameAnnOnly { }
- | NameAnnRArrow { }
- | NameAnnQuote { }
- | NameAnnTrailing {
- nann_trailing :: [TrailingAnn]
- data NameAdornment
- data NoEpAnns = NoEpAnns
- data AnnSortKey tag
- = NoAnnSortKey
- | AnnSortKey [tag]
- data DeclTag
- data BindTag
- data TrailingAnn
- = AddSemiAnn { }
- | AddCommaAnn { }
- | AddVbarAnn { }
- | AddDarrowAnn { }
- | AddDarrowUAnn { }
- trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn
- addTrailingAnnToA :: TrailingAnn -> EpAnnComments -> EpAnn AnnListItem -> EpAnn AnnListItem
- addTrailingAnnToL :: TrailingAnn -> EpAnnComments -> EpAnn AnnList -> EpAnn AnnList
- addTrailingCommaToN :: EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn
- noTrailingN :: SrcSpanAnnN -> SrcSpanAnnN
- l2l :: (HasLoc a, HasAnnotation b) => a -> b
- la2la :: (HasLoc l, HasAnnotation l2) => GenLocated l a -> GenLocated l2 a
- reLoc :: (HasLoc (GenLocated a e), HasAnnotation b) => GenLocated a e -> GenLocated b e
- class HasLoc a where
- getHasLocList :: HasLoc a => [a] -> SrcSpan
- srcSpan2e :: SrcSpan -> EpaLocation
- realSrcSpan :: SrcSpan -> RealSrcSpan
- reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (EpAnn ann) e
- reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a
- addAnns :: EpAnn [AddEpAnn] -> [AddEpAnn] -> EpAnnComments -> EpAnn [AddEpAnn]
- addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA
- widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan
- widenAnchor :: Anchor -> [AddEpAnn] -> Anchor
- widenAnchorS :: Anchor -> SrcSpan -> Anchor
- widenLocatedAn :: EpAnn an -> [AddEpAnn] -> EpAnn an
- getLocAnn :: Located a -> SrcSpanAnnA
- epAnnAnns :: EpAnn [AddEpAnn] -> [AddEpAnn]
- annParen2AddEpAnn :: AnnParen -> [AddEpAnn]
- epAnnComments :: EpAnn an -> EpAnnComments
- sortLocatedA :: HasLoc (EpAnn a) => [GenLocated (EpAnn a) e] -> [GenLocated (EpAnn a) e]
- mapLocA :: NoAnn ann => (a -> b) -> GenLocated SrcSpan a -> GenLocated (EpAnn ann) b
- combineLocsA :: Semigroup a => GenLocated (EpAnn a) e1 -> GenLocated (EpAnn a) e2 -> EpAnn a
- combineSrcSpansA :: Semigroup a => EpAnn a -> EpAnn a -> EpAnn a
- addCLocA :: (HasLoc a, HasLoc b, HasAnnotation l) => a -> b -> c -> GenLocated l c
- class HasAnnotation e where
- noAnnSrcSpan :: SrcSpan -> e
- locA :: HasLoc a => a -> SrcSpan
- noLocA :: HasAnnotation e => a -> GenLocated e a
- getLocA :: HasLoc a => GenLocated a e -> SrcSpan
- noSrcSpanA :: HasAnnotation e => e
- noComments :: EpAnnCO
- comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO
- addCommentsToEpAnn :: NoAnn ann => EpAnn ann -> EpAnnComments -> EpAnn ann
- setCommentsEpAnn :: NoAnn ann => EpAnn ann -> EpAnnComments -> EpAnn ann
- transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- transferAnnsOnlyA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- transferCommentsOnlyA :: EpAnn a -> EpAnn b -> (EpAnn a, EpAnn b)
- transferPriorCommentsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- transferFollowingA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- commentsOnlyA :: NoAnn ann => EpAnn ann -> EpAnn ann
- removeCommentsA :: EpAnn ann -> EpAnn ann
- placeholderRealSpan :: RealSrcSpan
Core Exact Print Annotation types
data AnnKeywordId #
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 | |
AnnBang |
|
AnnBackquote | '`' |
AnnBy | |
AnnCase | case or lambda case |
AnnCases | lambda cases |
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 |
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
|
AnnOpenB | '(|' |
AnnOpenBU | '(|', unicode variant |
AnnOpenC | '{' |
AnnOpenE | '[e|' or '[e||' |
AnnOpenEQ | '[|' |
AnnOpenEQU | '[|', unicode variant |
AnnOpenP | '(' |
AnnOpenS | '[' |
AnnOpenPH | '(#' |
AnnDollar | prefix |
AnnDollarDollar | prefix |
AnnPackageName | |
AnnPattern | |
AnnPercent |
|
AnnPercentOne | '%1' -- for HsLinearArrow |
AnnProc | |
AnnQualified | |
AnnRarrow |
|
AnnRarrowU |
|
AnnRec | |
AnnRole | |
AnnSafe | |
AnnSemi | ';' |
AnnSimpleQuote | ''' |
AnnSignature | |
AnnStatic |
|
AnnStock | |
AnnThen | |
AnnThTyQuote | double ''' |
AnnTilde |
|
AnnType | |
AnnUnit |
|
AnnUsing | |
AnnVal | e.g. INTEGER |
AnnValStr | String value, will need quotes when output |
AnnVbar | '|' |
AnnVia |
|
AnnWhere | |
Annlarrowtail |
|
AnnlarrowtailU |
|
Annrarrowtail |
|
AnnrarrowtailU |
|
AnnLarrowtail |
|
AnnLarrowtailU |
|
AnnRarrowtail |
|
AnnRarrowtailU |
|
Instances
data EpToken (tok :: Symbol) #
A token stored in the syntax tree. For example, when parsing a
let-expression, we store EpToken "let"
and EpToken "in"
.
The locations of those tokens can be used to faithfully reproduce
(exactprint) the original program text.
Constructors
NoEpTok | |
EpTok !EpaLocation |
Instances
KnownSymbol tok => Data (EpToken tok) # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpToken tok -> c (EpToken tok) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EpToken tok) # toConstr :: EpToken tok -> Constr # dataTypeOf :: EpToken tok -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EpToken tok)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EpToken tok)) # gmapT :: (forall b. Data b => b -> b) -> EpToken tok -> EpToken tok # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpToken tok -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpToken tok -> r # gmapQ :: (forall d. Data d => d -> u) -> EpToken tok -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpToken tok -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpToken tok -> m (EpToken tok) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpToken tok -> m (EpToken tok) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpToken tok -> m (EpToken tok) # | |
NoAnn (EpToken s) # | |
Defined in GHC.Parser.Annotation | |
Eq (EpToken tok) # | |
data EpUniToken (tok :: Symbol) (utok :: Symbol) #
With UnicodeSyntax
, there might be multiple ways to write the same
token. For example an arrow could be either ->
or →
. This choice must be
recorded in order to exactprint such tokens, so instead of EpToken "->"
we
introduce EpUniToken "->" "→"
.
Constructors
NoEpUniTok | |
EpUniTok !EpaLocation !IsUnicodeSyntax |
Instances
(KnownSymbol tok, KnownSymbol utok) => Data (EpUniToken tok utok) # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpUniToken tok utok -> c (EpUniToken tok utok) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EpUniToken tok utok) # toConstr :: EpUniToken tok utok -> Constr # dataTypeOf :: EpUniToken tok utok -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EpUniToken tok utok)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EpUniToken tok utok)) # gmapT :: (forall b. Data b => b -> b) -> EpUniToken tok utok -> EpUniToken tok utok # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpUniToken tok utok -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpUniToken tok utok -> r # gmapQ :: (forall d. Data d => d -> u) -> EpUniToken tok utok -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpUniToken tok utok -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpUniToken tok utok -> m (EpUniToken tok utok) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpUniToken tok utok -> m (EpUniToken tok utok) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpUniToken tok utok -> m (EpUniToken tok utok) # | |
NoAnn (EpUniToken s t) # | |
Defined in GHC.Parser.Annotation Methods noAnn :: EpUniToken s t # |
getEpTokenSrcSpan :: forall (tok :: Symbol). EpToken tok -> SrcSpan #
Layout information for declarations.
Constructors
EpExplicitBraces !(EpToken "{") !(EpToken "}") | Explicit braces written by the user. class C a where { foo :: a; bar :: a } |
EpVirtualBraces | Virtual braces inserted by the layout algorithm. class C a where foo :: a bar :: a |
Fields
| |
EpNoLayout | Empty or compiler-generated blocks do not have layout information associated with them. |
Instances
Data EpLayout # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpLayout -> c EpLayout # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpLayout # toConstr :: EpLayout -> Constr # dataTypeOf :: EpLayout -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpLayout) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpLayout) # gmapT :: (forall b. Data b => b -> b) -> EpLayout -> EpLayout # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpLayout -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpLayout -> r # gmapQ :: (forall d. Data d => d -> u) -> EpLayout -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpLayout -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpLayout -> m EpLayout # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpLayout -> m EpLayout # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpLayout -> m EpLayout # |
data EpaComment #
Constructors
EpaComment | |
Fields
|
Instances
data EpaCommentTok #
Constructors
EpaDocComment HsDocString | a docstring that can be pretty printed using pprHsDocString |
EpaDocOptions String | doc options (prune, ignore-exports, etc) |
EpaLineComment String | comment starting by "--" |
EpaBlockComment String | comment in {- -} |
Instances
Data EpaCommentTok # | |
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 # | |
Show EpaCommentTok # | |
Defined in GHC.Parser.Annotation Methods showsPrec :: Int -> EpaCommentTok -> ShowS # show :: EpaCommentTok -> String # showList :: [EpaCommentTok] -> ShowS # | |
Eq EpaCommentTok # | |
Defined in GHC.Parser.Annotation Methods (==) :: EpaCommentTok -> EpaCommentTok -> Bool # (/=) :: EpaCommentTok -> EpaCommentTok -> Bool # |
data IsUnicodeSyntax #
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
Constructors
UnicodeSyntax | |
NormalSyntax |
Instances
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Convert a normal annotation into its unicode equivalent one
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.
Instances
Data HasE # | |
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 # 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 # | |
Show HasE # | |
Eq HasE # | |
Ord HasE # | |
In-tree Exact Print Annotations
Captures an annotation, storing the
and its
location. The parser only ever inserts AnnKeywordId
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 EpaLocation
AddEpAnn
is created is using the mj
("make
jump") function, and then it can be inserted into the appropriate
annotation.
Constructors
AddEpAnn AnnKeywordId EpaLocation |
Instances
Data AddEpAnn # | |
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 # | |
NoAnn AddEpAnn # | |
Defined in GHC.Parser.Annotation | |
Outputable AddEpAnn # | |
Defined in GHC.Parser.Annotation | |
Eq AddEpAnn # | |
type EpaLocation = EpaLocation' [LEpaComment] #
data EpaLocation' a #
The anchor for an
. The Parser inserts the
AnnKeywordId
variant, giving the exact location of the original item
in the parsed source. This can be replaced by the EpaSpan
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.EpaDelta
Instances
epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan #
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 TokenLocation #
Tokens embedded in the AST have an EpaLocation, unless they come from generated code (e.g. by TH).
Constructors
NoTokenLoc | |
TokenLoc !EpaLocation |
Instances
Data TokenLocation # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenLocation -> c TokenLocation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenLocation # toConstr :: TokenLocation -> Constr # dataTypeOf :: TokenLocation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenLocation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenLocation) # gmapT :: (forall b. Data b => b -> b) -> TokenLocation -> TokenLocation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenLocation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenLocation -> r # gmapQ :: (forall d. Data d => d -> u) -> TokenLocation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenLocation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenLocation -> m TokenLocation # | |
Eq TokenLocation # | |
Defined in GHC.Parser.Annotation Methods (==) :: TokenLocation -> TokenLocation -> Bool # (/=) :: TokenLocation -> TokenLocation -> Bool # | |
Outputable a => Outputable (GenLocated TokenLocation a) # | |
Defined in GHC.Parser.Annotation Methods ppr :: GenLocated TokenLocation a -> SDoc # |
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
Data DeltaPos # | |
Defined in GHC.Types.SrcLoc 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 # | |
Show DeltaPos # | |
Outputable DeltaPos # | |
Defined in GHC.Types.SrcLoc | |
Eq DeltaPos # | |
Ord DeltaPos # | |
Defined in GHC.Types.SrcLoc |
deltaPos :: Int -> Int -> DeltaPos #
Smart constructor for a DeltaPos
. It preserves the invariant
that for the DifferentLine
constructor deltaLine
is always > 0.
getDeltaLine :: DeltaPos -> Int #
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 | |
Instances
Functor EpAnn # | |
Semigroup a => Semigroup (EpAnn a) # | |
Data ann => Data (EpAnn ann) # | |
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) # | |
NoAnn ann => HasAnnotation (EpAnn ann) # | |
Defined in GHC.Parser.Annotation Methods noAnnSrcSpan :: SrcSpan -> EpAnn ann # | |
HasLoc (EpAnn a) # | |
Defined in GHC.Parser.Annotation | |
NoAnn ann => NoAnn (EpAnn ann) # | |
Defined in GHC.Parser.Annotation | |
Outputable a => Outputable (EpAnn a) # | |
Defined in GHC.Parser.Annotation | |
Eq ann => Eq (EpAnn ann) # | |
Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # | |
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 (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # | |
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 GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcTc (LocatedA (HsCmd GhcTc))) # | |
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 GhcTc (LocatedA (HsExpr GhcTc))) # | |
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 (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # | |
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 (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # | |
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 GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcTc (LocatedA (HsCmd GhcTc))) # | |
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 GhcTc (LocatedA (HsExpr GhcTc))) # | |
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 (Match GhcPs (LocatedA (HsCmd GhcPs))) # | |
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 (Match GhcPs (LocatedA (HsExpr GhcPs))) # | |
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 GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcTc (LocatedA (HsCmd GhcTc))) # | |
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 GhcTc (LocatedA (HsExpr GhcTc))) # | |
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 (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # | |
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 (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # | |
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 GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcTc (LocatedA (HsCmd GhcTc))) # | |
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 GhcTc (LocatedA (HsExpr GhcTc))) # | |
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))) # | |
NamedThing (Located a) => NamedThing (LocatedAn an a) # | |
Defined in GHC.Parser.Annotation | |
(Outputable a, Outputable e) => Outputable (GenLocated (EpAnn a) e) # | |
Defined in GHC.Parser.Annotation Methods ppr :: GenLocated (EpAnn a) e -> SDoc # | |
(Outputable a, OutputableBndr e) => OutputableBndr (GenLocated (EpAnn a) e) # | |
Defined in GHC.Parser.Annotation Methods pprBndr :: BindingSite -> GenLocated (EpAnn a) e -> SDoc # pprPrefixOcc :: GenLocated (EpAnn a) e -> SDoc # pprInfixOcc :: GenLocated (EpAnn a) e -> SDoc # bndrIsJoin_maybe :: GenLocated (EpAnn a) e -> JoinPointHood # | |
Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # | |
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))) # | |
Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # | |
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 GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # | |
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 GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # | |
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 GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # | |
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 GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # | |
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))) # | |
type Anno (LocatedA (IE (GhcPass p))) # | |
Defined in GHC.Hs.ImpExp | |
type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] # | |
Defined in GHC.Parser.Types | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] # | |
Defined in GHC.Parser.Types | |
type Anno [LocatedA (IE (GhcPass p))] # | |
Defined in GHC.Hs.ImpExp | |
type Anno [LocatedA (ConDeclField (GhcPass _1))] # | |
Defined in GHC.Hs.Decls | |
type Anno [LocatedA (HsType (GhcPass p))] # | |
Defined in GHC.Hs.Type | |
type Anno (FamEqn p (LocatedA (HsType p))) # | |
Defined in GHC.Hs.Decls | |
type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) # | |
type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) # | |
type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) # | |
Defined in GHC.Parser.Types | |
type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) # | |
Defined in GHC.Hs.Expr | |
type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) # | |
Defined in GHC.Hs.Expr | |
type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) # | |
Defined in GHC.Parser.Types | |
type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr)))) # | |
Defined in GHC.Hs.Expr | |
type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) # | |
Defined in GHC.Parser.Types | |
type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) # | |
Defined in GHC.Hs.Expr |
type Anchor = EpaLocation #
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 the AST element is moved,
that relationship is tracked in the anchor_op
instead.
anchor :: EpaLocation' a -> RealSrcSpan #
spanAsAnchor :: SrcSpan -> EpaLocation' a #
realSpanAsAnchor :: RealSrcSpan -> EpaLocation' a #
noSpanAnchor :: NoAnn a => EpaLocation' a #
Instances
Comments in Annotations
data EpAnnComments #
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 occurring 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.
Constructors
EpaComments | |
Fields
| |
EpaCommentsBalanced | |
Fields
|
Instances
data NoComments #
Constructors
NoComments |
Instances
setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments #
setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments #
Annotations in GenLocated
type LocatedA = GenLocated SrcSpanAnnA #
type LocatedL = GenLocated SrcSpanAnnL #
type LocatedC = GenLocated SrcSpanAnnC #
type LocatedN = GenLocated SrcSpanAnnN #
type LocatedAn an = GenLocated (EpAnn an) #
General representation of a GenLocated
type carrying a
parameterised annotation type.
type LocatedP = GenLocated SrcSpanAnnP #
type SrcSpanAnnA = EpAnn AnnListItem #
type SrcSpanAnnL = EpAnn AnnList #
type SrcSpanAnnP = EpAnn AnnPragma #
type SrcSpanAnnC = EpAnn AnnContext #
type SrcSpanAnnN = EpAnn NameAnn #
type LocatedE = GenLocated EpaLocation #
Annotation data types used in GenLocated
data AnnListItem #
Annotation for items appearing in a list. They can have one or more trailing punctuations items, such as commas or semicolons.
Constructors
AnnListItem | |
Fields
|
Instances
Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.
Constructors
AnnList | |
Instances
Data AnnList # | |
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 # | |
NoAnn AnnList # | |
Defined in GHC.Parser.Annotation | |
Outputable AnnList # | |
Defined in GHC.Parser.Annotation | |
Eq AnnList # | |
exact print annotation for an item having surrounding "brackets", such as tuples or lists
Constructors
AnnParen | |
Fields |
Instances
Data AnnParen # | |
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 # | |
NoAnn AnnParen # | |
Defined in GHC.Parser.Annotation |
Detail of the "brackets" used in an AnnParen
exact print annotation.
Constructors
AnnParens | '(', ')' |
AnnParensHash | '(#', '#)' |
AnnParensSquare | '[', ']' |
Instances
Data ParenType # | |
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 # | |
Show ParenType # | |
Outputable ParenType # | |
Defined in GHC.Parser.Annotation | |
Eq ParenType # | |
Ord ParenType # | |
parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) #
Maps the ParenType
to the related opening and closing
AnnKeywordId. Used when actually printing the item.
exact print annotation used for capturing the locations of annotations in pragmas.
Instances
Data AnnPragma # | |
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 # | |
NoAnn AnnPragma # | |
Defined in GHC.Parser.Annotation | |
Outputable AnnPragma # | |
Defined in GHC.Parser.Annotation | |
Eq AnnPragma # | |
data AnnContext #
Exact print annotation for the Context
data type.
Constructors
AnnContext | |
Fields
|
Instances
Data AnnContext # | |
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 # | |
NoAnn AnnContext # | |
Defined in GHC.Parser.Annotation Methods noAnn :: AnnContext # | |
Outputable AnnContext # | |
Defined in GHC.Parser.Annotation Methods ppr :: AnnContext -> SDoc # |
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 |
Fields | |
NameAnnCommas | |
Fields | |
NameAnnBars | Used for |
Fields
| |
NameAnnOnly | Used for |
Fields | |
NameAnnRArrow | Used for |
Fields | |
NameAnnQuote | Used for an item with a leading |
Fields | |
NameAnnTrailing | Used when adding a |
Fields
|
Instances
Data NameAnn # | |
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 # | |
NoAnn NameAnn # | |
Defined in GHC.Parser.Annotation | |
Outputable NameAnn # | |
Defined in GHC.Parser.Annotation | |
Eq NameAnn # | |
data NameAdornment #
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
Constructors
NoEpAnns |
Instances
Data NoEpAnns # | |
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 # | |
NoAnn NoEpAnns # | |
Defined in GHC.Parser.Annotation | |
Outputable NoEpAnns # | |
Defined in GHC.Parser.Annotation | |
Eq NoEpAnns # | |
Ord NoEpAnns # | |
Defined in GHC.Parser.Annotation |
data AnnSortKey tag #
Captures the sort order of sub elements for ValBinds
,
ClassDecl
, ClsInstDecl
Constructors
NoAnnSortKey | |
AnnSortKey [tag] |
Instances
Monoid (AnnSortKey tag) # | |
Defined in GHC.Parser.Annotation Methods mempty :: AnnSortKey tag # mappend :: AnnSortKey tag -> AnnSortKey tag -> AnnSortKey tag # mconcat :: [AnnSortKey tag] -> AnnSortKey tag # | |
Semigroup (AnnSortKey tag) # | |
Defined in GHC.Parser.Annotation Methods (<>) :: AnnSortKey tag -> AnnSortKey tag -> AnnSortKey tag # sconcat :: NonEmpty (AnnSortKey tag) -> AnnSortKey tag # stimes :: Integral b => b -> AnnSortKey tag -> AnnSortKey tag # | |
Data tag => Data (AnnSortKey tag) # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnSortKey tag -> c (AnnSortKey tag) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnSortKey tag) # toConstr :: AnnSortKey tag -> Constr # dataTypeOf :: AnnSortKey tag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnSortKey tag)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnSortKey tag)) # gmapT :: (forall b. Data b => b -> b) -> AnnSortKey tag -> AnnSortKey tag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnSortKey tag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnSortKey tag -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnSortKey tag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnSortKey tag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnSortKey tag -> m (AnnSortKey tag) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSortKey tag -> m (AnnSortKey tag) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSortKey tag -> m (AnnSortKey tag) # | |
Outputable tag => Outputable (AnnSortKey tag) # | |
Defined in GHC.Parser.Annotation Methods ppr :: AnnSortKey tag -> SDoc # | |
Eq tag => Eq (AnnSortKey tag) # | |
Defined in GHC.Parser.Annotation Methods (==) :: AnnSortKey tag -> AnnSortKey tag -> Bool # (/=) :: AnnSortKey tag -> AnnSortKey tag -> Bool # |
Used to track interleaving of class methods, class signatures,
associated types and associate type defaults in ClassDecl
and
ClsInstDecl
.
Constructors
ClsMethodTag | |
ClsSigTag | |
ClsAtTag | |
ClsAtdTag |
Instances
Data DeclTag # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeclTag -> c DeclTag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeclTag # toConstr :: DeclTag -> Constr # dataTypeOf :: DeclTag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeclTag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeclTag) # gmapT :: (forall b. Data b => b -> b) -> DeclTag -> DeclTag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeclTag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeclTag -> r # gmapQ :: (forall d. Data d => d -> u) -> DeclTag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeclTag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeclTag -> m DeclTag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclTag -> m DeclTag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclTag -> m DeclTag # | |
Show DeclTag # | |
Outputable DeclTag # | |
Defined in GHC.Parser.Annotation | |
Eq DeclTag # | |
Ord DeclTag # | |
Defined in GHC.Parser.Annotation |
Used to track of interleaving of binds and signatures for ValBind
Instances
Data BindTag # | |
Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BindTag -> c BindTag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BindTag # toConstr :: BindTag -> Constr # dataTypeOf :: BindTag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BindTag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BindTag) # gmapT :: (forall b. Data b => b -> b) -> BindTag -> BindTag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BindTag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BindTag -> r # gmapQ :: (forall d. Data d => d -> u) -> BindTag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BindTag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BindTag -> m BindTag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BindTag -> m BindTag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BindTag -> m BindTag # | |
Show BindTag # | |
Outputable BindTag # | |
Defined in GHC.Parser.Annotation | |
Eq BindTag # | |
Ord BindTag # | |
Defined in GHC.Parser.Annotation |
Trailing annotations in lists
data TrailingAnn #
Captures the location of punctuation occurring between items, normally in a list. It is captured as a trailing annotation.
Constructors
AddSemiAnn | Trailing ';' |
Fields | |
AddCommaAnn | Trailing ',' |
Fields | |
AddVbarAnn | Trailing '|' |
Fields | |
AddDarrowAnn | Trailing '=>' |
Fields | |
AddDarrowUAnn | Trailing "⇒" |
Fields |
Instances
Data TrailingAnn # | |
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 # | |
Outputable TrailingAnn # | |
Defined in GHC.Parser.Annotation Methods ppr :: TrailingAnn -> SDoc # | |
Eq TrailingAnn # | |
Defined in GHC.Parser.Annotation |
trailingAnnToAddEpAnn :: TrailingAnn -> AddEpAnn #
Convert a TrailingAnn
to an AddEpAnn
addTrailingAnnToA :: TrailingAnn -> EpAnnComments -> EpAnn AnnListItem -> EpAnn AnnListItem #
Helper function used in the parser to add a TrailingAnn
items
to an existing annotation.
addTrailingAnnToL :: TrailingAnn -> EpAnnComments -> EpAnn AnnList -> EpAnn AnnList #
Helper function used in the parser to add a TrailingAnn
items
to an existing annotation.
addTrailingCommaToN :: EpAnn NameAnn -> EpaLocation -> EpAnn NameAnn #
Helper function used in the parser to add a comma location to an existing annotation.
noTrailingN :: SrcSpanAnnN -> SrcSpanAnnN #
Utilities for converting between different GenLocated
when
we do not care about the annotations.
l2l :: (HasLoc a, HasAnnotation b) => a -> b #
Helper function for converting annotation types. Discards any annotations
la2la :: (HasLoc l, HasAnnotation l2) => GenLocated l a -> GenLocated l2 a #
Helper function for converting annotation types. Discards any annotations
reLoc :: (HasLoc (GenLocated a e), HasAnnotation b) => GenLocated a e -> GenLocated b e #
Methods
conveniently calculate locations for things without locations attached
Instances
HasLoc EpaLocation # | |
Defined in GHC.Parser.Annotation Methods getHasLoc :: EpaLocation -> SrcSpan # | |
HasLoc SrcSpan # | |
Defined in GHC.Parser.Annotation | |
HasLoc (EpAnn a) # | |
Defined in GHC.Parser.Annotation | |
HasLoc a => HasLoc (Maybe a) # | |
Defined in GHC.Parser.Annotation | |
HasLoc l => HasLoc (GenLocated l a) # | |
Defined in GHC.Parser.Annotation Methods getHasLoc :: GenLocated l a -> SrcSpan # |
getHasLocList :: HasLoc a => [a] -> SrcSpan #
srcSpan2e :: SrcSpan -> EpaLocation #
realSrcSpan :: SrcSpan -> RealSrcSpan #
Building up annotations
reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (EpAnn ann) e #
reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a #
addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA #
widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan #
The annotations need to all come after the anchor. Make sure this is the case.
widenAnchor :: Anchor -> [AddEpAnn] -> Anchor #
widenAnchorS :: Anchor -> SrcSpan -> Anchor #
widenLocatedAn :: EpAnn an -> [AddEpAnn] -> EpAnn an #
Querying annotations
getLocAnn :: Located a -> SrcSpanAnnA #
annParen2AddEpAnn :: AnnParen -> [AddEpAnn] #
epAnnComments :: EpAnn an -> EpAnnComments #
Working with locations of annotations
sortLocatedA :: HasLoc (EpAnn a) => [GenLocated (EpAnn a) e] -> [GenLocated (EpAnn a) e] #
mapLocA :: NoAnn ann => (a -> b) -> GenLocated SrcSpan a -> GenLocated (EpAnn ann) b #
combineLocsA :: Semigroup a => GenLocated (EpAnn a) e1 -> GenLocated (EpAnn a) e2 -> EpAnn a #
addCLocA :: (HasLoc a, HasLoc b, HasAnnotation l) => a -> b -> c -> GenLocated l c #
Combine locations from two Located
things and add them to a third thing
Constructing GenLocated
annotation types when we do not care
class HasAnnotation e where #
Methods
noAnnSrcSpan :: SrcSpan -> e #
Instances
HasAnnotation EpaLocation # | |
Defined in GHC.Parser.Annotation Methods noAnnSrcSpan :: SrcSpan -> EpaLocation # | |
HasAnnotation SrcSpan # | |
Defined in GHC.Parser.Annotation Methods noAnnSrcSpan :: SrcSpan -> SrcSpan # | |
NoAnn ann => HasAnnotation (EpAnn ann) # | |
Defined in GHC.Parser.Annotation Methods noAnnSrcSpan :: SrcSpan -> EpAnn ann # |
noLocA :: HasAnnotation e => a -> GenLocated e a #
getLocA :: HasLoc a => GenLocated a e -> SrcSpan #
noSrcSpanA :: HasAnnotation e => e #
Working with comments in annotations
noComments :: EpAnnCO #
comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO #
addCommentsToEpAnn :: NoAnn ann => EpAnn ann -> EpAnnComments -> EpAnn ann #
Add additional comments to a EpAnn
, used for manipulating the
AST prior to exact printing the changed one.
setCommentsEpAnn :: NoAnn ann => EpAnn ann -> EpAnnComments -> EpAnn ann #
Replace any existing comments on a EpAnn
, used for manipulating the
AST prior to exact printing the changed one.
transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #
Transfer comments and trailing items from the annotations in the
first SrcSpanAnnA
argument to those in the second.
transferAnnsOnlyA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #
Transfer trailing items from the annotations in the
first SrcSpanAnnA
argument to those in the second.
transferCommentsOnlyA :: EpAnn a -> EpAnn b -> (EpAnn a, EpAnn b) #
Transfer comments from the annotations in the
first SrcSpanAnnA
argument to those in the second.
transferPriorCommentsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #
Transfer prior comments only from the annotations in the
first SrcSpanAnnA
argument to those in the second.
transferFollowingA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) #
Transfer trailing items but not comments from the annotations in the
first SrcSpanAnnA
argument to those in the second.
commentsOnlyA :: NoAnn ann => EpAnn ann -> EpAnn ann #
Remove the exact print annotations payload, leaving only the anchor and comments.
removeCommentsA :: EpAnn ann -> EpAnn ann #
Remove the comments, leaving the exact print annotations payload