Here is a hopefully cleaner attempt to rollback (and unrollback) the issue27
patches, using a multi-patch rollback and amend-record

Fri Sep 26 23:01:19 BST 2008  Eric Kow <[EMAIL PROTECTED]>
  * Resolve issue1102: recognise but do not generate patch log 'junk'.
  
  This is a partial rollback of the two issue27 patches below.  The patches 
exist
  to (a) generate patch log 'junk' and (b) hide such junk from users' view.
  Because of a feature freeze, we do not want junk generation to be part of 
darcs
  2.1; however, we do anticipate junk-generation being part of subsequent
  versions of darcs.  To avoid users being confused by this future junk, we only
  rollback the junk-generation part, retaining the junk-hiding part.
  
  rolling back:
  
  Wed Sep 17 16:46:57 BST 2008  David Roundy <[EMAIL PROTECTED]>
    * resolve issue27: add junk to patch identifiers.
  
  Wed Sep 17 18:09:13 BST 2008  David Roundy <[EMAIL PROTECTED]>
    * hokey fix to allow unit tests to generate random input.
  

Fri Sep 26 23:25:22 BST 2008  Eric Kow <[EMAIL PROTECTED]>
  * Restore issue27 patches.
  
  rolling back:
  
  Fri Sep 26 23:01:19 BST 2008  Eric Kow <[EMAIL PROTECTED]>
    * Resolve issue1102: recognise but do not generate patch log 'junk'.
    

New patches:

[Resolve issue1102: recognise but do not generate patch log 'junk'.
Eric Kow <[EMAIL PROTECTED]>**20080926220119
 
 This is a partial rollback of the two issue27 patches below.  The patches exist
 to (a) generate patch log 'junk' and (b) hide such junk from users' view.
 Because of a feature freeze, we do not want junk generation to be part of darcs
 2.1; however, we do anticipate junk-generation being part of subsequent
 versions of darcs.  To avoid users being confused by this future junk, we only
 rollback the junk-generation part, retaining the junk-hiding part.
 
 rolling back:
 
 Wed Sep 17 16:46:57 BST 2008  David Roundy <[EMAIL PROTECTED]>
   * resolve issue27: add junk to patch identifiers.
 
 Wed Sep 17 18:09:13 BST 2008  David Roundy <[EMAIL PROTECTED]>
   * hokey fix to allow unit tests to generate random input.
 
] hunk ./configure.ac 208
 
 dnl See if we need any packages from after the split base
 
