ghc-8.2.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

SrcLoc

Contents

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

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

Eq RealSrcSpan # 
Data RealSrcSpan # 

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 :: (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 #

Ord RealSrcSpan # 
Show RealSrcSpan # 
Outputable RealSrcSpan # 
ToJson RealSrcSpan # 

Methods

json :: RealSrcSpan -> JsonDoc #

data SrcSpan #

Source Span

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

Instances

Eq SrcSpan # 

Methods

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

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

Data SrcSpan # 

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 :: (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 #

Ord SrcSpan # 
Show SrcSpan # 
NFData SrcSpan # 

Methods

rnf :: SrcSpan -> () Source #

Outputable SrcSpan # 

Methods

ppr :: SrcSpan -> SDoc #

pprPrec :: Rational -> SrcSpan -> SDoc #

ToJson SrcSpan # 

Methods

json :: SrcSpan -> JsonDoc #

Binary SrcSpan # 
Binary a => Binary (GenLocated SrcSpan 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

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. Assumes the "file" part is the same in both inputs

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.

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

Functor (GenLocated l) # 

Methods

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

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

Foldable (GenLocated l) # 

Methods

fold :: Monoid m => GenLocated l m -> 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) # 

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 #

(Eq e, Eq l) => Eq (GenLocated l e) # 

Methods

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

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

(Data e, Data l) => Data (GenLocated l e) # 

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 a. (Data d, Data a) => c (t d a)) -> 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 :: (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 #

(Ord e, Ord l) => Ord (GenLocated l e) # 

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 #

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

Methods

ppr :: GenLocated l e -> SDoc #

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

Binary a => Binary (GenLocated SrcSpan a) # 
NamedThing e => NamedThing (GenLocated l e) # 

Constructing Located

noLoc :: e -> Located e #

Deconstructing Located

getLoc :: GenLocated l e -> l #

unLoc :: GenLocated l e -> e #

Combining and comparing Located values

eqLocated :: Eq a => Located a -> Located a -> Bool #

Tests whether the two located things are equal

cmpLocated :: Ord a => Located a -> Located a -> Ordering #

Tests the ordering of the two located things

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 #

Alternative strategies for ordering SrcSpans

leftmost_largest :: SrcSpan -> SrcSpan -> Ordering #

Alternative strategies for ordering SrcSpans

rightmost :: SrcSpan -> SrcSpan -> Ordering #

Alternative 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