Copyright | (c) Niklas Broberg 2009 |
---|---|
License | BSD-style (see the file LICENSE.txt) |
Maintainer | Niklas Broberg, d00nibro@chalmers.se |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
This module defines various data types representing source location information, of varying degree of preciseness.
Synopsis
- data SrcLoc = SrcLoc {}
- noLoc :: SrcLoc
- data SrcSpan = SrcSpan {}
- srcSpanStart :: SrcSpan -> (Int, Int)
- srcSpanEnd :: SrcSpan -> (Int, Int)
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- mergeSrcSpan :: SrcSpan -> SrcSpan -> SrcSpan
- isNullSpan :: SrcSpan -> Bool
- spanSize :: SrcSpan -> (Int, Int)
- data Loc a = Loc {}
- data SrcSpanInfo = SrcSpanInfo {
- srcInfoSpan :: SrcSpan
- srcInfoPoints :: [SrcSpan]
- noInfoSpan :: SrcSpan -> SrcSpanInfo
- noSrcSpan :: SrcSpanInfo
- infoSpan :: SrcSpan -> [SrcSpan] -> SrcSpanInfo
- combSpanInfo :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo
- combSpanMaybe :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo
- (<++>) :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo
- (<+?>) :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo
- (<?+>) :: Maybe SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo
- (<**) :: SrcSpanInfo -> [SrcSpan] -> SrcSpanInfo
- (<^^>) :: SrcSpan -> SrcSpan -> SrcSpanInfo
- class SrcInfo si where
Documentation
A single position in the source.
Instances
Eq SrcLoc Source # | |
Data SrcLoc Source # | |
Defined in Language.Haskell.Exts.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcLoc -> c SrcLoc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcLoc # toConstr :: SrcLoc -> Constr # dataTypeOf :: SrcLoc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcLoc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc) # gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcLoc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcLoc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc # | |
Ord SrcLoc Source # | |
Show SrcLoc Source # | |
Generic SrcLoc Source # | |
SrcInfo SrcLoc Source # | |
Pretty SrcLoc Source # | |
Defined in Language.Haskell.Exts.Pretty prettyPrec :: Int -> SrcLoc -> Doc | |
type Rep SrcLoc Source # | |
Defined in Language.Haskell.Exts.SrcLoc type Rep SrcLoc = D1 (MetaData "SrcLoc" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.20.3-KjyAxm84ddk16DoDOnTGLG" False) (C1 (MetaCons "SrcLoc" PrefixI True) (S1 (MetaSel (Just "srcFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "srcLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "srcColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) |
A portion of the source, spanning one or more lines and zero or more columns.
Instances
srcSpanStart :: SrcSpan -> (Int, Int) Source #
Returns srcSpanStartLine
and srcSpanStartColumn
in a pair.
srcSpanEnd :: SrcSpan -> (Int, Int) Source #
Returns srcSpanEndLine
and srcSpanEndColumn
in a pair.
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan Source #
Combine two locations in the source to denote a span.
mergeSrcSpan :: SrcSpan -> SrcSpan -> SrcSpan Source #
Merge two source spans into a single span from the start of the first to the end of the second. Assumes that the two spans relate to the same source file.
isNullSpan :: SrcSpan -> Bool Source #
Test if a given span starts and ends at the same location.
An entity located in the source.
Instances
Eq a => Eq (Loc a) Source # | |
Ord a => Ord (Loc a) Source # | |
Show a => Show (Loc a) Source # | |
Generic (Loc a) Source # | |
type Rep (Loc a) Source # | |
Defined in Language.Haskell.Exts.SrcLoc type Rep (Loc a) = D1 (MetaData "Loc" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.20.3-KjyAxm84ddk16DoDOnTGLG" False) (C1 (MetaCons "Loc" PrefixI True) (S1 (MetaSel (Just "loc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan) :*: S1 (MetaSel (Just "unLoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) |
data SrcSpanInfo Source #
A portion of the source, extended with information on the position of entities within the span.
Instances
noInfoSpan :: SrcSpan -> SrcSpanInfo Source #
Generate a SrcSpanInfo
with no positional information for entities.
noSrcSpan :: SrcSpanInfo Source #
A bogus SrcSpanInfo
, the location is noLoc
.
`noSrcSpan = noInfoSpan (mkSrcSpan noLoc noLoc)`
infoSpan :: SrcSpan -> [SrcSpan] -> SrcSpanInfo Source #
Generate a SrcSpanInfo
with the supplied positional information for entities.
combSpanInfo :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo Source #
Combine two SrcSpanInfo
s into one that spans the combined source area of
the two arguments, leaving positional information blank.
combSpanMaybe :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo Source #
Like '(+?)', but it also concatenates the srcInfoPoints
.
(<++>) :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo infixl 5 Source #
Short name for combSpanInfo
(<+?>) :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo infixl 4 Source #
Optionally combine the first argument with the second,
or return it unchanged if the second argument is Nothing
.
(<?+>) :: Maybe SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo infixl 4 Source #
Optionally combine the second argument with the first,
or return it unchanged if the first argument is Nothing
.
(<**) :: SrcSpanInfo -> [SrcSpan] -> SrcSpanInfo infixl 4 Source #
Add more positional information for entities of a span.
(<^^>) :: SrcSpan -> SrcSpan -> SrcSpanInfo infixl 6 Source #
Merge two SrcSpan
s and lift them to a SrcInfoSpan
with
no positional information for entities.
class SrcInfo si where Source #
A class to work over all kinds of source location information.
toSrcInfo :: SrcLoc -> [SrcSpan] -> SrcLoc -> si Source #
fromSrcInfo :: SrcSpanInfo -> si Source #
getPointLoc :: si -> SrcLoc Source #
fileName :: si -> String Source #
startLine :: si -> Int Source #
startColumn :: si -> Int Source #
Instances
SrcInfo SrcSpanInfo Source # | |
Defined in Language.Haskell.Exts.SrcLoc toSrcInfo :: SrcLoc -> [SrcSpan] -> SrcLoc -> SrcSpanInfo Source # fromSrcInfo :: SrcSpanInfo -> SrcSpanInfo Source # getPointLoc :: SrcSpanInfo -> SrcLoc Source # fileName :: SrcSpanInfo -> String Source # startLine :: SrcSpanInfo -> Int Source # startColumn :: SrcSpanInfo -> Int Source # | |
SrcInfo SrcSpan Source # | |
Defined in Language.Haskell.Exts.SrcLoc | |
SrcInfo SrcLoc Source # | |