srcloc-0.6: Data types for managing source code locations.
Copyright(c) Harvard University 2006-2011
(c) Geoffrey Mainland 2011-2015
LicenseBSD-style
MaintainerGeoffrey Mainland <mainland@cs.drexel.edu>
Safe HaskellSafe
LanguageHaskell2010

Data.Loc

Description

 
Synopsis

Documentation

data Pos Source #

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

Instances details
Eq Pos Source # 
Instance details

Defined in Data.Loc

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Data Pos Source # 
Instance details

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 #

toConstr :: Pos -> Constr #

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 # 
Instance details

Defined in Data.Loc

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Read Pos Source # 
Instance details

Defined in Data.Loc

Show Pos Source # 
Instance details

Defined in Data.Loc

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Located Pos Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: Pos -> Loc Source #

locOfList :: [Pos] -> Loc Source #

posFile :: Pos -> FilePath Source #

Position file.

posLine :: Pos -> Int Source #

Position line.

posCol :: Pos -> Int Source #

Position column.

posCoff :: Pos -> Int Source #

Position character offset.

startPos :: FilePath -> Pos Source #

Starting position for given file.

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.

data Loc Source #

Location type, consisting of a beginning position and an end position.

Constructors

NoLoc 
Loc !Pos !Pos

Beginning and end positions

Instances

Instances details
Eq Loc Source # 
Instance details

Defined in Data.Loc

Methods

(==) :: Loc -> Loc -> Bool #

(/=) :: Loc -> Loc -> Bool #

Data Loc Source # 
Instance details

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 #

toConstr :: Loc -> Constr #

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 # 
Instance details

Defined in Data.Loc

Methods

compare :: Loc -> Loc -> Ordering #

(<) :: Loc -> Loc -> Bool #

(<=) :: Loc -> Loc -> Bool #

(>) :: Loc -> Loc -> Bool #

(>=) :: Loc -> Loc -> Bool #

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Read Loc Source # 
Instance details

Defined in Data.Loc

Show Loc Source # 
Instance details

Defined in Data.Loc

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Semigroup Loc Source # 
Instance details

Defined in Data.Loc

Methods

(<>) :: Loc -> Loc -> Loc #

sconcat :: NonEmpty Loc -> Loc #

stimes :: Integral b => b -> Loc -> Loc #

Monoid Loc Source # 
Instance details

Defined in Data.Loc

Methods

mempty :: Loc #

mappend :: Loc -> Loc -> Loc #

mconcat :: [Loc] -> Loc #

Located Loc Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: Loc -> Loc Source #

locOfList :: [Loc] -> Loc Source #

IsLocation Loc Source # 
Instance details

Defined in Data.Loc

Methods

fromLoc :: Loc -> Loc Source #

fromPos :: Pos -> Loc Source #

locStart :: Loc -> Loc Source #

Starting position of the location.

locEnd :: Loc -> Loc Source #

Ending position of the location.

(<-->) :: (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.

newtype SrcLoc Source #

Source location type. Source location are all equal, which allows AST nodes to be compared modulo location information.

Constructors

SrcLoc Loc 

Instances

Instances details
Eq SrcLoc Source # 
Instance details

Defined in Data.Loc

Methods

(==) :: SrcLoc -> SrcLoc -> Bool #

(/=) :: SrcLoc -> SrcLoc -> Bool #

Data SrcLoc Source # 
Instance details

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 # 
Instance details

Defined in Data.Loc

Read SrcLoc Source # 
Instance details

Defined in Data.Loc

Show SrcLoc Source # 
Instance details

Defined in Data.Loc

Semigroup SrcLoc Source # 
Instance details

Defined in Data.Loc

Monoid SrcLoc Source # 
Instance details

Defined in Data.Loc

Located SrcLoc Source # 
Instance details

Defined in Data.Loc

IsLocation SrcLoc Source # 
Instance details

Defined in Data.Loc

srclocOf :: Located a => a -> SrcLoc Source #

The SrcLoc of a Located value.

srcspan :: (Located a, Located b) => a -> b -> SrcLoc infixl 6 Source #

A SrcLoc with (minimal) span that includes two Located values.

class IsLocation a where Source #

Locations

Minimal complete definition

fromLoc

Methods

fromLoc :: Loc -> a Source #

fromPos :: Pos -> a Source #

Instances

Instances details
IsLocation SrcLoc Source # 
Instance details

Defined in Data.Loc

IsLocation Loc Source # 
Instance details

Defined in Data.Loc

Methods

fromLoc :: Loc -> Loc Source #

fromPos :: Pos -> Loc Source #

noLoc :: IsLocation a => a Source #

No location.

class Located a where Source #

Located values have a location.

Minimal complete definition

locOf

Methods

locOf :: a -> Loc Source #

locOfList :: [a] -> Loc Source #

Instances

Instances details
Located SrcLoc Source # 
Instance details

Defined in Data.Loc

Located Loc Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: Loc -> Loc Source #

locOfList :: [Loc] -> Loc Source #

Located Pos Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: Pos -> Loc Source #

locOfList :: [Pos] -> Loc Source #

Located a => Located [a] Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: [a] -> Loc Source #

locOfList :: [[a]] -> Loc Source #

Located a => Located (Maybe a) Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: Maybe a -> Loc Source #

locOfList :: [Maybe a] -> Loc Source #

Located (L a) Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: L a -> Loc Source #

locOfList :: [L a] -> Loc Source #

class Relocatable a where Source #

Values that can be relocated

Methods

reloc :: Loc -> a -> a Source #

Instances

Instances details
Relocatable (L a) Source # 
Instance details

Defined in Data.Loc

Methods

reloc :: Loc -> L a -> L a Source #

data L a Source #

A value of type L a is a value of type a with an associated Loc, but this location is ignored when performing comparisons.

Constructors

L Loc a 

Instances

Instances details
Functor L Source # 
Instance details

Defined in Data.Loc

Methods

fmap :: (a -> b) -> L a -> L b #

(<$) :: a -> L b -> L a #

Eq x => Eq (L x) Source # 
Instance details

Defined in Data.Loc

Methods

(==) :: L x -> L x -> Bool #

(/=) :: L x -> L x -> Bool #

Data a => Data (L a) Source # 
Instance details

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) #

toConstr :: L a -> Constr #

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 # 
Instance details

Defined in Data.Loc

Methods

compare :: L x -> L x -> Ordering #

(<) :: L x -> L x -> Bool #

(<=) :: L x -> L x -> Bool #

(>) :: L x -> L x -> Bool #

(>=) :: L x -> L x -> Bool #

max :: L x -> L x -> L x #

min :: L x -> L x -> L x #

Show x => Show (L x) Source # 
Instance details

Defined in Data.Loc

Methods

showsPrec :: Int -> L x -> ShowS #

show :: L x -> String #

showList :: [L x] -> ShowS #

Relocatable (L a) Source # 
Instance details

Defined in Data.Loc

Methods

reloc :: Loc -> L a -> L a Source #

Located (L a) Source # 
Instance details

Defined in Data.Loc

Methods

locOf :: L a -> Loc Source #

locOfList :: [L a] -> Loc Source #

unLoc :: L a -> a Source #