diff-loc-0.1.0.0: Map file locations across diffs
Safe HaskellSafe-Inferred
LanguageHaskell2010

DiffLoc.Colline

Description

Line-column locations and its offset monoid.

Synopsis

Documentation

data Colline l c Source #

Line and column coordinates.

The generalization over types of line and column numbers frees us from any specific indexing scheme, notably whether columns are zero- or one-indexed.

Example

abc
de
fgh

Assuming the lines and columns are both 1-indexed, "b" is at location (Colline 1 2) and "h" is at location (Colline 3 3).

Constructors

Colline !l !c 

Instances

Instances details
(Show l, Show c) => Show (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

showsPrec :: Int -> Colline l c -> ShowS #

show :: Colline l c -> String #

showList :: [Colline l c] -> ShowS #

(Amor l, Origin c) => Amor (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

Associated Types

type Trans (Colline l c) Source #

Methods

(.+) :: Colline l c -> Trans (Colline l c) -> Colline l c Source #

(.-.?) :: Colline l c -> Colline l c -> Maybe (Trans (Colline l c)) Source #

(Origin l, Origin c) => Origin (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

origin :: Colline l c Source #

(Eq l, Eq c) => Eq (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

(==) :: Colline l c -> Colline l c -> Bool #

(/=) :: Colline l c -> Colline l c -> Bool #

(Ord l, Ord c) => Ord (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

compare :: Colline l c -> Colline l c -> Ordering #

(<) :: Colline l c -> Colline l c -> Bool #

(<=) :: Colline l c -> Colline l c -> Bool #

(>) :: Colline l c -> Colline l c -> Bool #

(>=) :: Colline l c -> Colline l c -> Bool #

max :: Colline l c -> Colline l c -> Colline l c #

min :: Colline l c -> Colline l c -> Colline l c #

type Trans (Colline l c) Source # 
Instance details

Defined in DiffLoc.Colline

type Trans (Colline l c) = Vallee (Trans l) (Trans c)

data Vallee dl dc Source #

The space between two Collines.

This type represents offsets between text locations x <= y as the number of newlines inbetween and the number of characters from the last new line to y, if there is at least one newline, or the number of characters from x to y.

Example

abc
de
fgh
  • The offset from "b" to "h" is Vallee 2 2 (two newlines to reach line 3, and from the beginning of that line, advance two characters to reach h).
  • The offset from "b" to "c" is Vallee 0 1 (advance one character).

The offset from "b" to "h" is actually the same as from "a" to "h" and from "c" to "h". Line-column offsets are thus not invertible. This was one of the main constraints in the design of the Amor class.

Constructors

Vallee !dl !dc 

Instances

Instances details
(Monoid l, Eq l, Monoid c) => Monoid (Vallee l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

mempty :: Vallee l c #

mappend :: Vallee l c -> Vallee l c -> Vallee l c #

mconcat :: [Vallee l c] -> Vallee l c #

(Monoid l, Eq l, Semigroup c) => Semigroup (Vallee l c) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

(<>) :: Vallee l c -> Vallee l c -> Vallee l c #

sconcat :: NonEmpty (Vallee l c) -> Vallee l c #

stimes :: Integral b => b -> Vallee l c -> Vallee l c #

(Show dl, Show dc) => Show (Vallee dl dc) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

showsPrec :: Int -> Vallee dl dc -> ShowS #

show :: Vallee dl dc -> String #

showList :: [Vallee dl dc] -> ShowS #

(Eq dl, Eq dc) => Eq (Vallee dl dc) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

(==) :: Vallee dl dc -> Vallee dl dc -> Bool #

(/=) :: Vallee dl dc -> Vallee dl dc -> Bool #

(Ord dl, Ord dc) => Ord (Vallee dl dc) Source # 
Instance details

Defined in DiffLoc.Colline

Methods

compare :: Vallee dl dc -> Vallee dl dc -> Ordering #

(<) :: Vallee dl dc -> Vallee dl dc -> Bool #

(<=) :: Vallee dl dc -> Vallee dl dc -> Bool #

(>) :: Vallee dl dc -> Vallee dl dc -> Bool #

(>=) :: Vallee dl dc -> Vallee dl dc -> Bool #

max :: Vallee dl dc -> Vallee dl dc -> Vallee dl dc #

min :: Vallee dl dc -> Vallee dl dc -> Vallee dl dc #

type Vallée = Vallee Source #

Sans commentaire.