loc-0.1.4.0: Types representing line and column positions and ranges in text files.
Safe HaskellNone
LanguageHaskell2010

Data.Loc.Types

Description

For convenience, this module exports only the important types from Loc.

Synopsis

Documentation

data Pos Source #

Pos stands for positive integer. You can also think of it as position, because we use it to represent line and column numbers (Line and Column).

Pos has instances of several of the standard numeric typeclasses, although many of the operations throw Underflow when non-positive values result. Pos does not have an Integral instance, because there is no sensible way to implement quotRem.

Instances

Instances details
Enum Pos Source #
>>> toEnum 3 :: Pos
3
>>> toEnum 0 :: Pos
*** Exception: arithmetic underflow
>>> fromEnum (3 :: Pos)
3
Instance details

Defined in Data.Loc.Pos

Methods

succ :: Pos -> Pos #

pred :: Pos -> Pos #

toEnum :: Int -> Pos #

fromEnum :: Pos -> Int #

enumFrom :: Pos -> [Pos] #

enumFromThen :: Pos -> Pos -> [Pos] #

enumFromTo :: Pos -> Pos -> [Pos] #

enumFromThenTo :: Pos -> Pos -> Pos -> [Pos] #

Eq Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

Data Pos Source # 
Instance details

Defined in Data.Loc.Pos

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 #

Num Pos Source #
>>> fromInteger 3 :: Pos
3
>>> fromInteger 0 :: Pos
*** Exception: arithmetic underflow
>>> 2 + 3 :: Pos
5
>>> 3 - 2 :: Pos
1
>>> 3 - 3 :: Pos
*** Exception: arithmetic underflow
>>> 2 * 3 :: Pos
6
>>> negate 3 :: Pos
*** Exception: arithmetic underflow
Instance details

Defined in Data.Loc.Pos

Methods

(+) :: Pos -> Pos -> Pos #

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

(*) :: Pos -> Pos -> Pos #

negate :: Pos -> Pos #

abs :: Pos -> Pos #

signum :: Pos -> Pos #

fromInteger :: Integer -> Pos #

Ord Pos Source # 
Instance details

Defined in Data.Loc.Pos

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.Pos

Real Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toRational :: Pos -> Rational #

Show Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

ToNat Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Pos -> Natural Source #

data Line Source #

Instances

Instances details
Enum Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

succ :: Line -> Line #

pred :: Line -> Line #

toEnum :: Int -> Line #

fromEnum :: Line -> Int #

enumFrom :: Line -> [Line] #

enumFromThen :: Line -> Line -> [Line] #

enumFromTo :: Line -> Line -> [Line] #

enumFromThenTo :: Line -> Line -> Line -> [Line] #

Eq Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

Data Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Line -> c Line #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Line #

toConstr :: Line -> Constr #

dataTypeOf :: Line -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Line) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Line) #

gmapT :: (forall b. Data b => b -> b) -> Line -> Line #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Line -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Line -> r #

gmapQ :: (forall d. Data d => d -> u) -> Line -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Line -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Line -> m Line #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Line -> m Line #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Line -> m Line #

Num Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

(+) :: Line -> Line -> Line #

(-) :: Line -> Line -> Line #

(*) :: Line -> Line -> Line #

negate :: Line -> Line #

abs :: Line -> Line #

signum :: Line -> Line #

fromInteger :: Integer -> Line #

Ord Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

compare :: Line -> Line -> Ordering #

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

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

(>) :: Line -> Line -> Bool #

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

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Read Line Source # 
Instance details

Defined in Data.Loc.Pos

Real Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toRational :: Line -> Rational #

Show Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

ToNat Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Line -> Natural Source #

data Column Source #

Instances

Instances details
Enum Column Source # 
Instance details

Defined in Data.Loc.Pos

Eq Column Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

Data Column Source # 
Instance details

Defined in Data.Loc.Pos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Column -> c Column #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Column #

toConstr :: Column -> Constr #

dataTypeOf :: Column -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Column) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Column) #

gmapT :: (forall b. Data b => b -> b) -> Column -> Column #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Column -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Column -> r #

gmapQ :: (forall d. Data d => d -> u) -> Column -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Column -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Column -> m Column #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Column -> m Column #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Column -> m Column #

