Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains types that relate to the positions of things in source files, and allow tagging of those things with locations
Synopsis
- data RealSrcLoc
- data SrcLoc
- mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
- mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
- mkGeneralSrcLoc :: FastString -> SrcLoc
- noSrcLoc :: SrcLoc
- generatedSrcLoc :: SrcLoc
- interactiveSrcLoc :: SrcLoc
- advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc
- srcLocFile :: RealSrcLoc -> FastString
- srcLocLine :: RealSrcLoc -> Int
- srcLocCol :: RealSrcLoc -> Int
- data RealSrcSpan
- data SrcSpan
- mkGeneralSrcSpan :: FastString -> SrcSpan
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
- noSrcSpan :: SrcSpan
- wiredInSrcSpan :: SrcSpan
- interactiveSrcSpan :: SrcSpan
- srcLocSpan :: SrcLoc -> SrcSpan
- realSrcLocSpan :: RealSrcLoc -> RealSrcSpan
- combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
- srcSpanFirstCharacter :: SrcSpan -> SrcSpan
- srcSpanStart :: SrcSpan -> SrcLoc
- srcSpanEnd :: SrcSpan -> SrcLoc
- realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
- realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
- srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
- pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc
- srcSpanFile :: RealSrcSpan -> FastString
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- isGoodSrcSpan :: SrcSpan -> Bool
- isOneLineSpan :: SrcSpan -> Bool
- containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
- type Located = GenLocated SrcSpan
- type RealLocated = GenLocated RealSrcSpan
- data GenLocated l e = L l e
- noLoc :: HasSrcSpan a => SrcSpanLess a -> a
- mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e
- getLoc :: HasSrcSpan a => a -> SrcSpan
- unLoc :: HasSrcSpan a => a -> SrcSpanLess a
- unRealSrcSpan :: RealLocated a -> a
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool
- cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering
- combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan
- addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
- rightmost :: SrcSpan -> SrcSpan -> Ordering
- spans :: SrcSpan -> (Int, Int) -> Bool
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- sortLocated :: HasSrcSpan a => [a] -> [a]
- class HasSrcSpan a where
- composeSrcSpan :: Located (SrcSpanLess a) -> a
- decomposeSrcSpan :: a -> Located (SrcSpanLess a)
- type family SrcSpanLess a
- dL :: HasSrcSpan a => a -> Located (SrcSpanLess a)
- cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- pattern LL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- onHasSrcSpan :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> SrcSpanLess b) -> a -> b
- liftL :: (HasSrcSpan a, HasSrcSpan b, Monad m) => (SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b
SrcLoc
data RealSrcLoc Source #
Real Source Location
Represents a single point within a file
Instances
Eq RealSrcLoc Source # | |
Defined in SrcLoc (==) :: RealSrcLoc -> RealSrcLoc -> Bool # (/=) :: RealSrcLoc -> RealSrcLoc -> Bool # | |
Ord RealSrcLoc Source # | |
Defined in SrcLoc compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
Show RealSrcLoc Source # | |
Defined in SrcLoc showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc Source # | |
Source Location
Constructing SrcLoc
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc Source #
mkGeneralSrcLoc :: FastString -> SrcLoc Source #
Creates a "bad" SrcLoc
that has no detailed information about its location
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
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
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
Eq SrcSpan Source # | |
Data SrcSpan Source # | |
Defined in SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Ord SrcSpan Source # | |
Show SrcSpan Source # | |
NFData SrcSpan Source # | |
Outputable SrcSpan Source # | |
ToJson SrcSpan Source # | |
Binary SrcSpan Source # | |
HasSrcSpan (Located a) Source # | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a Source # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) Source # | |
Binary a => Binary (Located a) Source # | |
NamedThing e => NamedThing (Located e) Source # | |
Data (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr # dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # | |
Data (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr # dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # | |
Data (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr # dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # |
Constructing SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpan Source #
Create a "bad" SrcSpan
that has not location information
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan Source #
Create a SrcSpan
between two points in a file
wiredInSrcSpan :: SrcSpan Source #
Built-in "bad" SrcSpan
s for common sources of location uncertainty
interactiveSrcSpan :: SrcSpan Source #
Built-in "bad" SrcSpan
s for common sources of location uncertainty
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 #
srcSpanEnd :: SrcSpan -> SrcLoc Source #
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString Source #
Obtains the filename for a SrcSpan
if it is "good"
pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc Source #
Unsafely deconstructing SrcSpan
srcSpanFile :: RealSrcSpan -> FastString Source #
srcSpanStartLine :: RealSrcSpan -> Int Source #
srcSpanEndLine :: RealSrcSpan -> Int Source #
srcSpanStartCol :: RealSrcSpan -> Int Source #
srcSpanEndCol :: RealSrcSpan -> Int Source #
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
type Located = GenLocated SrcSpan Source #
type RealLocated = GenLocated RealSrcSpan Source #
data GenLocated l e Source #
We attach SrcSpans to lots of things, so let's have a datatype for it.
L l e |
Instances
Functor (GenLocated l) Source # | |
Defined in SrcLoc fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
Foldable (GenLocated l) Source # | |
Defined in SrcLoc fold :: Monoid m => GenLocated l m -> m # foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m # foldMap' :: Monoid m => (a -> m) -> GenLocated l a -> m # foldr :: (a -> b -> b) -> b -> GenLocated l a -> b # foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b # foldl :: (b -> a -> b) -> b -> GenLocated l a -> b # foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b # foldr1 :: (a -> a -> a) -> GenLocated l a -> a # foldl1 :: (a -> a -> a) -> GenLocated l a -> a # toList :: GenLocated l a -> [a] # null :: GenLocated l a -> Bool # length :: GenLocated l a -> Int # elem :: Eq a => a -> GenLocated l a -> Bool # maximum :: Ord a => GenLocated l a -> a # minimum :: Ord a => GenLocated l a -> a # sum :: Num a => GenLocated l a -> a # product :: Num a => GenLocated l a -> a # | |
Traversable (GenLocated l) Source # | |
Defined in SrcLoc traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) # sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) # mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) # sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) # | |
HasSrcSpan (Located a) Source # | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a Source # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) Source # | |
Binary a => Binary (Located a) Source # | |
NamedThing e => NamedThing (Located e) Source # | |
(Eq l, Eq e) => Eq (GenLocated l e) Source # | |
Defined in SrcLoc (==) :: GenLocated l e -> GenLocated l e -> Bool # (/=) :: GenLocated l e -> GenLocated l e -> Bool # | |
(Data l, Data e) => Data (GenLocated l e) Source # | |
Defined in SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) # toConstr :: GenLocated l e -> Constr # dataTypeOf :: GenLocated l e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (GenLocated l e)) # gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # | |
Data (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr # dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # | |
Data (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr # dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # | |
Data (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source # | |
Defined in HsInstances 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)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr # dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) # gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # | |
(Ord l, Ord e) => Ord (GenLocated l e) Source # | |
Defined in SrcLoc 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) Source # | |
type SrcSpanLess (GenLocated l e) Source # | |
Defined in SrcLoc |
Constructing Located
noLoc :: HasSrcSpan a => SrcSpanLess a -> a Source #
mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e Source #
Deconstructing Located
getLoc :: HasSrcSpan a => a -> SrcSpan Source #
unLoc :: HasSrcSpan a => a -> SrcSpanLess a Source #
unRealSrcSpan :: RealLocated a -> a Source #
getRealSrcSpan :: RealLocated a -> RealSrcSpan Source #
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
combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan Source #
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 SrcSpan
s
leftmost_largest :: SrcSpan -> SrcSpan -> Ordering Source #
Alternative strategies for ordering SrcSpan
s
spans :: SrcSpan -> (Int, Int) -> Bool Source #
Determines whether a span encloses a given line and column index
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
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
HasSrcSpan Name Source # | |
Defined in Name composeSrcSpan :: Located (SrcSpanLess Name) -> Name Source # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) Source # | |
HasSrcSpan (Located a) Source # | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a Source # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) Source # | |
HasSrcSpan (LPat (GhcPass p)) Source # | |
Defined in HsPat composeSrcSpan :: Located (SrcSpanLess (LPat (GhcPass p))) -> LPat (GhcPass p) Source # decomposeSrcSpan :: LPat (GhcPass p) -> Located (SrcSpanLess (LPat (GhcPass p))) Source # |
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
type SrcSpanLess Name Source # | |
Defined in Name | |
type SrcSpanLess (LPat (GhcPass p)) Source # | |
type SrcSpanLess (GenLocated l e) Source # | |
Defined in SrcLoc |
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 #