ghc-6.12.2: The GHC APISource codeContentsIndex
SrcLoc
Contents
SrcLoc
Constructing SrcLoc
Unsafely deconstructing SrcLoc
Misc. operations on SrcLoc
Predicates on SrcLoc
SrcSpan
Constructing SrcSpan
Deconstructing SrcSpan
Unsafely deconstructing SrcSpan
Predicates on SrcSpan
Located
Constructing Located
Deconstructing Located
Combining and comparing Located values
Description
This module contains types that relate to the positions of things in source files, and allow tagging of those things with locations
Synopsis
data SrcLoc
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
mkGeneralSrcLoc :: FastString -> SrcLoc
noSrcLoc :: SrcLoc
generatedSrcLoc :: SrcLoc
interactiveSrcLoc :: SrcLoc
advanceSrcLoc :: SrcLoc -> Char -> SrcLoc
srcLocFile :: SrcLoc -> FastString
srcLocLine :: SrcLoc -> Int
srcLocCol :: SrcLoc -> Int
pprDefnLoc :: SrcSpan -> SDoc
isGoodSrcLoc :: SrcLoc -> Bool
data SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpan
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
noSrcSpan :: SrcSpan
wiredInSrcSpan :: SrcSpan
srcLocSpan :: SrcLoc -> SrcSpan
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
srcSpanStart :: SrcSpan -> SrcLoc
srcSpanEnd :: SrcSpan -> SrcLoc
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
srcSpanFile :: SrcSpan -> FastString
srcSpanStartLine :: SrcSpan -> Int
srcSpanEndLine :: SrcSpan -> Int
srcSpanStartCol :: SrcSpan -> Int
srcSpanEndCol :: SrcSpan -> Int
isGoodSrcSpan :: SrcSpan -> Bool
isOneLineSpan :: SrcSpan -> Bool
data Located e = L SrcSpan e
noLoc :: e -> Located e
mkGeneralLocated :: String -> e -> Located e
getLoc :: Located e -> SrcSpan
unLoc :: Located 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
SrcLoc
data SrcLoc Source
Represents a single point within a file
show/hide Instances
Constructing SrcLoc
mkSrcLoc :: FastString -> Int -> Int -> SrcLocSource
mkGeneralSrcLoc :: FastString -> SrcLocSource
Creates a bad SrcLoc that has no detailed information about its location
noSrcLoc :: SrcLocSource
generatedSrcLoc :: SrcLocSource
Built-in bad SrcLoc values for particular locations
interactiveSrcLoc :: SrcLocSource
advanceSrcLoc :: SrcLoc -> Char -> SrcLocSource
Move the SrcLoc down by one line if the character is a newline and across by one character in any other case
Unsafely deconstructing SrcLoc
srcLocFile :: SrcLoc -> FastStringSource
Gives the filename of the SrcLoc if it is available, otherwise returns a dummy value
srcLocLine :: SrcLoc -> IntSource
Raises an error when used on a bad SrcLoc
srcLocCol :: SrcLoc -> IntSource
Raises an error when used on a bad SrcLoc
Misc. operations on SrcLoc
pprDefnLoc :: SrcSpan -> SDocSource
Pretty prints information about the SrcSpan in the style defined at ...
Predicates on SrcLoc
isGoodSrcLoc :: SrcLoc -> BoolSource
Good SrcLocs have precise information about their location
SrcSpan
data SrcSpan Source

A SrcSpan 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.

show/hide Instances
Constructing SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpanSource
Create a bad SrcSpan that has not location information
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpanSource
Create a SrcSpan between two points in a file
noSrcSpan :: SrcSpanSource
wiredInSrcSpan :: SrcSpanSource
Built-in bad SrcSpans for common sources of location uncertainty
srcLocSpan :: SrcLoc -> SrcSpanSource
Create a SrcSpan corresponding to a single point
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpanSource
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
Deconstructing SrcSpan
srcSpanStart :: SrcSpan -> SrcLocSource
Returns the location at the start of the SrcSpan or a bad SrcSpan if that is unavailable
srcSpanEnd :: SrcSpan -> SrcLocSource
Returns the location at the end of the SrcSpan or a bad SrcSpan if that is unavailable
srcSpanFileName_maybe :: SrcSpan -> Maybe FastStringSource
Obtains the filename for a SrcSpan if it is good
Unsafely deconstructing SrcSpan
srcSpanFile :: SrcSpan -> FastStringSource
srcSpanStartLine :: SrcSpan -> IntSource
Raises an error when used on a bad SrcSpan
srcSpanEndLine :: SrcSpan -> IntSource
Raises an error when used on a bad SrcSpan
srcSpanStartCol :: SrcSpan -> IntSource
Raises an error when used on a bad SrcSpan
srcSpanEndCol :: SrcSpan -> IntSource
Raises an error when used on a bad SrcSpan
Predicates on SrcSpan
isGoodSrcSpan :: SrcSpan -> BoolSource
Test if a SrcSpan is good, i.e. has precise location information
isOneLineSpan :: SrcSpan -> BoolSource
True if the span is known to straddle only one line. For bad SrcSpan, it returns False
Located
data Located e Source
We attach SrcSpans to lots of things, so let's have a datatype for it.
Constructors
L SrcSpan e
show/hide Instances
Constructing Located
noLoc :: e -> Located eSource
mkGeneralLocated :: String -> e -> Located eSource
Deconstructing Located
getLoc :: Located e -> SrcSpanSource
unLoc :: Located e -> eSource
Combining and comparing Located values
eqLocated :: Eq a => Located a -> Located a -> BoolSource
Tests whether the two located things are equal
cmpLocated :: Ord a => Located a -> Located a -> OrderingSource
Tests the ordering of the two located things
combineLocs :: Located a -> Located b -> SrcSpanSource
addCLoc :: Located a -> Located b -> c -> Located cSource
Combine locations from two Located things and add them to a third thing
leftmost_smallest :: SrcSpan -> SrcSpan -> OrderingSource
leftmost_largest :: SrcSpan -> SrcSpan -> OrderingSource
Alternative strategies for ordering SrcSpans
rightmost :: SrcSpan -> SrcSpan -> OrderingSource
spans :: SrcSpan -> (Int, Int) -> BoolSource
Determines whether a span encloses a given line and column index
isSubspanOfSource
:: SrcSpanThe span that may be enclosed by the other
-> SrcSpanThe span it may be enclosed by
-> Bool
Determines whether a span is enclosed by another one
Produced by Haddock version 2.6.1