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

DiffLoc.Interval

Description

Interval implements Shift.

Synopsis

Documentation

data Interval p Source #

(i :.. n) represents a span of text between index i and index i+n.

The type of indices p is expected to be an instance of Amor.

The length n in an interval (i :.. n) may be zero.

The elements of the interval can be thought of as indexing the interstices between characters. A span of length zero is a single interstice between two characters, where some chunk of text may be inserted.

Example: drawing of 1 :.. 2 in "abcde".

 a b c d e
0 1 2 3 4 5
  ^b+c+ length = 2
  ^
  ^ start = 1

Constructors

!p :.. !(Trans p) infixl 3 

Instances

Instances details
(Show p, Show (Trans p)) => Show (Interval p) Source # 
Instance details

Defined in DiffLoc.Interval

Methods

showsPrec :: Int -> Interval p -> ShowS #

show :: Interval p -> String #

showList :: [Interval p] -> ShowS #

Amor p => BlockOrder (Interval p) Source # 
Instance details

Defined in DiffLoc.Interval

(Eq p, Eq (Trans p)) => Eq (Interval p) Source # 
Instance details

Defined in DiffLoc.Interval

Methods

(==) :: Interval p -> Interval p -> Bool #

(/=) :: Interval p -> Interval p -> Bool #

isZeroLength :: (Eq (Trans p), Monoid (Trans p)) => Interval p -> Bool Source #

Does the interval have length zero?

data Replace p Source #

A minimalistic representation of text replacements.

A replacement Replace i n m is given by a start location i, the length n of the interval to replace (source) and the length m of its replacement (target). This representation does not keep track of the actual data being inserted.

This may overapproximate the underlying text replacement, with intervals being wider than necessary. For example, the transformation from "abc" to "ac" could be represented by mkReplace 1 1 0 (replace "b" with "" at location 1), and also by mkReplace 0 2 1 (replace "ab" with "a" at location 0).

source   abc   abc
     -    b    ab
     +         a
target   a c   a c

Insertions are replacements with source intervals of length zero. Deletions are replacements with target intervals of length zero.

Constructors

Replace !p !(Trans p) !(Trans p) 

Instances

Instances details
Amor p => Semigroup (Replace p) Source #

The composition of two replacements l <> r represents the replacement r followed by l, as one replacement of an span that contains both r and l.

The right-to-left order of composition has the nice property that when l `precedes r, l <> r can also be viewed intuitively as performing l and r simultaneously.

Properties

(x <> y) <> z === x <> (y <> z :: Replace (Plain Int))
Instance details

Defined in DiffLoc.Interval

Methods

(<>) :: Replace p -> Replace p -> Replace p #

sconcat :: NonEmpty (Replace p) -> Replace p #

stimes :: Integral b => b -> Replace p -> Replace p #

(Show p, Show (Trans p)) => Show (Replace p) Source # 
Instance details

Defined in DiffLoc.Interval

Methods

showsPrec :: Int -> Replace p -> ShowS #

show :: Replace p -> String #

showList :: [Replace p] -> ShowS #

Amor p => Shift (Replace p) Source # 
Instance details

Defined in DiffLoc.Interval

Associated Types

type Block (Replace p) Source #

(Eq p, Eq (Trans p)) => Eq (Replace p) Source # 
Instance details

Defined in DiffLoc.Interval

Methods

(==) :: Replace p -> Replace p -> Bool #

(/=) :: Replace p -> Replace p -> Bool #

type Block (Replace p) Source # 
Instance details

Defined in DiffLoc.Interval

type Block (Replace p) = Interval p