loc-0.1.3.1: Types representing line and column positions and ranges in text files.

Safe HaskellNone
LanguageHaskell2010

Data.Loc

Contents

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

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

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

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

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

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.

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

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

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 # 

Methods

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

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

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

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 # 

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 # 
Real Pos Source # 

Methods

toRational :: Pos -> Rational #

Show Pos Source # 

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

ToNat Pos Source # 

Methods

toNat :: Pos -> Natural Source #

data OneToTwo a Source #

List of length 1 or 2.

Instances

Functor OneToTwo Source # 

Methods

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

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

Foldable OneToTwo Source # 

Methods

fold :: Monoid m => OneToTwo m -> 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 #

Eq a => Eq (OneToTwo a) Source # 

Methods

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

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

Ord a => Ord (OneToTwo a) Source # 

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 #

Read a => Read (OneToTwo a) Source # 
Show a => Show (OneToTwo a) Source # 

Methods

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

show :: OneToTwo a -> String #

showList :: [OneToTwo a] -> ShowS #

data ZeroToTwo a Source #

List of length 0, 1, or 2.

Instances

Functor ZeroToTwo Source # 

Methods

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

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

Foldable ZeroToTwo Source # 

Methods

fold :: Monoid m => ZeroToTwo m -> 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 #

Eq a => Eq (ZeroToTwo a) Source # 

Methods

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

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

Ord a => Ord (ZeroToTwo a) Source # 
Read a => Read (ZeroToTwo a) Source # 
Show a => Show (ZeroToTwo a) 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).

Minimal complete definition

toNat

Methods

toNat :: a -> Natural Source #