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

Data.Loc.Pos

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 #

class ToNat a where Source #

Types that can be converted to Natural.

This class mostly exists so that toNat can be used in situations that would normally call for toInteger (which we cannot use because Pos does not have an instance of Integral).

Methods

toNat :: a -> Natural Source #

Instances

Instances details
ToNat Column Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Column -> Natural Source #

ToNat Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Line -> Natural Source #

ToNat Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Pos -> Natural Source #

Show and Read

posShowsPrec :: Int -> Pos -> ShowS Source #

>>> posShowsPrec minPrec 1 ""
"1"
>>> posShowsPrec minPrec 42 ""
"42"

posReadPrec :: ReadPrec Pos Source #

>>> readPrec_to_S posReadPrec minPrec "1"
[(1,"")]
>>> readPrec_to_S posReadPrec minPrec "42"
[(42,"")]
>>> readPrec_to_S posReadPrec minPrec "0"
[]
>>> readPrec_to_S posReadPrec minPrec "-1"
[]