| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Types.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
- 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
- advanceBufPos :: BufPos -> BufPos
- srcLocFile :: RealSrcLoc -> FastString
- srcLocLine :: RealSrcLoc -> Int
- srcLocCol :: RealSrcLoc -> Int
- data RealSrcSpan
- data SrcSpan
- data UnhelpfulSpanReason
- mkGeneralSrcSpan :: FastString -> SrcSpan
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
- noSrcSpan :: SrcSpan
- generatedSrcSpan :: SrcSpan
- isGeneratedSrcSpan :: SrcSpan -> Bool
- 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
- pprUnhelpfulSpanReason :: UnhelpfulSpanReason -> SDoc
- pprUserSpan :: Bool -> SrcSpan -> SDoc
- unhelpfulSpanFS :: UnhelpfulSpanReason -> FastString
- srcSpanToRealSrcSpan :: SrcSpan -> Maybe RealSrcSpan
- srcSpanFile :: RealSrcSpan -> FastString
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- isGoodSrcSpan :: SrcSpan -> Bool
- isOneLineSpan :: SrcSpan -> Bool
- isZeroWidthSpan :: SrcSpan -> Bool
- containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
- newtype BufPos = BufPos {}
- getBufPos :: SrcLoc -> Maybe BufPos
- data BufSpan = BufSpan {- bufSpanStart, bufSpanEnd :: !BufPos
 
- getBufSpan :: SrcSpan -> Maybe BufSpan
- removeBufSpan :: SrcSpan -> SrcSpan
- type Located = GenLocated SrcSpan
- type RealLocated = GenLocated RealSrcSpan
- 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
- unRealSrcSpan :: RealLocated a -> a
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- pprLocated :: (Outputable l, Outputable e) => GenLocated l e -> SDoc
- mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b
- eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool
- cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering
- cmpBufSpan :: HasDebugCallStack => 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_smallest :: SrcSpan -> SrcSpan -> Ordering
- spans :: SrcSpan -> (Int, Int) -> Bool
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- isRealSubspanOf :: RealSrcSpan -> RealSrcSpan -> Bool
- sortLocated :: [Located a] -> [Located a]
- sortRealLocated :: [RealLocated a] -> [RealLocated a]
- lookupSrcLoc :: SrcLoc -> Map RealSrcLoc a -> Maybe a
- lookupSrcSpan :: SrcSpan -> Map RealSrcSpan a -> Maybe a
- liftL :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b)
- data PsLoc = PsLoc {- psRealLoc :: !RealSrcLoc
- psBufPos :: !BufPos
 
- data PsSpan = PsSpan {- psRealSpan :: !RealSrcSpan
- psBufSpan :: !BufSpan
 
- type PsLocated = GenLocated PsSpan
- advancePsLoc :: PsLoc -> Char -> PsLoc
- mkPsSpan :: PsLoc -> PsLoc -> PsSpan
- psSpanStart :: PsSpan -> PsLoc
- psSpanEnd :: PsSpan -> PsLoc
- mkSrcSpanPs :: PsSpan -> SrcSpan
- combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan
- data LayoutInfo
- leftmostColumn :: Int
SrcLoc
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
| Show RealSrcLoc # | |
| Defined in GHC.Types.SrcLoc | |
| Outputable RealSrcLoc # | |
| Defined in GHC.Types.SrcLoc Methods ppr :: RealSrcLoc -> SDoc # | |
| Eq RealSrcLoc # | |
| Defined in GHC.Types.SrcLoc | |
| Ord RealSrcLoc # | |
| Defined in GHC.Types.SrcLoc Methods compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
Source Location
Constructors
| RealSrcLoc !RealSrcLoc !(Maybe BufPos) | |
| UnhelpfulLoc FastString | 
Instances
| Show SrcLoc # | |
| Outputable SrcLoc # | |
| Defined in GHC.Types.SrcLoc | |
| Eq SrcLoc # | |
Constructing SrcLoc
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc #
mkGeneralSrcLoc :: FastString -> SrcLoc #
Creates a "bad" SrcLoc that has no detailed information about its location
Built-in "bad" SrcLoc values for particular locations
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
advanceBufPos :: BufPos -> BufPos #
Unsafely deconstructing SrcLoc
srcLocFile :: RealSrcLoc -> FastString #
Gives the filename of the SrcLoc
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 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.
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.
Constructors
| RealSrcSpan !RealSrcSpan !(Maybe BufSpan) | |
| UnhelpfulSpan !UnhelpfulSpanReason | 
Instances
data UnhelpfulSpanReason #
Constructors
| UnhelpfulNoLocationInfo | |
| UnhelpfulWiredIn | |
| UnhelpfulInteractive | |
| UnhelpfulGenerated | |
| UnhelpfulOther !FastString | 
Instances
| Show UnhelpfulSpanReason # | |
| Defined in GHC.Types.SrcLoc | |
| Binary UnhelpfulSpanReason # | |
| Defined in GHC.Utils.Binary Methods put_ :: BinHandle -> UnhelpfulSpanReason -> IO () # put :: BinHandle -> UnhelpfulSpanReason -> IO (Bin UnhelpfulSpanReason) # get :: BinHandle -> IO UnhelpfulSpanReason # | |
| Outputable UnhelpfulSpanReason # | |
| Defined in GHC.Types.SrcLoc Methods ppr :: UnhelpfulSpanReason -> SDoc # | |
| Eq UnhelpfulSpanReason # | |
| Defined in GHC.Types.SrcLoc Methods (==) :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool # (/=) :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool # | |
Constructing SrcSpan
mkGeneralSrcSpan :: FastString -> SrcSpan #
Create a "bad" SrcSpan that has not location information
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #
Create a SrcSpan between two points in a file
Built-in "bad" SrcSpans for common sources of location uncertainty
isGeneratedSrcSpan :: SrcSpan -> Bool #
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
realSrcLocSpan :: RealSrcLoc -> RealSrcSpan #
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan #
Combines two SrcSpan into one that spans at least all the characters
 within both spans. Returns UnhelpfulSpan if the files differ.
srcSpanFirstCharacter :: SrcSpan -> SrcSpan #
Convert a SrcSpan into one that represents only its first character
Deconstructing SrcSpan
srcSpanStart :: SrcSpan -> SrcLoc #
srcSpanEnd :: SrcSpan -> SrcLoc #
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc #
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString #
Obtains the filename for a SrcSpan if it is "good"
pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc #
pprUserSpan :: Bool -> SrcSpan -> SDoc #
Unsafely deconstructing SrcSpan
srcSpanFile :: RealSrcSpan -> FastString #
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEndCol :: RealSrcSpan -> Int #
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
isZeroWidthSpan :: SrcSpan -> Bool #
True if the span has a width of zero, as returned for "virtual"
 semicolons in the lexer.
 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.
StringBuffer locations
0-based offset identifying the raw location in the StringBuffer.
The lexer increments the BufPos every time a character (UTF-8 code point)
 is read from the input buffer. As UTF-8 is a variable-length encoding and
 StringBuffer needs a byte offset for indexing, a BufPos cannot be used
 for indexing.
The parser guarantees that BufPos are monotonic. See #17632. This means
 that syntactic constructs that appear later in the StringBuffer are guaranteed to
 have a higher BufPos. Constrast that with SrcLoc, which does *not* make the
 analogous guarantee about higher line/column numbers.
This is due to #line and {-# LINE ... #-} pragmas that can arbitrarily
 modify SrcLoc. Notice how setSrcLoc and resetAlrLastLoc in
 GHC.Parser.Lexer update PsLoc, modifying SrcLoc but preserving
 BufPos.
Monotonicity makes BufPos useful to determine the order in which syntactic
 elements appear in the source. Consider this example (haddockA041 in the test suite):
haddockA041.hs {-# LANGUAGE CPP #-} -- | Module header documentation module Comments_and_CPP_include where #include "IncludeMe.hs"
IncludeMe.hs: -- | Comment on T data T = MkT -- ^ Comment on MkT
After the C preprocessor runs, the StringBuffer will contain a program that
 looks like this (unimportant lines at the beginning removed):
# 1 "haddockA041.hs" {-# LANGUAGE CPP #-} -- | Module header documentation module Comments_and_CPP_include where # 1 "IncludeMe.hs" 1 -- | Comment on T data T = MkT -- ^ Comment on MkT # 7 "haddockA041.hs" 2
The line pragmas inserted by CPP make the error messages more informative. The downside is that we can't use RealSrcLoc to determine the ordering of syntactic elements.
With RealSrcLoc, we have the following location information recorded in the AST: * The module name is located at haddockA041.hs:3:8-31 * The Haddock comment "Comment on T" is located at IncludeMe:1:1-17 * The data declaration is located at IncludeMe.hs:2:1-32
Is the Haddock comment located between the module name and the data declaration? This is impossible to tell because the locations are not comparable; they even refer to different files.
On the other hand, with BufPos, we have the following location information:
   * The module name is located at 846-870
   * The Haddock comment "Comment on T" is located at 898-915
   * The data declaration is located at 916-928
Aside:  if you're wondering why the numbers are so high, try running
           ghc -E haddockA041.hs
         and see the extra fluff that CPP inserts at the start of the file.
For error messages, BufPos is not useful at all. On the other hand, this is
 exactly what we need to determine the order of syntactic elements:
    870 < 898, therefore the Haddock comment appears *after* the module name.
    915 < 916, therefore the Haddock comment appears *before* the data declaration.
We use BufPos in in GHC.Parser.PostProcess.Haddock to associate Haddock
 comments with parts of the AST using location information (#17544).
StringBuffer Source Span
Constructors
| BufSpan | |
| Fields 
 | |
getBufSpan :: SrcSpan -> Maybe BufSpan #
removeBufSpan :: SrcSpan -> SrcSpan #
Located
type Located = GenLocated SrcSpan #
type RealLocated = GenLocated RealSrcSpan #
data GenLocated l e #
We attach SrcSpans to lots of things, so let's have a datatype for it.
Constructors
| L l e | 
Instances
Constructing Located
mkGeneralLocated :: String -> e -> Located e #
Deconstructing Located
getLoc :: GenLocated l e -> l #
unLoc :: GenLocated l e -> e #
unRealSrcSpan :: RealLocated a -> a #
getRealSrcSpan :: RealLocated a -> RealSrcSpan #
pprLocated :: (Outputable l, Outputable e) => GenLocated l e -> SDoc #
Modifying Located
mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b #
Combining and comparing Located values
eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool #
Tests whether the two located things are equal
cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering #
Tests the ordering of the two located things
cmpBufSpan :: HasDebugCallStack => Located a -> Located a -> Ordering #
combineLocs :: Located a -> Located b -> SrcSpan #
addCLoc :: Located a -> Located b -> c -> Located c #
Combine locations from two Located things and add them to a third thing
spans :: SrcSpan -> (Int, Int) -> Bool #
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
Arguments
| :: RealSrcSpan | The span that may be enclosed by the other | 
| -> RealSrcSpan | The span it may be enclosed by | 
| -> Bool | 
Determines whether a span is enclosed by another one
sortLocated :: [Located a] -> [Located a] #
sortRealLocated :: [RealLocated a] -> [RealLocated a] #
lookupSrcLoc :: SrcLoc -> Map RealSrcLoc a -> Maybe a #
lookupSrcSpan :: SrcSpan -> Map RealSrcSpan a -> Maybe a #
liftL :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) #
Parser locations
A location as produced by the parser. Consists of two components:
- The location in the file, adjusted for #line and {-# LINE ... #-} pragmas (RealSrcLoc)
- The location in the string buffer (BufPos) with monotonicity guarantees (see #17632)
Constructors
| PsLoc | |
| Fields 
 | |
Constructors
| PsSpan | |
| Fields 
 | |
type PsLocated = GenLocated PsSpan #
advancePsLoc :: PsLoc -> Char -> PsLoc #
psSpanStart :: PsSpan -> PsLoc #
mkSrcSpanPs :: PsSpan -> SrcSpan #
combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan #
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
Layout information
data LayoutInfo #
Layout information for declarations.
Constructors
| ExplicitBraces | Explicit braces written by the user. class C a where { foo :: a; bar :: a }
 | 
| VirtualBraces | Virtual braces inserted by the layout algorithm. class C a where foo :: a bar :: a | 
| Fields 
 | |
| NoLayoutInfo | Empty or compiler-generated blocks do not have layout information associated with them. | 
Instances
| Data LayoutInfo # | |
| Defined in GHC.Types.SrcLoc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayoutInfo -> c LayoutInfo Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LayoutInfo Source # toConstr :: LayoutInfo -> Constr Source # dataTypeOf :: LayoutInfo -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LayoutInfo) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayoutInfo) Source # gmapT :: (forall b. Data b => b -> b) -> LayoutInfo -> LayoutInfo Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LayoutInfo -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutInfo -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo -> m LayoutInfo Source # | |
| Show LayoutInfo # | |
| Defined in GHC.Types.SrcLoc | |
| Eq LayoutInfo # | |
| Defined in GHC.Types.SrcLoc | |
| Ord LayoutInfo # | |
| Defined in GHC.Types.SrcLoc Methods compare :: LayoutInfo -> LayoutInfo -> Ordering # (<) :: LayoutInfo -> LayoutInfo -> Bool # (<=) :: LayoutInfo -> LayoutInfo -> Bool # (>) :: LayoutInfo -> LayoutInfo -> Bool # (>=) :: LayoutInfo -> LayoutInfo -> Bool # max :: LayoutInfo -> LayoutInfo -> LayoutInfo # min :: LayoutInfo -> LayoutInfo -> LayoutInfo # | |
leftmostColumn :: Int #
Indentation level is 1-indexed, so the leftmost column is 1.