#include "gadts.h"
module Darcs.Patch.Set ( PatchSet(..), Tagged(..), SealedPatchSet, Origin,
                         progressPatchSet, tags, appendPSFL,
                         newset2RL, newset2FL ) where
import Progress ( progress )
import Darcs.Patch.Info ( PatchInfo )
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info )
import Darcs.Witnesses.Ordered ( FL, RL(..), (+<+), reverseFL,
                                 reverseRL, mapRL_RL, concatRL, mapRL )
import Darcs.Witnesses.Sealed ( Sealed )
data Origin
type SealedPatchSet p C(start) = Sealed ((PatchSet p) C(start))
data PatchSet p C(start y) where
    PatchSet :: RL (PatchInfoAnd p) C(x y) -> RL (Tagged p) C(start x) -> PatchSet p C(start y)
data Tagged p C(x z) where
    Tagged :: PatchInfoAnd p C(y z) -> Maybe String
           -> RL (PatchInfoAnd p) C(x y) -> Tagged p C(x z)
newset2RL :: PatchSet p C(start x) -> RL (PatchInfoAnd p) C(start x)
newset2RL (PatchSet ps ts) = ps +<+ concatRL (mapRL_RL ts2rl ts)
    where ts2rl :: Tagged p C(y z) -> RL (PatchInfoAnd p) C(y z)
          ts2rl (Tagged t _ ps2) = t :<: ps2
newset2FL :: PatchSet p C(start x) -> FL (PatchInfoAnd p) C(start x)
newset2FL = reverseRL . newset2RL
appendPSFL :: PatchSet p C(start x) -> FL (PatchInfoAnd p) C(x y)
           -> PatchSet p C(start y)
appendPSFL (PatchSet ps ts) newps = PatchSet (reverseFL newps +<+ ps) ts
progressPatchSet :: String -> PatchSet p C(start x) -> PatchSet p C(start x)
progressPatchSet k (PatchSet ps0 ts0) = PatchSet (mapRL_RL prog ps0) $ mapRL_RL pts ts0
    where prog = progress k
          pts :: Tagged p C(y z) -> Tagged p C(y z)
          pts (Tagged t h ps) = Tagged (prog t) h (mapRL_RL prog ps)
tags :: PatchSet p C(start x) -> [PatchInfo]
tags (PatchSet _ ts) = mapRL f ts
    where f :: Tagged p C(y z) -> PatchInfo
          f (Tagged t _ _) = info t