loc-0.1.4.1: Line and column positions and ranges in text files
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Loc

Synopsis

Concepts

Line and Column are positive integers representing line and column numbers.

The product of Line and Column is a Loc, which represents a position between characters in multiline text. The smallest loc is origin: line 1, column 1.

Here's a small piece of text for illustration:

             1         2
    12345678901234567890123456789
  ┌───────────────────────────────┐
1 │ I have my reasons, you        │
2 │ have yours. What's obvious    │
3 │ to me isn't to everyone else, │
4 │ and vice versa.               │
  └───────────────────────────────┘

In this example, the word “obvious” starts at line 2, column 20, and it ends at line 2, column 27. The Show instance uses a shorthand notation denoting these locs as 2:20 and 2:27.

A Span is a nonempty contiguous region of text between two locs; think of it like a highlighted area in a simple text editor. In the above example, a span that covers the word “obvious” starts at 2:20 and ends at 2:27. The Show instance describes this tersely as 2:20-2:27.

Multiple non-overlapping regions form an Area. You may also think of an area like a span that can be empty or have “gaps”. In the example above, the first three words “I have my”, and not the spaces between them, are covered by the area [1:1-1:2,1:3-1:7,1:8-1:10].

Imports

Recommended import:

import Data.Loc.Types
import qualified Data.Loc as Loc

Core types

data Line Source #

Instances

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

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

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 #

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 #

Eq Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

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 #

ToNat Line Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Line -> Natural Source #

data Column Source #

Instances

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

Enum Column Source # 
Instance details

Defined in Data.Loc.Pos

Num 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

Eq Column Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

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

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 #

Eq Loc Source # 
Instance details

Defined in Data.Loc.Loc

Methods

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

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

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 #

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

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 #

Eq Span Source # 
Instance details

Defined in Data.Loc.Span

Methods

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

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

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 #

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 SpanOrLoc. If they differ, then the value is a SpanOrLoc.

Instances

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

Show SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

Eq SpanOrLoc Source # 
Instance details

Defined in Data.Loc.SpanOrLoc

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

Monoid Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

mempty :: Area #

mappend :: Area -> Area -> Area #

mconcat :: [Area] -> Area #

Semigroup Area Source #

<> = +

Instance details

Defined in Data.Loc.Area

Methods

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

sconcat :: NonEmpty Area -> Area #

stimes :: Integral b => b -> 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 #

Eq Area Source # 
Instance details

Defined in Data.Loc.Area

Methods

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

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

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 #

Constructing

Loc

loc :: Line -> Column -> Loc Source #

Create a Loc from a line number and column number.

This is an alias for loc.

origin :: Loc Source #

The smallest location: loc 1 1.

This is an alias for origin.

Span

spanFromTo :: Loc -> Loc -> Span Source #

Attempt to construct a Span from two Locs. The lesser loc will be the start, and the greater loc will be the end. The two locs must not be equal, or else this throws EmptySpan.

The safe version of this function is spanFromToMay.

This is an alias for fromTo.

spanFromToMay :: Loc -> Loc -> Maybe Span Source #

Attempt to construct a Span from two Locs. The lesser loc will be the start, and the greater loc will be the end. If the two locs are equal, the result is Nothing, because a span cannot be empty.

This is the safe version of spanFromTo, which throws an exception instead.

This is an alias for fromToMay.

SpanOrLoc

spanOrLocFromTo :: Loc -> Loc -> SpanOrLoc Source #

Construct a SpanOrLoc from two Locs. If the two locs are not equal, the lesser loc will be the start, and the greater loc will be the end.

This is an alias for fromTo.

Area

areaFromTo :: Loc -> Loc -> Area Source #

Construct a contiguous Area consisting of a single Span specified by two Locs. The lesser loc will be the start, and the greater loc will be the end. If the two locs are equal, the area will be empty.

This is an alias for fromTo.

spanArea :: Span -> Area Source #

Construct an Area consisting of a single Span.

This is an alias for spanArea.

Deconstructing

Loc

locLine :: Loc -> Line Source #

This is an alias for line.

locColumn :: Loc -> Column Source #

This is an alias for column.

Span

spanStart :: Span -> Loc Source #

This is an alias for start.

spanEnd :: Span -> Loc Source #

This is an alias for end.

SpanOrLoc

spanOrLocStart :: SpanOrLoc -> Loc Source #

This is an alias for start.

spanOrLocEnd :: SpanOrLoc -> Loc Source #

This is an alias for end.

Area

areaStart :: Area -> Maybe Loc Source #

This is an alias for start.

areaEnd :: Area -> Maybe Loc Source #

This is an alias for end.

areaSpansAsc :: Area -> [Span] Source #

A list of the Spans that constitute an Area, sorted in ascending order.

This is an alias for spansAsc.

Combining

Span

spanUnion :: Span -> Span -> OneToTwo Span Source #

Combine two Spans, merging them if they abut or overlap.

