ghc-8.8.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

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

Instances

Instances details
Eq RealSrcLoc # 
Instance details

Defined in SrcLoc

Ord RealSrcLoc # 
Instance details

Defined in SrcLoc

Show RealSrcLoc # 
Instance details

Defined in SrcLoc

Outputable RealSrcLoc # 
Instance details

Defined in SrcLoc

data SrcLoc Source #

Source Location

Instances

Instances details
Eq SrcLoc # 
Instance details

Defined in SrcLoc

Methods

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

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

Ord SrcLoc # 
Instance details

Defined in SrcLoc

Show SrcLoc # 
Instance details

Defined in SrcLoc

Outputable SrcLoc # 
Instance details

Defined in SrcLoc

Constructing SrcLoc

mkGeneralSrcLoc :: FastString -> SrcLoc Source #

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

noSrcLoc :: SrcLoc Source #

Built-in "bad" SrcLoc values for particular locations

generatedSrcLoc :: SrcLoc Source #

Built-in "bad" SrcLoc values for particular locations

interactiveSrcLoc :: SrcLoc Source #

Built-in "bad" SrcLoc values for particular locations

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

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

Gives the filename of the RealSrcLoc

srcLocLine :: RealSrcLoc -> Int Source #

Raises an error when used on a "bad" SrcLoc

srcLocCol :: RealSrcLoc -> Int Source #

Raises an error when used on a "bad" SrcLoc

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

Defined in SrcLoc

Data RealSrcSpan # 
Instance details

Defined in 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 #

Ord RealSrcSpan # 
Instance details

Defined in SrcLoc

Show RealSrcSpan # 
Instance details

Defined in SrcLoc

Outputable RealSrcSpan # 
Instance details

Defined in SrcLoc

ToJson RealSrcSpan # 
Instance details

Defined in SrcLoc

Binary RealSrcSpan # 
Instance details

Defined in Binary

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

Defined in SrcLoc

Methods

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

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

Data SrcSpan # 
Instance details

Defined in 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 #

Ord SrcSpan # 
Instance details

Defined in SrcLoc

Show SrcSpan # 
Instance details

Defined in SrcLoc

NFData SrcSpan # 
Instance details

Defined in SrcLoc

Methods

rnf :: SrcSpan -> () Source #

Outputable SrcSpan # 
Instance details

Defined in SrcLoc

ToJson SrcSpan # 
Instance details

Defined in SrcLoc

Methods

json :: SrcSpan -> JsonDoc Source #

Binary SrcSpan # 
Instance details

Defined in Binary

HasSrcSpan (Located a) # 
Instance details

Defined in SrcLoc

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

Defined in Binary

Methods

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

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

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

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

Defined in Name

Data (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

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

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) Source #

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

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

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

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

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

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

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

Data (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

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

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) Source #

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

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

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

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

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

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

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

Data (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

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

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) Source #

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

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

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

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

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

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

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

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

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

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.

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

Defined in SrcLoc

Methods

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

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

Foldable (GenLocated l) # 
Instance details

Defined in 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 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 #

HasSrcSpan (Located a) # 
Instance details

Defined in SrcLoc

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

Defined in Binary

Methods

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

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

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

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

Defined in Name

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

Defined in SrcLoc

Methods

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

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

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

Defined in 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 (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

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

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) Source #

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

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

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

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

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

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

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

Data (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

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

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) Source #

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

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

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

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

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

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

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

Data (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

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

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) Source #

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

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

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

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

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

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

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

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

Defined in 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 #

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

Defined in SrcLoc

type SrcSpanLess (GenLocated l e) # 
Instance details

Defined in SrcLoc

type SrcSpanLess (GenLocated l e) = e

Constructing Located

Deconstructing Located

Combining and comparing Located values

eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool Source #

Tests whether the two located things are equal

cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering Source #

Tests the ordering of the two located things

addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c Source #

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

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

Alternative strategies for ordering SrcSpans

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

Alternative strategies for ordering SrcSpans

rightmost :: SrcSpan -> SrcSpan -> Ordering Source #

Alternative 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

sortLocated :: HasSrcSpan a => [a] -> [a] Source #

HasSrcSpan

class HasSrcSpan a where Source #

A typeclass to set/get SrcSpans

Methods

composeSrcSpan :: Located (SrcSpanLess a) -> a Source #

Composes a SrcSpan decoration with an undecorated syntactic entity to form its decorated variant

decomposeSrcSpan :: a -> Located (SrcSpanLess a) Source #

Decomposes a decorated syntactic entity into its SrcSpan decoration and its undecorated variant

Instances

Instances details
HasSrcSpan Name # 
Instance details

Defined in Name

HasSrcSpan (Located a) # 
Instance details

Defined in SrcLoc

HasSrcSpan (LPat (GhcPass p)) # 
Instance details

Defined in HsPat

type family SrcSpanLess a Source #

Determines the type of undecorated syntactic entities For most syntactic entities E, where source location spans are introduced by a wrapper construtor of the same syntactic entity, we have `SrcSpanLess E = E`. However, some syntactic entities have a different type compared to a syntactic entity `e :: E` may have the type `Located E` when decorated by wrapping it with `L sp e` for a source span sp.

Instances

Instances details
type SrcSpanLess Name # 
Instance details

Defined in Name

type SrcSpanLess (LPat (GhcPass p)) # 
Instance details

Defined in HsPat

type SrcSpanLess (GenLocated l e) # 
Instance details

Defined in SrcLoc

type SrcSpanLess (GenLocated l e) = e

dL :: HasSrcSpan a => a -> Located (SrcSpanLess a) Source #

An abbreviated form of decomposeSrcSpan, mainly to be used in ViewPatterns

cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a Source #

An abbreviated form of composeSrcSpan, mainly to replace the hardcoded L

pattern LL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a Source #

A Pattern Synonym to Set/Get SrcSpans

onHasSrcSpan :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> SrcSpanLess b) -> a -> b Source #

Lifts a function of undecorated entities to one of decorated ones

liftL :: (HasSrcSpan a, HasSrcSpan b, Monad m) => (SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b Source #