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

DiffLoc.Shift

Description

Interfaces of structures used to implement ADiff.

Synopsis

Interfaces

Replacement

class (Semigroup r, BlockOrder (Block r)) => Shift r where Source #

Shift algebra.

Laws:

src <$>   shiftR r s   =     shiftBlock r (src s)
tgt <$>   shiftR r s   =     shiftBlock r (tgt s)
src <$> coshiftR r s   =   coshiftBlock r (src s)
tgt <$> coshiftR r s   =   coshiftBlock r (tgt s)

shiftBlock r b = Just d   <==>   coshiftBlock r d = Just b
shiftR     r s = Just z   <==>   coshiftR     r z = Just s

shiftR r s = Just z  &&  shiftR s r = Just q   ==>
  z <> r  =  q <> s

coshiftR r s = Just z  &&  coshiftR s r = Just q   ==>
  r <> z  =  s <> q

Duality laws:

src = tgt . dual
tgt = src . dual
shiftBlock = coshiftBlock . dual
coshiftBlock = shiftBlock . dual
coshiftR = shiftR . dual
shiftR = coshiftR . dual

Minimal complete definition

dual

Associated Types

type Block r :: Type Source #

Methods

src :: r -> Block r Source #

tgt :: r -> Block r Source #

shiftBlock :: r -> Block r -> Maybe (Block r) Source #

coshiftBlock :: r -> Block r -> Maybe (Block r) Source #

shiftR :: r -> r -> Maybe r Source #

coshiftR :: r -> r -> Maybe r Source #

dual :: r -> r Source #

Instances

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

Defined in DiffLoc.Interval

Associated Types

type Block (Replace p) Source #

class BlockOrder b where Source #

Partial ordering of interval-like things.

Methods

precedes :: b -> b -> Bool Source #

distantlyPrecedes :: b -> b -> Bool Source #

Precedes but not adjacent, provided you have a notion of adjacence. Otherwise it's fine to equate this with precedes.

Instances

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

Defined in DiffLoc.Interval

Indices and offsets

class (Ord p, Ord (Trans p), Monoid (Trans p)) => Amor p where Source #

Action d'un Monoïde Ordonné. Ordered monoid actions.

  • An ordered set of points Ord p.
  • An ordered monoid of translations (or "vectors") (Ord (Trans p), Monoid (Trans p)).

In addition to the Ord and Monoid laws, ordered monoids must have a monotone (<>):

v <= v'   ==>    w <= w'   =>   (v <> w) <= (v' <> w')
  • Points can be translated along vectors using (.+).
  • Given two ordered points i <= j, j .-.? i finds a vector n such that i + n = j.

In other words, we only require the existence of "positive" translations (this is unlike affine spaces, where translations exist between any two points). This makes it possible to implement this class for line-column locations (DiffLoc.Colline), where translations are not invertible.

(.-.?) is not part of a standard definition of ordered monoid actions. Feel free to suggest a better name for this structure or a way to not depend on this operation.

Laws:

              (x .+ v) .+ w  =  x .+ (v <> w)
x <= y  ==>  x .+ (y .-. x)  =  y
             (x .+ v) .-. x  =  x

Associated Types

type Trans p :: Type Source #

Type of translations between points of p.

Methods

(.+) :: p -> Trans p -> p infixr 6 Source #

Translate a point.

(.-.?) :: p -> p -> Maybe (Trans p) Source #

Translation between two points. j .-.? i must be defined (Just) if i <= j,

There is an unsafe wrapper (.-.) in DiffLoc.Unsafe.

Instances

Instances details
(Num a, Ord a) => Amor (Plain a) Source # 
Instance details

Defined in DiffLoc.Index

Associated Types

type Trans (Plain a) Source #

Methods

(.+) :: Plain a -> Trans (Plain a) -> Plain a Source #

(.-.?) :: Plain a -> Plain a -> Maybe (Trans (Plain a)) Source #

(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 #

(Num a, Ord a) => Amor (IndexFrom n a) Source # 
Instance details

Defined in DiffLoc.Index

Associated Types

type Trans (IndexFrom n a) Source #

Methods

(.+) :: IndexFrom n a -> Trans (IndexFrom n a) -> IndexFrom n a Source #

(.-.?) :: IndexFrom n a -> IndexFrom n a -> Maybe (Trans (IndexFrom n a)) Source #

Amor (f x) => Amor (f :$: x) Source # 
Instance details

Defined in DiffLoc.Starter

Associated Types

type Trans (f :$: x) Source #

Methods

(.+) :: (f :$: x) -> Trans (f :$: x) -> f :$: x Source #

(.-.?) :: (f :$: x) -> (f :$: x) -> Maybe (Trans (f :$: x)) Source #

class Amor p => Origin p where Source #

Extend Amor with an "origin" point from which vectors can be drawn to all points. To make the interface slightly more general, only the partial application (origin .-.) needs to be supplied.

Laws:

origin <= x

Methods

origin :: p Source #

Instances

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

Defined in DiffLoc.Colline

Methods

origin :: Colline l c Source #

(Num a, Ord a, KnownNat n) => Origin (IndexFrom n a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

origin :: IndexFrom n a Source #

Origin (f x) => Origin (f :$: x) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

origin :: f :$: x Source #

fromOrigin :: Origin p => p -> Trans p Source #

Find the vector from the origin to this point.

x <= y   =   fromOrigin x <= fromOrigin y

ofOrigin (fromOrigin x) = x
fromOrigin (ofOrigin v) = v

fromOrigin (x .+ v)  =   fromOrigin x <> v

ofOrigin :: Origin p => Trans p -> p Source #

Translate the origin along a vector.

x <= y   =   ofOrigin x <= ofOrigin y

ofOrigin x .+ v             =   ofOrigin (x .+ v)
ofOrigin x .-. ofOrigin y   =   x .-. y