| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Loc.Span
Synopsis
- data Span
- fromTo :: Loc -> Loc -> Span
- fromToMay :: Loc -> Loc -> Maybe Span
- start :: Span -> Loc
- end :: Span -> Loc
- lines :: Span -> NonEmpty Line
- overlapping :: Span -> Span -> Bool
- linesOverlapping :: Span -> Span -> Bool
- touching :: Span -> Span -> Bool
- join :: Span -> Span -> Span
- joinAsc :: [Span] -> [Span]
- (+) :: Span -> Span -> OneToTwo Span
- (-) :: Span -> Span -> ZeroToTwo Span
- spanShowsPrec :: Int -> Span -> ShowS
- spanReadPrec :: ReadPrec Span
Documentation
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
| Eq Span Source # | |
| Data Span Source # | |
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 # 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 # | |
| Read Span Source # | |
| Show Span Source # | |
Constructing
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
Arguments
| :: [Span] | A list of 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 contains what is covered by
- ba 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 - xZero
>>>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"[]