patches-vector-0.1.4.2: Patches (diffs) on vectors: composable, mergeable, and invertible.

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Patch.Internal

Description

For day-to-day use, please see Data.Patch

Synopsis

Documentation

>>> import Test.QuickCheck
>>> :{
let
  nonEmpty :: Vector a -> Bool
  nonEmpty = (>0) . Vector.length
  editsTo :: Arbitrary a => Vector a -> Gen (Edit a)
  editsTo v = do
    i <- choose (0, Vector.length v -1)
    c <- elements [const (Insert i), \o _ -> Delete i o, Replace i]
    x <- arbitrary
    return $ c (v Vector.! i) x
  patchesFrom' :: (Eq a, Arbitrary a) => Vector a -> Gen (Patch a)
  patchesFrom' v | Vector.length v > 0 = fromList <$> listOf (editsTo v)
  patchesFrom' _ | otherwise           = fromList <$> listOf (Insert 0 <$> arbitrary)
  patchesFrom :: Vector Int -> Gen (Patch Int)
  patchesFrom = patchesFrom'
  divergingPatchesFrom :: Vector Int -> Gen (Patch Int, Patch Int)
  divergingPatchesFrom v = (,) <$> patchesFrom v <*> patchesFrom v
  historyFrom d 0 = return []
  historyFrom d m = do
    p <- patchesFrom d
    r <- historyFrom (apply p d) $ m - 1
    return (p:r)
:}
>>> :set -XScopedTypeVariables
>>> instance Arbitrary a => Arbitrary (Vector a) where arbitrary = Vector.fromList <$> listOf arbitrary

Blah

forAll (patchesFrom d) $ \ x -> read (show x) == x

newtype Patch a Source

A patch is a collection of edits performed to a document, in this case a Vector. They are implemented as a list of Edit, and can be converted to and from raw lists of edits using toList and fromList respectively.

Patches form a groupoid (a Monoid with inverses, and a partial composition relation), where the inverse element can be computed with inverse and the groupoid operation is composition of patches. Applying p1 <> p2 is the same as applying p1 then p2 (see apply). This composition operator may produce structurally different patches depending on associativity, however the patches are guaranteed to be equivalent in the sense that the resultant document will be the same when they are applied.

For convenience, we make our composition operator here total, to fit the Monoid typeclass, but provide some predicates (composable and applicable) to determine if the operation can be validly used.

forAll (patchesFrom d) $ \a -> a <> mempty == a
forAll (patchesFrom d) $ \a -> mempty <> a == a
forAll (historyFrom d 3) $ \[a, b, c] -> apply (a <> (b <> c)) d == apply ((a <> b) <> c) d

The indices of the Edit s are all based on the original document, so:

>>> Vector.toList $ apply (fromList [Insert 0 'a', Insert 1 'b']) (Vector.fromList "123")
"a1b23"
>>> Vector.toList $ apply (fromList [Insert 0 'a', Insert 0 'b']) (Vector.fromList "123")
"ab123"

Note that the first Insert didn't introduce an offset for the second.

Constructors

Patch [Edit a] 

Instances

Eq a => Eq (Patch a) Source 
(Eq a, Read a) => Read (Patch a) Source 
Show a => Show (Patch a) Source 
Eq a => Monoid (Patch a) Source 

data Edit a Source

An Edit is a single alteration of the vector, either inserting, removing, or replacing an element.

Useful optics are provided below, for the index, the old element, and the new element.

Constructors

Insert Int a

Insert i x inserts the element x at position i.

Delete Int a

Delete i x deletes the element x from position i.

Replace Int a a

Replace i x x' replaces the element x at position i with x'.

Instances

Eq a => Eq (Edit a) Source 
Read a => Read (Edit a) Source 
Show a => Show (Edit a) Source 

inverse :: Patch a -> Patch a Source

Compute the inverse of a patch, such that:

forAll (patchesFrom d) $ \p -> p <> inverse p == mempty
forAll (patchesFrom d) $ \p -> inverse p <> p == mempty
forAll (patchesFrom d) $ \p -> inverse (inverse p) == p
forAll (historyFrom d 2) $ \[p, q] -> inverse (p <> q) == inverse q <> inverse p
forAll (patchesFrom d) $ \p -> inverse mempty == mempty
forAll (patchesFrom d) $ \p -> applicable (inverse p) (apply p d)
forAll (patchesFrom d) $ \p -> composable p (inverse p)
forAll (patchesFrom d) $ \p -> composable (inverse p) p

index :: Lens' (Edit a) Int Source

A lens for the index where an edit is to be performed.