-GHC_CHECK_MODULE(System.Random, random, randomRIO (0,10) :: IO Integer,,
-                 AC_MSG_ERROR(Cannot find System.Random; try installing the Haskell package random?))
-
 GHC_CHECK_MODULE(System.Directory, directory, doesFileExist "foo" :: IO Bool,,
                  AC_MSG_ERROR(Cannot find System.Directory; try installing the Haskell package directory?))
 GHC_CHECK_MODULE(System.Time, old-time, getClockTime :: IO ClockTime,,
hunk ./src/Darcs/Commands/AmendRecord.lhs 153
                                         Just a  -> a
                                         Nothing -> pi_author old_pinf
                            maybe_invert = if is_inverted old_pinf then invert_name else id
-                       new_pinf <- maybe_invert `fmap` patchinfo date new_name
-                                                                 new_author new_log
-                       let newp = fixp oldp chs new_pinf
+                           new_pinf = maybe_invert $ patchinfo date new_name new_author new_log
+                           newp = fixp oldp chs new_pinf
                        defineChanges newp
                        withGutsOf repository $ do
                          tentativelyRemovePatches repository opts (hopefully oldp :>: NilFL)
hunk ./src/Darcs/Commands/Record.lhs 200
                  -> [PatchInfo] -> FL Prim -> IO ()
 do_actual_record repository opts name date my_author my_log logf deps chs =
               do debugMessage "Writing the patch file..."
-                 mypatch <- namepatch date name my_author my_log $
-                            fromPrims $ progressFL "Writing changes:" chs
                  tentativelyAddPatch repository opts $ n2pia $ adddeps mypatch deps
                  debugMessage "Applying to pristine..."
                  withGutsOf repository (finalizeRepositoryChanges repository)
hunk ./src/Darcs/Commands/Record.lhs 209
                  when (isJust logf) $ removeFile (fromJust logf)
                  logMessage $ "Finished recording patch '"++name++"'"
     where (logMessage,_,_) = loggers opts
+          mypatch = namepatch date name my_author my_log $ fromPrims $ progressFL "Writing changes:" chs
           failuremessage = "Failed to record patch '"++name++"'" ++
                            case logf of Just lf -> "\nLogfile left in "++lf++"."
                                         Nothing -> ""
hunk ./src/Darcs/Commands/Record.lhs 389
 ask_about_depends :: RepoPatch p => Repository p -> FL Prim -> [DarcsFlag] -> IO [PatchInfo]
 ask_about_depends repository pa' opts = do
   pps <- read_repo repository
-  pa <- n2pia `fmap` anonymous (fromPrims pa')
-  let ps = (reverseRL $ headRL pps)+>+(pa:>:NilFL)
+  let pa = n2pia $ anonymous $ fromPrims pa'
+      ps = (reverseRL $ headRL pps)+>+(pa:>:NilFL)
       (pc, tps) = patch_choices_tps ps
       ta = case filter ((pa `unsafeCompare`) . tp_patch) $ unsafeUnFL tps of
                 [tp] -> tag tp
hunk ./src/Darcs/Commands/Rollback.lhs 137
             (name, my_log, logf) <- get_log opts newlog make_log $ invert ps''
             date <- getIsoDateTime
             my_author <- get_author opts
-            rbp <- n2pia `fmap` namepatch date name my_author my_log
-                                          (fromPrims $ invert ps'')
+            let rbp = n2pia $ namepatch date name my_author my_log $ fromPrims $ invert ps''
             debugMessage "Adding rollback patch to repository."
             Sealed pw <- tentativelyMergePatches repository "rollback" (MarkConflicts : opts)
                          NilFL (rbp :>: NilFL)
hunk ./src/Darcs/Commands/Tag.lhs 83
     name <- if (not . null) args
             then return $ "TAG " ++ unwords args
             else get_patchname opts
-    myinfo <- patchinfo date name the_author []
-    let mypatch = infopatch myinfo identity
+    let mypatch = namepatch date name the_author [] identity
+        myinfo = patchinfo date name the_author []
        in do
        tentativelyAddPatch repository opts $ n2pia $ adddeps mypatch deps
        finalizeRepositoryChanges repository
hunk ./src/Darcs/Commands/Unrevert.lhs 129
         case get_common_and_uncommon (rep,rep) of
             (common,_ :\/: _) -> do
                 date <- getIsoDateTime
-                np <- namepatch date "unrevert" "anon" [] (fromRepoPrims repository p')
                 writeDocBinFile (unrevertUrl repository) $
hunk ./src/Darcs/Commands/Unrevert.lhs 130
-                             make_bundle [Unified] rec common (np :>: NilFL)
+                             make_bundle [Unified] rec common
+                            (namepatch date "unrevert" "anonymous" []
+                                           (fromRepoPrims repository p') :>: NilFL)
                 where fromRepoPrims :: RepoPatch p => Repository p C(r u t) -> FL Prim C(r y) -> p C(r y)
                       fromRepoPrims _ xs = fromPrims xs
 \end{code}
hunk ./src/Darcs/Patch/Core.lhs 104
 join_patchesFL :: FL Patch C(x y) -> Patch C(x y)
 join_patchesFL ps = ComP $! ps
 
+namepatch :: Patchy p => String -> String -> String -> [String] -> p C(x y) -> Named p C(x y)
 infopatch :: Patchy p => PatchInfo -> p C(x y) -> Named p C(x y)
 adddeps :: Named p C(x y) -> [PatchInfo] -> Named p C(x y)
 getdeps :: Named p C(x y) -> [PatchInfo]
hunk ./src/Darcs/Patch/Core.lhs 108
-
-namepatch :: Patchy p => String -> String -> String -> [String] -> p C(x y) -> IO (Named p C(x y))
 namepatch date name author desc p
     | '\n' `elem` name = error "Patch names cannot contain newlines."
hunk ./src/Darcs/Patch/Core.lhs 110
-    | otherwise = do pinf <- patchinfo date name author desc
-                     return $ NamedP pinf [] p
-
-anonymous :: Patchy p => p C(x y) -> IO (Named p C(x y))
+    | otherwise = NamedP (patchinfo date name author desc) [] p
+anonymous :: Patchy p => p C(x y) -> Named p C(x y)
 anonymous p = namepatch "today" "anonymous" "unknown" ["anonymous"] p
hunk ./src/Darcs/Patch/Core.lhs 113
-
 infopatch pi p = NamedP pi [] p
 adddeps (NamedP pi _ p) ds = NamedP pi ds p
 getdeps (NamedP _ ds _) = ds
hunk ./src/Darcs/Patch/Info.lhs 20
 
 \begin{code}
 module Darcs.Patch.Info ( PatchInfo, patchinfo, invert_name, is_inverted,
-                          idpatchinfo, add_junk,
+                          idpatchinfo,
                           make_filename, make_alt_filename, readPatchInfo,
                           just_name, just_author, repopatchinfo, RepoPatchInfo,
                           human_friendly, to_xml, pi_date, set_pi_date,
hunk ./src/Darcs/Patch/Info.lhs 28
                           showPatchInfo,
                         ) where
 import Text.Html hiding (name, text)
-import System.Random ( randomRIO )
-import Numeric ( showHex )
 import Data.List ( isPrefixOf )
 
 import FastPackedString
hunk ./src/Darcs/Patch/Info.lhs 54
                  deriving (Eq,Ord)
 
 idpatchinfo :: PatchInfo
-idpatchinfo = PatchInfo myid myid myid [] False
-    where myid = packString "identity"
+idpatchinfo = patchinfo "identity" "identity" "identity" []
 
hunk ./src/Darcs/Patch/Info.lhs 56
-patchinfo :: String -> String -> String -> [String] -> IO PatchInfo
+patchinfo :: String -> String -> String -> [String] -> PatchInfo
 patchinfo date name author log =
hunk ./src/Darcs/Patch/Info.lhs 58
-    add_junk $ PatchInfo { _pi_date = packString date
+               PatchInfo { _pi_date = packString date
                          , _pi_name = packString name
                          , _pi_author = packString author
                          , _pi_log = map packString log
hunk ./src/Darcs/Patch/Info.lhs 64
                          , is_inverted = False }
 
-add_junk :: PatchInfo -> IO PatchInfo
-add_junk pinf =
-    do x <- randomRIO (0,2^(128 ::Integer) :: Integer)
-       return $ pinf { _pi_log = packString (head ignored++showHex x ""):
-                                 ignore_junk (_pi_log pinf) }
-
 ignored :: [String] -- this is a [String] so we can change the junk header.
 ignored = ["Ignore-this: "]
 
hunk ./src/Darcs/Patch/Test.lhs 43
              ) where
 
 import Prelude hiding ( pi )
-import System.IO.Unsafe ( unsafePerformIO )
 import Test.QuickCheck
 import Control.Monad ( liftM, liftM2, liftM3, liftM4, replicateM )
 
hunk ./src/Darcs/Patch/Test.lhs 195
   where len = if n < 15 then n`div`3 else 3
 
 arbpi :: Gen PatchInfo
-arbpi = do n <- unempty
-           a <- unempty
-           l <- unempty
-           d <- unempty
-           return $ unsafePerformIO $ patchinfo n d a l
+arbpi = liftM4 patchinfo unempty unempty unempty unempty
 
 instance Arbitrary PatchInfo where
     arbitrary = arbpi
hunk ./src/Darcs/Population.lhs 43
 import Darcs.Patch ( RepoPatch, applyToPop, patchcontents, patchChanges,
                      Effect, effect )
 import Darcs.Ordered ( FL(..), RL(..), reverseRL, concatRL, mapRL )
-import Darcs.Patch.Info ( PatchInfo, idpatchinfo, to_xml )
+import Darcs.Patch.Info ( PatchInfo, patchinfo, to_xml )
 import Darcs.Patch.Set ( PatchSet )
 import Darcs.Sealed ( Sealed(..), seal, unseal )
 import Darcs.Repository ( withRepositoryDirectory, ($-), read_repo )
hunk ./src/Darcs/Population.lhs 59
 
 \begin{code}
 nullPI :: PatchInfo
-nullPI = idpatchinfo
+nullPI = patchinfo [] [] [] []
 \end{code}
 
 population of an empty repository
hunk ./src/Darcs/Repository/Internal.lhs 523
          them = mapFL_FL hopefully themi
      _ :/\: pc <- return $ merge (progressFL "Merging them" them :\/: progressFL "Merging us" us)
      pend <- get_unrecorded_unsorted r -- we don't care if it looks pretty...
-     anonpend <- anonymous (fromPrims pend)
-     pend' :/\: pw <- return $ merge (pc :\/: anonpend :>: NilFL)
+     pend' :/\: pw <- return $ merge (pc :\/: anonymous (fromPrims pend) :>: NilFL)
      let pwprim = joinPatches $ progressFL "Examining patches for conflicts" $ mapFL_FL patchcontents pw
      Sealed standard_resolved_pw <- return $ standard_resolution pwprim
      debugMessage "Checking for conflicts..."
hunk ./src/Darcs/SelectChanges.lhs 199
     Sealed pend <- if ignore_pending
                    then return $ seal (NilFL :: FL Prim C(r r))
                    else read_pending repository
-    pend_ <- n2pia `fmap` anonymous (fromPrims pend)
+    let pend_ = n2pia $ anonymous $ fromPrims pend
     sp <- without_buffering $ wspfr jn (doesnt_not_match opts)
                               (concatRL p_s) NilFL pend_
     case sp of
hunk ./src/unit.lhs 50
 
 \begin{code}
 import Control.Monad (when)
-import System.IO.Unsafe ( unsafePerformIO )
 import FastPackedString
 import Darcs.Patch
 import Darcs.Patch.Test
hunk ./src/unit.lhs 675
 test_patches_merged :: [Patch]
 valid_patches :: [Patch]
 
-test_patches_named = [unsafePerformIO $
-                      namepatch "date is" "patch name" "David Roundy" []
+test_patches_named = [namepatch "date is" "patch name" "David Roundy" []
                                 (fromPrim $ addfile "test"),
hunk ./src/unit.lhs 677
-                      unsafePerformIO $
                       namepatch "Sat Oct 19 08:31:13 EDT 2002"
                                 "This is another patch" "David Roundy"
                                 ["This log file has","two lines in it"]
[Restore issue27 patches.
Eric Kow <[EMAIL PROTECTED]>**20080926222522
 
 rolling back:
 
 Fri Sep 26 23:01:19 BST 2008  Eric Kow <[EMAIL PROTECTED]>
   * Resolve issue1102: recognise but do not generate patch log 'junk'.
   
] hunk ./src/unit.lhs 677
 
 test_patches_named = [namepatch "date is" "patch name" "David Roundy" []
                                 (fromPrim $ addfile "test"),
+                      unsafePerformIO $
                       namepatch "Sat Oct 19 08:31:13 EDT 2002"
                                 "This is another patch" "David Roundy"
                                 ["This log file has","two lines in it"]
hunk ./src/unit.lhs 675
 test_patches_merged :: [Patch]
 valid_patches :: [Patch]
 
-test_patches_named = [namepatch "date is" "patch name" "David Roundy" []
+test_patches_named = [unsafePerformIO $
+                      namepatch "date is" "patch name" "David Roundy" []
                                 (fromPrim $ addfile "test"),
                       unsafePerformIO $
                       namepatch "Sat Oct 19 08:31:13 EDT 2002"
hunk ./src/unit.lhs 50
 
 \begin{code}
 import Control.Monad (when)
+import System.IO.Unsafe ( unsafePerformIO )
 import FastPackedString
 import Darcs.Patch
 import Darcs.Patch.Test
hunk ./src/Darcs/SelectChanges.lhs 199
     Sealed pend <- if ignore_pending
                    then return $ seal (NilFL :: FL Prim C(r r))
                    else read_pending repository
-    let pend_ = n2pia $ anonymous $ fromPrims pend
+    pend_ <- n2pia `fmap` anonymous (fromPrims pend)
     sp <- without_buffering $ wspfr jn (doesnt_not_match opts)
                               (concatRL p_s) NilFL pend_
     case sp of
hunk ./src/Darcs/Repository/Internal.lhs 523
          them = mapFL_FL hopefully themi
      _ :/\: pc <- return $ merge (progressFL "Merging them" them :\/: progressFL "Merging us" us)
      pend <- get_unrecorded_unsorted r -- we don't care if it looks pretty...
-     pend' :/\: pw <- return $ merge (pc :\/: anonymous (fromPrims pend) :>: NilFL)
+     anonpend <- anonymous (fromPrims pend)
+     pend' :/\: pw <- return $ merge (pc :\/: anonpend :>: NilFL)
      let pwprim = joinPatches $ progressFL "Examining patches for conflicts" $ mapFL_FL patchcontents pw
      Sealed standard_resolved_pw <- return $ standard_resolution pwprim
      debugMessage "Checking for conflicts..."
hunk ./src/Darcs/Population.lhs 59
 
 \begin{code}
 nullPI :: PatchInfo
-nullPI = patchinfo [] [] [] []
+nullPI = idpatchinfo
 \end{code}
 
 population of an empty repository
hunk ./src/Darcs/Population.lhs 43
 import Darcs.Patch ( RepoPatch, applyToPop, patchcontents, patchChanges,
                      Effect, effect )
 import Darcs.Ordered ( FL(..), RL(..), reverseRL, concatRL, mapRL )
-import Darcs.Patch.Info ( PatchInfo, patchinfo, to_xml )
+import Darcs.Patch.Info ( PatchInfo, idpatchinfo, to_xml )
 import Darcs.Patch.Set ( PatchSet )
 import Darcs.Sealed ( Sealed(..), seal, unseal )
 import Darcs.Repository ( withRepositoryDirectory, ($-), read_repo )
hunk ./src/Darcs/Patch/Test.lhs 195
   where len = if n < 15 then n`div`3 else 3
 
 arbpi :: Gen PatchInfo
-arbpi = liftM4 patchinfo unempty unempty unempty unempty
+arbpi = do n <- unempty
+           a <- unempty
+           l <- unempty
+           d <- unempty
+           return $ unsafePerformIO $ patchinfo n d a l
 
 instance Arbitrary PatchInfo where
     arbitrary = arbpi
hunk ./src/Darcs/Patch/Test.lhs 43
              ) where
 
 import Prelude hiding ( pi )
+import System.IO.Unsafe ( unsafePerformIO )
 import Test.QuickCheck
 import Control.Monad ( liftM, liftM2, liftM3, liftM4, replicateM )
 
hunk ./src/Darcs/Patch/Info.lhs 64
                          , _pi_log = map packString log
                          , is_inverted = False }
 
+add_junk :: PatchInfo -> IO PatchInfo
+add_junk pinf =
+    do x <- randomRIO (0,2^(128 ::Integer) :: Integer)
+       return $ pinf { _pi_log = packString (head ignored++showHex x ""):
+                                 ignore_junk (_pi_log pinf) }
+
 ignored :: [String] -- this is a [String] so we can change the junk header.
 ignored = ["Ignore-this: "]
 
hunk ./src/Darcs/Patch/Info.lhs 58
 
 patchinfo :: String -> String -> String -> [String] -> PatchInfo
 patchinfo date name author log =
-               PatchInfo { _pi_date = packString date
+    add_junk $ PatchInfo { _pi_date = packString date
                          , _pi_name = packString name
                          , _pi_author = packString author
                          , _pi_log = map packString log
hunk ./src/Darcs/Patch/Info.lhs 56
 idpatchinfo :: PatchInfo
 idpatchinfo = patchinfo "identity" "identity" "identity" []
 
-patchinfo :: String -> String -> String -> [String] -> PatchInfo
+patchinfo :: String -> String -> String -> [String] -> IO PatchInfo
 patchinfo date name author log =
     add_junk $ PatchInfo { _pi_date = packString date
                          , _pi_name = packString name
hunk ./src/Darcs/Patch/Info.lhs 54
                  deriving (Eq,Ord)
 
 idpatchinfo :: PatchInfo
-idpatchinfo = patchinfo "identity" "identity" "identity" []
+idpatchinfo = PatchInfo myid myid myid [] False
+    where myid = packString "identity"
 
 patchinfo :: String -> String -> String -> [String] -> IO PatchInfo
 patchinfo date name author log =
hunk ./src/Darcs/Patch/Info.lhs 28
                           showPatchInfo,
                         ) where
 import Text.Html hiding (name, text)
+import System.Random ( randomRIO )
+import Numeric ( showHex )
 import Data.List ( isPrefixOf )
 
 import FastPackedString
hunk ./src/Darcs/Patch/Info.lhs 20
 
 \begin{code}
 module Darcs.Patch.Info ( PatchInfo, patchinfo, invert_name, is_inverted,
-                          idpatchinfo,
+                          idpatchinfo, add_junk,
                           make_filename, make_alt_filename, readPatchInfo,
                           just_name, just_author, repopatchinfo, RepoPatchInfo,
                           human_friendly, to_xml, pi_date, set_pi_date,
hunk ./src/Darcs/Patch/Core.lhs 113
     | otherwise = NamedP (patchinfo date name author desc) [] p
 anonymous :: Patchy p => p C(x y) -> Named p C(x y)
 anonymous p = namepatch "today" "anonymous" "unknown" ["anonymous"] p
+
 infopatch pi p = NamedP pi [] p
 adddeps (NamedP pi _ p) ds = NamedP pi ds p
 getdeps (NamedP _ ds _) = ds
hunk ./src/Darcs/Patch/Core.lhs 110
 getdeps :: Named p C(x y) -> [PatchInfo]
 namepatch date name author desc p
     | '\n' `elem` name = error "Patch names cannot contain newlines."
-    | otherwise = NamedP (patchinfo date name author desc) [] p
-anonymous :: Patchy p => p C(x y) -> Named p C(x y)
+    | otherwise = do pinf <- patchinfo date name author desc
+                     return $ NamedP pinf [] p
+
+anonymous :: Patchy p => p C(x y) -> IO (Named p C(x y))
 anonymous p = namepatch "today" "anonymous" "unknown" ["anonymous"] p
 
 infopatch pi p = NamedP pi [] p
hunk ./src/Darcs/Patch/Core.lhs 108
 infopatch :: Patchy p => PatchInfo -> p C(x y) -> Named p C(x y)
 adddeps :: Named p C(x y) -> [PatchInfo] -> Named p C(x y)
 getdeps :: Named p C(x y) -> [PatchInfo]
+
+namepatch :: Patchy p => String -> String -> String -> [String] -> p C(x y) -> IO (Named p C(x y))
 namepatch date name author desc p
     | '\n' `elem` name = error "Patch names cannot contain newlines."
     | otherwise = do pinf <- patchinfo date name author desc
hunk ./src/Darcs/Patch/Core.lhs 104
 join_patchesFL :: FL Patch C(x y) -> Patch C(x y)
 join_patchesFL ps = ComP $! ps
 
-namepatch :: Patchy p => String -> String -> String -> [String] -> p C(x y) -> Named p C(x y)
 infopatch :: Patchy p => PatchInfo -> p C(x y) -> Named p C(x y)
 adddeps :: Named p C(x y) -> [PatchInfo] -> Named p C(x y)
 getdeps :: Named p C(x y) -> [PatchInfo]
hunk ./src/Darcs/Commands/Unrevert.lhs 130
             (common,_ :\/: _) -> do
                 date <- getIsoDateTime
                 writeDocBinFile (unrevertUrl repository) $
-                             make_bundle [Unified] rec common
-                            (namepatch date "unrevert" "anonymous" []
-                                           (fromRepoPrims repository p') :>: NilFL)
+                             make_bundle [Unified] rec common (np :>: NilFL)
                 where fromRepoPrims :: RepoPatch p => Repository p C(r u t) -> FL Prim C(r y) -> p C(r y)
                       fromRepoPrims _ xs = fromPrims xs
 \end{code}
hunk ./src/Darcs/Commands/Unrevert.lhs 129
         case get_common_and_uncommon (rep,rep) of
             (common,_ :\/: _) -> do
                 date <- getIsoDateTime
+                np <- namepatch date "unrevert" "anon" [] (fromRepoPrims repository p')
                 writeDocBinFile (unrevertUrl repository) $
                              make_bundle [Unified] rec common (np :>: NilFL)
                 where fromRepoPrims :: RepoPatch p => Repository p C(r u t) -> FL Prim C(r y) -> p C(r y)
hunk ./src/Darcs/Commands/Tag.lhs 83
     name <- if (not . null) args
             then return $ "TAG " ++ unwords args
             else get_patchname opts
-    let mypatch = namepatch date name the_author [] identity
-        myinfo = patchinfo date name the_author []
+    myinfo <- patchinfo date name the_author []
+    let mypatch = infopatch myinfo identity
        in do
        tentativelyAddPatch repository opts $ n2pia $ adddeps mypatch deps
        finalizeRepositoryChanges repository
hunk ./src/Darcs/Commands/Rollback.lhs 137
             (name, my_log, logf) <- get_log opts newlog make_log $ invert ps''
             date <- getIsoDateTime
             my_author <- get_author opts
-            let rbp = n2pia $ namepatch date name my_author my_log $ fromPrims $ invert ps''
+            rbp <- n2pia `fmap` namepatch date name my_author my_log
+                                          (fromPrims $ invert ps'')
             debugMessage "Adding rollback patch to repository."
             Sealed pw <- tentativelyMergePatches repository "rollback" (MarkConflicts : opts)
                          NilFL (rbp :>: NilFL)
hunk ./src/Darcs/Commands/Record.lhs 389
 ask_about_depends :: RepoPatch p => Repository p -> FL Prim -> [DarcsFlag] -> IO [PatchInfo]
 ask_about_depends repository pa' opts = do
   pps <- read_repo repository
-  let pa = n2pia $ anonymous $ fromPrims pa'
-      ps = (reverseRL $ headRL pps)+>+(pa:>:NilFL)
+  pa <- n2pia `fmap` anonymous (fromPrims pa')
+  let ps = (reverseRL $ headRL pps)+>+(pa:>:NilFL)
       (pc, tps) = patch_choices_tps ps
       ta = case filter ((pa `unsafeCompare`) . tp_patch) $ unsafeUnFL tps of
                 [tp] -> tag tp
hunk ./src/Darcs/Commands/Record.lhs 209
                  when (isJust logf) $ removeFile (fromJust logf)
                  logMessage $ "Finished recording patch '"++name++"'"
     where (logMessage,_,_) = loggers opts
-          mypatch = namepatch date name my_author my_log $ fromPrims $ progressFL "Writing changes:" chs
           failuremessage = "Failed to record patch '"++name++"'" ++
                            case logf of Just lf -> "\nLogfile left in "++lf++"."
                                         Nothing -> ""
hunk ./src/Darcs/Commands/Record.lhs 200
                  -> [PatchInfo] -> FL Prim -> IO ()
 do_actual_record repository opts name date my_author my_log logf deps chs =
               do debugMessage "Writing the patch file..."
+                 mypatch <- namepatch date name my_author my_log $
+                            fromPrims $ progressFL "Writing changes:" chs
                  tentativelyAddPatch repository opts $ n2pia $ adddeps mypatch deps
                  debugMessage "Applying to pristine..."
                  withGutsOf repository (finalizeRepositoryChanges repository)
hunk ./src/Darcs/Commands/AmendRecord.lhs 153
                                         Just a  -> a
                                         Nothing -> pi_author old_pinf
                            maybe_invert = if is_inverted old_pinf then invert_name else id
-                           new_pinf = maybe_invert $ patchinfo date new_name new_author new_log
-                           newp = fixp oldp chs new_pinf
+                       new_pinf <- maybe_invert `fmap` patchinfo date new_name
+                                                                 new_author new_log
+                       let newp = fixp oldp chs new_pinf
                        defineChanges newp
                        withGutsOf repository $ do
                          tentativelyRemovePatches repository opts (hopefully oldp :>: NilFL)
hunk ./configure.ac 208
 
 dnl See if we need any packages from after the split base
 
+GHC_CHECK_MODULE(System.Random, random, randomRIO (0,10) :: IO Integer,,
+                 AC_MSG_ERROR(Cannot find System.Random; try installing the Haskell package random?))
+
 GHC_CHECK_MODULE(System.Directory, directory, doesFileExist "foo" :: IO Bool,,
                  AC_MSG_ERROR(Cannot find System.Directory; try installing the Haskell package directory?))
 GHC_CHECK_MODULE(System.Time, old-time, getClockTime :: IO ClockTime,,

Context:

[TAG 2.1.0pre2
Eric Kow <[EMAIL PROTECTED]>**20080925081049
 Ignore-this: 99b608f2401e8f14358e121e9b95e211
] 
[Move issue1078 test from bugs to tests.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080925180103
 Ignore-this: f735ee2e36bdf8f446cab61d1f7ac334
] 
[Resolve issue1078: make ioAbsolute work with symbolic links in file paths.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080925175726
 Ignore-this: af4cf0bd842b9aae5e2fffe4500a1aa5
] 
[Make FileName.drop_dotdot work with absolute paths.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080925175711
 Ignore-this: 46c625a35bb11bea19b0749756d1a225
] 
[Force hidden conflicts test to use the darcs-2 format.
Eric Kow <[EMAIL PROTECTED]>**20080925175251
 Move it to the tests directory because it passes if we do
 this.  We consider this to be a bug that is solved by using
 the darcs 2 format.
] 
[Use init+pull instead of get in issue27 test.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080925142606
 Ignore-this: e8be404b0ccbc56d8f547b11b6e58c76
 This would hopefully make it pass on NFS.
] 
[Exceptions to GPL granted as of 2008-09-11.
Eric Kow <[EMAIL PROTECTED]>**20080911120758] 
[Update manual to reflect --darcs-2 default.
Eric Kow <[EMAIL PROTECTED]>**20080925142538] 
[resolve issue1003: don't sever transfer-mode connection on IO error.
David Roundy <[EMAIL PROTECTED]>**20080925145150
 Ignore-this: 3aecb8cffa83170847b0a2452c5763f0
 There was a bug in Ssh, in which unless the very first file we access
 on a given server was present, we severed the connection.  This fixes
 that bug.
] 
[preliminary hoogle indexing
Simon Michael <[EMAIL PROTECTED]>**20080925084432
 If haddock and hoogle are installed, "make hoogle" generates api-doc/main.hoo.
 Use it at the command-line like so: hoogle --data=api-doc/main.hoo something
] 
[simplify patches in rollback.
David Roundy <[EMAIL PROTECTED]>**20080923150619
 Ignore-this: fd3d327f800e2f1799ec97bc4524f612
 This makes it nicer to incrementally rollback changes from one large
 change:  you aren't prompted for changes that have already been rolled
 back.
] 
[Bump version number to 2.1.0pre2.
Eric Kow <[EMAIL PROTECTED]>**20080925081019
 Ignore-this: 9d1aa701ce0b8cfc87007216207166fe
 It was initially planned that the upcoming release be called 2.0.3, but
 since we are initializing darcs-2 format repositories by default, we are
 bumping the version number higher.
] 
[ChangeLog entries for 2.1.0pre2
Eric Kow <[EMAIL PROTECTED]>**20080925080141
 Ignore-this: 1b1e57d425f8528e00e03e7b4a23ad78
] 
[ChangeLog entries: more stuff to ignore
Eric Kow <[EMAIL PROTECTED]>**20080925080129
 Ignore-this: 45362ed8bbabdacf222928cba6756aa4
] 
[resolve issue805: make darcs-2 format the default for new repositories.
David Roundy <[EMAIL PROTECTED]>**20080924141158
 Ignore-this: e7952cb0cdc3124ffa50b0775822000e
] 
[make flagsToPristine obey repository format.
David Roundy <[EMAIL PROTECTED]>**20080924135319
 Ignore-this: 6038a7d05126af9e446406022ca608a0
 This reduces the number of places we set the default repository format
 (hopefully to one?).
] 
[More readable length comparison.
Eric Kow <[EMAIL PROTECTED]>**20080924142304] 
[Haddock some primitive patch functions.
Eric Kow <[EMAIL PROTECTED]>**20080924142157] 
[move issue27 test to bugs directory, since it fails.
David Roundy <[EMAIL PROTECTED]>**20080923215936
 Ignore-this: 4556b273a9f8728de8ac855aae8442d0
] 
[Add test for issue27.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080918135923] 
[give more useful failure message in HTTP for proxy errors.
David Roundy <[EMAIL PROTECTED]>**20080923153400
 Ignore-this: 3d6d204da399175eedf68bedfed8e504
] 
[HTTP: detect proxy server (failing if we want one)
Eric Kow <[EMAIL PROTECTED]>**20080923123539
 The HTTP package has proxy server support, but putting it to use seems
 to be complicated.  Since fetchUrl seems to be used only in optional
 situations, it seems safe to just return an error message (as opposed
 to waiting around for a timeout).
] 
[fix filepath code to work with FilePath package that preceded filepath.
[EMAIL PROTECTED]
 Ignore-this: 6aa0d8b357b0f966403ebe5965dcdec4
] 
[fix type witness bug in createRepository.
David Roundy <[EMAIL PROTECTED]>**20080922234321
 Ignore-this: 2c50393ca25740ce3e210dd24fe8d8fa
] 
[simplify fix for issue1041.
David Roundy <[EMAIL PROTECTED]>**20080922233019
 Ignore-this: a3002e9bba5271790c62ac634e08f472
 It turns out that the simple solution works once a bug in the
 conflict-doppleganger test was fixed!
] 
[translate conflict-doppleganger test to bash.
David Roundy <[EMAIL PROTECTED]>**20080922232839
 Ignore-this: de2a050022dea4251cdc2cc5e8b55c8c
] 
[remove test_unit from disttest to speed things up.
David Roundy <[EMAIL PROTECTED]>**20080922225355
 Ignore-this: b3b21bcd3fa72c8d602b5bd0e601021a
 The unit test is only affected by very rarely-modified code, and it's
 overkill to run it absolutely every single time we push code
 (particularly as it sometimes takes exponentially long to generate its
 test cases).
] 
[resolve issue1041: add test for issue1041.
David Roundy <[EMAIL PROTECTED]>**20080922183320
 Ignore-this: 5a6330158d16a24d45f58268c0edb823
 Note that this issue was actually resolved by Vlad Dogaru.  I just
 wrote the test.
] 
[Get: if URL is invalid, direcotry is not created (#1041)
Vlad Dogaru <[EMAIL PROTECTED]>**20080922171705] 
[Add a test case for issue1078
Eric Kow <[EMAIL PROTECTED]>**20080923081757
 Ignore-this: 33f7f1f63c7b707ff148531f8229ceb0
] 
[Translate mark-conflicts test into shell.
Eric Kow <[EMAIL PROTECTED]>**20080922224858
 It was failing because it expects init to be completely silent.  Since we
 were going to tweak it anyway, we might as well simplify the script.
] 
[Stop calling the darcs-2 format experimental.
Eric Kow <[EMAIL PROTECTED]>**20080922221024] 
[Move repository creation to Darcs.Repository.
Eric Kow <[EMAIL PROTECTED]>**20080922215913
 This is just to avoid importing the DarcsRepo and HashedRepo code in higher
 level code.
] 
[Resolve conflict between replace patches in Darcs.Arguments
Eric Kow <[EMAIL PROTECTED]>**20080922202647] 
[Resolve issue53: check for windows filename validity in darcs add/mv.
Eric Kow <[EMAIL PROTECTED]>**20080922172004] 
[Use --reserved-ok to allow a file with ':' in it in tests.
Eric Kow <[EMAIL PROTECTED]>**20080922171519
 It's likely that this test will just fail under Windows and
 we will have to disable it.
] 
[Add test for issue53.
Eric Kow <[EMAIL PROTECTED]>**20080922152256] 
[Add --reserved-ok flag for darcs add and mv.
Eric Kow <[EMAIL PROTECTED]>**20080922141532
 This is just the flag, not the actual effect.
] 
[Check for filepath package in configure.
Eric Kow <[EMAIL PROTECTED]>**20080922140520] 
[Replace --without-docs with less ambiguous --without-manual (issue1082).
Trent W. Buck <[EMAIL PROTECTED]>**20080922002602
 It's confusing for ./configure --without-docs to complain about missing haddock.
] 
[Documentation for --allow-unrelated-repos.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080922121122
 Ignore-this: d2630826313c8aeb00acb6853030c22d
] 
[Rename --ignore-unrelated-repos to --allow-unrelated-repos.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080922120727
 Ignore-this: a5990f1741c867316a948e6721118651
] 
[fix  bug I introduced into issue1039 test.
David Roundy <[EMAIL PROTECTED]>**20080921213043
 Ignore-this: 5b3c6476abae6bb050be014555d05bbe
] 
[Fix hang after a user input error (for example, EOF).
Judah Jacobson <[EMAIL PROTECTED]>**20080918163017] 
[replace consRLSealed with a more  general mapFlipped.
David Roundy <[EMAIL PROTECTED]>**20080921185241
 Ignore-this: c28f73f165254582cba6a14ba6ce93
] 
[make issue1039 fix allow small dissimilar  repositories.
David Roundy <[EMAIL PROTECTED]>**20080921184515
 Ignore-this: 918a09df18ef48c649c1bfaa866d6176
] 
[revert refactor that breaks type witnesses.
David Roundy <[EMAIL PROTECTED]>**20080921182331
 Ignore-this: dd692cffc1a238d6726448bacfe9cacc
] 
[Add '--ignore-unrelated-repos' option to disable unrelated repositories check.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919152631] 
[Resolve issue1039: detect seemingly unrelated repositories when doing push, pull and send.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919144553] 
[Refactor in pull_cmd.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919135349
 Ignore-this: e26a489a7a53aeaba544ae5ad0006700
] 
[Test for issue1039.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919153011] 
[manual: add an example of record --pipe prompts similar to tag --pipe docs
Simon Michael <[EMAIL PROTECTED]>**20080918205353] 
[user manual corrections regarding what record and tag --pipe prompt for
Simon Michael <[EMAIL PROTECTED]>**20080918204500] 
[clarify the short help for --pipe
Simon Michael <[EMAIL PROTECTED]>**20080918193717] 
[Spaces in Darcs.Arguments.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919150440] 
[Spaces in Darcs.Commands.Send.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919150139] 
[Spaces in Darcs.Commands.Pull.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919145812] 
[Spaces in Darcs.Commands.Push.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919145553] 
[Print "We have the following patches to send:" only when we really have somthing to send.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080919114229] 
[Use gmakeisms for prettier output.
Trent W. Buck <[EMAIL PROTECTED]>**20080919071358] 
[fix changes.pl test (translating to bash)
David Roundy <[EMAIL PROTECTED]>**20080917182432
 Ignore-this: 5f8bc7e1f9eadc073402a935142281c4
 This test made assumptions such as that darcs wouldn't ever add a long
 comment to its internal representation of changes, which are now
 broken.
] 
[hokey fix to allow unit tests to generate random input.
David Roundy <[EMAIL PROTECTED]>**20080917170913
 Ignore-this: 31e847e82eef741f4c6cc857fd79a245
 A nicer fix would be to move namepatch and patchinfo into some sort of
 random-number monad rather than leaving them in IO and using
 unsafePerformIO in the example-generation scripts.
] 
[resolve issue27: add junk to patch identifiers.
David Roundy <[EMAIL PROTECTED]>**20080917154657
 Ignore-this: b91ab6f6e05e0fda25488fa51653b741
] 
[TAG 2.0.3pre1
Eric Kow <[EMAIL PROTECTED]>**20080918023645] 
Patch bundle hash:
59dab0b43a1502f98a4cf8a0748d41effe7c920f
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to