Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data (a1 :> a2) wX wY = forall wZ. (a1 wX wZ) :> (a2 wZ wY)
- data FL a wX wZ where
- data RL a wX wZ where
- data (a1 :\/: a2) wX wY = forall wZ. (a1 wZ wX) :\/: (a2 wZ wY)
- data (a3 :/\: a4) wX wY = forall wZ. (a3 wX wZ) :/\: (a4 wY wZ)
- data (a1 :||: a2) wX wY = (a1 wX wY) :||: (a2 wX wY)
- data Fork common left right wA wX wY = forall wU. Fork (common wA wU) (left wU wX) (right wU wY)
- nullFL :: FL a wX wZ -> Bool
- nullRL :: RL a wX wZ -> Bool
- lengthFL :: FL a wX wZ -> Int
- lengthRL :: RL a wX wZ -> Int
- mapFL :: (forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
- mapRL :: (forall wW wZ. a wW wZ -> b) -> RL a wX wY -> [b]
- mapFL_FL :: (forall wW wY. a wW wY -> b wW wY) -> FL a wX wZ -> FL b wX wZ
- mapRL_RL :: (forall wW wY. a wW wY -> b wW wY) -> RL a wX wZ -> RL b wX wZ
- foldrFL :: (forall wA wB. p wA wB -> r -> r) -> FL p wX wY -> r -> r
- foldlRL :: (forall wA wB. r -> p wA wB -> r) -> r -> RL p wX wY -> r
- foldrwFL :: (forall wA wB. p wA wB -> r wB -> r wA) -> FL p wX wY -> r wY -> r wX
- foldlwRL :: (forall wA wB. p wA wB -> r wA -> r wB) -> RL p wX wY -> r wX -> r wY
- foldlwFL :: (forall wA wB. p wA wB -> r wA -> r wB) -> FL p wX wY -> r wX -> r wY
- foldrwRL :: (forall wA wB. p wA wB -> r wB -> r wA) -> RL p wX wY -> r wY -> r wX
- allFL :: (forall wX wY. a wX wY -> Bool) -> FL a wW wZ -> Bool
- allRL :: (forall wA wB. a wA wB -> Bool) -> RL a wX wY -> Bool
- anyFL :: (forall wX wY. a wX wY -> Bool) -> FL a wW wZ -> Bool
- anyRL :: (forall wA wB. a wA wB -> Bool) -> RL a wX wY -> Bool
- filterFL :: (forall wX wY. a wX wY -> Bool) -> FL a wW wZ -> [Sealed2 a]
- filterRL :: (forall wX wY. p wX wY -> Bool) -> RL p wA wB -> [Sealed2 p]
- foldFL_M :: Monad m => (forall wA wB. r wA -> p wA wB -> m (r wB)) -> r wX -> FL p wX wY -> m (r wY)
- foldRL_M :: Monad m => (forall wA wB. p wA wB -> r wB -> m (r wA)) -> RL p wX wY -> r wY -> m (r wX)
- splitAtFL :: Int -> FL a wX wZ -> (FL a :> FL a) wX wZ
- splitAtRL :: Int -> RL a wX wZ -> (RL a :> RL a) wX wZ
- filterOutFLFL :: (forall wX wY. p wX wY -> EqCheck wX wY) -> FL p wW wZ -> FL p wW wZ
- filterOutRLRL :: (forall wX wY. p wX wY -> EqCheck wX wY) -> RL p wW wZ -> RL p wW wZ
- reverseFL :: FL a wX wZ -> RL a wX wZ
- reverseRL :: RL a wX wZ -> FL a wX wZ
- (+>+) :: FL a wX wY -> FL a wY wZ -> FL a wX wZ
- (+<+) :: RL a wX wY -> RL a wY wZ -> RL a wX wZ
- (+>>+) :: RL p wX wY -> FL p wY wZ -> FL p wX wZ
- (+<<+) :: RL p wX wY -> FL p wY wZ -> RL p wX wZ
- concatFL :: FL (FL a) wX wZ -> FL a wX wZ
- concatRL :: RL (RL a) wX wZ -> RL a wX wZ
- dropWhileFL :: (forall wX wY. a wX wY -> Bool) -> FL a wR wV -> FlippedSeal (FL a) wV
- dropWhileRL :: (forall wX wY. a wX wY -> Bool) -> RL a wR wV -> Sealed (RL a wR)
- bunchFL :: Int -> FL a wX wY -> FL (FL a) wX wY
- spanFL :: (forall wW wY. a wW wY -> Bool) -> FL a wX wZ -> (FL a :> FL a) wX wZ
- spanFL_M :: forall a m wX wZ. Monad m => (forall wW wY. a wW wY -> m Bool) -> FL a wX wZ -> m ((FL a :> FL a) wX wZ)
- zipWithFL :: (forall wX wY. a -> p wX wY -> q wX wY) -> [a] -> FL p wW wZ -> FL q wW wZ
- consGapFL :: Gap w => (forall wX wY. p wX wY) -> w (FL p) -> w (FL p)
- concatGapsFL :: Gap w => [w (FL p)] -> w (FL p)
- joinGapsFL :: Gap w => [w p] -> w (FL p)
- mapFL_FL_M :: Monad m => (forall wW wY. a wW wY -> m (b wW wY)) -> FL a wX wZ -> m (FL b wX wZ)
- sequenceFL_ :: Monad m => (forall wW wZ. a wW wZ -> m b) -> FL a wX wY -> m ()
- initsFL :: FL p wX wY -> [Sealed ((p :> FL p) wX)]
- isShorterThanRL :: RL a wX wY -> Int -> Bool
- spanRL :: (forall wA wB. p wA wB -> Bool) -> RL p wX wY -> (RL p :> RL p) wX wY
- breakRL :: (forall wA wB. p wA wB -> Bool) -> RL p wX wY -> (RL p :> RL p) wX wY
- takeWhileRL :: (forall wA wB. a wA wB -> Bool) -> RL a wX wY -> FlippedSeal (RL a) wY
- concatRLFL :: RL (FL p) wX wY -> RL p wX wY
Directed Types
Darcs patches have a notion of transforming between contexts. This naturally leads us to container types that are "directed" and transform from one context to another.
For example, the swap of names of files x and y could be represented with the following sequence of patches:
Move x z:>
Move y x:>
Move z y
or using forward lists, like
Move x z:>:
Move y x:>:
Move z y:>:
NilFL
data (a1 :> a2) wX wY infixr 1 Source #
Directed Forward Pairs
forall wZ. (a1 wX wZ) :> (a2 wZ wY) infixr 1 |
Instances
Ident p => Ident (p :> p) Source # | |
Invert p => Invert (p :> p) Source # | |
(Eq2 a, Eq2 b) => Eq2 (a :> b) Source # | |
(Show2 a, Show2 b) => Show2 (a :> b) Source # | |
Defined in Darcs.Patch.Witnesses.Ordered | |
(Show2 a, Show2 b) => Show1 ((a :> b) wX) Source # | |
(Show2 a, Show2 b) => Show ((a :> b) wX wY) Source # | |
(Eq2 a, Eq2 b) => Eq ((a :> b) wX wY) Source # | |
type PatchId (p :> p) Source # | |
Defined in Darcs.Patch.Ident |
data FL a wX wZ where Source #
Forward lists
Instances
data RL a wX wZ where Source #
Reverse lists
Instances
Merge Types
When we have two patches which commute and share the same pre-context we can
merge the patches. Whenever patches, or sequences of patches, share a
pre-context we say they are Forking Pairs (:\/:
). The same way, when
patches or sequences of patches, share a post-context we say they are
Joining Pairs (:/\:
).
The following diagram shows the symmetry of merge types:
wZ:/\:
a3 / \ a4 / \ wX wY \ / a1 \ / a2:\/:
wZ
data (a1 :\/: a2) wX wY infix 1 Source #
Forking Pairs (Implicit starting context)
forall wZ. (a1 wZ wX) :\/: (a2 wZ wY) infix 1 |
data (a3 :/\: a4) wX wY infix 1 Source #
Joining Pairs
forall wZ. (a3 wX wZ) :/\: (a4 wY wZ) infix 1 |
data Fork common left right wA wX wY Source #
Forking Pair (Explicit starting context)
wX wY \ / \ / \ / wU | | | wA
forall wU. Fork (common wA wU) (left wU wX) (right wU wY) |
Functions for FL
s and RL
s
foldlRL :: (forall wA wB. r -> p wA wB -> r) -> r -> RL p wX wY -> r Source #
The "natural" fold over an RL i.e. associating to the left.
foldlwFL :: (forall wA wB. p wA wB -> r wA -> r wB) -> FL p wX wY -> r wX -> r wY Source #
Strict left associative fold for FL
s that transforms a witnessed state
in the direction of the patches. This is for apply-like functions that
transform the witnesses in forward direction.
foldrwRL :: (forall wA wB. p wA wB -> r wB -> r wA) -> RL p wX wY -> r wY -> r wX Source #
Strict right associative fold for RL
s that transforms a witnessed state
in the opposite direction of the patches. This is for unapply-like functions
that transform the witnesses in backward direction.
foldFL_M :: Monad m => (forall wA wB. r wA -> p wA wB -> m (r wB)) -> r wX -> FL p wX wY -> m (r wY) Source #
Monadic fold over an FL
associating to the left, sequencing
effects from left to right.
The order of arguments follows the standard foldM
from base.
foldRL_M :: Monad m => (forall wA wB. p wA wB -> r wB -> m (r wA)) -> RL p wX wY -> r wY -> m (r wX) Source #
Monadic fold over an FL
associating to the right, sequencing
effects from right to left.
Mostly useful for prepend-like operations with an effect where the
order of effects is not relevant.
filterOutFLFL :: (forall wX wY. p wX wY -> EqCheck wX wY) -> FL p wW wZ -> FL p wW wZ Source #
filterOutFLFL p xs
deletes any x
in xs
for which p x == IsEq
(indicating that x
has no effect as far as we are concerned, and can be
safely removed from the chain)
(+>+) :: FL a wX wY -> FL a wY wZ -> FL a wX wZ infixr 5 Source #
Concatenate two FL
s. This traverses only the left hand side.
(+<+) :: RL a wX wY -> RL a wY wZ -> RL a wX wZ infixl 5 Source #
Concatenate two RL
s. This traverses only the right hand side.
dropWhileFL :: (forall wX wY. a wX wY -> Bool) -> FL a wR wV -> FlippedSeal (FL a) wV Source #
FL
only
spanFL_M :: forall a m wX wZ. Monad m => (forall wW wY. a wW wY -> m Bool) -> FL a wX wZ -> m ((FL a :> FL a) wX wZ) Source #
joinGapsFL :: Gap w => [w p] -> w (FL p) Source #
mapFL_FL_M :: Monad m => (forall wW wY. a wW wY -> m (b wW wY)) -> FL a wX wZ -> m (FL b wX wZ) Source #
sequenceFL_ :: Monad m => (forall wW wZ. a wW wZ -> m b) -> FL a wX wY -> m () Source #
RL
only
takeWhileRL :: (forall wA wB. a wA wB -> Bool) -> RL a wX wY -> FlippedSeal (RL a) wY Source #