Copyright | (c) Harvard University 2006-2011 (c) Geoffrey Mainland 2011-2015 |
---|---|
License | BSD-style |
Maintainer | Geoffrey Mainland <mainland@cs.drexel.edu> |
Safe Haskell | Safe |
Language | Haskell2010 |
Data.Loc
Description
Synopsis
- data Pos = Pos !FilePath !Int !Int !Int
- posFile :: Pos -> FilePath
- posLine :: Pos -> Int
- posCol :: Pos -> Int
- posCoff :: Pos -> Int
- startPos :: FilePath -> Pos
- linePos :: FilePath -> Int -> Pos
- advancePos :: Pos -> Char -> Pos
- displayPos :: Pos -> String
- displaySPos :: Pos -> ShowS
- data Loc
- locStart :: Loc -> Loc
- locEnd :: Loc -> Loc
- (<-->) :: (Located a, Located b) => a -> b -> Loc
- displayLoc :: Loc -> String
- displaySLoc :: Loc -> ShowS
- newtype SrcLoc = SrcLoc Loc
- srclocOf :: Located a => a -> SrcLoc
- srcspan :: (Located a, Located b) => a -> b -> SrcLoc
- class IsLocation a where
- noLoc :: IsLocation a => a
- class Located a where
- class Relocatable a where
- data L a = L Loc a
- unLoc :: L a -> a
Documentation
Position type.
Constructors
Pos !FilePath !Int !Int !Int | Source file name, line, column, and character offset. Line numbering starts at 1, column offset starts at 1, and character offset starts at 0. |
Instances
Eq Pos Source # | |
Data Pos Source # | |
Defined in Data.Loc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos # dataTypeOf :: Pos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) # gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # | |
Ord Pos Source # | |
Read Pos Source # | |
Show Pos Source # | |
Located Pos Source # | |
linePos :: FilePath -> Int -> Pos Source #
Position corresponding to given file and line.
Note that the associated character offset is set to 0.
advancePos :: Pos -> Char -> Pos Source #
Advance a position by a single character. Newlines increment the line number, tabs increase the position column following a tab stop width of 8, and all other characters increase the position column by one. All characters, including newlines and tabs, increase the character offset by 1.
Note that advancePos
assumes UNIX-style newlines.
displayPos :: Pos -> String Source #
Format a position in a human-readable way, returning an ordinary
String
.
displaySPos :: Pos -> ShowS Source #
Format a position in a human-readable way.
Location type, consisting of a beginning position and an end position.
Instances
Eq Loc Source # | |
Data Loc Source # | |
Defined in Data.Loc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc # dataTypeOf :: Loc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Loc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) # gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # | |
Ord Loc Source # | |
Read Loc Source # | |
Show Loc Source # | |
Semigroup Loc Source # | |
Monoid Loc Source # | |
Located Loc Source # | |
IsLocation Loc Source # | |
(<-->) :: (Located a, Located b) => a -> b -> Loc infixl 6 Source #
Merge the locations of two Located
values.
displayLoc :: Loc -> String Source #
Format a location in a human-readable way, returning an ordinary
String
.
displaySLoc :: Loc -> ShowS Source #
Format a location in a human-readable way.
Source location type. Source location are all equal, which allows AST nodes to be compared modulo location information.
Instances
Eq SrcLoc Source # | |
Data SrcLoc Source # | |
Defined in Data.Loc Methods 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 :: forall r r'. (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 # | |
Read SrcLoc Source # | |
Show SrcLoc Source # | |
Semigroup SrcLoc Source # | |
Monoid SrcLoc Source # | |
Located SrcLoc Source # | |
IsLocation SrcLoc Source # | |
noLoc :: IsLocation a => a Source #
No location.
class Located a where Source #
Located values have a location.
Minimal complete definition
class Relocatable a where Source #
Values that can be relocated
A value of type L a
is a value of type a
with an associated Loc
, but
this location is ignored when performing comparisons.
Instances
Functor L Source # | |
Eq x => Eq (L x) Source # | |
Data a => Data (L a) Source # | |
Defined in Data.Loc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> L a -> c (L a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (L a) # dataTypeOf :: L a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (L a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (L a)) # gmapT :: (forall b. Data b => b -> b) -> L a -> L a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> L a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> L a -> r # gmapQ :: (forall d. Data d => d -> u) -> L a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> L a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> L a -> m (L a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> L a -> m (L a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> L a -> m (L a) # | |
Ord x => Ord (L x) Source # | |
Show x => Show (L x) Source # | |
Relocatable (L a) Source # | |
Located (L a) Source # | |