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

Data.Loc.Span

Synopsis

Documentation

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 #

Constructing

fromTo :: 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 fromToMay.

fromToMay :: 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 fromTo, which throws an exception instead.

Querying

Calculations

lines :: Span -> NonEmpty Line Source #

All of the lines that a span touches.

>>> NonEmpty.toList (lines (read "2:6-2:10"))
[2]
>>> NonEmpty.toList (lines (read "2:6-8:4"))
[2,3,4,5,6,7,8]

overlapping :: Span -> Span -> Bool Source #

Spans that are directly abutting do not count as overlapping.

>>> overlapping (read "1:5-1:8") (read "1:8-1:12")
False

But these spans overlap by a single character:

>>> overlapping (read "1:5-1:9") (read "1:8-1:12")
True

Spans are overlapping if one is contained entirely within another.

>>> overlapping (read "1:5-1:15") (read "1:6-1:10")
True

Spans are overlapping if they are identical.

>>> overlapping (read "1:5-1:15") (read "1:5-1:15")
True

linesOverlapping :: Span -> Span -> Bool Source #

Determines whether the two spans touch any of the same lines.

>>> linesOverlapping (read "1:1-1:2") (read "1:1-1:2")
True
>>> linesOverlapping (read "1:1-1:2") (read "1:1-2:1")
True
>>> linesOverlapping (read "1:1-1:2") (read "2:1-2:2")
False

touching :: Span -> Span -> Bool Source #

Two spans are considered to "touch" if they are overlapping or abutting; in other words, if there is no space between them.

>>> touching (read "1:1-1:2") (read "1:2-1:3")
True
>>> touching (read "1:1-1:2") (read "1:1-1:3")
True
>>> touching (read "1:1-1:2") (read "1:3-1:4")
False

join :: Span -> Span -> Span Source #

>>> join (read "1:1-1:2") (read "1:2-1:3")
1:1-1:3
>>> join (read "1:1-1:2") (read "1:1-1:3")
1:1-1:3

joinAsc Source #

Arguments

:: [Span]

A list of Spans sorted in ascending order.

This precondition is not checked.

-> [Span] 

Given an ascending list of Spans, combine those which abut or overlap.

(+) :: Span -> Span -> OneToTwo Span Source #

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

>>> read "1:1-1:2" + read "1:2-1:3"
One 1:1-1:3
>>> read "1:1-1:2" + read "1:1-3:1"
One 1:1-3:1
>>> read "1:1-1:2" + read "1:1-11:1"
One 1:1-11:1

If the spans are not overlapping or abutting, they are returned unmodified in the same order in which they were given as parameters.

>>> read "1:1-1:2" + read "2:1-2:5"
Two 1:1-1:2 2:1-2:5
>>> read "2:1-2:5" + read "1:1-1:2"
Two 2:1-2:5 1:1-1:2

(-) :: Span -> Span -> ZeroToTwo Span Source #

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

>>> read "2:5-4:1" - read "2:9-3:5"
Two 2:5-2:9 3:5-4:1
>>> read "2:5-4:1" - read "2:5-3:5"
One 3:5-4:1
>>> read "2:5-4:1" - read "2:2-3:5"
One 3:5-4:1

Subtracting a thing from itself yields nothing.

>>> let x = read "2:5-4:1" in x - x
Zero
>>> read "2:5-4:1" - read "2:2-4:4"
Zero
>>> read "1:1-8:1" - read "1:2-8:1"
One 1:1-1:2

Show and Read

spanShowsPrec :: Int -> Span -> ShowS Source #

>>> spanShowsPrec minPrec (fromTo (read "3:14") (read "6:5")) ""
"3:14-6:5"

spanReadPrec :: ReadPrec Span Source #

>>> readPrec_to_S spanReadPrec minPrec "3:14-6:5"
[(3:14-6:5,"")]
>>> readPrec_to_S spanReadPrec minPrec "6:5-3:14"
[(3:14-6:5,"")]
>>> readPrec_to_S spanReadPrec minPrec "6:5-6:5"
[]