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

DiffLoc.Index

Description

Indices and offsets.

Synopsis

One-dimensional indices

Unbounded indices

newtype Plain a Source #

One-dimensional indices.

Constructors

Plain a 

Instances

Instances details
Show a => Show (Plain a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

showsPrec :: Int -> Plain a -> ShowS #

show :: Plain a -> String #

showList :: [Plain a] -> ShowS #

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

Eq a => Eq (Plain a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

(==) :: Plain a -> Plain a -> Bool #

(/=) :: Plain a -> Plain a -> Bool #

Ord a => Ord (Plain a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

compare :: Plain a -> Plain a -> Ordering #

(<) :: Plain a -> Plain a -> Bool #

(<=) :: Plain a -> Plain a -> Bool #

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

(>=) :: Plain a -> Plain a -> Bool #

max :: Plain a -> Plain a -> Plain a #

min :: Plain a -> Plain a -> Plain 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 (Plain :$: a) Source # 
Instance details

Defined in DiffLoc.Starter

Methods

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

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

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

type Trans (Plain a) Source # 
Instance details

Defined in DiffLoc.Index

type Trans (Plain a) = Offset a

Indices bounded by an origin

data IndexFrom (n :: Nat) a Source #

One-dimensional indices with an origin (an initial index). Indices must be greater than the origin, hence the constructor is hidden.

Use indexFromM to construct indices, with TypeApplications to make the indexing scheme explicit, and fromIndex to destruct them.

(origin :: IndexFrom n a) <= i    -- for all i

Instances

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

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

Defined in DiffLoc.Index

Methods

showsPrec :: Int -> IndexFrom n a -> ShowS #

show :: IndexFrom n a -> String #

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

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 #

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

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

Defined in DiffLoc.Index

Methods

origin :: IndexFrom n a Source #

Eq a => Eq (IndexFrom n a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

(==) :: IndexFrom n a -> IndexFrom n a -> Bool #

(/=) :: IndexFrom n a -> IndexFrom n a -> Bool #

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

Defined in DiffLoc.Index

Methods

compare :: IndexFrom n a -> IndexFrom n a -> Ordering #

(<) :: IndexFrom n a -> IndexFrom n a -> Bool #

(<=) :: IndexFrom n a -> IndexFrom n a -> Bool #

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

(>=) :: IndexFrom n a -> IndexFrom n a -> Bool #

max :: IndexFrom n a -> IndexFrom n a -> IndexFrom n a #

min :: IndexFrom n a -> IndexFrom n a -> IndexFrom n a #

type Trans (IndexFrom n a) Source # 
Instance details

Defined in DiffLoc.Index

type Trans (IndexFrom n a) = Trans (Plain a)

indexFromM :: forall n a. (KnownNat n, Num a, Ord a) => a -> Maybe (IndexFrom n a) Source #

Constructor for IndexFrom.

See also indexFrom in DiffLoc.Unsafe, a variant of indexFromM that throws errors instead of using Maybe.

indexFromM0 :: forall a. (Num a, Ord a) => a -> Maybe (IndexFrom 0 a) Source #

indexFromM specialized to 0-indexing.

indexFromM1 :: forall a. (Num a, Ord a) => a -> Maybe (IndexFrom 1 a) Source #

indexFromM specialized to 1-indexing.

fromIndex :: forall n a. IndexFrom n a -> a Source #

Destructor for IndexFrom.

fromIndex0 :: IndexFrom 0 a -> a Source #

fromIndex specialized to 0-indexing.

fromIndex1 :: IndexFrom 1 a -> a Source #

fromIndex specialized to 1-indexing.

zeroIndex :: Num a => IndexFrom 1 a -> IndexFrom 0 a Source #

Convert from one-indexing to zero-indexing.

oneIndex :: Num a => IndexFrom 0 a -> IndexFrom 1 a Source #

Convert from zero-indexing to one-indexing.

Offsets

data Offset a Source #

Type of nonnegative offsets.

Instances

Instances details
Num a => Monoid (Offset a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

mempty :: Offset a #

mappend :: Offset a -> Offset a -> Offset a #

mconcat :: [Offset a] -> Offset a #

Num a => Semigroup (Offset a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

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

sconcat :: NonEmpty (Offset a) -> Offset a #

stimes :: Integral b => b -> Offset a -> Offset a #

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

Defined in DiffLoc.Index

Methods

showsPrec :: Int -> Offset a -> ShowS #

show :: Offset a -> String #

showList :: [Offset a] -> ShowS #

Eq a => Eq (Offset a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

(==) :: Offset a -> Offset a -> Bool #

(/=) :: Offset a -> Offset a -> Bool #

Ord a => Ord (Offset a) Source # 
Instance details

Defined in DiffLoc.Index

Methods

compare :: Offset a -> Offset a -> Ordering #

(<) :: Offset a -> Offset a -> Bool #

(<=) :: Offset a -> Offset a -> Bool #

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

(>=) :: Offset a -> Offset a -> Bool #

max :: Offset a -> Offset a -> Offset a #

min :: Offset a -> Offset a -> Offset 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 #

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 #

offsetM :: (Num a, Ord a) => a -> Maybe (Offset a) Source #

Construct a nonnegative Offset.

See also offset in DiffLoc.Unsafe, a variant of offsetM that throws errors instead of using Maybe.

fromOffset :: Offset a -> a Source #

Unwrap Offset.