ghc-9.4.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.SrcLoc

Description

This module contains types that relate to the positions of things in source files, and allow tagging of those things with locations

Synopsis

SrcLoc

data RealSrcLoc Source #

Real Source Location

Represents a single point within a file

data SrcLoc Source #

Source Location

Instances

Instances details
Show SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc Source #

Eq SrcLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Constructing SrcLoc

mkGeneralSrcLoc :: FastString -> SrcLoc Source #

Creates a "bad" RealSrcLoc that has no detailed information about its location

noSrcLoc :: SrcLoc Source #

Built-in "bad" RealSrcLoc values for particular locations

generatedSrcLoc :: SrcLoc Source #

Built-in "bad" RealSrcLoc values for particular locations

interactiveSrcLoc :: SrcLoc Source #

Built-in "bad" RealSrcLoc values for particular locations

advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc Source #

Move the RealSrcLoc down by one line if the character is a newline, to the next 8-char tabstop if it is a tab, and across by one character in any other case

Unsafely deconstructing SrcLoc

srcLocFile :: RealSrcLoc -> FastString Source #

Gives the filename of the RealSrcLoc

srcLocLine :: RealSrcLoc -> Int Source #

Raises an error when used on a "bad" RealSrcLoc

srcLocCol :: RealSrcLoc -> Int Source #

Raises an error when used on a "bad" RealSrcLoc

SrcSpan

data RealSrcSpan Source #

A RealSrcSpan delimits a portion of a text file. It could be represented by a pair of (line,column) coordinates, but in fact we optimise slightly by using more compact representations for single-line and zero-length spans, both of which are quite common.

The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.

Real Source Span

Instances

Instances details
Data RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: RealSrcSpan -> Constr Source #

dataTypeOf :: RealSrcSpan -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Binary RealSrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

ToJson RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc Source #

