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

DiffLoc.Starter

Description

Basic configurations to get started.

Synopsis

The heavy lifter

type Diff p = ADiff (Replace p) Source #

A shorthand for the common use case of Diff.

Basic index types

type Z = Plain :$: Int Source #

Integers.

type N = IndexFrom 0 :$: Int Source #

Natural numbers.

type N' = IndexFrom 1 :$: Int Source #

Positive numbers.

Under the hood

newtype f :$: x Source #

A trick to reduce noise by hiding newtype wrapper constructors. This makes the documentation more palatable.

>>> show (NoShow (Plain 3) :: Plain :$: Int)
"3"
>>> show (Colline 4 2 :.. Vallee (offset 3) (offset 3) :: Interval (Colline N N))
"Colline 4 2 :.. Vallee (offset 3) (offset 3)"

Constructors

NoShow (f x) 

Instances

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

Defined in DiffLoc.Starter

Methods

mempty :: f :$: x #

mappend :: (f :$: x) -> (f :$: x) -> f :$: x #

mconcat :: [f :$: x] -> f :$: x #

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

Defined in DiffLoc.Starter

Methods

(<>) :: (f :$: x) -> (f :$: x) -> f :$: x #

sconcat :: NonEmpty (f :$: x) -> f :$: x #

stimes :: Integral b => b -> (f :$: x) -> f :$: x #

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

Defined in DiffLoc.Starter

Methods

(+) :: (IndexFrom n :$: a) -> (IndexFrom n :$: a) -> IndexFrom n :$: a #

(-) :: (IndexFrom n :$: a) -> (IndexFrom n :$: a) -> IndexFrom n :$: a #

(*) :: (IndexFrom n :$: a) -> (IndexFrom n :$: a) -> IndexFrom n :$: a #

negate :: (IndexFrom n :$: a) -> IndexFrom n :$: a #

abs :: (IndexFrom n :$: a) -> IndexFrom n :$: a #

signum :: (IndexFrom n :$: a) -> IndexFrom n :$: a #

fromInteger :: Integer -> IndexFrom n :$: a #

(Num a, Ord a) => Num (Offset :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

(+) :: (Offset :$: a) -> (Offset :$: a) -> Offset :$: a #

(-) :: (Offset :$: a) -> (Offset :$: a) -> Offset :$: a #

(*) :: (Offset :$: a) -> (Offset :$: a) -> Offset :$: a #

negate :: (Offset :$: a) -> Offset :$: a #

abs :: (Offset :$: a) -> Offset :$: a #

signum :: (Offset :$: a) -> Offset :$: a #

fromInteger :: Integer -> Offset :$: a #

Num a => Num (Plain :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

(+) :: (Plain :$: a) -> (Plain :$: a) -> Plain :$: a #

(-) :: (Plain :$: a) -> (Plain :$: a) -> Plain :$: a #

(*) :: (Plain :$: a) -> (Plain :$: a) -> Plain :$: a #

negate :: (Plain :$: a) -> Plain :$: a #

abs :: (Plain :$: a) -> Plain :$: a #

signum :: (Plain :$: a) -> Plain :$: a #

fromInteger :: Integer -> Plain :$: a #

Show a => Show (IndexFrom n :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

showsPrec :: Int -> (IndexFrom n :$: a) -> ShowS #

show :: (IndexFrom n :$: a) -> String #

showList :: [IndexFrom n :$: a] -> ShowS #

Show a => Show (Offset :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

showsPrec :: Int -> (Offset :$: a) -> ShowS #

show :: (Offset :$: a) -> String #

showList :: [Offset :$: a] -> ShowS #

Show a => Show (Plain :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

showsPrec :: Int -> (Plain :$: a) -> ShowS #

show :: (Plain :$: a) -> String #

showList :: [Plain :$: a] -> ShowS #

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 #

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

Defined in DiffLoc.Starter

Methods

origin :: f :$: x Source #

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

Defined in DiffLoc.Starter

Methods

(==) :: (f :$: x) -> (f :$: x) -> Bool #

(/=) :: (f :$: x) -> (f :$: x) -> Bool #

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

Defined in DiffLoc.Starter

Methods

compare :: (f :$: x) -> (f :$: x) -> Ordering #

(<) :: (f :$: x) -> (f :$: x) -> Bool #

(<=) :: (f :$: x) -> (f :$: x) -> Bool #

(>) :: (f :$: x) -> (f :$: x) -> Bool #

(>=) :: (f :$: x) -> (f :$: x) -> Bool #

max :: (f :$: x) -> (f :$: x) -> f :$: x #

min :: (f :$: x) -> (f :$: x) -> f :$: x #

type Trans (f :$: x) Source # 
Instance details

Defined in DiffLoc.Starter

type Trans (f :$: x) = Trans (f x)