Num Column Source # 
Instance details

Defined in Data.Loc.Pos

Ord Column Source # 
Instance details

Defined in Data.Loc.Pos

Read Column Source # 
Instance details

Defined in Data.Loc.Pos

Real Column Source # 
Instance details

Defined in Data.Loc.Pos

Show Column Source # 
Instance details

Defined in Data.Loc.Pos

ToNat Column Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Column -> Natural Source #

data Loc Source #

Stands for location. Consists of a Line and a Column. You can think of a Loc like a caret position in a text editor. Following the normal convention for text editors and such, line and column numbers start with 1.

Instances

Instances details
Eq Loc Source # 
Instance details

Defined in Data.Loc.Loc

Methods

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

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

Data Loc Source # 
Instance details

Defined in Data.Loc.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.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 #

readPrec = locReadPrec

Instance details

Defined in Data.Loc.Loc

Show Loc Source #

showsPrec = locShowsPrec

Instance details

Defined in Data.Loc.Loc

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

data Span Source #

A Span consists of a start location (start) and an end location (end). The end location must be greater than the start location; in other words, empty or backwards spans are not permitted.

Construct and combine spans using fromTo, fromToMay, +, and -.

Instances

Instances details
Eq Span Source # 
Instance details

Defined in Data.Loc.Span

Methods

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

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

Data Span Source # 
Instance details

Defined in Data.Loc.Span

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span #

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Span) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) #

gmapT :: (forall b. Data b => b -> b) -> Span -> Span #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

Ord Span Source # 
Instance details

Defined in Data.Loc.Span

Methods

compare :: Span -> Span -> Ordering #

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

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

(>) :: Span -> Span -> Bool #

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

max :: Span -> Span -> Span #

min :: Span -> Span -> Span #

Read Span Source #

readPrec = spanReadPrec

Instance details

Defined in Data.Loc.Span

Show Span Source #

showsPrec = spanShowsPrec

Instance details

Defined in Data.Loc.Span

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

data SpanOrLoc Source #

A SpanOrLoc consists of a start location and an end location. The end location must be greater than or equal to the start location; in other words, backwards spans are not permitted.

If the start and end location are the same, then the value is a Loc. If they differ, then the value is a Span.

Instances

Instances details
Eq SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

Data SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpanOrLoc -> c SpanOrLoc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpanOrLoc #

toConstr :: SpanOrLoc -> Constr #

dataTypeOf :: SpanOrLoc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpanOrLoc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpanOrLoc) #

gmapT :: (forall b. Data b => b -> b) -> SpanOrLoc -> SpanOrLoc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpanOrLoc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpanOrLoc -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpanOrLoc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpanOrLoc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpanOrLoc -> m SpanOrLoc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpanOrLoc -> m SpanOrLoc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpanOrLoc -> m SpanOrLoc #

Ord SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

Show SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

data Area Source #

A set of non-overlapping, non-abutting Spans. You may also think of an Area like a span that can be empty or have “gaps”.

Construct and combine areas using mempty, spanArea, fromTo, +, and -.

Instances

Instances details
Eq Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

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

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

Data Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Area -> c Area #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Area #

toConstr :: Area -> Constr #

dataTypeOf :: Area -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Area) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Area) #

gmapT :: (forall b. Data b => b -> b) -> Area -> Area #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Area -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Area -> r #

gmapQ :: (forall d. Data d => d -> u) -> Area -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Area -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Area -> m Area #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Area -> m Area #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Area -> m Area #

Ord Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

compare :: Area -> Area -> Ordering #

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

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

(>) :: Area -> Area -> Bool #

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

max :: Area -> Area -> Area #

min :: Area -> Area -> Area #

Read Area Source #

readPrec = areaReadPrec

Instance details

Defined in Data.Loc.Area

Show Area Source #

showsPrec = areaShowsPrec

Instance details

Defined in Data.Loc.Area

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Semigroup Area Source #

<> = +

Instance details

Defined in Data.Loc.Area

Methods

(<>) :: Area -> Area -> Area #

sconcat :: NonEmpty Area -> Area #

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

Monoid Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

mempty :: Area #

mappend :: Area -> Area -> Area #

mconcat :: [Area] -> Area #