ghc-9.0.2: 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 #

Real Source Location

Represents a single point within a file

data SrcLoc #

Source Location

Instances

Instances details
Show SrcLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc #

pprPrec :: Rational -> SrcLoc -> SDoc #

Eq SrcLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Constructing SrcLoc

mkGeneralSrcLoc :: FastString -> SrcLoc #

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

noSrcLoc :: SrcLoc #

Built-in "bad" SrcLoc values for particular locations

generatedSrcLoc :: SrcLoc #

Built-in "bad" SrcLoc values for particular locations

interactiveSrcLoc :: SrcLoc #

Built-in "bad" SrcLoc values for particular locations

advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc #

Move the SrcLoc 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 #

Gives the filename of the RealSrcLoc

srcLocLine :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc

srcLocCol :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc

SrcSpan

data RealSrcSpan #

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 # 
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 # 
Instance details

Defined in GHC.Types.SrcLoc

Binary RealSrcSpan # 
Instance details

Defined in GHC.Utils.Binary

ToJson RealSrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc #

Outputable RealSrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Eq RealSrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

data SrcSpan #

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 # 
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 # 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () Source #

Binary SrcSpan # 
Instance details

Defined in GHC.Utils.Binary

ToJson SrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

pprPrec :: Rational -> SrcSpan -> SDoc #

Eq SrcSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Data (LHsTypeArg GhcPs) # 
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) -> LHsTypeArg GhcPs -> c (LHsTypeArg GhcPs) Source #

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

toConstr :: LHsTypeArg GhcPs -> Constr Source #

dataTypeOf :: LHsTypeArg GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (LHsTypeArg GhcRn) # 
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) -> LHsTypeArg GhcRn -> c (LHsTypeArg GhcRn) Source #

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

toConstr :: LHsTypeArg GhcRn -> Constr Source #

dataTypeOf :: LHsTypeArg GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (LHsTypeArg GhcTc) # 
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) -> LHsTypeArg GhcTc -> c (LHsTypeArg GhcTc) Source #

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

toConstr :: LHsTypeArg GhcTc -> Constr Source #

dataTypeOf :: LHsTypeArg GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Types.Name

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

Defined in GHC.Utils.Binary

Methods

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

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

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

Constructing SrcSpan

mkGeneralSrcSpan :: FastString -> SrcSpan #

Create a "bad" SrcSpan that has not location information

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan #

Create a SrcSpan between two points in a file

mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #

Create a SrcSpan between two points in a file

noSrcSpan :: SrcSpan #

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

generatedSrcSpan :: SrcSpan #

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

wiredInSrcSpan :: SrcSpan #

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

interactiveSrcSpan :: SrcSpan #

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

srcLocSpan :: SrcLoc -> SrcSpan #

Create a SrcSpan corresponding to a single point

combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan #

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

srcSpanFirstCharacter :: SrcSpan -> SrcSpan #

Convert a SrcSpan into one that represents only its first character

Deconstructing SrcSpan

srcSpanStart :: SrcSpan -> SrcLoc #

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

srcSpanEnd :: SrcSpan -> SrcLoc #

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

srcSpanFileName_maybe :: SrcSpan -> Maybe FastString #

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

Unsafely deconstructing SrcSpan

Predicates on SrcSpan

isGoodSrcSpan :: SrcSpan -> Bool #

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

isOneLineSpan :: SrcSpan -> Bool #

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

containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool #

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 #

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
Show BufPos # 
Instance details

Defined in GHC.Types.SrcLoc

Binary BufPos # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: BinHandle -> BufPos -> IO () #

put :: BinHandle -> BufPos -> IO (Bin BufPos) #

get :: BinHandle -> IO BufPos #

Eq BufPos # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord BufPos # 
Instance details

Defined in GHC.Types.SrcLoc

data BufSpan #

StringBuffer Source Span

Constructors

BufSpan 

Instances

Instances details
Semigroup BufSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Show BufSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Binary BufSpan # 
Instance details

Defined in GHC.Utils.Binary

Eq BufSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord BufSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Located

data GenLocated l e #

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

Constructors

L l e 

Instances

Instances details
Data (LHsTypeArg GhcPs) # 
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) -> LHsTypeArg GhcPs -> c (LHsTypeArg GhcPs) Source #

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

toConstr :: LHsTypeArg GhcPs -> Constr Source #

dataTypeOf :: LHsTypeArg GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (LHsTypeArg GhcRn) # 
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) -> LHsTypeArg GhcRn -> c (LHsTypeArg GhcRn) Source #

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

toConstr :: LHsTypeArg GhcRn -> Constr Source #

dataTypeOf :: LHsTypeArg GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (LHsTypeArg GhcTc) # 
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) -> LHsTypeArg GhcTc -> c (LHsTypeArg GhcTc) Source #

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

toConstr :: LHsTypeArg GhcTc -> Constr Source #

dataTypeOf :: LHsTypeArg GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Foldable (GenLocated l) # 
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) # 
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) # 
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) # 
Instance details

Defined in GHC.Types.Name

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

Defined in GHC.Utils.Binary

Methods

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

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

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

(Data l, Data e) => Data (GenLocated l e) # 
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 #

(Outputable l, Outputable e) => Outputable (GenLocated l e) # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: GenLocated l e -> SDoc #

pprPrec :: Rational -> GenLocated l e -> SDoc #

(Eq l, Eq e) => Eq (GenLocated l e) # 
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) # 
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 #

Constructing Located

noLoc :: e -> Located e #

Deconstructing Located

getLoc :: GenLocated l e -> l #

unLoc :: GenLocated l e -> e #

Modifying Located

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

Combining and comparing Located values

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

Tests whether the two located things are equal

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

Tests the ordering of the two located things

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

Compare the BufSpan of two located things.

Precondition: both operands have an associated BufSpan.

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

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

leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering #

Strategies for ordering SrcSpans

leftmost_largest :: SrcSpan -> SrcSpan -> Ordering #

Strategies for ordering SrcSpans

rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering #

Strategies for ordering SrcSpans

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

Determines whether a span encloses a given line and column index

isSubspanOf #

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 #

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) #

Parser locations

data PsLoc #

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 # 
Instance details

Defined in GHC.Types.SrcLoc

Eq PsLoc # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord PsLoc # 
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 #

Constructors

PsSpan 

Instances

Instances details
Show PsSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Eq PsSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Ord PsSpan # 
Instance details

Defined in GHC.Types.SrcLoc

Layout information

data LayoutInfo #

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 # 
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 # 
Instance details

Defined in GHC.Types.SrcLoc

Eq LayoutInfo # 
Instance details

Defined in GHC.Types.SrcLoc

Ord LayoutInfo # 
Instance details

Defined in GHC.Types.SrcLoc

leftmostColumn :: Int #

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