nonEmpty d ==> forAll (editsTo d) $ \e -> set index v e ^. index == v
nonEmpty d ==> forAll (editsTo d) $ \e -> set index (e ^. index) e == e
nonEmpty d ==> forAll (editsTo d) $ \e -> set index v' (set index v e) == set index v' e

old :: Traversal' (Edit a) a Source

A traversal for the old element to be replaced/deleted. Empty in the case of an Insert.

new :: Traversal' (Edit a) a Source

A traversal for the new value to be inserted or replacing the old value. Empty in the case of a Delete.

toList :: Patch a -> [Edit a] Source

Convert a patch to a list of edits.

unsafeFromList :: [Edit a] -> Patch a Source

Directly convert a list of edits to a patch, without sorting edits by index, and resolving contradictory edits. Use this function if you know that the input list is already a wellformed patch.

fromList :: Eq a => [Edit a] -> Patch a Source

Convert a list of edits to a patch, making sure to eliminate conflicting edits and sorting by index.

normalise :: [Edit a] -> [Edit a] Source

Internal: Eliminate conflicting edits

applicable :: Eq a => Patch a -> Vector a -> Bool Source

Returns true if a patch can be safely applied to a document, that is, applicable p d holds when d is a valid source document for the patch p.

applicable mempty d
forAll (patchesFrom d) $ \p -> applicable p d
forAll (historyFrom d 2) $ \[p, q] -> applicable p d && applicable q (apply p d)
forAll (historyFrom d 2) $ \[p, q] -> applicable (p <> q) d

composable :: Eq a => Patch a -> Patch a -> Bool Source

Returns true if a patch can be validly composed with another. That is, composable p q holds if q can be validly applied after p.

forAll (patchesFrom d) $ \p -> composable mempty p
forAll (patchesFrom d) $ \p -> composable p mempty
forAll (historyFrom d 2) $ \[p, q] -> composable p q

apply :: Patch a -> Vector a -> Vector a Source

Apply a patch to a document.

Technically, apply is a monoid morphism to the monoid of endomorphisms Vector a -> Vector a, and that's how we can derive the following two laws:

forAll (historyFrom d 2) $ \[a, b] -> apply b (apply a d) == apply (a <> b) d
apply mempty d == d

transformWith :: Eq a => (a -> a -> a) -> Patch a -> Patch a -> (Patch a, Patch a) Source

Given two diverging patches p and q, transform m p q returns a pair of updated patches (p',q') such that q <> p' and p <> q' are equivalent patches that incorporate the changes of both p and q, up to merge conflicts, which are handled by the provided function m.

This is the standard transform function of Operational Transformation patch resolution techniques, and can be thought of as the mapping for morphisms in a groupoid fibration from a present version to a past version.

forAll (divergingPatchesFrom d) $ \(p,q) -> let (p', q') = transformWith ours p q in apply (p <> q') d == apply (q <> p') d
forAll (divergingPatchesFrom d) $ \(p,q) -> let (p', q') = transformWith ours p q in applicable p' (apply q d) && applicable q' (apply p d)
forAll (divergingPatchesFrom d) $ \(p,q) -> let (p', q') = transformWith ours p q in composable p q' && composable q p'

This function is commutative iff m is commutative.

forAll (divergingPatchesFrom d) $ \(p,q) -> let (p', q') = transformWith (*) p q; (q'', p'') = transformWith (*) q p in p' == p'' && q' == q''
forAll (patchesFrom d) $ \ p -> transformWith (*) mempty p == (mempty, p)
forAll (patchesFrom d) $ \ p -> transformWith (*) p mempty == (p, mempty)

Some example conflict strategies are provided below.

ours :: a -> a -> a Source

Resolve a conflict by always using the left-hand side

theirs :: a -> a -> a Source

Resolve a conflict by always using the right-hand side

transform :: (Eq a, Monoid a) => Patch a -> Patch a -> (Patch a, Patch a) Source

A convenience version of transformWith which resolves conflicts using mappend.

diff :: Eq a => Vector a -> Vector a -> Patch a Source

Compute the difference between two documents, using the Wagner-Fischer algorithm. O(mn) time and space.

apply (diff d e) d == e
apply (diff d e) d == apply (inverse (diff e d)) d
apply (diff a b <> diff b c) a == apply (diff a c) a
applicable (diff a b) a

data HunkStatus Source

The four different ways a hunk may have been manipulated.

type Hunks a = [(Vector a, HunkStatus)] Source

The type for a series of hunks; a patch as it may be displayed to a user.

hunks :: Patch a -> Vector a -> Hunks a Source

Render a patch on a document as a list of change hunks. Good for displaying a patch to a user.

forAll (patchesFrom d) $ \p -> Vector.concat (map fst (filter ((/= Deleted) . snd) (hunks p d))) == apply p d