| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- 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 e = GenLocated SrcSpan e
- type RealLocated e = GenLocated RealSrcSpan e
- data GenLocated l e = L l e
- noLoc :: e -> Located e
- mkGeneralLocated :: String -> e -> Located e
- getLoc :: GenLocated l e -> l
- unLoc :: GenLocated l e -> e
- eqLocated :: Eq a => Located a -> Located a -> Bool
- cmpLocated :: Ord a => Located a -> Located a -> Ordering
- combineLocs :: Located a -> Located b -> SrcSpan
- addCLoc :: Located a -> Located b -> c -> Located 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 :: [Located a] -> [Located a]
SrcLoc
Source Location
Constructors
| RealSrcLoc !RealSrcLoc | |
| UnhelpfulLoc FastString | 
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
Source Span
A SrcSpan identifies either a specific portion of a text file
 or a human-readable description of a location.
Constructors
| RealSrcSpan !RealSrcSpan | |
| UnhelpfulSpan !FastString | 
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" SrcSpans for common sources of location uncertainty
interactiveSrcSpan :: SrcSpan Source #
Built-in "bad" SrcSpans 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. Assumes the "file" part is the same in both inputs
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 e = GenLocated SrcSpan e Source #
type RealLocated e = GenLocated RealSrcSpan e Source #
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
| Functor (GenLocated l) Source # | |
| Foldable (GenLocated l) Source # | |
| Traversable (GenLocated l) Source # | |
| (Eq e, Eq l) => Eq (GenLocated l e) Source # | |
| (Data e, Data l) => Data (GenLocated l e) Source # | |
| (Ord e, Ord l) => Ord (GenLocated l e) Source # | |
| (Outputable l, Outputable e) => Outputable (GenLocated l e) Source # | |
| Binary a => Binary (GenLocated SrcSpan a) Source # | |
| NamedThing e => NamedThing (GenLocated l e) Source # | |
Constructing Located
mkGeneralLocated :: String -> e -> Located e Source #
Deconstructing Located
getLoc :: GenLocated l e -> l Source #
unLoc :: GenLocated l e -> e Source #
Combining and comparing Located values
eqLocated :: Eq a => Located a -> Located a -> Bool Source #
Tests whether the two located things are equal
cmpLocated :: Ord a => Located a -> Located a -> Ordering Source #
Tests the ordering of the two located things
addCLoc :: Located a -> Located b -> c -> Located c Source #
Combine locations from two Located things and add them to a third thing
leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering Source #
Alternative strategies for ordering SrcSpans
leftmost_largest :: 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
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 :: [Located a] -> [Located a] Source #