Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- leftmostColumn :: Int
- 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
- isNoSrcSpan :: SrcSpan -> Bool
- isPointRealSpan :: RealSrcSpan -> Bool
- newtype BufPos = BufPos {}
- getBufPos :: SrcLoc -> Maybe BufPos
- data BufSpan = BufSpan {
- bufSpanStart :: !BufPos
- bufSpanEnd :: !BufPos
- getBufSpan :: SrcSpan -> Maybe BufSpan
- removeBufSpan :: SrcSpan -> SrcSpan
- combineBufSpans :: BufSpan -> BufSpan -> BufSpan
- 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
- pprLocatedAlways :: (Outputable l, Outputable e) => GenLocated l e -> SDoc
- 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
- 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
- psLocatedToLocated :: PsLocated a -> Located a
- data EpaLocation' a
- type NoCommentsLocation = EpaLocation' NoComments
- data NoComments = NoComments
- data DeltaPos
- = SameLine {
- deltaColumn :: !Int
- | DifferentLine {
- deltaLine :: !Int
- deltaColumn :: !Int
- = SameLine {
- deltaPos :: Int -> Int -> DeltaPos
- getDeltaLine :: DeltaPos -> Int
SrcLoc
data RealSrcLoc Source #
Real Source Location
Represents a single point within a file
Instances
Outputable RealSrcLoc Source # | |
Defined in GHC.Types.SrcLoc ppr :: RealSrcLoc -> SDoc Source # | |
Show RealSrcLoc Source # | |
Defined in GHC.Types.SrcLoc showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Eq RealSrcLoc Source # | |
Defined in GHC.Types.SrcLoc (==) :: RealSrcLoc -> RealSrcLoc -> Bool # (/=) :: RealSrcLoc -> RealSrcLoc -> Bool # | |
Ord RealSrcLoc Source # | |
Defined in GHC.Types.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 # |
Constructing SrcLoc
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc Source #
mkGeneralSrcLoc :: FastString -> SrcLoc Source #
Creates a "bad" SrcLoc
that has no detailed information about its location
leftmostColumn :: Int Source #
Indentation level is 1-indexed, so the leftmost column is 1.
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
advanceBufPos :: BufPos -> BufPos Source #
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
data UnhelpfulSpanReason Source #
UnhelpfulNoLocationInfo | |
UnhelpfulWiredIn | |
UnhelpfulInteractive | |
UnhelpfulGenerated | |
UnhelpfulOther !FastString |
Instances
Binary UnhelpfulSpanReason Source # | |
Defined in GHC.Utils.Binary put_ :: WriteBinHandle -> UnhelpfulSpanReason -> IO () Source # put :: WriteBinHandle -> UnhelpfulSpanReason -> IO (Bin UnhelpfulSpanReason) Source # get :: ReadBinHandle -> IO UnhelpfulSpanReason Source # | |
Outputable UnhelpfulSpanReason Source # | |
Defined in GHC.Types.SrcLoc ppr :: UnhelpfulSpanReason -> SDoc Source # | |
Show UnhelpfulSpanReason Source # | |
Defined in GHC.Types.SrcLoc showsPrec :: Int -> UnhelpfulSpanReason -> ShowS # show :: UnhelpfulSpanReason -> String # showList :: [UnhelpfulSpanReason] -> ShowS # | |
Eq UnhelpfulSpanReason Source # | |
Defined in GHC.Types.SrcLoc (==) :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool # (/=) :: UnhelpfulSpanReason -> UnhelpfulSpanReason -> Bool # |
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
generatedSrcSpan :: SrcSpan Source #
Built-in "bad" SrcSpan
s for common sources of location uncertainty
isGeneratedSrcSpan :: SrcSpan -> Bool Source #
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
isZeroWidthSpan :: SrcSpan -> Bool Source #
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 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.
isNoSrcSpan :: SrcSpan -> Bool Source #
Predicates on RealSrcSpan
isPointRealSpan :: RealSrcSpan -> Bool Source #
True
if the span is a single point
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
. Contrast that with RealSrcLoc
, which does *not* make the
analogous guarantee about higher line/column numbers.
This is due to #line and {-# LINE ... #-} pragmas that can arbitrarily
modify RealSrcLoc
. Notice how setSrcLoc
and resetAlrLastLoc
in
GHC.Parser.Lexer update PsLoc
, modifying RealSrcLoc
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).
Instances
Data BufPos Source # | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BufPos -> c BufPos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BufPos # toConstr :: BufPos -> Constr # dataTypeOf :: BufPos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BufPos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BufPos) # gmapT :: (forall b. Data b => b -> b) -> BufPos -> BufPos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BufPos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BufPos -> r # gmapQ :: (forall d. Data d => d -> u) -> BufPos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BufPos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BufPos -> m BufPos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BufPos -> m BufPos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BufPos -> m BufPos # | |
Show BufPos Source # | |
Eq BufPos Source # | |
Ord BufPos Source # | |
StringBuffer Source Span
BufSpan | |
|
Instances
Semigroup BufSpan Source # | |
Data BufSpan Source # | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BufSpan -> c BufSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BufSpan # toConstr :: BufSpan -> Constr # dataTypeOf :: BufSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BufSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BufSpan) # gmapT :: (forall b. Data b => b -> b) -> BufSpan -> BufSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BufSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BufSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> BufSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BufSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BufSpan -> m BufSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BufSpan -> m BufSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BufSpan -> m BufSpan # | |
Show BufSpan Source # | |
Eq BufSpan Source # | |
Ord BufSpan Source # | |
removeBufSpan :: SrcSpan -> SrcSpan Source #
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
Constructing Located
mkGeneralLocated :: String -> e -> Located e Source #
Deconstructing Located
getLoc :: GenLocated l e -> l Source #
unLoc :: GenLocated l e -> e Source #
unRealSrcSpan :: RealLocated a -> a Source #
getRealSrcSpan :: RealLocated a -> RealSrcSpan Source #
pprLocated :: (Outputable l, Outputable e) => GenLocated l e -> SDoc Source #
pprLocatedAlways :: (Outputable l, Outputable e) => GenLocated l e -> SDoc Source #
Always prints the location, even without -dppr-debug
Combining and comparing Located values
eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool Source #
Tests whether the two located things are equal
cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering Source #
Tests the ordering of the two located things
cmpBufSpan :: HasDebugCallStack => Located a -> Located a -> Ordering Source #
addCLoc :: Located a -> Located b -> c -> Located c Source #
Combine locations from two Located
things and add them to a third thing
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
:: 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] Source #
sortRealLocated :: [RealLocated a] -> [RealLocated a] Source #
lookupSrcLoc :: SrcLoc -> Map RealSrcLoc a -> Maybe a Source #
lookupSrcSpan :: SrcSpan -> Map RealSrcSpan a -> Maybe a Source #
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)
PsLoc | |
|
PsSpan | |
|
Instances
Data PsSpan Source # | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PsSpan -> c PsSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PsSpan # toConstr :: PsSpan -> Constr # dataTypeOf :: PsSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PsSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PsSpan) # gmapT :: (forall b. Data b => b -> b) -> PsSpan -> PsSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PsSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PsSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> PsSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PsSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PsSpan -> m PsSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PsSpan -> m PsSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PsSpan -> m PsSpan # | |
Show PsSpan Source # | |
Eq PsSpan Source # | |
Ord PsSpan Source # | |
type PsLocated = GenLocated PsSpan Source #
psSpanStart :: PsSpan -> PsLoc Source #
mkSrcSpanPs :: PsSpan -> SrcSpan Source #
combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan 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
psLocatedToLocated :: PsLocated a -> Located a Source #
Exact print locations
data EpaLocation' a Source #
The anchor for an exact print annotation. The Parser inserts the
variant, giving the exact location of the original item
in the parsed source. This can be replaced by the EpaSpan
version, to provide a position for the item relative to the end of
the previous item in the source. This is useful when editing an
AST prior to exact printing the changed one.
The EpaDelta also contains the original EpaDelta
for use by
tools wanting to manipulate the AST after converting it using
ghc-exactprint' SrcSpan
.makeDeltaAst
Instances
data NoComments Source #
Instances
Spacing between output items when exact printing. It captures
the spacing from the current print position on the page to the
position required for the thing about to be printed. This is
either on the same line in which case is is simply the number of
spaces to emit, or it is some number of lines down, with a given
column offset. The exact printing algorithm keeps track of the
column offset pertaining to the current anchor position, so the
deltaColumn
is the additional spaces to add in this case. See
https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations for
details.
SameLine | |
| |
DifferentLine | |
|
Instances
Outputable DeltaPos Source # | |
Data DeltaPos Source # | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeltaPos -> c DeltaPos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeltaPos # toConstr :: DeltaPos -> Constr # dataTypeOf :: DeltaPos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeltaPos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeltaPos) # gmapT :: (forall b. Data b => b -> b) -> DeltaPos -> DeltaPos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQ :: (forall d. Data d => d -> u) -> DeltaPos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeltaPos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # | |
Show DeltaPos Source # | |
Eq DeltaPos Source # | |
Ord DeltaPos Source # | |
Defined in GHC.Types.SrcLoc |
deltaPos :: Int -> Int -> DeltaPos Source #
Smart constructor for a DeltaPos
. It preserves the invariant
that for the DifferentLine
constructor deltaLine
is always > 0.
getDeltaLine :: DeltaPos -> Int Source #