This is an alias for +.

spanDifference :: Span -> Span -> ZeroToTwo Span Source #

The difference between two Spanss. a - b contains what is covered by a and not covered by b.

This is an alias for -.

Area

areaUnion :: Area -> Area -> Area Source #

The union of two Areas. Spans that overlap or abut will be merged in the result.

This is an alias for +.

areaDifference :: Area -> Area -> Area Source #

The difference between two Areas. a `areaDifference` b contains what is covered by a and not covered by b.

This is an alias for -.

Miscellaneous

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

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

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 #

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 #

Eq Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

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

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

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 #

ToNat Pos Source # 
Instance details

Defined in Data.Loc.Pos

Methods

toNat :: Pos -> Natural Source #

data OneToTwo a Source #

List of length 1 or 2.

Instances

Instances details
Foldable OneToTwo Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Methods

fold :: Monoid m => OneToTwo m -> m #

foldMap :: Monoid m => (a -> m) -> OneToTwo a -> m #

foldMap' :: Monoid m => (a -> m) -> OneToTwo a -> m #

foldr :: (a -> b -> b) -> b -> OneToTwo a -> b #

foldr' :: (a -> b -> b) -> b -> OneToTwo a -> b #

foldl :: (b -> a -> b) -> b -> OneToTwo a -> b #

foldl' :: (b -> a -> b) -> b -> OneToTwo a -> b #

foldr1 :: (a -> a -> a) -> OneToTwo a -> a #

foldl1 :: (a -> a -> a) -> OneToTwo a -> a #

toList :: OneToTwo a -> [a] #

null :: OneToTwo a -> Bool #

length :: OneToTwo a -> Int #

elem :: Eq a => a -> OneToTwo a -> Bool #

maximum :: Ord a => OneToTwo a -> a #

minimum :: Ord a => OneToTwo a -> a #

sum :: Num a => OneToTwo a -> a #

product :: Num a => OneToTwo a -> a #

Functor OneToTwo Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Methods

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

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

Read a => Read (OneToTwo a) Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Show a => Show (OneToTwo a) Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Methods

showsPrec :: Int -> OneToTwo a -> ShowS #

show :: OneToTwo a -> String #

showList :: [OneToTwo a] -> ShowS #

Eq a => Eq (OneToTwo a) Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Methods

(==) :: OneToTwo a -> OneToTwo a -> Bool #

(/=) :: OneToTwo a -> OneToTwo a -> Bool #

Ord a => Ord (OneToTwo a) Source # 
Instance details

Defined in Data.Loc.List.OneToTwo

Methods

compare :: OneToTwo a -> OneToTwo a -> Ordering #

(<) :: OneToTwo a -> OneToTwo a -> Bool #

(<=) :: OneToTwo a -> OneToTwo a -> Bool #

(>) :: OneToTwo a -> OneToTwo a -> Bool #

(>=) :: OneToTwo a -> OneToTwo a -> Bool #

max :: OneToTwo a -> OneToTwo a -> OneToTwo a #

min :: OneToTwo a -> OneToTwo a -> OneToTwo a #

data ZeroToTwo a Source #

List of length 0, 1, or 2.

Instances

Instances details
Foldable ZeroToTwo Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

Methods

fold :: Monoid m => ZeroToTwo m -> m #

foldMap :: Monoid m => (a -> m) -> ZeroToTwo a -> m #

foldMap' :: Monoid m => (a -> m) -> ZeroToTwo a -> m #

foldr :: (a -> b -> b) -> b -> ZeroToTwo a -> b #

foldr' :: (a -> b -> b) -> b -> ZeroToTwo a -> b #

foldl :: (b -> a -> b) -> b -> ZeroToTwo a -> b #

foldl' :: (b -> a -> b) -> b -> ZeroToTwo a -> b #

foldr1 :: (a -> a -> a) -> ZeroToTwo a -> a #

foldl1 :: (a -> a -> a) -> ZeroToTwo a -> a #

toList :: ZeroToTwo a -> [a] #

null :: ZeroToTwo a -> Bool #

length :: ZeroToTwo a -> Int #

elem :: Eq a => a -> ZeroToTwo a -> Bool #

maximum :: Ord a => ZeroToTwo a -> a #

minimum :: Ord a => ZeroToTwo a -> a #

sum :: Num a => ZeroToTwo a -> a #

product :: Num a => ZeroToTwo a -> a #

Functor ZeroToTwo Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

Methods

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

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

Read a => Read (ZeroToTwo a) Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

Show a => Show (ZeroToTwo a) Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

Eq a => Eq (ZeroToTwo a) Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

Methods

(==) :: ZeroToTwo a -> ZeroToTwo a -> Bool #

(/=) :: ZeroToTwo a -> ZeroToTwo a -> Bool #

Ord a => Ord (ZeroToTwo a) Source # 
Instance details

Defined in Data.Loc.List.ZeroToTwo

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 #