Eq RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable e => Outputable (GenLocated RealSrcSpan e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

data SrcSpan Source #

Source Span

A SrcSpan identifies either a specific portion of a text file or a human-readable description of a location.

Instances

Instances details
Data SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: SrcSpan -> Constr Source #

dataTypeOf :: SrcSpan -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () Source #

Binary SrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

ToJson SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc Source #

Outputable SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc Source #

Eq SrcSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

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

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> Located a -> IO () Source #

put :: BinHandle -> Located a -> IO (Bin (Located a)) Source #

get :: BinHandle -> IO (Located a) Source #

Outputable e => Outputable (Located e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (Located (FieldLabelStrings p)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndr (Located (AmbiguousFieldOcc (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.Type

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Constructing SrcSpan

mkGeneralSrcSpan :: FastString -> SrcSpan Source #

Create a "bad" SrcSpan that has not location information

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan Source #

Create a SrcSpan between two points in a file

mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan Source #

Create a SrcSpan between two points in a file

noSrcSpan :: SrcSpan Source #

Built-in "bad" SrcSpans for common sources of location uncertainty

generatedSrcSpan :: SrcSpan Source #

Built-in "bad" SrcSpans for common sources of location uncertainty

wiredInSrcSpan :: SrcSpan Source #

Built-in "bad" SrcSpans for common sources of location uncertainty

interactiveSrcSpan :: SrcSpan Source #

Built-in "bad" SrcSpans for common sources of location uncertainty

srcLocSpan :: SrcLoc -> SrcSpan Source #

Create a SrcSpan corresponding to a single point

combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan Source #

Combines two SrcSpan into one that spans at least all the characters within both spans. Returns UnhelpfulSpan if the files differ.

srcSpanFirstCharacter :: SrcSpan -> SrcSpan Source #

Convert a SrcSpan into one that represents only its first character

Deconstructing SrcSpan

srcSpanStart :: SrcSpan -> SrcLoc Source #

Returns the location at the start of the SrcSpan or a "bad" SrcSpan if that is unavailable

srcSpanEnd :: SrcSpan -> SrcLoc Source #

Returns the location at the end of the SrcSpan or a "bad" SrcSpan if that is unavailable

srcSpanFileName_maybe :: SrcSpan -> Maybe FastString Source #

Obtains the filename for a SrcSpan if it is "good"

Unsafely deconstructing SrcSpan

Predicates on SrcSpan

isGoodSrcSpan :: SrcSpan -> Bool Source #

Test if a SrcSpan is "good", i.e. has precise location information

isOneLineSpan :: SrcSpan -> Bool Source #

True if the span is known to straddle only one line. For "bad" SrcSpan, it returns False

isZeroWidthSpan :: SrcSpan -> Bool Source #

True if the span has a width of zero, as returned for "virtual" semicolons in the lexer. For "bad" SrcSpan, it returns False

containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool Source #

Tests whether the first span "contains" the other span, meaning that it covers at least as much source code. True where spans are equal.

StringBuffer locations

newtype BufPos Source #

0-based offset identifying the raw location in the StringBuffer.

The lexer increments the BufPos every time a character (UTF-8 code point) is read from the input buffer. As UTF-8 is a variable-length encoding and StringBuffer needs a byte offset for indexing, a BufPos cannot be used for indexing.

The parser guarantees that BufPos are monotonic. See #17632. This means that syntactic constructs that appear later in the StringBuffer are guaranteed to have a higher BufPos. Constrast that with RealSrcLoc, which does *not* make the analogous guarantee about higher line/column numbers.

This is due to #line and {-# LINE ... #-} pragmas that can arbitrarily modify RealSrcLoc. Notice how setSrcLoc and resetAlrLastLoc in GHC.Parser.Lexer update PsLoc, modifying RealSrcLoc but preserving BufPos.

Monotonicity makes BufPos useful to determine the order in which syntactic elements appear in the source. Consider this example (haddockA041 in the test suite):

haddockA041.hs {-# LANGUAGE CPP #-} -- | Module header documentation module Comments_and_CPP_include where #include "IncludeMe.hs"

IncludeMe.hs: -- | Comment on T data T = MkT -- ^ Comment on MkT

After the C preprocessor runs, the StringBuffer will contain a program that looks like this (unimportant lines at the beginning removed):

# 1 "haddockA041.hs" {-# LANGUAGE CPP #-} -- | Module header documentation module Comments_and_CPP_include where # 1 "IncludeMe.hs" 1 -- | Comment on T data T = MkT -- ^ Comment on MkT # 7 "haddockA041.hs" 2

The line pragmas inserted by CPP make the error messages more informative. The downside is that we can't use RealSrcLoc to determine the ordering of syntactic elements.

With RealSrcLoc, we have the following location information recorded in the AST: * The module name is located at haddockA041.hs:3:8-31 * The Haddock comment "Comment on T" is located at IncludeMe:1:1-17 * The data declaration is located at IncludeMe.hs:2:1-32

Is the Haddock comment located between the module name and the data declaration? This is impossible to tell because the locations are not comparable; they even refer to different files.

On the other hand, with BufPos, we have the following location information: * The module name is located at 846-870 * The Haddock comment "Comment on T" is located at 898-915 * The data declaration is located at 916-928

Aside: if you're wondering why the numbers are so high, try running ghc -E haddockA041.hs and see the extra fluff that CPP inserts at the start of the file.

For error messages, BufPos is not useful at all. On the other hand, this is exactly what we need to determine the order of syntactic elements: 870 < 898, therefore the Haddock comment appears *after* the module name. 915 < 916, therefore the Haddock comment appears *before* the data declaration.

We use BufPos in in GHC.Parser.PostProcess.Haddock to associate Haddock comments with parts of the AST using location information (#17544).

Constructors

BufPos 

Fields

Instances

Instances details
Data BufPos Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: BufPos -> Constr Source #

dataTypeOf :: BufPos -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show BufPos Source # 
Instance details

Defined in GHC.Types.SrcLoc

Eq BufPos Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord BufPos Source # 
Instance details

Defined in GHC.Types.SrcLoc

data BufSpan Source #

StringBuffer Source Span

Constructors

BufSpan 

Instances

Instances details
Data BufSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: BufSpan -> Constr Source #

dataTypeOf :: BufSpan -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Semigroup BufSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Show BufSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Eq BufSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord BufSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Located

data GenLocated l e Source #

We attach SrcSpans to lots of things, so let's have a datatype for it.

Constructors

L l e 

Instances

Instances details
Foldable (GenLocated l) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

fold :: Monoid m => GenLocated l m -> m Source #

foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m Source #

foldMap' :: Monoid m => (a -> m) -> GenLocated l a -> m Source #

foldr :: (a -> b -> b) -> b -> GenLocated l a -> b Source #

foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b Source #

foldl :: (b -> a -> b) -> b -> GenLocated l a -> b Source #

foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b Source #

foldr1 :: (a -> a -> a) -> GenLocated l a -> a Source #

foldl1 :: (a -> a -> a) -> GenLocated l a -> a Source #

toList :: GenLocated l a -> [a] Source #

null :: GenLocated l a -> Bool Source #

length :: GenLocated l a -> Int Source #

elem :: Eq a => a -> GenLocated l a -> Bool Source #

maximum :: Ord a => GenLocated l a -> a Source #

minimum :: Ord a => GenLocated l a -> a Source #

sum :: Num a => GenLocated l a -> a Source #

product :: Num a => GenLocated l a -> a Source #

Traversable (GenLocated l) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) Source #

sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) Source #

mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) Source #

sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) Source #

Functor (GenLocated l) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

fmap :: (a -> b) -> GenLocated l a -> GenLocated l b Source #

(<$) :: a -> GenLocated l b -> GenLocated l a Source #

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

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

Defined in GHC.Parser.Annotation

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

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> Located a -> IO () Source #

put :: BinHandle -> Located a -> IO (Bin (Located a)) Source #

get :: BinHandle -> IO (Located a) Source #

Outputable e => Outputable (Located e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc Source #

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (Located (FieldLabelStrings p)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Expr

OutputableBndr (Located (AmbiguousFieldOcc (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.Type

(Data l, Data e) => Data (GenLocated l e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: GenLocated l e -> Constr Source #

dataTypeOf :: GenLocated l e -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show l, Show e) => Show (GenLocated l e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

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

Defined in GHC.Parser.Annotation

Outputable (GenLocated Anchor EpaComment) Source # 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc Source #

Outputable e => Outputable (GenLocated RealSrcSpan e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

(Outputable a, OutputableBndr e) => OutputableBndr (GenLocated (SrcSpanAnn' a) e) Source # 
Instance details

Defined in GHC.Parser.Annotation

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

(Eq l, Eq e) => Eq (GenLocated l e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

(==) :: GenLocated l e -> GenLocated l e -> Bool #

(/=) :: GenLocated l e -> GenLocated l e -> Bool #

(Ord l, Ord e) => Ord (GenLocated l e) Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

compare :: GenLocated l e -> GenLocated l e -> Ordering #

(<) :: GenLocated l e -> GenLocated l e -> Bool #

(<=) :: GenLocated l e -> GenLocated l e -> Bool #

(>) :: GenLocated l e -> GenLocated l e -> Bool #

(>=) :: GenLocated l e -> GenLocated l e -> Bool #

max :: GenLocated l e -> GenLocated l e -> GenLocated l e #

min :: GenLocated l e -> GenLocated l e -> GenLocated l e #

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.ImpExp

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.Types

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Type

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Hs.Expr

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

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Expr

Constructing Located

noLoc :: e -> Located e Source #

Deconstructing Located

unLoc :: GenLocated l e -> e Source #

pprLocatedAlways :: (Outputable l, Outputable e) => GenLocated l e -> SDoc Source #

Always prints the location, even without -dppr-debug

Modifying Located

mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b Source #

Combining and comparing Located values

eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool Source #

Tests whether the two located things are equal

cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering Source #

Tests the ordering of the two located things

cmpBufSpan :: HasDebugCallStack => Located a -> Located a -> Ordering Source #

Compare the BufSpan of two located things.

Precondition: both operands have an associated BufSpan.

addCLoc :: Located a -> Located b -> c -> Located c Source #

Combine locations from two Located things and add them to a third thing

leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering Source #

Strategies for ordering SrcSpans

leftmost_largest :: SrcSpan -> SrcSpan -> Ordering Source #

Strategies for ordering SrcSpans

rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering Source #

Strategies for ordering SrcSpans

spans :: SrcSpan -> (Int, Int) -> Bool Source #

Determines whether a span encloses a given line and column index

isSubspanOf Source #

Arguments

:: SrcSpan

The span that may be enclosed by the other

-> SrcSpan

The span it may be enclosed by

-> Bool 

Determines whether a span is enclosed by another one

isRealSubspanOf Source #

Arguments

:: RealSrcSpan

The span that may be enclosed by the other

-> RealSrcSpan

The span it may be enclosed by

-> Bool 

Determines whether a span is enclosed by another one

liftL :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) Source #

Parser locations

data PsLoc Source #

A location as produced by the parser. Consists of two components:

  • The location in the file, adjusted for #line and {-# LINE ... #-} pragmas (RealSrcLoc)
  • The location in the string buffer (BufPos) with monotonicity guarantees (see #17632)

Constructors

PsLoc 

Instances

Instances details
Show PsLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Eq PsLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord PsLoc Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

compare :: PsLoc -> PsLoc -> Ordering #

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

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

(>) :: PsLoc -> PsLoc -> Bool #

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

max :: PsLoc -> PsLoc -> PsLoc #

min :: PsLoc -> PsLoc -> PsLoc #

data PsSpan Source #

Constructors

PsSpan 

Instances

Instances details
Data PsSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: PsSpan -> Constr Source #

dataTypeOf :: PsSpan -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show PsSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Eq PsSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord PsSpan Source # 
Instance details

Defined in GHC.Types.SrcLoc

combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan Source #

Combines two SrcSpan into one that spans at least all the characters within both spans. Assumes the "file" part is the same in both inputs

Layout information

data LayoutInfo Source #

Layout information for declarations.

Constructors

ExplicitBraces

Explicit braces written by the user.

class C a where { foo :: a; bar :: a }
VirtualBraces

Virtual braces inserted by the layout algorithm.

class C a where
  foo :: a
  bar :: a

Fields

  • !Int

    Layout column (indentation level, begins at 1)

NoLayoutInfo

Empty or compiler-generated blocks do not have layout information associated with them.

Instances

Instances details
Data LayoutInfo Source # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: LayoutInfo -> Constr Source #

dataTypeOf :: LayoutInfo -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show LayoutInfo Source # 
Instance details

Defined in GHC.Types.SrcLoc

Eq LayoutInfo Source # 
Instance details

Defined in GHC.Types.SrcLoc

Ord LayoutInfo Source # 
Instance details

Defined in GHC.Types.SrcLoc

leftmostColumn :: Int Source #

Indentation level is 1-indexed, so the leftmost column is 1.