David,

I have more type witnesses coming up, but I'm finally done screwing up and
fixing Darcs.Repository.Internal so I thought I'd send it your way for a
review :)

Jason

Thu Aug  7 18:53:43 PDT 2008  Jason Dagit <[EMAIL PROTECTED]>
  * Make Darcs.Repository.Internal compile with type witnesses.

Thu Aug  7 19:30:25 PDT 2008  Jason Dagit <[EMAIL PROTECTED]>
  * fixed a bug in identity_commutes property
  In the right identity check the patch order should have gone from
  (identity :> p) to (p2 :> i2).  I added a rigid type context too
  so that ghc 6.8 and newer would type the definition.

New patches:

[Make Darcs.Repository.Internal compile with type witnesses.
Jason Dagit <[EMAIL PROTECTED]>**20080808015343] hunk ./GNUmakefile 119
-	src/Darcs/Repository/Pristine.hi src/Darcs/Repository/DarcsRepo.hi
+	src/Darcs/Repository/Pristine.hi src/Darcs/Repository/DarcsRepo.hi \
+	src/Darcs/Repository/Internal.hi
hunk ./src/Darcs/Commands/Annotate.lhs 24
-import Control.Monad ( when )
+import Control.Monad ( when, liftM )
hunk ./src/Darcs/Commands/Annotate.lhs 56
-import Darcs.Sealed ( Sealed(..), liftSM )
hunk ./src/Darcs/Commands/Annotate.lhs 119
-  p <- match_patch opts `liftSM` read_repo repository
+  p <- match_patch opts `liftM` read_repo repository
hunk ./src/Darcs/Commands/Annotate.lhs 155
-  Sealed r <- read_repo repository
+  r <- read_repo repository
hunk ./src/Darcs/Commands/Annotate.lhs 305
-  old_pis <- (dropWhile (/= pinfo).mapRL info.concatRL) `liftSM` read_repo repository
+  old_pis <- (dropWhile (/= pinfo).mapRL info.concatRL) `liftM` read_repo repository
hunk ./src/Darcs/Commands/Apply.lhs 126
-  Sealed us <- read_repo repository
+  us <- read_repo repository
hunk ./src/Darcs/Commands/Apply.lhs 161
-    pw <- tentativelyMergePatches repository "apply" opts
-          (reverseRL $ head $ unsafeUnRL us') to_be_applied
+    Sealed pw <- tentativelyMergePatches repository "apply" opts
+                 (reverseRL $ head $ unsafeUnRL us') to_be_applied
hunk ./src/Darcs/Commands/Changes.lhs 66
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Changes.lhs 121
-  Sealed patches <- read_repo repository
+  patches <- read_repo repository
hunk ./src/Darcs/Commands/Changes.lhs 131
-            Sealed ps <- read_repo repository
+            ps <- read_repo repository
hunk ./src/Darcs/Commands/Changes.lhs 263
-  Sealed r <- read_repo repository
+  r <- read_repo repository
hunk ./src/Darcs/Commands/Check.lhs 47
-import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal )
+import Darcs.Sealed ( unsafeUnflippedseal )
hunk ./src/Darcs/Commands/Check.lhs 104
-  Sealed patches <- read_repo repository -- FIXME: This should be lazy!
+  patches <- read_repo repository -- FIXME: This should be lazy!
hunk ./src/Darcs/Commands/Check.lhs 153
-       Sealed r <- read_repo repository
+       r <- read_repo repository
hunk ./src/Darcs/Commands/Convert.lhs 59
-import Darcs.Sealed ( Sealed(..), FlippedSeal(..) )
+import Darcs.Sealed ( FlippedSeal(..) )
hunk ./src/Darcs/Commands/Convert.lhs 135
-      Sealed theirstuff <- read_repo themrepo
+      theirstuff <- read_repo themrepo
hunk ./src/Darcs/Commands/Diff.lhs 54
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Diff.lhs 206
-    Sealed morepatches <- read_repo repository
+    morepatches <- read_repo repository
hunk ./src/Darcs/Commands/Get.lhs 255
-       Sealed patches <- read_repo repository
+       patches <- read_repo repository
hunk ./src/Darcs/Commands/Get.lhs 301
-  Sealed patches <- read_repo fromrepo
+  patches <- read_repo fromrepo
hunk ./src/Darcs/Commands/MarkConflicts.lhs 76
-  Sealed r <- read_repo repository
+  r <- read_repo repository
hunk ./src/Darcs/Commands/Optimize.lhs 58
-import Darcs.Sealed ( Sealed(..), FlippedSeal(..), unsafeUnseal, liftSM )
+import Darcs.Sealed ( FlippedSeal(..), unsafeUnseal )
hunk ./src/Darcs/Commands/Optimize.lhs 161
-get_tag [] r = do Sealed ps <- read_repo r
+get_tag [] r = do ps <- read_repo r
hunk ./src/Darcs/Commands/Optimize.lhs 167
-    do Sealed ps <- read_repo r
+    do ps <- read_repo r
hunk ./src/Darcs/Commands/Optimize.lhs 302
-    psnew <- choose_order `liftSM` read_repo repository
+    psnew <- choose_order `liftM` read_repo repository
hunk ./src/Darcs/Commands/Pull.lhs 127
-  Sealed us <- read_repo repository
+  us <- read_repo repository
hunk ./src/Darcs/Commands/Pull.lhs 156
-      pw <- tentativelyMergePatches repository "pull" merge_opts
-                 (reverseRL $ head $ unsafeUnRL us') to_be_pulled
+      Sealed pw <- tentativelyMergePatches repository "pull" merge_opts
+                   (reverseRL $ head $ unsafeUnRL us') to_be_pulled
hunk ./src/Darcs/Commands/Pull.lhs 196
-    do rs <- mapM (\u -> identifyRepositoryFor to_repo u >>= read_repo) us
+    do rs <- mapM (\u -> do r <- identifyRepositoryFor to_repo u
+                            ps <- read_repo r
+                            return $ seal ps) us
hunk ./src/Darcs/Commands/Push.lhs 52
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Push.lhs 127
-  Sealed them <- identifyRepositoryFor repository repodir >>= read_repo
+  them <- identifyRepositoryFor repository repodir >>= read_repo
hunk ./src/Darcs/Commands/Push.lhs 133
-  Sealed us <- read_repo repository
+  us <- read_repo repository
hunk ./src/Darcs/Commands/Put.lhs 33
-import Darcs.Sealed ( Sealed(..), seal )
hunk ./src/Darcs/Commands/Put.lhs 103
-  Sealed patchset <- if have_patchset_match opts
-                       then do ps <- get_one_patchset repository opts  -- todo: make sure get_one_patchset has the right type
-                               return . seal $ ps
-                       else read_repo repository
-  Sealed patchset2 <- if have_patchset_match opts
-                       then do ps <- get_one_patchset repository opts  -- todo: make sure get_one_patchset has the right type
-                               return . seal $ ps
-                       else read_repo repository
+  patchset <- if have_patchset_match opts
+              then get_one_patchset repository opts  -- todo: make sure get_one_patchset has the right type
+              else read_repo repository
+  patchset2 <- if have_patchset_match opts
+               then get_one_patchset repository opts  -- todo: make sure get_one_patchset has the right type
+               else read_repo repository
hunk ./src/Darcs/Commands/Record.lhs 66
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Record.lhs 389
-  Sealed pps <- read_repo repository
+  pps <- read_repo repository
hunk ./src/Darcs/Commands/Repair.lhs 44
-import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal )
+import Darcs.Sealed ( unsafeUnflippedseal )
hunk ./src/Darcs/Commands/Repair.lhs 96
-                Sealed patches <- read_repo repository
+                patches <- read_repo repository
hunk ./src/Darcs/Commands/Repair.lhs 102
-                      Sealed rawpatches <- read_repo repository
+                      rawpatches <- read_repo repository
hunk ./src/Darcs/Commands/Rollback.lhs 118
-  Sealed allpatches <- read_repo repository
+  allpatches <- read_repo repository
hunk ./src/Darcs/Commands/Rollback.lhs 139
-            pw <- tentativelyMergePatches repository "rollback" (MarkConflicts : opts)
-                  NilFL (rbp :>: NilFL)
+            Sealed pw <- tentativelyMergePatches repository "rollback" (MarkConflicts : opts)
+                         NilFL (rbp :>: NilFL)
hunk ./src/Darcs/Commands/Send.lhs 66
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Send.lhs 149
-        Sealed them <- read_repo repo
+        them <- read_repo repo
hunk ./src/Darcs/Commands/Send.lhs 172
-  Sealed us <- read_repo repo
+  us <- read_repo repo
hunk ./src/Darcs/Commands/ShowAuthors.lhs 31
-import Darcs.Sealed ( unsafeUnseal )
hunk ./src/Darcs/Commands/ShowAuthors.lhs 68
-  let authors = mapRL process $ concatRL $ unsafeUnseal patches
+  let authors = mapRL process $ concatRL patches
hunk ./src/Darcs/Commands/ShowRepo.lhs 53
-import Darcs.Sealed ( unsealM )
hunk ./src/Darcs/Commands/ShowRepo.lhs 192
-numPatches r = read_repo r `unsealM` (return . sum . unsafeUnRL . mapRL_RL lengthRL)
+numPatches r = read_repo r >>= (return . sum . unsafeUnRL . mapRL_RL lengthRL)
hunk ./src/Darcs/Commands/ShowTags.lhs 27
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/ShowTags.lhs 68
-  Sealed patches <- read_repo repository
+  patches <- read_repo repository
hunk ./src/Darcs/Commands/Tag.lhs 21
-import Control.Monad ( when )
+import Control.Monad ( when, liftM )
hunk ./src/Darcs/Commands/Tag.lhs 35
-import Darcs.Sealed ( liftSM )
hunk ./src/Darcs/Commands/Tag.lhs 79
-    deps <- get_tags_right `liftSM` read_repo repository
+    deps <- get_tags_right `liftM` read_repo repository
hunk ./src/Darcs/Commands/TrackDown.lhs 35
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/TrackDown.lhs 78
-  Sealed patches <- read_repo repository
+  patches <- read_repo repository
hunk ./src/Darcs/Commands/Unrecord.lhs 51
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/Darcs/Commands/Unrecord.lhs 157
-  Sealed allpatches <- read_repo repository
+  allpatches <- read_repo repository
hunk ./src/Darcs/Commands/Unrecord.lhs 312
-  Sealed allpatches <- read_repo repository
+  allpatches <- read_repo repository
hunk ./src/Darcs/Commands/Unrevert.lhs 89
-  Sealed us <- read_repo repository
+  us <- read_repo repository
hunk ./src/Darcs/Commands/Unrevert.lhs 95
-      pw <- considerMergeToWorking repository "pull" (MarkConflicts:opts)
-                 (reverseRL $ headRL us') (reverseRL $ headRL them')
+      Sealed pw <- considerMergeToWorking repository "pull" (MarkConflicts:opts)
+                   (reverseRL $ headRL us') (reverseRL $ headRL them')
hunk ./src/Darcs/Commands/Unrevert.lhs 124
-        Sealed rep <- read_repo repository
+        rep <- read_repo repository
hunk ./src/Darcs/HopefullyPrivate.lhs 178
-instance Conflict (p C(x y)) => Conflict (PatchInfoAnd (p C(x y))) where
+instance Conflict p => Conflict (PatchInfoAnd p) where
hunk ./src/Darcs/HopefullyPrivate.lhs 185
-instance RepoPatch (p C(x y)) => Patchy (PatchInfoAnd (p C(x y)))
+instance RepoPatch p => Patchy (PatchInfoAnd p)
hunk ./src/Darcs/Match.lhs 59
-import Darcs.Sealed ( Sealed(..), FlippedSeal(..), unsafeUnseal, unsealM )
+import Darcs.Sealed ( FlippedSeal(..), unsafeUnseal )
hunk ./src/Darcs/Match.lhs 270
-        Just m -> do Sealed ps <- read_repo repository
+        Just m -> do ps <- read_repo repository
hunk ./src/Darcs/Match.lhs 351
-get_matcher r m = do Sealed repo <- read_repo r
+get_matcher r m = do repo <- read_repo r
hunk ./src/Darcs/Match.lhs 359
-    do Sealed repo <- read_repo r
+    do repo <- read_repo r
hunk ./src/Darcs/Match.lhs 403
-    Sealed repo <- read_repo r
+    repo <- read_repo r
hunk ./src/Darcs/Match.lhs 459
-                   read_repo r `unsealM` (apply_patches [] . invertRL . safetake n . concatRL)
+                   read_repo r >>= (apply_patches [] . invertRL . safetake n . concatRL)
hunk ./src/Darcs/Match.lhs 471
-    Sealed ps <- read_repo r
+    ps <- read_repo r
hunk ./src/Darcs/Patch/Ordered.lhs 27
-                             splitAtFL, bunchFL, foldlRL,
+                             splitAtFL, bunchFL, foldlRL, dropWhileFL, dropWhileRL,
hunk ./src/Darcs/Patch/Ordered.lhs 33
-                             unsafeCoerceP
+                             consFLSealed, consRLSealed,
+                             unsafeCoerceP, unsafeCoerceP2
hunk ./src/Darcs/Patch/Ordered.lhs 40
-import Darcs.Sealed ( FlippedSeal(..), flipSeal )
+import Darcs.Sealed ( Sealed(..), seal, FlippedSeal(..), flipSeal )
hunk ./src/Darcs/Patch/Ordered.lhs 85
+unsafeCoerceP2 :: t C(w x y z) -> t C(a b c d)
+unsafeCoerceP2 = unsafeCoerce#
+
hunk ./src/Darcs/Patch/Ordered.lhs 244
+dropWhileFL :: (FORALL(x y) a C(x y) -> Bool) -> FL a C(r v) -> FlippedSeal (FL a) C(v)
+dropWhileFL _ NilFL       = flipSeal NilFL
+dropWhileFL p xs@(x:>:xs')
+              | p x       = dropWhileFL p xs'
+              | otherwise = flipSeal xs
+
+dropWhileRL :: (FORALL(x y) a C(x y) -> Bool) -> RL a C(r v) -> Sealed (RL a C(r))
+dropWhileRL _ NilRL = seal NilRL
+dropWhileRL p xs@(x:<:xs')
+              | p x       = dropWhileRL p xs'
+              | otherwise = seal xs
+
+consFLSealed :: a C(x y) -> Sealed (FL a C(y)) -> Sealed (FL a C(x))
+consFLSealed a (Sealed as) = seal $ a :>: as
+
+consRLSealed :: a C(y z) -> FlippedSeal (RL a) C(y) -> FlippedSeal (RL a) C(z)
+consRLSealed a (FlippedSeal as) = flipSeal $ a :<: as
+
hunk ./src/Darcs/Population.lhs 44
-import Darcs.Sealed ( liftSM )
hunk ./src/Darcs/Population.lhs 49
+import Control.Monad ( liftM )
hunk ./src/Darcs/Population.lhs 95
-      pinfo <- (head . mapRL info . concatRL) `liftSM` read_repo repository
+      pinfo <- (head . mapRL info . concatRL) `liftM` read_repo repository
hunk ./src/Darcs/Population.lhs 105
-   do pips <- concatRL `liftSM` read_repo repository
+   do pips <- concatRL `liftM` read_repo repository
hunk ./src/Darcs/Repository.lhs 98
-import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal, unsealM )
+import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal )
hunk ./src/Darcs/Repository.lhs 125
-      copyAnythingToOld r = withCurrentDirectory todir $ read_repo r `unsealM` 
+      copyAnythingToOld r = withCurrentDirectory todir $ read_repo r >>=
hunk ./src/Darcs/Repository.lhs 135
-                Sealed patches <- read_repo fromrepo
+                patches <- read_repo fromrepo
hunk ./src/Darcs/Repository.lhs 174
-           Sealed local_patches <- read_repo torepository
+           local_patches <- read_repo torepository
hunk ./src/Darcs/Repository.lhs 200
-           then do Sealed local_patches <- read_repo torepository
+           then do local_patches <- read_repo torepository
hunk ./src/Darcs/Repository.lhs 208
-           else do read_repo torepository `unsealM` (apply_patches opts . reverseRL . concatRL)
+           else do read_repo torepository >>= (apply_patches opts . reverseRL . concatRL)
hunk ./src/Darcs/Repository.lhs 236
-    read_repo repo `unsealM` (apply_patches opts . reverseRL . concatRL)
+    read_repo repo >>= (apply_patches opts . reverseRL . concatRL)
hunk ./src/Darcs/Repository.lhs 248
-                Sealed r <- read_repo torepository
+                r <- read_repo torepository
hunk ./src/Darcs/Repository/Checkpoint.lhs 65
-import Darcs.Sealed ( Sealed(Sealed), FlippedSeal(..), unsafeUnseal, liftSM )
+import Darcs.Sealed ( Sealed(Sealed), FlippedSeal(..), unsafeUnseal )
+import Control.Monad ( liftM )
hunk ./src/Darcs/Repository/Checkpoint.lhs 106
-  pis <- (map info . catMaybes . mapRL lastRL) `liftSM` read_repo repository
+  pis <- (map info . catMaybes . mapRL lastRL) `liftM` read_repo repository
hunk ./src/Darcs/Repository/Checkpoint.lhs 130
-    ps <- (mapFL_FL hopefully.reverseRL.concatRL) `liftSM` read_repo r
+    ps <- (mapFL_FL hopefully.reverseRL.concatRL) `liftM` read_repo r
hunk ./src/Darcs/Repository/Checkpoint.lhs 143
-          `liftSM` read_repo repo
+          `liftM` read_repo repo
hunk ./src/Darcs/Repository/Checkpoint.lhs 164
-    Sealed ps <- read_repo r
+    ps <- read_repo r
hunk ./src/Darcs/Repository/DarcsRepo.lhs 56
-                                    read_repo, write_and_read_patch,
+                                    read_repo, read_tentative_repo, write_and_read_patch,
hunk ./src/Darcs/Repository/DarcsRepo.lhs 250
+read_tentative_repo :: RepoPatch p => [DarcsFlag] -> String -> IO (SealedPatchSet p)
+read_tentative_repo opts d = do
+  realdir <- absolute_dir d
+  let k = "Reading tentative inventory of repository "++d
+  beginTedious k
+  read_repo_private k opts realdir "tentative_inventory" `catch`
+                        (\e -> do hPutStrLn stderr ("Invalid repository:  " ++ realdir)
+                                  ioError e)
+
hunk ./src/Darcs/Repository/HashedRepo.lhs 31
-                                     read_repo, write_and_read_patch,
+                                     read_repo, read_tentative_repo, write_and_read_patch,
hunk ./src/Darcs/Repository/HashedRepo.lhs 317
-apply_pristine :: Patchy q => Cache -> [DarcsFlag] -> String -> String -> q C(() ()) -> IO ()
+apply_pristine :: Patchy q => Cache -> [DarcsFlag] -> String -> String -> q C(x y) -> IO ()
hunk ./src/Darcs/Repository/HashedRepo.lhs 323
-apply_to_tentative_pristine :: Patchy q => Cache -> [DarcsFlag] -> q C(() ()) -> IO ()
+apply_to_tentative_pristine :: Patchy q => Cache -> [DarcsFlag] -> q C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 71
-import Darcs.Patch ( Effect, is_hunk, is_binary, description,
+import Darcs.Patch ( Patch, RealPatch, Effect, is_hunk, is_binary, description,
hunk ./src/Darcs/Repository/Internal.lhs 73
-import Darcs.Patch.Prim ( try_shrinking_inverse )
+import Darcs.Patch.Prim ( try_shrinking_inverse, Conflict )
hunk ./src/Darcs/Repository/Internal.lhs 86
-                              add_to_tentative_inventory, read_repo, clean_pristine,
+                              add_to_tentative_inventory,
+                              read_repo, read_tentative_repo, clean_pristine,
hunk ./src/Darcs/Repository/Internal.lhs 97
-                             (+>+), lengthFL,
-                             unsafeUnFL, allFL, filterFL,
+                             (+>+), lengthFL, nullFL,
+                             allFL, filterFL, dropWhileFL,
hunk ./src/Darcs/Repository/Internal.lhs 101
-import Darcs.Patch ( RepoPatch, Patchy, Prim, RealPatch, Patch, merge,
+import Darcs.Patch ( RepoPatch, Patchy, Prim, merge,
hunk ./src/Darcs/Repository/Internal.lhs 127
-import Darcs.Sealed ( Sealed(Sealed), mapSeal, unsafeUnseal, liftSM, seal )
+import Darcs.Sealed ( Sealed(Sealed), mapSeal, seal, FlippedSeal(FlippedSeal),
+                      Sealed2(Sealed2), seal2 )
hunk ./src/Darcs/Repository/Internal.lhs 133
-maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p))
+maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p C(r u t)))
hunk ./src/Darcs/Repository/Internal.lhs 157
-identifyDarcs1Repository :: [DarcsFlag] -> String -> IO (Repository Patch)
+identifyDarcs1Repository :: [DarcsFlag] -> String -> IO (Repository Patch C(r u t))
hunk ./src/Darcs/Repository/Internal.lhs 164
-identifyRepositoryFor :: RepoPatch p => Repository p -> String -> IO (Repository p)
+identifyRepositoryFor :: forall p C(r u t). RepoPatch p => Repository p C(r u t) -> String -> IO (Repository p C(r u t))
hunk ./src/Darcs/Repository/Internal.lhs 166
-    do Repo absurl _ rf' t <- identifyDarcs1Repository opts url
+    do Repo absurl _ rf_ t <- identifyDarcs1Repository opts url
hunk ./src/Darcs/Repository/Internal.lhs 168
-       case readfrom_and_writeto_problem rf' rf of
+       case readfrom_and_writeto_problem rf_ rf of
hunk ./src/Darcs/Repository/Internal.lhs 170
-         Nothing -> return $ Repo absurl opts rf' t'
+         Nothing -> return $ Repo absurl opts rf_ t'
hunk ./src/Darcs/Repository/Internal.lhs 235
-slurp_pending :: RepoPatch p => Repository p -> IO Slurpy
+slurp_pending :: RepoPatch p => Repository p C(r u t) -> IO Slurpy
hunk ./src/Darcs/Repository/Internal.lhs 238
-  pend <- read_pending repo
+  Sealed pend <- read_pending repo
hunk ./src/Darcs/Repository/Internal.lhs 244
-slurp_recorded :: RepoPatch p => Repository p -> IO Slurpy
+slurp_recorded :: RepoPatch p => Repository p C(r u t) -> IO Slurpy
hunk ./src/Darcs/Repository/Internal.lhs 255
-slurp_recorded_and_unrecorded :: RepoPatch p => Repository p -> IO (Slurpy, Slurpy)
+slurp_recorded_and_unrecorded :: RepoPatch p => Repository p C(r u t) -> IO (Slurpy, Slurpy)
hunk ./src/Darcs/Repository/Internal.lhs 258
-  pend <- read_pending repo
+  Sealed pend <- read_pending repo
hunk ./src/Darcs/Repository/Internal.lhs 268
-read_pending :: RepoPatch p => Repository p -> IO (FL Prim)
+read_pending :: RepoPatch p => Repository p C(r u t) -> IO (Sealed (FL Prim C(r)))
hunk ./src/Darcs/Repository/Internal.lhs 272
-add_to_pending :: RepoPatch p => Repository p -> FL Prim -> IO ()
+add_to_pending :: RepoPatch p => Repository p C(r u t) -> FL Prim C(u y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 279
-readPrims s = case readPatch s of
+readPrims s = case readPatch s :: Maybe (Sealed (Patch C(x )), PackedString) of
hunk ./src/Darcs/Repository/Internal.lhs 281
-              Just (Sealed p,_) -> Sealed (effect (p :: Patch C(x y)))
+              Just (Sealed p,_) -> Sealed (effect p)
hunk ./src/Darcs/Repository/Internal.lhs 283
-read_pendingfile :: String -> IO (FL Prim)
+read_pendingfile :: String -> IO (Sealed (FL Prim C(x)))
hunk ./src/Darcs/Repository/Internal.lhs 286
-  case readPrims pend of
-    Sealed p -> return p
+  return $ readPrims pend
hunk ./src/Darcs/Repository/Internal.lhs 288
-make_new_pending :: RepoPatch p => Repository p -> FL Prim -> IO ()
+make_new_pending :: forall p C(r u t x y). RepoPatch p => Repository p C(r u t) -> FL Prim C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 294
-       writePatch newname (fromPrims $ sift_for_pending origp :: Patch)
+       Sealed sfp <- return $ sift_for_pending origp
+       writeSealedPatch newname $ seal $ fromPrims $ sfp
hunk ./src/Darcs/Repository/Internal.lhs 297
-       p <- read_pendingfile newname
+       Sealed p <- read_pendingfile newname
hunk ./src/Darcs/Repository/Internal.lhs 307
+    where writeSealedPatch :: FilePath -> Sealed (Patch C(x)) -> IO ()
+          writeSealedPatch fp (Sealed p) = writePatch fp p
hunk ./src/Darcs/Repository/Internal.lhs 310
-sift_for_pending :: FL Prim -> FL Prim
+sift_for_pending :: FL Prim C(x y) -> Sealed (FL Prim C(x))
hunk ./src/Darcs/Repository/Internal.lhs 314
-    then oldps
-    else 
-      case try_to_shrink $ sfp NilFL $ reverseFL oldps of
-      ps | lengthFL ps < lengthFL oldps -> sift_for_pending ps
-         | otherwise -> ps
-      where sfp :: FL Prim C(x y) -> RL Prim C(y z) -> FL Prim C(x z)
-            sfp sofar NilRL = sofar
+    then seal oldps
+    else fromJust $ do
+      Sealed x <- return $ sfp NilFL $ reverseFL oldps
+      return (case try_to_shrink x of
+              ps | lengthFL ps < lengthFL oldps -> sift_for_pending ps
+                 | otherwise -> seal ps)
+      where sfp :: FL Prim C(a b) -> RL Prim C(c a) -> Sealed (FL Prim C(c))
+            sfp sofar NilRL = seal sofar
hunk ./src/Darcs/Repository/Internal.lhs 329
-get_unrecorded_no_look_for_adds :: RepoPatch p => Repository p -> IO (FL Prim)
+get_unrecorded_no_look_for_adds :: RepoPatch p => Repository p C(r u t) -> IO (FL Prim C(r u))
hunk ./src/Darcs/Repository/Internal.lhs 332
-get_unrecorded_unsorted :: RepoPatch p => Repository p -> IO (FL Prim)
+get_unrecorded_unsorted :: RepoPatch p => Repository p C(r u t) -> IO (FL Prim C(r u))
hunk ./src/Darcs/Repository/Internal.lhs 335
-get_unrecorded :: RepoPatch p => Repository p -> IO (FL Prim)
+get_unrecorded :: RepoPatch p => Repository p C(r u t) -> IO (FL Prim C(r u))
hunk ./src/Darcs/Repository/Internal.lhs 338
-get_unrecorded_private :: RepoPatch p => ([DarcsFlag]->[DarcsFlag]) -> Repository p -> IO (FL Prim)
+get_unrecorded_private :: RepoPatch p => ([DarcsFlag]->[DarcsFlag]) -> Repository p C(r u t) -> IO (FL Prim C(r u))
hunk ./src/Darcs/Repository/Internal.lhs 340
-    | NoUpdateWorking `elem` opts = return NilFL
+    | NoUpdateWorking `elem` opts = return $ unsafeCoerceP NilFL
hunk ./src/Darcs/Repository/Internal.lhs 351
-    pend <- read_pending repository
+    Sealed pend <- read_pending repository
hunk ./src/Darcs/Repository/Internal.lhs 367
-read_repo :: RepoPatch p => Repository p -> IO (SealedPatchSet p)
+read_repo :: RepoPatch p => Repository p C(r u t) -> IO (PatchSet p C(r))
hunk ./src/Darcs/Repository/Internal.lhs 370
-                                         return $ seal ps
-    | otherwise = DarcsRepo.read_repo opts r
+                                         return ps
+    | otherwise = do Sealed ps <- DarcsRepo.read_repo opts r
+                     return $ unsafeCoerceP ps
hunk ./src/Darcs/Repository/Internal.lhs 374
-makePatchLazy :: RepoPatch p => Repository p -> PatchInfoAnd p -> IO (PatchInfoAnd p)
+readTentativeRepo :: RepoPatch p => Repository p C(r u t) -> IO (PatchSet p C(t))
+readTentativeRepo repo@(Repo r opts rf _)
+    | format_has HashedInventory rf = do ps <- HashedRepo.read_tentative_repo repo opts r
+                                         return ps
+    | otherwise = do Sealed ps <- DarcsRepo.read_tentative_repo opts r
+                     return $ unsafeCoerceP ps
+
+makePatchLazy :: RepoPatch p => Repository p C(r u t) -> PatchInfoAnd p C(x y) -> IO (PatchInfoAnd p C(x y))
hunk ./src/Darcs/Repository/Internal.lhs 386
-sync_repo :: Repository p -> IO ()
+sync_repo :: Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 391
-prefsUrl :: Repository p -> String
+prefsUrl :: Repository p C(r u t) -> String
hunk ./src/Darcs/Repository/Internal.lhs 394
-unrevertUrl :: Repository p -> String
+unrevertUrl :: Repository p C(r u t) -> String
hunk ./src/Darcs/Repository/Internal.lhs 397
-applyToWorking :: Patchy p => Repository p1 -> [DarcsFlag] -> p -> IO ()
+applyToWorking :: Patchy p => Repository p1 C(r u t) -> [DarcsFlag] -> p C(u y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 403
-handle_pend_for_add :: (RepoPatch p, Effect q) => Repository p -> q -> IO ()
+handle_pend_for_add :: forall p q C(r u t x y). (RepoPatch p, Effect q) 
+                    => Repository p C(r u t) -> q C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 412
-       writePatch pn $ (fromPrims newpend :: Patch)
-    where rmpend :: FL Prim C(x y) -> FL Prim C(x z) -> Sealed (FL Prim) C(y)
+       writePatch pn $ fromPrims_ newpend
+    where rmpend :: FL Prim C(a b) -> FL Prim C(a c) -> Sealed (FL Prim C(b))
hunk ./src/Darcs/Repository/Internal.lhs 419
+          fromPrims_ :: FL Prim C(a b) -> Patch C(a b)
+          fromPrims_ = fromPrims
hunk ./src/Darcs/Repository/Internal.lhs 439
-tentativelyMergePatches :: RepoPatch p => Repository p -> String -> [DarcsFlag]
-                        -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (FL Prim)
+
+tentativelyMergePatches :: RepoPatch p
+                        => Repository p C(r u t) -> String -> [DarcsFlag]
+                        -> FL (PatchInfoAnd p) C(u r) -> FL (PatchInfoAnd p) C(u y)
+                        -> IO (Sealed (FL Prim C(u)))
hunk ./src/Darcs/Repository/Internal.lhs 446
-considerMergeToWorking :: RepoPatch p => Repository p -> String -> [DarcsFlag]
-                       -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (FL Prim)
+considerMergeToWorking :: RepoPatch p
+                       => Repository p C(r u t) -> String -> [DarcsFlag]
+                       -> FL (PatchInfoAnd p) C(u r) -> FL (PatchInfoAnd p) C(u y)
+                       -> IO (Sealed (FL Prim C(u)))
hunk ./src/Darcs/Repository/Internal.lhs 454
-tentativelyMergePatches_ :: RepoPatch p => MakeChanges
-                         -> Repository p -> String -> [DarcsFlag]
-                         -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (FL Prim)
+tentativelyMergePatches_ :: forall p C(r u t y). RepoPatch p
+                         => MakeChanges
+                         -> Repository p C(r u t) -> String -> [DarcsFlag]
+                         -> FL (PatchInfoAnd p) C(u r) -> FL (PatchInfoAnd p) C(u y)
+                         -> IO (Sealed (FL Prim C(u)))
hunk ./src/Darcs/Repository/Internal.lhs 462
-         pc = case merge (progressFL "Merging them" them :\/: progressFL "Merging us" us) of
-              _ :/\: x -> x
+     Sealed pc <- case merge (progressFL "Merging them" them :\/: progressFL "Merging us" us) of
+                  _ :/\: x -> return $ seal x
hunk ./src/Darcs/Repository/Internal.lhs 467
-         Sealed standard_resolved_pw = standard_resolution pwprim
+     Sealed standard_resolved_pw <- return $ standard_resolution pwprim
hunk ./src/Darcs/Repository/Internal.lhs 477
-     pw_resolution <-
+     Sealed pw_resolution <-
hunk ./src/Darcs/Repository/Internal.lhs 480
-                                  then NilFL
-                                  else standard_resolved_pw
-          (_,False) -> return standard_resolved_pw
-          (Just c, True) -> unsafeUnseal `fmap`
-                            external_resolution working c
+                                  then seal NilFL
+                                  else seal standard_resolved_pw
+          (_,False) -> return $ Sealed standard_resolved_pw
+          (Just c, True) -> external_resolution working c
hunk ./src/Darcs/Repository/Internal.lhs 488
-          do let themi' = case usi of NilFL -> themi
-                                      _ -> mapFL_FL n2pia pc
+          do Sealed2 themi' <- return $ case usi of NilFL -> seal2 themi
+                                                    _ -> seal2 $ mapFL_FL n2pia pc
hunk ./src/Darcs/Repository/Internal.lhs 496
-     return (effect pwprim +>+ pw_resolution)
+     return $ seal (effect pwprim +>+ pw_resolution)
hunk ./src/Darcs/Repository/Internal.lhs 498
-announce_merge_conflicts :: String -> [DarcsFlag] -> FL Prim -> IO Bool
+announce_merge_conflicts :: String -> [DarcsFlag] -> FL Prim C(x y) -> IO Bool
hunk ./src/Darcs/Repository/Internal.lhs 516
-check_unrecorded_conflicts :: forall p. RepoPatch p => [DarcsFlag] -> FL (Named p) -> IO Bool
+check_unrecorded_conflicts :: forall p C(r y). RepoPatch p => [DarcsFlag] -> FL (Named p) C(r y) -> IO Bool
hunk ./src/Darcs/Repository/Internal.lhs 520
-       mpend <- read_pending repository
-       case mpend of
-         NilFL -> return False
-         pend ->
-             case merge (fromPrims pend :\/: fromPrims (concatFL $ mapFL_FL effect pc)) of
-             _ :/\: (pend' :: p) ->
-                 case list_conflicted_files pend' of
-                 [] -> return False
-                 fs -> do yorn <- promptYorn
-                                  ("You have conflicting local changes to:\n"
-                                   ++ unwords fs++"\nProceed?")
-                          when (yorn /= 'y') $
-                               do putStr "Cancelled."
-                                  exitWith ExitSuccess
-                          return True
+       cuc repository
+    where cuc :: Repository Patch C(r u t) -> IO Bool
+          cuc r = do Sealed mpend <- read_pending r :: IO (Sealed (FL Prim C(r)))
+                     case mpend of
+                       NilFL -> return False
+                       pend ->
+                           case merge (fromPrims_ pend :\/: fromPrims_ (concatFL $ mapFL_FL effect pc)) of
+                           _ :/\: pend' ->
+                               case list_conflicted_files pend' of
+                               [] -> return False
+                               fs -> do yorn <- promptYorn
+                                                ("You have conflicting local changes to:\n"
+                                                 ++ unwords fs++"\nProceed?")
+                                        when (yorn /= 'y') $
+                                             do putStr "Cancelled."
+                                                exitWith ExitSuccess
+                                        return True
+          fromPrims_ :: FL Prim C(a b) -> p C(a b)
+          fromPrims_ = fromPrims
hunk ./src/Darcs/Repository/Internal.lhs 540
-tentativelyAddPatch :: RepoPatch p => Repository p -> [DarcsFlag] -> PatchInfoAnd p -> IO ()
+tentativelyAddPatch :: RepoPatch p
+                    => Repository p C(r u t) -> [DarcsFlag] -> PatchInfoAnd p C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 546
-tentativelyAddPatch_ :: RepoPatch p => UpdatePristine -> Repository p -> [DarcsFlag]
-                     -> PatchInfoAnd p -> IO ()
+tentativelyAddPatch_ :: RepoPatch p
+                     => UpdatePristine -> Repository p C(r u t) -> [DarcsFlag]
+                     -> PatchInfoAnd p C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 561
-applyToTentativePristine :: (Effect q, Patchy q) => Repository p -> q -> IO ()
+applyToTentativePristine :: (Effect q, Patchy q) => Repository p C(r u t) -> q C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 568
-tentativelyAddToPending :: forall p. RepoPatch p => Repository p -> [DarcsFlag] -> FL Prim -> IO ()
+tentativelyAddToPending :: forall p C(r u t x y). RepoPatch p 
+                        => Repository p C(r u t) -> [DarcsFlag] -> FL Prim C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 577
-      pend <- gzReadFilePS tpn `catchall` (return nilPS)
-      let newpend = case readPrims pend of
-                    Sealed NilFL -> patch
-                    Sealed p -> p +>+ patch
-      writePatch tpn $ (fromPrims newpend :: Patch)
+      Sealed pend <- readPrims `liftM` (gzReadFilePS tpn `catchall` (return nilPS))
+      Sealed newpend_ <- return $ newpend pend patch
+      writePatch tpn $ fromPrims_ newpend_
+      where newpend :: FL Prim C(b c) -> FL Prim C(a b) -> Sealed (FL Prim C(a))
+            newpend NilFL patch_ = seal patch_
+            newpend p     patch_ = seal $ patch_ +>+ p
+            fromPrims_ :: FL Prim C(a b) -> Patch C(a b)
+            fromPrims_ = fromPrims
hunk ./src/Darcs/Repository/Internal.lhs 586
-setTentativePending :: forall p. RepoPatch p => Repository p -> FL Prim -> IO ()
+setTentativePending :: forall p C(r u t x y). RepoPatch p => Repository p C(r u t) -> FL Prim C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 588
-setTentativePending (Repo dir _ _ rt) patch =
+setTentativePending (Repo dir _ _ rt) patch = do
+    Sealed prims <- return $ sift_for_pending patch
hunk ./src/Darcs/Repository/Internal.lhs 591
-    writePatch (pendingName rt ++ ".tentative") $ (fromPrims (sift_for_pending patch) :: Patch)
+      writePatch (pendingName rt ++ ".tentative") $ fromPrims_ prims
+    where fromPrims_ :: FL Prim C(a b) -> Patch C(a b)
+          fromPrims_ = fromPrims
hunk ./src/Darcs/Repository/Internal.lhs 595
-prepend :: forall p. RepoPatch p => Repository p -> FL Prim -> IO ()
+prepend :: forall p C(r u t x y). RepoPatch p => Repository p C(r u t) -> FL Prim C(x y) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 598
-                                   pend <- gzReadFilePS pn `catchall` (return nilPS)
-                                   let newpend = case readPrims pend of
-                                                 Sealed NilFL -> patch
-                                                 Sealed p -> patch +>+ p
-                                   writePatch pn $ (fromPrims (crude_sift newpend) :: Patch)
+                                   Sealed pend <- readPrims `liftM` (gzReadFilePS pn `catchall` (return nilPS))
+                                   Sealed newpend_ <- return $ newpend pend patch
+                                   writePatch pn $ fromPrims_ (crude_sift newpend_)
+      where newpend :: FL Prim C(b c) -> FL Prim C(a b) -> Sealed (FL Prim C(a))
+            newpend NilFL patch_ = seal patch_
+            newpend p     patch_ = seal $ patch_ +>+ p
+            fromPrims_ :: FL Prim C(a b) -> Patch C(a b)
+            fromPrims_ = fromPrims
hunk ./src/Darcs/Repository/Internal.lhs 607
-tentativelyRemovePatches :: RepoPatch p => Repository p -> [DarcsFlag]
-                         -> FL (Named p) -> IO ()
+tentativelyRemovePatches :: RepoPatch p => Repository p C(r u t) -> [DarcsFlag]
+                         -> FL (Named p) C(x t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 612
-                          -> Repository p -> [DarcsFlag]
-                          -> FL (Named p) -> IO ()
+                          -> Repository p C(r u t) -> [DarcsFlag]
+                          -> FL (Named p) C(x t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 628
-tentativelyReplacePatches :: RepoPatch p => Repository p -> [DarcsFlag]
-                          -> FL (Named p) -> IO ()
+tentativelyReplacePatches :: RepoPatch p => Repository p C(r u t) -> [DarcsFlag]
+                          -> FL (Named p) C(x t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 635
-finalize_pending :: RepoPatch p => Repository p -> IO ()
+finalize_pending :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 643
-                                let tpend = unsafeUnseal $ readPrims tpfile
-                                    new_pending = sift_for_pending tpend
+                                Sealed tpend <- return $ readPrims tpfile
+                                Sealed new_pending <- return $ sift_for_pending tpend
hunk ./src/Darcs/Repository/Internal.lhs 647
-finalizeRepositoryChanges :: RepoPatch p => Repository p -> IO ()
+finalizeRepositoryChanges :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 666
-testTentative :: RepoPatch p => Repository p -> IO ()
+testTentative :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 685
-revertRepositoryChanges :: RepoPatch p => Repository p -> IO ()
+revertRepositoryChanges :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 691
-       x <- read_pending r
+       Sealed x <- read_pending r
hunk ./src/Darcs/Repository/Internal.lhs 697
-patchSetToPatches :: RepoPatch p => PatchSet p -> FL (Named p)
+patchSetToPatches :: RepoPatch p => PatchSet p C(x) -> FL (Named p) C(() x)
hunk ./src/Darcs/Repository/Internal.lhs 705
-withGutsOf :: Repository p -> IO () -> IO ()
+withGutsOf :: Repository p C(r u t) -> IO () -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 709
-withRepository :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
+withRepository :: [DarcsFlag] -> (forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 712
-withRepositoryDirectory :: [DarcsFlag] -> String
-                        -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
+withRepositoryDirectory :: forall a. [DarcsFlag] -> String
+                        -> (forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 719
-                 job (Repo dir opts rf rt' :: Repository (FL RealPatch))
+                 job1_ (Repo dir opts rf rt')
hunk ./src/Darcs/Repository/Internal.lhs 721
-                 job (Repo dir opts rf rt :: Repository Patch)
+                 job2_ (Repo dir opts rf rt)
+  where job1_ :: Repository (FL RealPatch) C(r u t) -> IO a
+        job1_ = job
+        job2_ :: Repository Patch C(r u t) -> IO a
+        job2_ = job
+
hunk ./src/Darcs/Repository/Internal.lhs 728
-($-) :: ((forall p. RepoPatch p => Repository p -> IO a) -> IO a)
-     -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
+($-) ::((forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a)
+     -> (forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 732
-withRepoLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
+withRepoLock :: [DarcsFlag] -> (forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 746
-withRepoReadLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
+withRepoReadLock :: [DarcsFlag] -> (forall p C(r u t). RepoPatch p => Repository p C(r u t) -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 761
-remove_from_unrevert_context :: RepoPatch p => Repository p -> FL (Named p) -> IO ()
+remove_from_unrevert_context :: forall p C(r u t x). RepoPatch p
+                             => Repository p C(r u t) -> FL (Named p) C(x t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 764
-  bundle <- unrevert_patch_bundle `catchall` return (NilRL:<:NilRL)
-  case bundle of
-    NilRL:<:NilRL -> return ()
-    _ -> do
-    let unrevert_loc = unrevertUrl repository
-    debugMessage "Adjusting the context of the unrevert changes..."
-    Sealed ref <- read_repo repository
-    case get_common_and_uncommon (bundle, ref) of
-        (common,(h_us:<:NilRL):<:NilRL :\/: NilRL:<:NilRL) ->
-            case commuteRL (reverseFL ps :> hopefully h_us) of
-            Nothing -> unrevert_impossible unrevert_loc
-            Just (us' :> _) -> do
-                s <- slurp_recorded repository
-                writeDocBinFile unrevert_loc $
-                             make_bundle [] s
-                             (common \\ pis) (us':>:NilFL)
-        (common,(x:<:NilRL):<:NilRL:\/:_)
-            | isr && any (`elem` common) pis -> unrevert_impossible unrevert_loc
-            | isr -> return ()
-            where isr = isJust $ hopefullyM x
-        _ -> unrevert_impossible unrevert_loc
+  Sealed bundle <- unrevert_patch_bundle `catchall` (return $ seal (NilRL:<:NilRL))
+  remove_from_unrevert_context_ bundle
hunk ./src/Darcs/Repository/Internal.lhs 773
-        unrevert_patch_bundle :: RepoPatch p => IO (PatchSet p)
+        unrevert_patch_bundle :: IO (SealedPatchSet p)
hunk ./src/Darcs/Repository/Internal.lhs 776
-                                     Right (Sealed foo) -> return foo
+                                     Right foo -> return foo
hunk ./src/Darcs/Repository/Internal.lhs 778
+        remove_from_unrevert_context_ :: PatchSet p C(z) -> IO ()
+        remove_from_unrevert_context_ (NilRL :<: NilRL) = return ()
+        remove_from_unrevert_context_ bundle = do
+            let unrevert_loc = unrevertUrl repository
+            debugMessage "Adjusting the context of the unrevert changes..."
+            ref <- readTentativeRepo repository
+            case get_common_and_uncommon (bundle, ref) of
+                 (common,(h_us:<:NilRL):<:NilRL :\/: NilRL:<:NilRL) ->
+                    case commuteRL (reverseFL ps :> hopefully h_us) of
+                    Nothing -> unrevert_impossible unrevert_loc
+                    Just (us' :> _) -> do
+                        s <- slurp_recorded repository
+                        writeDocBinFile unrevert_loc $
+                             make_bundle [] s
+                             (common \\ pis) (us':>:NilFL)
+                 (common,(x:<:NilRL):<:NilRL:\/:_)
+                        | isr && any (`elem` common) pis -> unrevert_impossible unrevert_loc
+                        | isr -> return ()
+                        where isr = isJust $ hopefullyM x
+                 _ -> unrevert_impossible unrevert_loc
hunk ./src/Darcs/Repository/Internal.lhs 801
-optimizeInventory :: RepoPatch p => Repository p -> IO ()
+optimizeInventory :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 803
-    do Sealed ps <- read_repo repository
+    do ps <- read_repo repository
hunk ./src/Darcs/Repository/Internal.lhs 811
-cleanRepository :: RepoPatch p => Repository p -> IO ()
+cleanRepository :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 817
-replacePristine :: Repository p -> FilePath -> IO ()
+replacePristine :: Repository p C(r u t) -> FilePath -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 822
-createPristineDirectoryTree :: RepoPatch p => Repository p -> FilePath -> IO ()
+createPristineDirectoryTree :: RepoPatch p => Repository p C(r u t) -> FilePath -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 830
-           unless done $ do patches <- (reverseRL . concatRL) `liftSM` read_repo repo
+           unless done $ do Sealed patches <- (seal . reverseRL . concatRL) `liftM` read_repo repo
hunk ./src/Darcs/Repository/Internal.lhs 834
-createPartialsPristineDirectoryTree :: RepoPatch p => Repository p -> [FilePath] -> FilePath -> IO ()
+createPartialsPristineDirectoryTree :: RepoPatch p => Repository p C(r u t) -> [FilePath] -> FilePath -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 846
-pristineFromWorking :: RepoPatch p => Repository p -> IO ()
+pristineFromWorking :: RepoPatch p => Repository p C(r u t) -> IO ()
hunk ./src/Darcs/Repository/Internal.lhs 853
-withRecorded :: RepoPatch p => Repository p -> ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
+withRecorded :: RepoPatch p => Repository p C(r u t) -> ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 858
-checkPristineAgainstCwd :: RepoPatch p => Repository p -> IO Bool
+checkPristineAgainstCwd :: RepoPatch p => Repository p C(r u t) -> IO Bool
hunk ./src/Darcs/Repository/Internal.lhs 866
-       case smart_diff opts ftf s1 s2 of
-         NilFL -> return True
-         _ -> return False
+       return $ nullFL $ smart_diff opts ftf s1 s2
hunk ./src/Darcs/Repository/Internal.lhs 868
-withTentative :: forall p a. RepoPatch p =>
-                 Repository p -> ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
+withTentative :: forall p a C(r u t). RepoPatch p =>
+                 Repository p C(r u t) -> ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
hunk ./src/Darcs/Repository/Internal.lhs 876
-    do ps <- read_patches (dir ++ "/"++darcsdir++"/tentative_pristine")
+    do Sealed ps <- read_patches (dir ++ "/"++darcsdir++"/tentative_pristine")
hunk ./src/Darcs/Repository/Internal.lhs 879
-    where read_patches :: FilePath -> IO (FL p)
+    where read_patches :: FilePath -> IO (Sealed (FL p C(x)))
hunk ./src/Darcs/Repository/Internal.lhs 882
-                                           Just (Sealed x, _) -> x
-                                           Nothing -> NilFL
+                                           Just (x, _) -> x
+                                           Nothing -> seal NilFL
hunk ./src/Darcs/Repository/Internal.lhs 887
-getMarkedupFile :: RepoPatch p => Repository p -> PatchInfo -> FilePath -> IO MarkedUpFile
+getMarkedupFile :: RepoPatch p => Repository p C(r u t) -> PatchInfo -> FilePath -> IO MarkedUpFile
hunk ./src/Darcs/Repository/Internal.lhs 889
-  patches <- (dropWhile ((/= pinfo) . info) . unsafeUnFL
-              . reverseRL . concatRL) `liftSM` read_repo repository
+  Sealed (FlippedSeal patches) <- (seal . dropWhileFL ((/= pinfo) . info)
+                                  . reverseRL . concatRL) `liftM` read_repo repository
hunk ./src/Darcs/Repository/Internal.lhs 892
-do_mark_all :: RepoPatch p => [PatchInfoAnd p]
+do_mark_all :: RepoPatch p => FL (PatchInfoAnd p) C(x y)
hunk ./src/Darcs/Repository/Internal.lhs 894
-do_mark_all (hp:pps) (f, mk) =
+do_mark_all (hp:>:pps) (f, mk) =
hunk ./src/Darcs/Repository/Internal.lhs 898
-do_mark_all [] (f, mk) = (f, mk)
+do_mark_all NilFL (f, mk) = (f, mk)
hunk ./src/Darcs/Resolution.lhs 158
-                    -> IO (Sealed (FL Prim C(x)))
+                    -> IO (Sealed (FL Prim C(a)))
hunk ./src/Darcs/SelectChanges.lhs 68
-import Darcs.Sealed ( Sealed(..) )
+import Darcs.Sealed ( Sealed(..), seal )
hunk ./src/Darcs/SelectChanges.lhs 170
-    Sealed p_s <- read_repo repository
-    pend <- if ignore_pending
-            then return NilFL
-            else read_pending repository
+    p_s <- read_repo repository
+    Sealed pend <- if ignore_pending
+                   then return $ seal NilFL
+                   else read_pending repository
hunk ./src/list_authors.hs 25
-import Darcs.Sealed ( Sealed(..) )
hunk ./src/list_authors.hs 46
-       do Sealed darcs_history <- read_repo repository
+       do darcs_history <- read_repo repository
hunk ./src/make_changelog.hs 30
-import Darcs.Sealed ( liftSM )
hunk ./src/make_changelog.hs 53
-        full_backward_history <- concatRL `liftSM` read_repo repository
+        full_backward_history <- concatRL `liftM` read_repo repository

[fixed a bug in identity_commutes property
Jason Dagit <[EMAIL PROTECTED]>**20080808023025
 In the right identity check the patch order should have gone from
 (identity :> p) to (p2 :> i2).  I added a rigid type context too
 so that ghc 6.8 and newer would type the definition.
] hunk ./src/Darcs/Patch/Properties.lhs 69
-identity_commutes :: Patchy p => p C(x y) -> Maybe Doc
+identity_commutes :: forall p C(x y). Patchy p => p C(x y) -> Maybe Doc
hunk ./src/Darcs/Patch/Properties.lhs 74
-                          case commute (identity :> p) of
-                          Nothing -> Just $ redText "identity_commutes failed 2:" $$ showPatch p
-                          Just (i2 :> p2) | IsEq <- i2 =\/= identity,
-                                            IsEq <- p2 =\/= p -> Nothing
-                          Just _ -> Just $ greenText "identity_commutes 2"
+                              checkRightIdentity $ commute $ identity :> p
hunk ./src/Darcs/Patch/Properties.lhs 76
+  where checkRightIdentity :: Maybe ((p :> p) C(x y)) -> Maybe Doc
+        checkRightIdentity Nothing = Just $ redText "identity_commutes failed 2:" $$ showPatch p
+        checkRightIdentity (Just (p2 :> i2)) | IsEq <- i2 =\/= identity,
+                                               IsEq <- p2 =\/= p = Nothing
+        checkRightIdentity (Just _) = Just $ greenText "identity_commutes 2"

Context:

[small makefile refactoring: allow just the normal tests to be run, without bugs/*
Simon Michael <[EMAIL PROTECTED]>**20080805203242] 
[Rectify dist help
[EMAIL PROTECTED]
 Removed the "make dist" suggestion, the manual is a better place for that.
 Instead, make clear that it operates on a clean copy of the tree, and
 mention the "predist" functionality.
] 
[website: explain that darcs 2 is required to get the darcs source.
Simon Michael <[EMAIL PROTECTED]>**20080803181216] 
[Canonize Gaetan Lehmann and Daniel Buenzli.
Eric Kow <[EMAIL PROTECTED]>**20080730104357
 (for Daniel B, avoid an accent in his name)
] 
[configure: check for packages needed with split base.
Eric Kow <[EMAIL PROTECTED]>**20080730103840
 Now that all packages must be used explicitly.
] 
[fix type witness compile errors specific to ghc 6.8
Jason Dagit <[EMAIL PROTECTED]>**20080722182729] 
[avoid import of unused function fromMaybe.
David Roundy <[EMAIL PROTECTED]>**20080729172825] 
[configure: suggest regex-compat before text
Eric Kow <[EMAIL PROTECTED]>**20080725095336] 
[configure: mention Haskell in 'try installing' suggestion
Eric Kow <[EMAIL PROTECTED]>**20080725095015] 
[Typo (Text.Regex)
Eric Kow <[EMAIL PROTECTED]>**20080715121708] 
[Use haskeline to have a readline-like behavior when asking something to the user
[EMAIL PROTECTED]
 Unlike the implementations using readline or editline packages, this code
 code doesn't break the Ctrl-C behavior.
] 
[Improve generic rules for English plurals. 
Eric Kow <[EMAIL PROTECTED]>**20080604123728] 
[add configure check for Network.URI.
David Roundy <[EMAIL PROTECTED]>**20080711011914] 
[add -hide-all-packages to default GHCFLAGS.
David Roundy <[EMAIL PROTECTED]>**20080711010952] 
[add support for outputting patch numbers in darcs changes.
David Roundy <[EMAIL PROTECTED]>**20080710011211] 
[add support for matching single patches by index.
David Roundy <[EMAIL PROTECTED]>**20080710004512] 
[add support for matching ranges of patches (counting back from present).
David Roundy <[EMAIL PROTECTED]>**20080710003225] 
[Better avoid silly manpage error.
Trent W. Buck <[EMAIL PROTECTED]>**20080704024920
 
 It turned out only initialize's help string used 'quotes', so just
 remove them.  This makes init's docstring consistent with the others.
] 
[Missing period at end of sentence.
Trent W. Buck <[EMAIL PROTECTED]>**20080704024232] 
[darcs --overview no longer works, so don't document it.
Trent W. Buck <[EMAIL PROTECTED]>**20080704030804] 
[Avoid silly manpage error.
Trent W. Buck <[EMAIL PROTECTED]>**20080703010733
 man (nroff) treats an apostrophe in the first column specially,
 resulting in a syntax error without this patch.
 
 Ideally, all cases of 'foo' in the manpage (i.e. docstrings) should
 become `foo', since man -Tps turns ` and ' into left and right single
 quotes respectively.
] 
[obliterate whitespace in Darcs.Commands.Get
[EMAIL PROTECTED]
 'twas causing lhs/haddock difficulties where a \end{code} wasn't getting recognized.
] 
[rm haddock CPP business
[EMAIL PROTECTED]
 Try as I might, I can't see any reason to special-case some Haddock CPP logic to deal with some *commented-out guards*, unless CPP magically restores and uncomments the code if Haddock isn't being run.
] 
[make pull less verbose when --verbose flag is given.
David Roundy <[EMAIL PROTECTED]>**20080624170035] 
[fix makefile to remember to regenerate version information after running configure.
David Roundy <[EMAIL PROTECTED]>**20080624170001] 
[TAG 2.0.2
David Roundy <[EMAIL PROTECTED]>**20080624012041] 
Patch bundle hash:
ac03fc5143967aa214b7f638244ea9d64a65144e
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to