[darcs-users] darcs patch: Add LANGUAGE pragmas for explicit langua... (and 3 more)

Reinier Lamers tux_rocker at reinier.de
Fri Oct 31 22:06:15 UTC 2008


On Wednesday 29 October 2008 03:39:14 David Roundy wrote:
> > Sun Oct 26 16:40:09 GMT 2008  tux_rocker at reinier.de
> >   * add a get_unrecorded_in_files to check for unrecorded changes in a
> > subset of working directory
> >
> > Sun Oct 26 19:06:12 GMT 2008  tux_rocker at reinier.de
> >   * make get_unrecorded_private work with type witnesses again
> >
> > Sun Oct 26 19:46:36 GMT 2008  tux_rocker at reinier.de
> >   * make whatsnew use the lstat-saving functions to scan the working copy
>
> These look very appealing, and have some nice ideas, but are also buggy. 
> :(

Here's a patch on top of these that removes the bugs you saw. It moves the 
unsafeness deeper inward: the juggling with Sealed goes from WhatsNew.lhs to 
Internal.lhs, the concatenation of primitive patches goes from Internal.lhs to 
Diff.lhs.

If you review this patch, please also watch carefully if I get the stuff with 
the Seal's right in Internal.lhs. It took some restructuring to make the type 
checker happy.

Regards,
Reinier


-------------- next part --------------
Fri Oct 31 22:59:44 CET 2008  Reinier Lamers <tux_rocker at reinier.de>
  * hopefully less buggy version of get_unrecorded_in_files

New patches:

[hopefully less buggy version of get_unrecorded_in_files
Reinier Lamers <tux_rocker at reinier.de>**20081031215944
 Ignore-this: 9f4f2320a1784cf6f7546ab23eb6bf61
] hunk ./src/Darcs/Commands/WhatsNew.lhs 39
                         list_registered_files,
                       )
 import Darcs.Arguments ( summary )
-import Darcs.Patch.TouchesFiles ( choose_touching )
-import Darcs.RepoPath ( toFilePath, sp2fn )
+import Darcs.RepoPath ( sp2fn )
 import Darcs.Repository ( Repository, withRepository, ($-), slurp_recorded,
                           get_unrecorded_no_look_for_adds, 
                           get_unrecorded_in_files, amInRepository )
hunk ./src/Darcs/Commands/WhatsNew.lhs 45
 import Darcs.Repository.Prefs ( filetype_function )
 import Darcs.Diff ( smart_diff )
-import Darcs.Patch ( RepoPatch, Prim, summarize, apply_to_slurpy, is_hunk,
-                     invert, apply_to_filepaths )
+import Darcs.Patch ( RepoPatch, Prim, summarize, apply_to_slurpy, is_hunk )
 import Darcs.Patch.Permutations ( partitionRL )
 import Darcs.Patch.Real ( RealPatch, prim2real )
 import Darcs.PrintPatch ( printPatch, contextualPrintPatch )
hunk ./src/Darcs/Commands/WhatsNew.lhs 50
 import Darcs.Ordered ( FL(..), mapFL_FL, reverseRL, reverseFL, (:>)(..), nullFL )
-import Darcs.Sealed ( Sealed(..), unseal, mapSeal )
 import Printer ( putDocLn, renderString, vcat, text )
 #include "impossible.h"
 \end{code}
hunk ./src/Darcs/Commands/WhatsNew.lhs 106
     chold <- get_unrecorded_no_look_for_adds repository (map sp2fn files)
     s <- slurp_recorded repository
     ftf <- filetype_function
-    let pre_changed_files = apply_to_filepaths (invert chold) $ map toFilePath files
-        select_files = choose_touching pre_changed_files
-    Sealed cho <- return $ select_files chold
-    cho_adds :> _ <- return $ partitionRL is_hunk $ reverseFL cho
-    Sealed all_fs <- return $ select_files all_changes
-    cha :> _ <- return $ partitionRL is_hunk $ reverseFL all_fs
+    cho_adds :> _ <- return $ partitionRL is_hunk $ reverseFL chold
+    cha :> _ <- return $ partitionRL is_hunk $ reverseFL all_changes
     let chn    = smart_diff [LookForAdds,Summary] ftf
                             (fromJust $ apply_to_slurpy (reverseRL cho_adds) s)
                             (fromJust $ apply_to_slurpy (reverseRL cha) s)
hunk ./src/Darcs/Commands/WhatsNew.lhs 111
-    exitOnNoChanges (chn, cho)
-    putDocLn $ summarize cho
+    exitOnNoChanges (chn, chold)
+    putDocLn $ summarize chold
     printSummary chn
     where lower_as x = vcat $ map (text . l_as) $ lines x
           l_as ('A':x) = 'a':x
hunk ./src/Darcs/Commands/WhatsNew.lhs 131
          putStrLn $ "What's new in "++unwords (map show files)++":\n"
     changes <- get_unrecorded_in_files repository (map sp2fn files)
     when (nullFL changes) $ putStrLn "No changes!" >> (exitWith $ ExitFailure 1)
-    let pre_changed_files = apply_to_filepaths (invert changes) $ map toFilePath files
-    unseal (printSummary repository) $ mapSeal (mapFL_FL prim2real) $ choose_touching pre_changed_files changes
+    printSummary repository $ mapFL_FL prim2real changes
        where printSummary :: RepoPatch p => Repository p C(r u t) -> FL RealPatch C(r y) -> IO ()
              printSummary _ NilFL = do putStrLn "No changes!"
                                        exitWith $ ExitFailure 1
hunk ./src/Darcs/Diff.lhs 26
 
 #include "gadts.h"
 
-module Darcs.Diff ( diff_at_path, smart_diff, sync, cmp
+module Darcs.Diff ( unsafeDiffAtPaths, smart_diff, sync, cmp
 #ifndef GADT_WITNESSES
                   , diff_files
 #endif
hunk ./src/Darcs/Diff.lhs 41
 import Control.Monad ( liftM, when )
 import Data.List ( sort
 #ifndef GADT_WITNESSES
-                 , intersperse
+                 , intersperse, isPrefixOf
 #endif
                  )
hunk ./src/Darcs/Diff.lhs 44
+#ifndef GADT_WITNESSES
+import Data.Maybe ( catMaybes )
+#endif
 
 import FastPackedString ( hGetPS, lengthPS
 #ifndef GADT_WITNESSES
hunk ./src/Darcs/Diff.lhs 92
 #include "impossible.h"
 #endif
 
--- | The diff_at_path function compares what two slurpies have at a certain
---   location.  This is useful when the user requests a diff for a file that
---   is created or removed in the working copy: then there is no slurpy for
---   the file in the /current/ or /working/ slurpy respectively.
+-- | The unsafeDiffAtPaths function calls diff_at_path for a set of files and 
+--   returns all changes to those files. It does *not* explore the given paths
+--   recursively.
+--
+--   Comparing paths and not slurpies is useful when the user
+--   requests a diff for a file that is created or removed in the working copy:
+--   then there is no slurpy for the file in the /current/ or /working/ slurpy
+--   respectively.
 --
 --   The given paths must always be fixed repository paths starting with a
hunk ./src/Darcs/Diff.lhs 102
---   ".".
---   
---   It returns Nothing if there is nothing at the given location in both
---   slurpies, and the differences between what's there in the slurpies in
---   all other cases.
-diff_at_path :: [DarcsFlag] -> (FilePath -> FileType) ->
-                    Slurpy -> Slurpy -> FilePath -> Maybe (FL Prim C(x y))
+--   ".". It is safe to pass overlapping paths.
+--
+--   The booleans in the first argument tell whether to ignore mtimes, whether
+--   we must look for additions and if we're diffing for a summary only.
+--
+--   It returns an FL of patches, that contains all the changes that have been
+--   made at all those paths.
+unsafeDiffAtPaths :: (Bool, Bool, Bool) -> (FilePath -> FileType) ->
+               Slurpy -> Slurpy -> [FilePath] -> FL Prim C(x y)
 #ifdef GADT_WITNESSES
hunk ./src/Darcs/Diff.lhs 112
-diff_at_path = undefined
+unsafeDiffAtPaths = undefined
 #else
hunk ./src/Darcs/Diff.lhs 114
-diff_at_path opts filetypeFunction s1 s2 path =
-    let pathIn1 = get_slurp (fp2fn path) s1 
-        pathIn2 = get_slurp (fp2fn path) s2 in
+unsafeDiffAtPaths flags filetypeFunction s1 s2 paths = 
+    foldr (+>+) NilFL (catMaybes diffsPerPath)
+  where diffsPerPath = map differ safePaths 
+        differ       = diff_at_path flags filetypeFunction s1 s2
+        safePaths    = make_nonoverlapping_path_set paths
+
+diff_at_path :: (Bool, Bool, Bool) -> (FilePath -> FileType)
+                -> Slurpy -> Slurpy -> FilePath -> Maybe (FL Prim)
+diff_at_path (ignoreTimes, lookForAdds, summary) filetypeFunction s1 s2 path =
     case (pathIn1, pathIn2) of
         (Nothing, Nothing) -> Nothing
hunk ./src/Darcs/Diff.lhs 125
-        (Nothing, Just s2LocationSlurpy) -> do
-            Just $ diff_added summary filetypeFunction initialFps s2LocationSlurpy NilFL
-        (Just s1LocationSlurpy, Nothing) -> do
-            Just $ diff_removed filetypeFunction initialFps s1LocationSlurpy NilFL
-        (Just s1LocationSlurpy, Just s2LocationSlurpy) ->
-            Just $ gendiff (ignore_times, look_for_adds, summary) filetypeFunction 
-                           initialFps s1LocationSlurpy s2LocationSlurpy NilFL
-  where ignore_times = IgnoreTimes `elem` opts
-        look_for_adds = LookForAdds `elem` opts
-        -- NoSummary/Summary both present gives False
-        -- Just Summary gives True
-        -- Just NoSummary gives False
-        -- Neither gives False
-        summary = Summary `elem` opts && NoSummary `notElem` opts
+        (Nothing, Just s2PathSlurpy) -> do
+            Just $ diff_added summary filetypeFunction initialFps s2PathSlurpy NilFL
+        (Just s1PathSlurpy, Nothing) -> do
+            Just $ diff_removed filetypeFunction initialFps s1PathSlurpy NilFL
+        (Just s1PathSlurpy, Just s2PathSlurpy) -> 
+            Just $ gendiff (ignoreTimes, lookForAdds, summary) filetypeFunction              
+                           initialFps s1PathSlurpy s2PathSlurpy NilFL
+  where pathIn1 = get_slurp (fp2fn path) s1 
+        pathIn2 = get_slurp (fp2fn path) s2
         initialFps = tail $ reverse (breakup path)
hunk ./src/Darcs/Diff.lhs 135
+
+make_nonoverlapping_path_set :: [FilePath] -> [FilePath]
+make_nonoverlapping_path_set = map unbreakup . delete_overlapping . map breakup . sort
+  where
+    delete_overlapping :: [[FilePath]] -> [[FilePath]]
+    delete_overlapping (p1:p2:ps) = if p1 `isPrefixOf` p2
+                                      then delete_overlapping (p1:ps)
+                                      else p1 : delete_overlapping (p2:ps)
+    delete_overlapping ps         = ps
+    unbreakup = concat . intersperse "/"
 #endif
 
 \end{code}
hunk ./src/Darcs/Diff.lhs 161
 smart_diff = undefined
 #else
 smart_diff opts wt s1 s2
-    = case diff_at_path opts wt s1 s2 "" of
+    = case diff_at_path (ignoreTimes, lookForAdds, summary)  wt s1 s2 "" of
           Just d -> d
           _      -> impossible -- because "" always exists in a slurpy 
hunk ./src/Darcs/Diff.lhs 164
+  where -- NoSummary/Summary both present gives False
+        -- Just Summary gives True
+        -- Just NoSummary gives False
+        -- Neither gives False
+        summary = Summary `elem` opts && NoSummary `notElem` opts
+        lookForAdds = LookForAdds `elem` opts
+        ignoreTimes = IgnoreTimes `elem` opts
 
 mk_filepath :: [FilePath] -> FilePath
 mk_filepath fps = concat $ intersperse "/" $ reverse fps
hunk ./src/Darcs/Diff.lhs 179
         -> (FilePath -> FileType) -> [FilePath] -> Slurpy -> Slurpy
         -> (FL Prim -> FL Prim)
 gendiff opts@(isparanoid,_,_) wt fps s1 s2
-    | is_file s1 && is_file s2 && maybe_differ =
-          case wt n2 of
-          TextFile -> diff_files f b1 b2
-          BinaryFile -> if b1 /= b2 then (binary f b1 b2:>:)
-                                    else id
+    | is_file s1 && is_file s2 = diff_regular_files isparanoid wt f s1 s2
     | is_dir s1 && is_dir s2 =
           let fps' = case n2 of
                          "." -> fps
hunk ./src/Darcs/Diff.lhs 188
     | otherwise = id
     where n2 = slurp_name s2
           f = mk_filepath (n2:fps)
-          b1 = get_filecontents s1
-          b2 = get_filecontents s2
           dc1 = get_dircontents s1
           dc2 = get_dircontents s2
hunk ./src/Darcs/Diff.lhs 190
-          maybe_differ = isparanoid
-                      || get_mtime s1 == undefined_time
-                      || get_mtime s1 /= get_mtime s2
-                      || get_length s1 == undefined_size
-                      || get_length s1 /= get_length s2
 
 -- recur_diff or recursive diff
 -- First parameter is (IgnoreTimes?, LookforAdds?, Summary?)
hunk ./src/Darcs/Diff.lhs 214
 recur_diff (_,False,_) _ _ [] _ = id
 recur_diff _ _ _ _ _ = impossible
 
+-- diff, taking into account paranoidness and file type, two regular files
+diff_regular_files :: Bool -> (FilePath -> FileType) -> FilePath -> Slurpy -> Slurpy -> (FL Prim -> FL Prim)
+diff_regular_files ignoreTimes filetypeFunction f s1 s2 = 
+    if maybe_differ   
+        then case filetypeFunction (slurp_name s2) of                                     
+               TextFile -> diff_files f b1 b2                    
+               BinaryFile -> if b1 /= b2 then (binary f b1 b2:>:)
+                                         else id                 
+        else id
+  where maybe_differ = ignoreTimes
+                     || get_mtime s1 == undefined_time
+                     || get_mtime s1 /= get_mtime s2
+                     || get_length s1 == undefined_size
+                     || get_length s1 /= get_length s2
+        b1 = get_filecontents s1
+        b2 = get_filecontents s2
+
 -- creates a diff for a file or directory which needs to be added to the
 -- repository
 diff_added :: Bool -> (FilePath -> FileType) -> [FilePath] -> Slurpy
hunk ./src/Darcs/Repository/Internal.lhs 57
 
 import Printer ( putDocLn, (<+>), text, ($$) )
 
-import Data.Maybe ( isJust, isNothing, catMaybes )
+import Data.Maybe ( isJust, isNothing )
 import Darcs.Repository.Prefs ( get_prefval )
 import Darcs.Resolution ( standard_resolution, external_resolution )
 import System.Exit ( ExitCode(..), exitWith )
hunk ./src/Darcs/Repository/Internal.lhs 82
 import FastPackedString ( PackedString, readFilePS, gzReadFilePS, nilPS, packString, takePS )
 import Darcs.Patch ( Patch, RealPatch, Effect, is_hunk, is_binary, description,
 
-                     try_to_shrink, commuteFL, commute )
+                     try_to_shrink, commuteFL, commute, apply_to_filepaths )
 import Darcs.Patch.Prim ( try_shrinking_inverse, Conflict )
 import Darcs.Patch.Bundle ( scan_bundle, make_bundle )
 import Darcs.Patch.FileName ( FileName, fn2fp )
hunk ./src/Darcs/Repository/Internal.lhs 86
+import Darcs.Patch.TouchesFiles ( choose_touching )
 import Darcs.SlurpDirectory ( Slurpy, slurp_unboring, mmap_slurp, co_slurp,
                               slurp_has, list_slurpy_files )
 import Darcs.Hopefully ( PatchInfoAnd, info, n2pia,
hunk ./src/Darcs/Repository/Internal.lhs 106
 import Darcs.Flags ( DarcsFlag(AnyOrder, Boring, LookForAdds, Verbose, Quiet,
                                MarkConflicts, AllowConflicts, NoUpdateWorking,
                                RepoDir, WorkDir, UMask, Test, LeaveTestDir,
-                               SetScriptsExecutable, DryRun, IgnoreTimes ),
+                               SetScriptsExecutable, DryRun, IgnoreTimes,
+                               Summary, NoSummary),
                      want_external_merge, compression )
 import Darcs.Ordered ( FL(..), RL(..), EqCheck(..), unsafeCoerceP,
                              (:\/:)(..), (:/\:)(..), (:>)(..),
hunk ./src/Darcs/Repository/Internal.lhs 133
 import Darcs.Patch.Set ( PatchSet, SealedPatchSet )
 import Darcs.Patch.Apply ( markup_file, LineMark(None) )
 import Darcs.Patch.Depends ( get_common_and_uncommon, deep_optimize_patchset )
-import Darcs.Diff ( diff_at_path, smart_diff )
+import Darcs.Diff ( unsafeDiffAtPaths, smart_diff )
 import Darcs.RepoPath ( FilePathLike, AbsolutePath, toFilePath )
 import Darcs.Utils ( promptYorn, catchall, withCurrentDirectory, withUMask, nubsort )
 import Darcs.Progress ( progressFL, debugMessage )
hunk ./src/Darcs/Repository/Internal.lhs 405
 -- | The /unrecorded/ includes the pending and the working directory changes.
 --   The third argument is a list of paths: if this list is [], it will diff
 --   the whole repo, but if there are elements in it, the function will return
---   only changes to files under those paths.
+--   only changes to files under those paths. The paths must be fixed paths 
+--   starting with ".", but need not yet be unique.
 get_unrecorded_private :: RepoPatch p => ([DarcsFlag]->[DarcsFlag]) -> Repository p C(r u t) -> [FileName] -> IO (FL Prim C(r y))
 get_unrecorded_private _ (Repo _ opts _ _) _
     | NoUpdateWorking `elem` opts = return $ unsafeCoerceP NilFL
hunk ./src/Darcs/Repository/Internal.lhs 422
             else co_slurp cur "."
     ftf <- filetype_function
     Sealed pend <- read_pending repository
+    let changed_files = apply_to_filepaths pend filesFP
+        pre_changed_files = apply_to_filepaths (invert pend) filesFP
+    Sealed relevantPend <- return $ if null files
+                                      then seal pend
+                                      else choose_touching pre_changed_files pend
     debugMessage "diffing dir..."
hunk ./src/Darcs/Repository/Internal.lhs 428
-    -- the unsafeCoerceP below is necessary to be able to concatenate
-    -- pend with NilFL to form dif. See http://hpaste.org/11480
     let diffs = if null files
                   then smart_diff opts ftf cur work
hunk ./src/Darcs/Repository/Internal.lhs 430
-                  else let diffsPerFile = catMaybes (map (diff_at_path opts ftf cur work) (map fn2fp files)) 
-                       in foldr (+>+) (unsafeCoerceP NilFL) diffsPerFile
+                  else unsafeDiffAtPaths (ignoreTimes, lookForAdds, summary) ftf cur work changed_files
         dif = if AnyOrder `elem` opts
hunk ./src/Darcs/Repository/Internal.lhs 432
-                  then pend +>+ diffs
-                  else sort_coalesceFL $ pend +>+ diffs
+                  then relevantPend +>+ diffs
+                  else sort_coalesceFL $ relevantPend +>+ diffs
     seq dif $ debugMessage "Found unrecorded changes."
     return dif)
     where myfilt s nboring f = slurp_has f s || nboring [f] /= []
hunk ./src/Darcs/Repository/Internal.lhs 438
           opts = modopts oldopts
+          -- NoSummary/Summary both present gives False
+          -- Just Summary gives True
+          -- Just NoSummary gives False
+          -- Neither gives False
+          summary = Summary `elem` opts && NoSummary `notElem` opts
+          lookForAdds = LookForAdds `elem` opts
+          ignoreTimes = IgnoreTimes `elem` opts
+          filesFP = map fn2fp files
 
 -- @todo: we should not have to open the result of HashedRepo and
 -- seal it.  Instead, update this function to work with type witnesses

Context:

[quickCheck tests  for QuickCheck 2.1
Florent Becker <florent.becker at ens-lyon.org>**20081006135708] 
[make whatsnew use the lstat-saving functions to scan the working copy
tux_rocker at reinier.de**20081026194636
 Ignore-this: 54b7a07b7b1d49b3d20050bc905db665
] 
[make get_unrecorded_private work with type witnesses again
tux_rocker at reinier.de**20081026190612
 Ignore-this: 97418e6487ef9c9508473d4c65f295ca
] 
[add a get_unrecorded_in_files to check for unrecorded changes in a subset of working directory
tux_rocker at reinier.de**20081026164009
 Ignore-this: 7d36ff983e8745049101a92f5b2326fb
] 
[replace insanely low level version of ifHeadThenTail with uncons
Don Stewart <dons at galois.com>**20081026231745
 Ignore-this: 5e5e344762762b49da5f4bf835a4a869
] 
[Remove dead code: reversePS
Don Stewart <dons at galois.com>**20081026002812
 Ignore-this: 9b8b888551f3c44f59bfb83c37beec69
] 
[add exception to haskell_policy.sh for Data.ByteString.readFile
Jason Dagit <dagit at codersbase.com>**20081026004929] 
[Fixup LANGUAGE pragmas for the sake of ghc6.6
Jason Dagit <dagit at codersbase.com>**20081028015457] 
[Add -fno-warn-name-shadowing
Don Stewart <dons at galois.com>**20081025231134] 
[Add LANGUAGE pragmas for explicit language extensions
Don Stewart <dons at galois.com>**20081025230140] 
[Add LANGUAGE extensions for explicit language extensions
Don Stewart <dons at galois.com>**20081025225922] 
[Add LANGUAGE pragmas for explicit language extensions
Don Stewart <dons at galois.com>**20081025225900] 
[Add LANGUAGE pragmas for explicit language extensions
Don Stewart <dons at galois.com>**20081025225709] 
[use fmap in Darcs.Utils
Jason Dagit <dagit at codersbase.com>**20081028065217
 Ignore-this: 326fcc3a02607e3fd7b65a5e39468514
] 
[use fmap in DateMatcher
Jason Dagit <dagit at codersbase.com>**20081028065038
 Ignore-this: a5a60e0ce67713b48aa7813cf46e41f3
] 
[use fmap in list_authors.hs
Jason Dagit <dagit at codersbase.com>**20081028064846
 Ignore-this: 81c1321396a1a6f46b17899bcc60925
] 
[add one more Functor instance
Jason Dagit <dagit at codersbase.com>**20081028063511
 Ignore-this: 90f8762fcb3abab8209084a1d07c9bc4
] 
[add more Functor instances
Jason Dagit <dagit at codersbase.com>**20081028063419
 Ignore-this: a248acfbae7091e84ab783920bac61ec
] 
[add some Functor instances
Jason Dagit <dagit at codersbase.com>**20081028063336
 Ignore-this: 9f27cd23a8a10bf8e0205c1d6e9f4a7c
] 
[use fmap in Compat
Jason Dagit <dagit at codersbase.com>**20081028060001
 Ignore-this: 2c8082a0d040b5834f28b542f66a61f4
] 
[use fmap in Commands.Tag
Jason Dagit <dagit at codersbase.com>**20081028055832
 Ignore-this: c05385bac706f19e409d6816adaa48ca
] 
[use fmap in Commands.Replace
Jason Dagit <dagit at codersbase.com>**20081028055646
 Ignore-this: 112359c5dbcc9a4a5a0a371861c3b00d
] 
[use fmap in Commands.Optimize
Jason Dagit <dagit at codersbase.com>**20081028055538
 Ignore-this: 762297167e5b79f3a2cddea16c405ad8
] 
[use fmap in Commands.Diff
Jason Dagit <dagit at codersbase.com>**20081028055417
 Ignore-this: fe413212ee228f5336352875c794d661
] 
[use fmap in Commands.Add
Jason Dagit <dagit at codersbase.com>**20081028055224
 Ignore-this: a9c7999d262b71aae8925941bc48fbc9
] 
[use fmap in ArgumentDefaults
Jason Dagit <dagit at codersbase.com>**20081028055040
 Ignore-this: 9b24af71ff643fbc883e8bf5c499c6d8
] 
[add some haddock to get_slurp_context_*
Ganesh Sittampalam <ganesh at earth.li>**20081025150927] 
[remove export of read_pending.
David Roundy <droundy at darcs.net>**20081028014338
 Ignore-this: 3d66fe67d0630eca0050540863d27536
 This is an ugly function that is hard to use correctly, so it seems best
 not to export it.
] 
[cut unused argument to with_selected_patch_from_repo.
David Roundy <droundy at darcs.net>**20081028014244
 Ignore-this: 538ce58d90829bfdc8050c5fa61382af
] 
["make continuous" or "make ci" rebuilds darcs whenever files change 
Simon Michael <simon at joyful.com>**20081027070341
 Ignore-this: 10d7c3097310b08b93c3e70fadda9005
 Leave this running in a side window, or in a emacs
 compilation/comint-minor-mode buffer, to get rapid feedback from GHC as
 you edit code. Useful! Requires a patched version of searchpath, see
 makefile.
] 
[resolve issue0839: enable global cache by default
Simon Michael <simon at joyful.com>**20081026225004
 Ignore-this: 50deab104a57c707bfaf4e00a00c69cb
] 
[refactor get_global, make it more cross-platform
Simon Michael <simon at joyful.com>**20081026220354
 Ignore-this: 1d7f456379a3ea9fe08598e96fe700e6
 get_global fetches global preferences from the user's ~/.darcs directory.
 This patch uses the more portable getAppUserDataDirectory, so global
 prefs will work on windows without requiring a HOME environment
 variable, and will be stored in the standard windows app data dir
 (eg C:/Documents And Settings/user/Application Data/darcs).
 Cf http://hackage.haskell.org/trac/ghc/ticket/1838 .
 It also reduces the use of error-hiding catchall.
] 
[explain global cache a little more clearly
Simon Michael <simon at joyful.com>**20081026171125
 Ignore-this: 73b47bfa1508641d044a0d2bf2e6405e
] 
[resolve issue1046: record nothing when only a non-repo file is specified
Simon Michael <simon at joyful.com>**20081026075251
 Ignore-this: efa65ddd1adaa6a8ef4a1c390e70e408
] 
[fix bug in haddock docs.
David Roundy <droundy at darcs.net>**20081027170550
 Ignore-this: bf6386afe60b95bc483a6a93713e0a82
] 
[accumulate hash strictly in hash/hashPS
Ganesh Sittampalam <ganesh at earth.li>**20081025121857] 
[remove trailing whitespace
Ganesh Sittampalam <ganesh at earth.li>**20080830014910] 
[add a few comments/update annotate docs slightly
Ganesh Sittampalam <ganesh at earth.li>**20081025103006] 
[resolve issue395: warn the user when the patch name looks like a command line option
tux_rocker at reinier.de**20081024212022] 
[Fix newline endings on Windows for HTTP module.
Salvatore Insalaco <kirby81 at gmail.com>**20081025120900
 Ignore-this: f44ed6b1127d1ecc686353d4179c2b62
] 
[resolve issue1023: bracket file writing to prevent windows permission errors.
Salvatore Insalaco <kirby81 at gmail.com>**20081025134220
 Ignore-this: b457533b264b97952a52b8ab65d3de0b
] 
[resolve issue1000: warn when tags are too short (length name <2)
Christian Kellerman <Christian.Kellermann at nefkom.net>**20081025203101] 
[$DARCS is no longer set by shell_harness.
Trent W. Buck <trentbuck at gmail.com>**20081024093255] 
[Cleanup after others before running tests.
Trent W. Buck <trentbuck at gmail.com>**20081024062308
 When running tests in non-reverse order, these were failing.
] 
[resolve issue1051: Allow --dry-run --interactive
florent.becker at ens-lyon.org**20081024163636
 Ignore-this: 31efa8f7d63fa97050780ba206db9642
] 
[franchise now has optimization-disabling built in.
David Roundy <droundy at darcs.net>**20081024185501
 Ignore-this: b0c123e8a119f5df572291ebdb662cdb
] 
[making Darcs.Patch.Set comment into haddock
Florent Becker <florent.becker at ens-lyon.org>**20081022124230
 Ignore-this: ca2a6273ef5f38faf07141d969bc45d8
 
 With questions about the semantics of PatchSets.
] 
[fix documentation bug.
David Roundy <droundy at darcs.net>**20081024183357
 Ignore-this: ce6c4b16d613dbc8d7874c6519b9a808
] 
[Haddock typoes and formatting in Darcs.Match
florent.becker at ens-lyon.org**20081024110015
 Ignore-this: 95747c855b220f6c761435c92c672855
] 
[enable the use of $SENDMAIL for darcs send
Christian Kellermann <Christian.Kellermann at nefkom.net>**20081024112941
 Ignore-this: 731ff4dbc8076fb417f39b17a5a2addb
] 
[resolve issue628: reuse the long comment code from Darcs.record
Christian Kellermann <Christian.Kellermann at nefkom.net>**20081024133002
 Ignore-this: 36de69ba67d480651715c9296df5b90a
] 
[code cleanup
Christian Kellermann <Christian.Kellermann at nefkom.net>**20081024131904] 
[Canonize Christian Kellermann
Christian Kellermann <Christian.Kellermann at nefkom.net>**20081024135228
 Ignore-this: af44e8b80738c98bafe30bb5e15ef5ba
] 
[Clarify darcs transfer-mode debug message.
Eric Kow <eric.kow at gmail.com>**20081024091824
 Ignore-this: 502677248b4bee41a6d319c84d661a55
] 
[Use ANNOUNCE_GHC convention for .depend.
Trent W. Buck <trentbuck at gmail.com>**20081024024444] 
[Use $@ to avoid repetition in makefile.
Trent W. Buck <trentbuck at gmail.com>**20081023023447] 
[improve test_unit performance with QuickCheck 2.1
tux_rocker at reinier.de**20081023205622] 
[Remove unused functions just_dir and drop_paths from FilePathUtils.
Eric Kow <eric.kow at gmail.com>**20081023202557
 Ignore-this: b2c87df3986ef1c7b2cd682287e4749b
] 
[Replace just_dir with System.FilePath.takeFileName.
Eric Kow <eric.kow at gmail.com>**20081023202009
 Ignore-this: 294cdde35f8656e98ff30052fe41600
] 
[Appease GHC by removing unused import.
Trent W. Buck <trentbuck at gmail.com>**20081023074144] 
[Typo.
Trent W. Buck <trentbuck at gmail.com>**20081023073644] 
[Haddock documentation for Darcs.Patch.Match
Florent Becker <florent.becker at ens-lyon.org>**20081022125326
 Ignore-this: b020f089363e6c0a20fde963e071f112
] 
[haddock documentation and better names for Darcs.Match
Florent Becker <florent.becker at ens-lyon.org>**20081023141924
 Ignore-this: 27ef66ea7f77ff38d92d224b316b591c
] 
[remove duplicate Darcs.Match.doesnt_not_match
Florent Becker <florent.becker at ens-lyon.org>**20081023134139
 Ignore-this: d2af9cbfc1c3a0f3daa84de5d7ba481d
] 
[Do not use literate Haskell for Darcs.Population and PopulationData
Eric Kow <eric.kow at gmail.com>**20081023151214
 Ignore-this: a1d30b874d011b17640119373ce1f71f
] 
[Convert Darcs.Population and Darcs.PopulationData comments into haddock.
Eric Kow <eric.kow at gmail.com>**20081023151058
 Ignore-this: cdfbc7b827e4f4309f4c52999ce7b3f3
 These were meant to be API documentation.
] 
[Remove redundant nullPI
Eric Kow <eric.kow at gmail.com>**20081023144058
 Ignore-this: f61f60dfe29657872d555f9dc7c6e02e
] 
[Fix placement of ChangeLog signatures.
Eric Kow <eric.kow at gmail.com>**20081023143555
 Ignore-this: a01bf584d8a0259b45f81807b7b91942
] 
[Make threading mandatory in darcs.cabal.in.
Eric Kow <eric.kow at gmail.com>**20081023142817
 Ignore-this: d9681fe2e2e97f594d2253df4de182d8
] 
[Remove Changelog.README.
Eric Kow <eric.kow at gmail.com>**20081023122647
 Ignore-this: 467216ef492df50ecb568e80380927cb
 We no longer generate the ChangeLog automatically.
] 
[Style tweak in Darcs.Utils.firstNotBlank
Eric Kow <eric.kow at gmail.com>**20081022130841
 Ignore-this: eed1e68813f891f5e90fb61f89bcde9b
] 
[Minor Haskell style refactor.
Eric Kow <eric.kow at gmail.com>**20081022130825
 Ignore-this: ee6b29b703b6315bcc88291de30babde
] 
[make releaseVersion explicitly depend on the version, not Setup.hs.
David Roundy <droundy at darcs.net>**20081022211347
 Ignore-this: acebecb3d11941c6c81d972c9ebb127a
] 
[remove unneeded cd .. from Setup.hs.
David Roundy <droundy at darcs.net>**20081022143623
 Ignore-this: 4d51f5a20c038b562028b8972e33f66c
] 
[change setup.hs to Setup.hs in Setup.hs.
David Roundy <droundy at darcs.net>**20081022210724
 Ignore-this: 52a91ee40dfcbea225c6bfa0ebca746e
] 
[cut unused amInRepo from Setup.hs.
David Roundy <droundy at darcs.net>**20081022185639
 Ignore-this: 242baf8f224e86109a2613febe53e076
] 
[Do not recompute ChangeLog files at all.
Eric Kow <eric.kow at gmail.com>**20081021104308
 Ignore-this: 55d1494237fa59b1cfa567781fb16f3f
] 
[Do not recompute ChangeLog (franchise).
Eric Kow <eric.kow at gmail.com>**20081021104020
 Ignore-this: 103adab99f27a6c41be5000c4337551d
] 
[Hard-code darcs-2.1.0 ChangeLog entries.
Eric Kow <eric.kow at gmail.com>**20081021103725
 Ignore-this: b5e03d213c5ed90092362b5ebe3fc0b
] 
[Rollback accidentally applied darcs.cabal patch.
Eric Kow <eric.kow at gmail.com>**20081022150750
 Ignore-this: c3fae9a61e09d2e20cb3da9a7dfa08ff
 
 rolling back:
 
 Sun Oct 19 12:07:35 BST 2008  Eric Kow <eric.kow at gmail.com>
   * Add cabal file modified from Petr and Gwern's cabalisation branch.
] 
[Rename tests/template so it doesn't get deleted by make clean.
Eric Kow <eric.kow at gmail.com>**20081022105753
 Ignore-this: 4e3688d7f9de8f61cb77a081faf194c2
] 
[Allow empty matchers in Patch.Match
Florent Becker <florent.becker at ens-lyon.org>**20081022131118
 Ignore-this: 2128e8001ed23aa200aec125147a8852
 This allows one to put "amend-record   match 'author me'"
 in their defaults, and amend other people's patches using
 --match ''
] 
[Avoid using ls to get test files (makefile).
Eric Kow <eric.kow at gmail.com>**20081022104632
 Ignore-this: dd4132179155ea27190f943c4cb35b08
 Thanks to Trent Buck!
] 
[Simplify test targets in makefile.
Eric Kow <eric.kow at gmail.com>**20081022104120
 Ignore-this: 6b7f13facff53107214ebbe53deae8dd
 Do not use a discard filter.  Instead, just let the individual tests determine
 if they should run or not.
] 
[Simplify darcs.cabal.in and add more precise dependencies.
Eric Kow <eric.kow at gmail.com>**20081022094015
 Ignore-this: ccf1a93e98f91a5e6175777ff4144516
 This removes any information from the cabal file which is redundant
 with franchise, reduces the number of choices you can make (haskeline
 and terminfo now mandatory) and adds more precise package dependency
 information.
] 
[Simplify author field in darcs.cabal.in.
Eric Kow <eric.kow at gmail.com>**20081021131711
 Ignore-this: b528eca77d99c1827f704f1ac593f546
 I think the et al. confuses my mail client.
] 
[don't install franchise while testing.
David Roundy <droundy at darcs.net>**20081021212101
 Ignore-this: aef13450f0d8b110dca782c789ec11e3
] 
[make pull work with multiple --repodirs.
David Roundy <droundy at darcs.net>**20081021181317
 Ignore-this: 8741d0b7356079cb828d70d7042d0922
] 
[call $(MAKE) instead of 'make', because GNUMake is not called 'make' everywhere
Chistian Kellermann <Christian.Kellermann at nefkom.net>**20081021123122] 
[Add a darcs-nightly target to the makefile.
Eric Kow <eric.kow at gmail.com>**20081020214102
 Ignore-this: bb2bdd61ac32b241ddf9498a8f08987b
 This attaches a version number with patch count to the darcs binary.
 It is meant for use by an automatic nightly build script.
] 
[Add cabal file modified from Petr and Gwern's cabalisation branch.
Eric Kow <eric.kow at gmail.com>**20081019110735
 I have updated the version number, simplified the text, and removed a
 couple of files that are generated by their Setup.lhs
] 
[prefer recursive acronymn to embarrassing one
David Roundy <droundy at darcs.net>**20081021113728
 Ignore-this: 55330f8d447f308db408aeea5065f95e
] 
[Create the darcs.cabal file in franchise.
Eric Kow <eric.kow at gmail.com>**20081021095925
 Ignore-this: db1dc72b5589178c521c1daee8b32f63
] 
[Add a template for building the darcs.cabal file.
Eric Kow <eric.kow at gmail.com>**20081021095743
 Ignore-this: 51eaff43be4eec36dcdbd238fb317931
 This is slightly modified from Gwern Branwern's and Petr Rockai's
 cabalisation work.
] 
[resolve issue784: fix file handle leak and check for exceptions on process running.
Salvatore Insalaco <kirby81 at gmail.com>**20081019065904] 
[Reenable some tests under Windows now that we are ignoring setCooked errors.
Eric Kow <eric.kow at gmail.com>**20081014072549] 
[avoid needless work in Setup.hs
David Roundy <droundy at darcs.net>**20081020200931
 Ignore-this: 52f3e0416edfd888d926a01ced7b6714
] 
[enable franchise build tests under wine 1.0.
David Roundy <droundy at darcs.net>**20081020182156
 Ignore-this: 2b6ea78bb8ae5e432c4823019ef6e589
] 
[enable test of franchise build.
David Roundy <droundy at darcs.net>**20081020172147
 Ignore-this: bf5e21492195919296450851c07789c2
] 
[only build ChangeLog if we're in a darcs repository.
David Roundy <droundy at darcs.net>**20081020143550
 Ignore-this: e79c7ca9ca2525ff4489a4c6926cbcaa
] 
[remove dependence on haskell98 package from preproc.hs and make_changelog.hs.
David Roundy <droundy at darcs.net>**20081019220256
 Ignore-this: 2bda2dcb172e3c815bd5a2c068a064e2
] 
[we don't need to announce we're on windows, just log it.
David Roundy <droundy at darcs.net>**20081019213320
 Ignore-this: 23d4ca75eb60dcf4ef52123a5cb6c4eb
] 
[reorganize and comment ./Setup.hs flags.
David Roundy <droundy at darcs.net>**20081019211118
 Ignore-this: 954c53a14e398fc0e037c8a1371bd598
] 
[simplify checking for windows using franchise.
David Roundy <droundy at darcs.net>**20081019211048
 Ignore-this: 37e425429c107b80776dc3c28ca7c544
] 
[test for endianness using franchise.
David Roundy <droundy at darcs.net>**20081018213539
 Ignore-this: 9c418723de4ae70bc83cd0e6bc9b1dfd
] 
[fix test-franchise-build.sh to work with renamed Setup.hs.
David Roundy <droundy at darcs.net>**20081018183619
 Ignore-this: 7b810e0be231c6088e5fc0cde9533192
] 
[Capitalise Setup.hs for consistency.
Eric Kow <eric.kow at gmail.com>**20081018152001] 
[Add import list for System.Process in Exec.lhs
J. Garrett Morris <jgmorris at cecs.pdx.edu>**20081017195920] 
[add CURSES test to setup.hs.
David Roundy <droundy at darcs.net>**20081017164048
 Ignore-this: 1262a90b249d39c916e8e36bfdb6b63b
] 
[half-resolve issue1138: make it possible in setup.hs to not use -Werror.
David Roundy <droundy at darcs.net>**20081016201336
 Ignore-this: 4f4f31cf24e25774a8217c26813ddbd3
] 
[use unlessFlag in setup.hs to simplify haskeline check.
David Roundy <droundy at darcs.net>**20081016200649
 Ignore-this: 5a2b4ced454b56180f4b9422ff03c41f
] 
[Use command_control_list directly in run_the_command.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015181141
 Ignore-this: 8c4fb4d8602638648ba4afc6d2e9eeb8
] 
[Fix imports in Darcs.ArgumentDefaults.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015180629
 Ignore-this: e57422b5a224179b7b1431de262bf8ea
] 
[Refactor Darcs.ArgumentDefaults to use command_control_list directly.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015175540
 Ignore-this: c832abf95dc438a3b71ed2b9a84cc413
] 
[Refactor Darcs.Commands, move command run code to Darcs.RunCommand.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015174031
 Ignore-this: 3b8c32701f62f3d7b1e0834eaa406dc5
] 
[Remove unused extended_usage.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015142503
 Ignore-this: 1d86f17d2bc3ec0c004e3cd1016d303
] 
[Use help_cmd instead of usage in main.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015134236
 Ignore-this: fced70e6714d5294783bbe98f0d81e47
] 
[Use help_cmd directly in main.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015132942
 Ignore-this: 8ded4d8a8cf51f862794a78eea4ef137
] 
[Refactor 'darcs --commands' to list_available_commands.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081015125827
 Ignore-this: 114b79a90e6446169dd87ff8591bc6ff
] 
[fix Submitting patches to darcs with respect to send -u
Thorkil Naur <naur at post11.tele.dk>**20081015073751] 
[add haskeline test to setup.hs.
David Roundy <droundy at darcs.net>**20081014201513
 Ignore-this: 1472b07696d83f70bf8ad8f7b3d5cf1
] 
[finished cleanup of default_boring entries
benjamin.franksen at bessy.de**20081014100840
 Ignore-this: e5ad0567cabe64142bf3876c2d73535e
] 
[clean up setup.hs by using lookForModule instead of catching exceptions.
David Roundy <droundy at darcs.net>**20081014160159
 Ignore-this: 8f5c7bd5be2ca099fda5bd52d35dc429
] 
[simplify pull_many_files.sh.
David Roundy <droundy at darcs.net>**20081014165155
 Ignore-this: 9f7a7cc5b02a9d51810149a8875e987f
] 
[add test for siginfo.h (which shows up on SunOS maybe?)
David Roundy <droundy at darcs.net>**20081014154814
 Ignore-this: 72d32ff1b4b57dbf75eab937be5a0e22
] 
[Use fgrep in printer.sh test (more portable than grep -F)
Eric Kow <eric.kow at gmail.com>**20081014135138] 
[have makefile make hspwd rather than shell_harness.
David Roundy <droundy at darcs.net>**20081013192943
 Ignore-this: 31008f1993c5a2281b229b9c5cdca66c
 I think there was a problem that make -j check could cause ghc --make
 to be run simultaneously.  Now it's run just once, before running any
 tests.
] 
[slightly hokey approach to solving pwd problem.
David Roundy <droundy at darcs.net>**20081013184209
 Ignore-this: 762f0339c99f1d4a529ab031ad353cd0
 I think this may help the Solaris/BSD test portability issue, and it's
 also (I think) a slightly cleaner alternative to the portable_pwd
 hack.
] 
[clean up test-franchise-build.sh a bit more...
David Roundy <droundy at darcs.net>**20081013175711
 Ignore-this: 619fff6a0be4bc8172cd8c39a5591079
] 
[clean up test-franchise-build.sh
David Roundy <droundy at darcs.net>**20081013162935
 Ignore-this: a1bd36f8bb8d3d75519abcc8d8388a99
 Among other infelicities, it wasn't using a clean franchise build
 except under wine.
] 
[add test that timestamps are properly set.
David Roundy <droundy at darcs.net>**20081013152933
 Ignore-this: caf36b9fff70f9a44b0f35078f3a5aee
] 
[on windows, try renameFile before deleting target file.
David Roundy <droundy at darcs.net>**20081010204009
 Ignore-this: 6946caec86d1c7177510baf62e2ed275
 The trouble was that if we were renaming a file to itself, we ended up
 deleting the file we were renaming (oops!).  It's a stupid hack, but
 that's what we're forced to do when running on windows.  (Note that
 it's potentially hard to determine if two paths describe the same
 file.)
] 
[clean up setup.hs configure a bit.
David Roundy <droundy at darcs.net>**20081010154959
 Ignore-this: 10855edc3e6fda315e03b6ea1c64b05e
 This removes redundant output, and warns when fast http libraries
 aren't found (or no http library at all).
] 
[Remove bashisms and GNUisms
Matthias Kilian <kili at outback.escape.de>**20081012123017
 
 Replace some bashisms and GNUisms by more standards compliant command
 lines, i.e.:
 
 - Don't use `\|' in BREs, since it's undefined according to POSIX.
   Instead just use grep -E with an ERE.
 
 - Don't create "funny" strings with the $'\x01...' bashism but use
   printf(1) instead. Note that this isn't strictly necessary to fix
   printer.sh on non-GNUish systems, but it makes it much simpler to test
   what's going on.
 
 - In test_line(), just use grep -F, and unescape all second arguments
   passed to test_line(). This makes the script much more readable and
   actually fixes it for non-GNUish systems.
] 
[simplify write_default_prefs.
David Roundy <droundy at darcs.net>**20081013121512
 Ignore-this: 4f72699d2406802e771a0ceadc913550
 It's easier to read this way, and shorter, too.
] 
[documented provenance of .tmp_versions and .DS_Store files in default boring
ben.franksen at online.de**20081012220207] 
[Fix curl version in setup.hs.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081012094214
 Ignore-this: 5c44008cb7105279c37a2297e668a070
] 
[cleanup default boring
ben.franksen at online.de**20081011234148
 
 Also turn default_boring and default_binaries into (pure) CAFs.
] 
[avoid re-checking for windows.
David Roundy <droundy at darcs.net>**20081011223905
 Ignore-this: 93c42ffc6b67c6cca803e1dcb18a9497
] 
[setup.hs: don't fail if darcs doesn't yet exist.
David Roundy <droundy at darcs.net>**20081011223824
 Ignore-this: 6d318961490a9343f5e792f2d740fd27
] 
[fix spelling error in setup.hs.
David Roundy <droundy at darcs.net>**20081011205353
 Ignore-this: 6d521f633d74aae8705391eff9489b2c
] 
[make setup.hs look for libcurl
David Roundy <droundy at darcs.net>**20081011195923
 Ignore-this: c9a267184e89b188f074171f8887b3b4
] 
[resolve issue1139: make special cases handle no arguments gracefully.
David Roundy <droundy at darcs.net>**20081011161059
 Ignore-this: 12b17a3940558860dd4caf7bb2619ec7
 I accidentally broke this when refactoring Darcs.Match.  This change
 restores some efficiency when no arguments are given and thus we are
 creating copies of all the files in the repository.
] 
[add tests for issue1139.
David Roundy <droundy at darcs.net>**20081011155324
 Ignore-this: ff50784059114f969fb4657ea5e92025
] 
[Copyright and licensing notes and rationales.
Trent W. Buck <trentbuck at gmail.com>**20081011035925] 
[Document DARCS_KEEP_TMPDIR in manual.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081011115026
 Ignore-this: bd77d5a85fa44094dcd1a867c2a63d2e
] 
[Documentation for DARCS_KEEP_TMPDIR.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081011113042
 Ignore-this: 5e3d6598aed4b681a099341c3ec5017a
] 
[Simplify Darcs.Lock.withDir.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081011110639
 Ignore-this: c01257f9e0fc40c415562448cb52d67d
] 
[Do not remove temporary directories if DARCS_KEEP_TMPDIR environment variable is set.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081011105808
 Ignore-this: 5ea0e206e45dc9be73c29c3bf89643b9
] 
[add new test that optimize --reorder behaves itself on lazy repos.
David Roundy <droundy at darcs.net>**20081010194834
 Ignore-this: 5246d20700c153490da1997caede4369
] 
[give more debug output in test.
David Roundy <droundy at darcs.net>**20081010191209
 Ignore-this: a13ec79ae69f4fe9621ea3c16c9b41d6
] 
[remove reimplementation of zipWith.
David Roundy <droundy at darcs.net>**20081010191051
 Ignore-this: 277f49de513ec84bc6db0b4da6c633b1
] 
[Fix spurious diff and missing cd in diff test.
Eric Kow <eric.kow at gmail.com>**20081008192142
 
 If tests are run in parallel, each instance of the diff test may
 attempt to create temporary directories for use by darcs diff.
 Darcs itself handles this fine; only the test script gets confused
 by the spurious difference that results.
] 
[Help the test harness clean to up after tests.
Eric Kow <eric.kow at gmail.com>**20081008190340
 A typical use case is if a test sets restrictive permissions
 and dies.  Notes:
 * we do this after each test so that one test result doesn't
   contaminate others
 * we explicitly do /not/ remove these temporary directories
   because you may want them around for forensics
] 
[ratify use of readFile in setup.hs
David Roundy <droundy at darcs.net>**20081010150105
 Ignore-this: 92627010ec07e16d271bcc5e7f325c64
] 
[Minor refactor in URL.urlThread.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081010071649
 Ignore-this: 809d750f10adc8073ebe0dd3d432f2a2
] 
[clean up code formatting in Hopefully.
David Roundy <droundy at darcs.net>**20081010144943
 Ignore-this: 65a4dbb17505adbc0c0c615c445a8926
] 
[clean up unused exports in Hopefully.
David Roundy <droundy at darcs.net>**20081010144918
 Ignore-this: a016b66fd64f756295555255b268e80a
] 
[haddock documentation for Hopefully
florent.becker at ens-lyon.org**20081001081315] 
[resolve issue1062: ignore setCooked and setEcho errors.
Eric Kow <eric.kow at gmail.com>**20081010122047
 Ignore-this: 2f8c8710faefdcdb6b224244995a00af
 The issue in question is only about setCooked.
 I presume setEcho can similarly fail.
] 
[add script for testing the franchise build.
David Roundy <droundy at darcs.net>**20081010142711
 Ignore-this: 5aa40dc14c0827b199b9d23d1c7ef27d
 This includes testing the cross-compile to windows using wine.  It's
 part of my scripts that are run on each push to darcs-unstable.
] 
[add a --prompt-for-dependencies to restore the default behaviour
florent.becker at ens-lyon.org**20081010123240
 Ignore-this: 92480353c19dea1b67aff89b933759a2
 Add a --prompt-for-dependencies flag so that one can put
 --dont-prompt-for-dependencies in their defaults file and
 still get back the default behavior when needed.
] 
[eliminate autogeneration of Workaround.hs.
David Roundy <droundy at darcs.net>**20081010134727
 Ignore-this: 784a4b08bab1e22c93f54c1c5cd710f1
] 
[add franchise setup file.
David Roundy <droundy at darcs.net>**20081009203410
 Ignore-this: f1738c7608e6093aa18e808d3d41d000
] 
[add missing createLink to win32/System/Posix/Files.hsc.
David Roundy <droundy at darcs.net>**20081010133500
 Ignore-this: 39d246ab1db8c31f78e0b8362ad05ca3
] 
[make make_changelog default to quiet output.
David Roundy <droundy at darcs.net>**20081009203322
 Ignore-this: 55eba7a68a3c8a5683d23cc99848bd6f
 You can restore previous behavior by defining the VERBOSE environment
 variable.
] 
[remove unused and unneeded Workarounds.
David Roundy <droundy at darcs.net>**20081009194541
 Ignore-this: bca5a7a2444d4ddffeed673cbbfa19ec
] 
[rename lazy-deps to dont-prompt-for-dependencies.
David Roundy <droundy at darcs.net>**20081009171030
 Ignore-this: 78393e28c184c9339c89cecaa852dbc9
] 
[fix incompatibilities with ghc 6.6
David Roundy <droundy at darcs.net>**20081009165845
 Ignore-this: 18739c880a49b976ec151363f4ff9296
] 
[basic tests for --lazy-deps
Florent Becker <florent.becker at ens-lyon.org>**20081008124956
 Ignore-this: 79d8a312943813e9fe5448bc2ab86aa0
] 
[added a --lazy-deps option
Florent Becker <florent.becker at ens-lyon.org>**20081008122224
 Ignore-this: d934868e56f0084067f5aedf0512a533
 This option means that you don't get asked about patches which do not match
 a --match, but are depended upon by a patch that does. These patches will get
 ilently selected. 
 
] 
[refactor of SelectChanges
Florent Becker <florent.becker at ens-lyon.org>**20081008100551
 Ignore-this: e620d36d6e52eb62a2205fe5122d7076
] 
[refactor Match to handle --store-in-memory itself.
David Roundy <droundy at darcs.net>**20081008172748
 Ignore-this: 647c75f78d2d4981e67039ae1b6e96df
 This reduces the amount of duplicate code, at the cost of adding a
 class to Darcs.Match--but at least it isn't exported.
] 
[make writeSlurpy work properly when given "."
David Roundy <droundy at darcs.net>**20081008172207
 Ignore-this: 9d5d077bcdf3a9bb7bfa8477ab9d96d5
 This isn't a bugfix per se, but rather a feature addition.
 writeSlurpy has a "safety feature" that it refuses to overwrite a
 directory, but that safety feature doesn't really apply to the
 directory ".", since "." explicitly means that we want to overwrite
 the directory.
] 
[change a bit of code to accept FilePathLike arguments.
David Roundy <droundy at darcs.net>**20081008172047
 Ignore-this: 87032e071bb49117133d99a90bdfd0e1
 These functions really should expect FileName, and this is an
 incremental move in that direction.
] 
[Implement Commands.Check in terms of Repository.Repair functionality.
me at mornfall.net**20080926144006] 
[Implement Commands.Repair in terms of Repository.Repair functionality.
me at mornfall.net**20080926143919] 
[Export testTentative from Darcs.Repository.
me at mornfall.net**20080926143839] 
[Implement Repository.Repair to provide primitives for check and repair commands.
me at mornfall.net**20080926143721] 
[keep changepref patches from breaking the toSimple optimization.
David Roundy <droundy at darcs.net>**20080924162022
 Ignore-this: 404a4386b048b74dd9afcdde47bc1b11
] 
[rewrite push_coalesce_patch to avoid calls to lengthFL.
David Roundy <droundy at darcs.net>**20080924161517
 Ignore-this: cf746702c3b1e06ab2d400878e20e305
] 
[make various autoconf simplifications.
David Roundy <droundy at darcs.net>**20080923150742
 Ignore-this: 213c53eda0b54c01909c8d15b2a5fdd6
] 
[Restore send-external.sh test.
David Roundy <droundy at darcs.net>**20081009140121
 Ignore-this: 700f9c538033108cac397c1d757fbfc4
] 
[TAG 2.1.0
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081009120532] 
[Rollback send-external test.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081009101224
 I was over-optimistic about pulling this into stable.
 It fails under Windows.
 
 rolling back:
 
 Tue Oct  7 23:28:04 BST 2008  David Roundy <droundy at darcs.net>
   * add test for send --sendmail-command.
 
     A ./tests/send-external.sh
] 
[ChangeLog entries for 2.1.0 (tweaks).
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081009090247] 
[disable tests/issue1078_symlink.sh on Windows
zooko at zooko.com**20081001130248
 (Windows does not have symlinks.)
] 
[use minimum Cachable time in corner case where f/=f' and c/=c'.
David Roundy <droundy at darcs.net>**20081008173804
 Ignore-this: 51f2a68ac4139420bd116e8293cc5cc2
] 
[Bump version number to 2.1.0.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081008203033] 
[Canonize Benjamin Franksen.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081008202951] 
[ChangeLog entries for darcs 2.1.0.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081008202927] 
[add test of Ignore-this functionality.
David Roundy <droundy at darcs.net>**20081008192621
 Ignore-this: 47b7bf225e2997dd78c351763c769738
] 
[warn users if they try to record a change beginning with Ignore-this:.
David Roundy <droundy at darcs.net>**20081008192001
 Ignore-this: 94828726d609f46e384c2ab8091e49db
 Ignore-this: I am testing the functionality of this feature.
] 
[allow users to add their own ignored information to patches.
David Roundy <droundy at darcs.net>**20081008190038
 Ignore-this: fe8294776896b6fdcd489752a29d1069
] 
[haddock documentation for Printer
florent.becker at ens-lyon.org**20081007211959] 
[Use copyFile+renameFile for safe copy in URL.waitNextUrl.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081008134308
 Ignore-this: a9a8889c2b57a5dca2785344cbd18a2f
] 
[remove excessive indentation that made the code very hard to read.
David Roundy <droundy at darcs.net>**20081008173358
 Ignore-this: d93e312c27f0d9a1ef993855c6872257
] 
[When requesting same URL with different cachability choose least cachable.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081008145049
 Ignore-this: fddacf3e706a68c55871f81438d283b
] 
[add simple test of interactive record.
David Roundy <droundy at darcs.net>**20081008172036
 Ignore-this: ebb01acdb477174095e1b66aac230629
] 
[Improve test pull.sh cleanup
Thorkil Naur <naur at post11.tele.dk>**20081008115539] 
[resolve issue1124: Test pull.sh failed when run as root
Thorkil Naur <naur at post11.tele.dk>**20081008114134] 
[Allow dist command to take a tag argument (issue 286).
Stephen Hicks <sdh33 at cornell.edu>**20081006075133
 It should probably be a "match_one_context" instead of a "match_one"
 option type, and then instead of using the "nonranged" matcher, we'd
 use the "patchset" ones (that don't exist yet).  But I couldn't figure
 out how to blend "get_nonrange_match" and "get_one_patchset" in any
 sensical way to get immediate pristine output (and all the more so for
 the "_s" variants).  So for now, contexts are not supported, but it
 would be nice if they were someday.
] 
[clean up RepoPath a bit (removing unused methods from classes).
David Roundy <droundy at darcs.net>**20081008161906
 Ignore-this: 4e69882ebe10f20bb67350b106bd10af
] 
[clean up exportation of SlurmMonad private internals.
David Roundy <droundy at darcs.net>**20081008151758
 Ignore-this: 3763cc352b6f28fa83d8fbe5b1077985
] 
[Optimize clean_hashdir's use of cleanCaches.
Petr Rockai <me at mornfall.net>**20081007191237
 
 We now only ask cleanCaches to look at files we have unlinked and therefore
 might have caused their cached equivalents to drop link-count to 1. Limits
 number of stats to O(n), n = number of cleaned out files.
] 
[Resolve issue1131: accept download requests for different files.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081008113040
 Ignore-this: a45dc4c336f87a61bda3b3c96a8656fa
] 
[add test for send --sendmail-command.
David Roundy <droundy at darcs.net>**20081007222804
 Ignore-this: f84bb43f50a6a07e0cddde739b602e6a
] 
[fixed accidental merge of two lines in default boring; removed pattern for directory "dist"
ben.franksen at online.de**20081007185233] 
[resolve issue1128: must call execSendmail inside body of withOpenTemp
benjamin.franksen at bessy.de**20081007115303] 
[Nicer bug output (it was missing a space).
Eric Kow <eric.kow at gmail.com>**20081007155214] 
[partial haddock documentation of Arguments.lhs
Florent Becker <florent.becker at ens-lyon.org>**20081007131122] 
[haddock documentation for ColorPrinter
florent.becker at ens-lyon.org**20081002203509] 
[disable progress reports when connecting to an ssh server.
David Roundy <droundy at darcs.net>**20081002215119
 Ignore-this: 5088b46719072abcecf0c8c406b8f6d7
] 
[Resolve issue1104: stop progress reports in exec.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081002130157
 Ignore-this: 40bd4c27fd600f6dbcc3f89a62db9104
] 
[Resolve issue1109: stop progress reports in exec_interactive.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20081002125805
 Ignore-this: 2938508e82322b41fb9e18db4ee4ceba
] 
[fix tab in Replace that broke haskell-policy.sh test.
David Roundy <droundy at darcs.net>**20081006171036
 Ignore-this: c02875410986f3e2e48da0da19333311
] 
[Restore quiet grep in portable_pwd
Eric Kow <eric.kow at gmail.com>**20081005164212
 Only this time, we use > /dev/null.
] 
[Disable a test that triggers a setCooked failure under Windows.
Eric Kow <eric.kow at gmail.com>**20081005145124] 
[hint about replace --force [issue864]
Tommy Pettersson <ptp at lysator.liu.se>**20081005160640] 
[fix issue966 test, use better temp dir name, and start clean
Tommy Pettersson <ptp at lysator.liu.se>**20081005000117] 
[mv nfs-failure test to the bugs/ folder, since it fails.
David Roundy <droundy at darcs.net>**20081005130112
 Ignore-this: 73c6e55558233f1b56d7ff51f327f454
] 
[further makefile cleanups.
David Roundy <droundy at darcs.net>**20081005124353
 Ignore-this: 8c498e4b793b7049e273d6ac98441256
] 
[Simplify testing in makefile.
Eric Kow <eric.kow at gmail.com>**20081005092416] 
[Revise test documentation to reflect consolidation to shell tests.
Eric Kow <eric.kow at gmail.com>**20081005091131] 
[Remove Perl test harness and convenience copies.
Eric Kow <eric.kow at gmail.com>**20081005090921] 
[Do not use Perl test harness.
Eric Kow <eric.kow at gmail.com>**20081005090903] 
[Hopefully fix issue595 test on Solaris.
Eric Kow <eric.kow at gmail.com>**20081005090156
 
 I'm not entirely clear on what is causing this to fail.
 The basic test is:
   mkdir -p restrictive/liberal
   chmod 111 restrictive
   cd restrictive/liberal
   darcs get
 
 This is apparantly known to fail under Solaris.  The original Perl test
 claims it's because you can't cd into restrictive/liberal, but the shell
 variant seems to manage fine.  In any case, I think this touch file
 check is simpler.
] 
[Translate merging_newlines bug into shell and restore bug context.
Eric Kow <eric.kow at gmail.com>**20081005085031
 
 This used to be a TODO item at the end of the merging_newlines
 test, but when it was moved out, the actions required to set up
 a bug were forgotten.  This patch restores those actions.
] 
[Translate some Perl bugs into shell.
Eric Kow <eric.kow at gmail.com>**20081005084157] 
[fix bug in external.sh translation.
David Roundy <droundy at darcs.net>**20081005122814
 Ignore-this: 1291ebf27ea9c4a04d79c877b0f6f82d
] 
[Translate printer test into shell.
Eric Kow <eric.kow at gmail.com>**20081005020140] 
[Translate still more Perl tests into shell.
Eric Kow <eric.kow at gmail.com>**20081005012058] 
[Translate pull_many_files tests into shell and avoid redoing work.
Eric Kow <eric.kow at gmail.com>**20081005004120
 Just use whatever format is in .darcs/defaults
] 
[Remove residual Perlisms in match-date.
Eric Kow <eric.kow at gmail.com>**20081005000324] 
[Translate date matching test to shell.
Eric Kow <eric.kow at gmail.com>**20081005000243] 
[Skip filepath test which does not work on Windows.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081004234806] 
[Fix non-portable use of grep -q in tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081004234524] 
[Make sed usage more portable in hidden_conflict2 test.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081004233717] 
[Use example.com in external.pl tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080928082407
 This avoids timing out in some DNS lookup.  When I first wrote this
 test, I did not know that RFC2606 has reserved example.{com,net,org}
 which seems to be useful in precisely this situation.
] 
[fix incorrect merging_newlines.sh test.
David Roundy <droundy at darcs.net>**20081004223547
 Ignore-this: 33ebc10cd54112ec101750dd6c75fdf9
] 
[Move merging_newlines test to bugs and add a simpler version.
Eric Kow <eric.kow at gmail.com>**20081004135724
 
 There are two issues I noticed when converting this Perl test into
 shell.  This test was passing, but I made some mistakes translating it,
 and in doing so, noticed two potential bugs.
 
 The first is a potentially hidden conflict.  If we start from
 a file
   from temp1
   <EOF>
 And then it seems that a change which adds an empty line should
 conflict with a change that adds a line with content.
 
 The second is that if you do omit the newline, as the original
 test does,
   from temp1<EOF>
 you get some strange-looking changes, namely that appending a
 line to this yields two addline changes and not one.
] 
[fix wrong ../path in failing issue1013 test
Tommy Pettersson <ptp at lysator.liu.se>**20081004140200] 
[Add a toolbox.sh to tests
Eric Kow <eric.kow at gmail.com>**20081004202139
 Like template.sh, this is not a real test, but just helper
 code for writing tests.  The toolbox just provides a single
 place you can go to look up how to do things.
] 
[Translate some more Perl tests into shell.
Eric Kow <eric.kow at gmail.com>**20081004201632] 
[Translate some more Perl tests into shell.
Eric Kow <eric.kow at gmail.com>**20081004163850
 Shell equivalents already exist for these particular tests,
 but they may not do the same thing.
] 
[Move non-date-matching code out of match.pl
Eric Kow <eric.kow at gmail.com>**20081004145445
 The goal is to minimise and eventually eliminate our use of Perl
 for regression tests.
] 
[Fix minor bug in conflict-doppelganger test.
Eric Kow <eric.kow at gmail.com>**20081004163746
 It does not account for --old-fashioned-inventory being
 in .darcs/defaults
] 
[Update tests to reflect --darcs-2 default.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080925143252
 We need to explicitly say --old-fashioned-inventory to test
 accordingly.
] 
[mv issue1111 to tests/
David Roundy <droundy at darcs.net>**20081004143649
 Ignore-this: 51683a80094a4d7733a31b4a40e94016
] 
[resolve issue1111: patchset_intersection used wrong selection for partitionRL
Tommy Pettersson <ptp at lysator.liu.se>**20081004123851
 We want to commute the non-common patches away, so we can stick the
 remaining common patches to the rest of the common patch set.
] 
[use longer patch names in issue1111 test for safer grep result
Tommy Pettersson <ptp at lysator.liu.se>**20081003230323
 The 'not grep C out' found the author--date line of patch A, which
 contained my timezone (CEST), so the test failed even when it should have
 succeeded.
] 
[Translate some more Perl tests into shell.
Eric Kow <eric.kow at gmail.com>**20081004092507] 
[The pager defaults to less(1), not more(1)
Matthias Kilian <kili at outback.escape.de>**20081003212319
 
 It would be better to change get_viewer in Darcs/Utils.lhs to default
 to more(1), but since this may be too intrusive for the upcoming
 release, just let the manual tell the truth (i.e., we're using
 less(1) by default).
 
] 
[remove -q from diff in test, not supported on solaris
Tommy Pettersson <ptp at lysator.liu.se>**20081003205756] 
[Fix cd bugs in conflict-doppleganger test.
Eric Kow <eric.kow at gmail.com>**20081004094407
 We were not always exiting from darcs repositories when we
 meant to.
] 
[fix test issue1110, remove duplicates of cd ..
Tommy Pettersson <ptp at lysator.liu.se>**20081003182126
 They got us out of the test dir, up in the file tree hierarchy, to the
 darcs root dir, and beyond, where the test continued to run test commands
 and cleanups (ooops!!)
] 
[Translate some Perl tests into shell.
Eric Kow <eric.kow at gmail.com>**20081003183746] 
[Convert tag.pl test into shell.
Eric Kow <eric.kow at gmail.com>**20081003095231] 
[Add a shell test template.
Eric Kow <eric.kow at gmail.com>**20081003095005
 This provides helper functions and a basic repository
 setup.  The idea is that when making a new shell test,
 you start by making a copy of the template.
] 
[Reformat Darcs.CommandsAux comments as haddock.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080927123217] 
[haddock documentation for ColorPrinter
Tommy Pettersson <ptp at lysator.liu.se>**20081003175214] 
[only  show 'diffing dir' when debugging.
David Roundy <droundy at darcs.net>**20081001134124
 Ignore-this: 277810d9083e36b42f27fa7ac4c47386
] 
[TAG 2.1.0pre3
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081002091241] 
[Bump version number to 2.1.0pre3.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081002091226] 
[ChangeLog entries for darcs 2.1.0pre3
Eric Kow <E.Y.Kow at brighton.ac.uk>**20081002091155] 
[make boring file and tests work with hpc.
David Roundy <droundy at darcs.net>**20081001202849
 Ignore-this: a699af014f672cc32c1a88863db8ffec
] 
[make default_boring and default_binaries NOINLINE
David Roundy <droundy at darcs.net>**20081001202731
 Ignore-this: f74741738a612bb283d1e871d70aa492
 This is primarily so I won't have to recompile all of darcs when these
 change, but also because they shouldn't be inlined.  It would just be
 a waste of space (and would slow down darcs).
] 
[trim exports of IsoDate.
David Roundy <droundy at darcs.net>**20081001194015
 Ignore-this: 6f1ef595002c05c07821c2d1332e054b
] 
[fix bug in 1105 fix that led to improper overrides of defaults
David Roundy <droundy at darcs.net>**20081001175907
 Ignore-this: 8413d2596f97076ccb096900585f0c62
 The problem is illustrated in the tests/override-defaults.sh that I've
 recorded separately.  We want conflicting defaults in
 ~/.darcs/defaults and _darcs/prefs/defaults to be resolved in favor of
 the default residing in _darcs/prefs/defaults.
] 
[add test that overriding of defaults works right.
David Roundy <droundy at darcs.net>**20081001175645
 Ignore-this: aedfd923676b1fa35c25c72abb88c8f3
] 
[Test for issue1105.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080929142205
 Ignore-this: 5b7c2f7d270ab614eb1294566048a586
] 
[Resolve issue1105: check if default options are valid.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080929141948
 Ignore-this: 17b4b27e31545689f21496f7fc9c9fe7
] 
[fix bugs in second issue1110 test.
David Roundy <droundy at darcs.net>**20081001171147
 Ignore-this: 2757852f2b599cfd55936cccd1b83b5f
] 
[Add another test case for issue1110.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080930220818] 
[generate a tidier hoogle frame, add required files, simplify framed doc generation
Simon Michael <simon at joyful.com>**20080930204518
 Ignore-this: e60b456f1fdd001b5ae456f9aae05999
] 
[haddock documenation for DateTester
florent.becker at ens-lyon.org**20080926165323] 
[haddock documentation for DateMatcher
florent.becker at ens-lyon.org**20080926164753] 
[make installdocs should not install TeX intermediaries.
Trent W. Buck <trentbuck at gmail.com>**20080930030315
 I'm unilaterally classing the DVI and PostScript versions as
 "intermediaries" to the PDF version, and only installing the latter.
] 
[Add test cases for issue1043.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080930105032
 There are two known variants, one of which was fixed by
 resolve issue1043: fix bug in mergeAfterConflicting.
] 
[resolve issue1110: fix get --hashed.
David Roundy <droundy at darcs.net>**20080929175725
 Ignore-this: d0aaaa26583dd3ab37bedfc738fb6117
] 
[add test that show bug works right.
David Roundy <droundy at darcs.net>**20080929152909
 Ignore-this: 4829e300015120adeed108079324e5e2
] 
[Add a test case for issue1110.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080929151743] 
[Tone down unnecessarily scary language when cancelling
Simon Michael <simon at joyful.com>**20080928004013
 Ignore-this: c5940d14099953b7bc963c70591739d1
] 
[darcshoogle script and emacs integration example
Simon Michael <simon at joyful.com>**20080927210609
 Ignore-this: 93d5a0ff269d314d32f213dfbe4325be
] 
[Fix doubled verb `be' in documentation on apply posthooks in _darcs/prefs/defaults.
Taylor R Campbell <campbell at mumble.net>**20080928200954] 
[the issue864 test was misnamed
Simon Michael <simon at joyful.com>**20080928231942
 Ignore-this: a0b643bf0abc6f4b6237e5683e9f6dad
] 
[add tests for pull --union and --intersection.
David Roundy <droundy at darcs.net>**20080929150711
 Ignore-this: 356f506f79ca89a2d1246d068aaa8b2b
 --intersection fails, which is issue1111.
] 
[add more output to URL bug message.
David Roundy <droundy at darcs.net>**20080929145544
 Ignore-this: 868e0ba5819dba2a4f5b8819080e9407
 I triggered this bug a few times, but once I added the extra output, I
 wasn't able to do it again.  So I'm leaving the extra information in
 the bug message so if someone else runs into it, we can more easily
 track down the issue.
] 
[answer darcs-doc question: no, that would be wrong.
David Roundy <droundy at darcs.net>**20080926220229
 Ignore-this: 419afd7bd9832e06d3dca45880276296
] 
[haddockification of IsoDate
florent.becker at ens-lyon.org**20080926163257
 Docstrings by Eric Kow
] 
[Make UglyFileName.super_name work with "/foo" paths.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080926223753
 Ignore-this: 6e4abb72087272ed03e5839a5420f82f
] 
[Restore 'simplify patches in rollback'.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080926225429] 
[Rollback 'simplify patches in rollback'
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080926225411
 I made the mistake of pulling this into stable despite a darcs 2.1
 feature freeze.
 rolling back:
 
 Tue Sep 23 16:06:19 BST 2008  David Roundy <droundy at darcs.net>
   * simplify patches in rollback.
] 
[Restore issue27 patches.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080926222522
 
 rolling back:
 
 Fri Sep 26 23:01:19 BST 2008  Eric Kow <E.Y.Kow at brighton.ac.uk>
   * Resolve issue1102: recognise but do not generate patch log 'junk'.
   
] 
[Resolve issue1102: recognise but do not generate patch log 'junk'.
Eric Kow <E.Y.Kow at brighton.ac.uk>**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 <droundy at darcs.net>
   * resolve issue27: add junk to patch identifiers.
 
 Wed Sep 17 18:09:13 BST 2008  David Roundy <droundy at darcs.net>
   * hokey fix to allow unit tests to generate random input.
 
] 
["make api-doc-frames" converts api docs to a frame layout
Simon Michael <simon at joyful.com>**20080927091919
 Ignore-this: 2a600aefe4399d17a4c2f14ea1cec350
] 
[hoogleindex no longer depends on api-doc dir
Simon Michael <simon at joyful.com>**20080927090139
 Ignore-this: 3a29b9bbd1ba1cdbccea03f4c04727c8
] 
[make hoogle targets more robust
Simon Michael <simon at joyful.com>**20080927083125
 Ignore-this: 2aac81020d3855ce8ffc9c4deef3e949
] 
[fix makefile indentation
Simon Michael <simon at joyful.com>**20080927020444
 Ignore-this: 847051698f40dc1fd03a8e1db93ff7a1
] 
["make hoogleweb" configures the hoogle web interface in hoogle/ 
Simon Michael <simon at joyful.com>**20080927015904
 Ignore-this: dcc4e2526b3c92859ccf9a6f1cb57ad2
 The hoogle index target is now "make hoogleindex". Requires the hoogle
 source tree (perhaps patched to configure result link urls).
 Tested on GNU/Linux with hoogle 4.0.0.5.
] 
[make haddock less noisy 
Simon Michael <simon at joyful.com>**20080927012958
 Ignore-this: 84921fbd34b1f7345dec2571c3ec32ae
] 
[resolve issue1043: fix bug in mergeAfterConflicting.
David Roundy <droundy at darcs.net>**20080926211928
 Ignore-this: 1416605539b44b32c18b348f3b4f459d
 This is moderately deep in the internals of the darcs-2 conflict
 handling code.  I had made an assumption that turned out not to be
 correct.  I fix this by switching to use a variant of the commute
 function that doesn't allow conflicting patches to commute, which I
 think should restore correctness here.  It's a scary bug, though, and
 if anyone were to create a moderately small test case, I'd be
 extremely grateful.
] 
[Roll back Dmitry's drop_dotdot change in Darcs.Patch.Filename.  
David Roundy <droundy at darcs.net>**20080926145013
 Ignore-this: d432374bbbe4cc006a26deeb3d15c3ec
 
 The key here is that he didn't want to change the internal
 patch-handling code, just the use of drop_dotdots in Darcs.RepoPath,
 which now uses UglyFileName for this purpose (which has Dmitry's code
 in it).
 
 rolling back:
 
 Thu Sep 25 13:57:11 EDT 2008  Dmitry Kurochkin <dmitry.kurochkin at gmail.com>
   * Make FileName.drop_dotdot work with absolute paths.
 
     M ./src/Darcs/Patch/FileName.lhs -7 +12
] 
[split FileName into two modules.
David Roundy <droundy at darcs.net>**20080926144501
 Ignore-this: dbb6650c6300745101bacd41bef431f0
 This duplicates some code, and makes a Darcs.Patch.FileName into the
 module (which FileName originally was) for handling paths within a
 darcs repository.  Code that had gotten agglomerated into this module
 is now in UglyFileName.lhs, which I hope to eliminate.  I went through
 the imports of FileName and tried to separate them between those that
 use FileName to deal with paths in a repository and those that use the
 extra functions what were added there, and those that abuse FileName
 to handle other sorts of paths (absolute paths, in particular).
] 
["make api-doc-with-source" generates docs with links to colourised source code
Simon Michael <simon at joyful.com>**20080925213719
 Ignore-this: c16b935c727838c606fa5daa29ccc41f
 This works with current hs-colour on GNU/Linux but may not be
 portable; I made it a separate make target to start with.  Only
 per-module source links are enabled until there is a fix for the
 haddock/hoogle issue noted.
] 
[issue27.sh is still sporadically buggy.
David Roundy <droundy at darcs.net>**20080926134948
 Ignore-this: ec2bf07485a6dc0fda83c786a7982df1
] 
[add test that fails sporadically on nfs under ghc 6.6.
David Roundy <droundy at darcs.net>**20080925202350
 Ignore-this: 8aae9073ea132935f1951f7e187bc2ea
 I haven't time to track this down, but it doesn't look like a bug in
 the test script.  This was the issue27 test.
] 
[Move issue1078 test from bugs to tests.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080925180103
 Ignore-this: f735ee2e36bdf8f446cab61d1f7ac334
] 
[Resolve issue1078: make ioAbsolute work with symbolic links in file paths.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080925175726
 Ignore-this: af4cf0bd842b9aae5e2fffe4500a1aa5
] 
[Make FileName.drop_dotdot work with absolute paths.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080925175711
 Ignore-this: 46c625a35bb11bea19b0749756d1a225
] 
[Force hidden conflicts test to use the darcs-2 format.
Eric Kow <E.Y.Kow at brighton.ac.uk>**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 <dmitry.kurochkin at gmail.com>**20080925142606
 Ignore-this: e8be404b0ccbc56d8f547b11b6e58c76
 This would hopefully make it pass on NFS.
] 
[Exceptions to GPL granted as of 2008-09-11.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080911120758] 
[Update manual to reflect --darcs-2 default.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080925142538] 
[resolve issue1003: don't sever transfer-mode connection on IO error.
David Roundy <droundy at darcs.net>**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 <simon at joyful.com>**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
] 
[TAG 2.1.0pre2
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080925081049
 Ignore-this: 99b608f2401e8f14358e121e9b95e211
] 
[Bump version number to 2.1.0pre2.
Eric Kow <E.Y.Kow at brighton.ac.uk>**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 <E.Y.Kow at brighton.ac.uk>**20080925080141
 Ignore-this: 1b1e57d425f8528e00e03e7b4a23ad78
] 
[ChangeLog entries: more stuff to ignore
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080925080129
 Ignore-this: 45362ed8bbabdacf222928cba6756aa4
] 
[More readable length comparison.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080924142304] 
[Haddock some primitive patch functions.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080924142157] 
[resolve issue805: make darcs-2 format the default for new repositories.
David Roundy <droundy at darcs.net>**20080924141158
 Ignore-this: e7952cb0cdc3124ffa50b0775822000e
] 
[make flagsToPristine obey repository format.
David Roundy <droundy at darcs.net>**20080924135319
 Ignore-this: 6038a7d05126af9e446406022ca608a0
 This reduces the number of places we set the default repository format
 (hopefully to one?).
] 
[move issue27 test to bugs directory, since it fails.
David Roundy <droundy at darcs.net>**20080923215936
 Ignore-this: 4556b273a9f8728de8ac855aae8442d0
] 
[Add test for issue27.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080918135923] 
[Add a test case for issue1078
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080923081757
 Ignore-this: 33f7f1f63c7b707ff148531f8229ceb0
] 
[give more useful failure message in HTTP for proxy errors.
David Roundy <droundy at darcs.net>**20080923153400
 Ignore-this: 3d6d204da399175eedf68bedfed8e504
] 
[HTTP: detect proxy server (failing if we want one)
Eric Kow <E.Y.Kow at brighton.ac.uk>**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).
] 
[simplify patches in rollback.
David Roundy <droundy at darcs.net>**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.
] 
[fix filepath code to work with FilePath package that preceded filepath.
droundy at darcs.net**20080923000405
 Ignore-this: 6aa0d8b357b0f966403ebe5965dcdec4
] 
[fix type witness bug in createRepository.
David Roundy <droundy at darcs.net>**20080922234321
 Ignore-this: 2c50393ca25740ce3e210dd24fe8d8fa
] 
[Resolve conflict between replace patches in Darcs.Arguments
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080922202647] 
[Resolve issue53: check for windows filename validity in darcs add/mv.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080922172004] 
[Use --reserved-ok to allow a file with ':' in it in tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**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 <E.Y.Kow at brighton.ac.uk>**20080922152256] 
[Add --reserved-ok flag for darcs add and mv.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080922141532
 This is just the flag, not the actual effect.
] 
[Check for filepath package in configure.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080922140520] 
[simplify fix for issue1041.
David Roundy <droundy at darcs.net>**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 <droundy at darcs.net>**20080922232839
 Ignore-this: de2a050022dea4251cdc2cc5e8b55c8c
] 
[Translate mark-conflicts test into shell.
Eric Kow <E.Y.Kow at brighton.ac.uk>**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 <E.Y.Kow at brighton.ac.uk>**20080922221024] 
[Move repository creation to Darcs.Repository.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080922215913
 This is just to avoid importing the DarcsRepo and HashedRepo code in higher
 level code.
] 
[remove test_unit from disttest to speed things up.
David Roundy <droundy at darcs.net>**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 <droundy at darcs.net>**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 <ddvlad at anaconda.cs.pub.ro>**20080922171705] 
[Replace --without-docs with less ambiguous --without-manual (issue1082).
Trent W. Buck <trentbuck at gmail.com>**20080922002602
 It's confusing for ./configure --without-docs to complain about missing haddock.
] 
[Documentation for --allow-unrelated-repos.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080922121122
 Ignore-this: d2630826313c8aeb00acb6853030c22d
] 
[Rename --ignore-unrelated-repos to --allow-unrelated-repos.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080922120727
 Ignore-this: a5990f1741c867316a948e6721118651
] 
[fix  bug I introduced into issue1039 test.
David Roundy <droundy at darcs.net>**20080921213043
 Ignore-this: 5b3c6476abae6bb050be014555d05bbe
] 
[Fix hang after a user input error (for example, EOF).
Judah Jacobson <judah.jacobson at gmail.com>**20080918163017] 
[replace consRLSealed with a more  general mapFlipped.
David Roundy <droundy at darcs.net>**20080921185241
 Ignore-this: c28f73f165254582cba6a14ba6ce93
] 
[make issue1039 fix allow small dissimilar  repositories.
David Roundy <droundy at darcs.net>**20080921184515
 Ignore-this: 918a09df18ef48c649c1bfaa866d6176
] 
[revert refactor that breaks type witnesses.
David Roundy <droundy at darcs.net>**20080921182331
 Ignore-this: dd692cffc1a238d6726448bacfe9cacc
] 
[Add '--ignore-unrelated-repos' option to disable unrelated repositories check.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919152631] 
[Resolve issue1039: detect seemingly unrelated repositories when doing push, pull and send.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919144553] 
[Refactor in pull_cmd.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919135349
 Ignore-this: e26a489a7a53aeaba544ae5ad0006700
] 
[Test for issue1039.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919153011] 
[manual: add an example of record --pipe prompts similar to tag --pipe docs
Simon Michael <simon at joyful.com>**20080918205353] 
[user manual corrections regarding what record and tag --pipe prompt for
Simon Michael <simon at joyful.com>**20080918204500] 
[clarify the short help for --pipe
Simon Michael <simon at joyful.com>**20080918193717] 
[Spaces in Darcs.Arguments.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919150440] 
[Spaces in Darcs.Commands.Send.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919150139] 
[Spaces in Darcs.Commands.Pull.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919145812] 
[Spaces in Darcs.Commands.Push.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919145553] 
[Print "We have the following patches to send:" only when we really have somthing to send.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080919114229] 
[Use gmakeisms for prettier output.
Trent W. Buck <trentbuck at gmail.com>**20080919071358] 
[TAG 2.0.3pre1
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080918023645] 
[Bump version number to 2.0.3pre1.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080918023634] 
[Canonize Florent Becker, Matthias Killian, Trent Buck, Thorkil Naur
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080918020453] 
[ChangeLog entries for darcs 2.0.3pre1 again.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080918020442] 
[Re-enable haskeline by default.  Require haskeline>=0.3.1 which fixes issue1050.
Judah Jacobson <judah.jacobson at gmail.com>**20080917194007] 
[Throw an error when haskeline returns an EOF/EOT.
Judah Jacobson <judah.jacobson at gmail.com>**20080917180124] 
[Disable more record_editor tests under Windows.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080917192602
 It still appears to be failing under Cygwin.
] 
[fix changes.pl test (translating to bash)
David Roundy <droundy at darcs.net>**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 <droundy at darcs.net>**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 <droundy at darcs.net>**20080917154657
 Ignore-this: b91ab6f6e05e0fda25488fa51653b741
] 
[add a couple of tests of unrecord.
David Roundy <droundy at darcs.net>**20080917133738] 
[add a few (passing) tests of pending handling in obliterate and unrecord.
David Roundy <droundy at darcs.net>**20080917130423] 
[Use putStrLn for "Cancelled." message.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080916205014] 
[remove now-unused is_addrmfile and is_addrmdir.
David Roundy <droundy at darcs.net>**20080916173136] 
[resolve issue1012: it seems to be fixed by the fix for issue709.
David Roundy <droundy at darcs.net>**20080916173116] 
[resolve issue885: fix patchSetToRepository to work with hashed.
David Roundy <droundy at darcs.net>**20080916173030] 
[resolve issue709: avoid adding changes to pending in rmpend when possible.
David Roundy <droundy at darcs.net>**20080916173002] 
[first-stage fix for issue709.
David Roundy <droundy at darcs.net>**20080916170333
 Here I fix the bug which leads to a corrupt pending being left, with a
 rmfile change but no hunk removing the contents.  This doesn't fix
 issue709, since an incorrect pending is left, it's just no longer a
 corrupt pending (i.e. it's still got the rmfile, but if you record it
 there's no problem).
] 
[add new test that we don't do anything when repairing a clean repo.
David Roundy <droundy at darcs.net>**20080916165437] 
[whitespace change in prepend.
David Roundy <droundy at darcs.net>**20080916160425] 
[make shell_harness print summary of passing tests when running bugs tests.
David Roundy <droundy at darcs.net>**20080916145820] 
[trailing whitespace cleanup in Repository.Internal.
David Roundy <droundy at darcs.net>**20080916142112] 
[tiny refactor in Internal.lhs.
David Roundy <droundy at darcs.net>**20080916155922] 
[simplify issue965 test (which took quite a while for me to figure out).
David Roundy <droundy at darcs.net>**20080916152028] 
[Test for issue691.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080916111332] 
[Make match.pl test understand Windows dates.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080916011339
 Windows does not abbreviate its timezones.
] 
[Disable some tests that don't work under Windows.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080916000912] 
[Translate get.pl test into shell.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080916000227
 The original get.pl uses the Perl Cwd library, which seems not
 to work for purposes of this test under MSYS.
] 
[Resolve issue691: distinguish between NoArg and ReqArg in defaults parser.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080915224046] 
[Move get_default_flag type to definition.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080915220316] 
[reverse overly-invasive haddocking.
David Roundy <droundy at darcs.net>**20080915110353] 
[In darcs send if POST fails try sendmail.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914234314] 
[Grammar in Darcs.Commands.Send.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914232923] 
[Print "Successfully sent patch bundle to" only when we really sent something.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914232905] 
[Fix overzealous escaping in haddock.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080915070926] 
[Haddock documentation for English.lhs
florent.becker at ens-lyon.org**20080913143844
 Docstrings by Eric Kow
] 
[Haddock documentation for PrintPatch
florent.becker at ens-lyon.org**20080913143420] 
[Haddock documentation for Flags
florent.becker at ens-lyon.org**20080913143026] 
[Haddock documentation for Motd
florent.becker at ens-lyon.org**20080913141335
 docstring by Eric Kow
] 
[Haddock string for TheCommands
florent.becker at ens-lyon.org**20080913141040
 Docstring by Eric Kow
] 
[Run testing in temp directories to avoid collosions, fail if DarcsURL header is not found.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914223930] 
[Use tempfile() UNLINK option to automatically remove temp files at exit.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914223827] 
[Coding style in upload.cgi.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914223751] 
[Stop after we found the first DarcsURL: in patch bundle.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914220421] 
[Spaces in upload.cgi.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080914220324] 
[Really allow pull.sh test to pass on Windows.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080914211458
 
 It seems that these redirections cause an openBinaryFile failure under
 Windows.  I do not yet understand why using different names makes a
 difference, but it could provide an interesting clue.
] 
[ChangeLog entries for darcs 2.0.3pre1
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080914094144] 
[Disable amend-cancelling test under Cygwin.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080913213039] 
[Make binary.sh test more portable (avoid copying an exe).
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080913212843
 Under Windows, copying the exe file will result in an .exe extension
 being appended to the filename.  This confuses the test.
] 
[rewrite upload.cgi so it won't need any customization by default.
David Roundy <droundy at darcs.net>**20080913171447
 The downside is that it has to do a darcs get --lazy in order to check if
 the patch can be applied.  If you define $target_repo, however, it doesn't
 need to do this (but then can only accept patches to a single
 locally-present repo).
] 
[when _darcs/prefs/post is present, use _darcs/prefs/post for To: header.
David Roundy <droundy at darcs.net>**20080913171025] 
[sketchy documentation of _darcs/prefs/post
David Roundy <droundy at darcs.net>**20080913115655] 
[set default upload.cgi to work on darcs-unstable.
David Roundy <droundy at darcs.net>**20080913112227] 
[Improve upload.cgi.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912230953
 - check if patch is valid before sending
 - use sendmail to send patches or drop to maildir
] 
[Spaces and punctuation in upload.cgi.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912230827] 
[fix problem in Darcs.URL refactor pointed out by Eric.
David Roundy <droundy at darcs.net>**20080913104327] 
[Disable a pull.sh test under Windows.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080912224027
 It relies on darcs not working if we chmod u-r a file.
 This seems to have little effect in Windows.
] 
[refactor Darcs.URL to eliminate use of Regexes.
David Roundy <droundy at darcs.net>**20080912173611
 The algorithms here are not tricky, and I find this easier to read.
] 
[change is_file to return false on droundy at darcs.net:
David Roundy <droundy at darcs.net>**20080912173501] 
[clean up whitespace.
David Roundy <droundy at darcs.net>**20080912150248] 
[fix manual for optional arguments.
David Roundy <droundy at darcs.net>**20080912150231] 
[clean up whitespace.
David Roundy <droundy at darcs.net>**20080912145708] 
[add test for new --output-auto-name feature.
David Roundy <droundy at darcs.net>**20080912145648] 
[Spaces in Darcs.Commands.Send module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912122223] 
[Make '--output-auto-name' accept optional directory argument.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912120516] 
[Add DarcsOptAbsPathOption for options with optional path argument.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912112458] 
[Refactor Darcs.Repository.Prefs.getCaches.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912055204] 
[Print warning when '--http-pipelining' option is used, but darcs is compiled without HTTP pipelining support.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912054253] 
[Do not download URL we have speculated before.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912053236] 
[Spaces and parentheses in URL module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080912053000] 
[Coding style in Darcs.Arguments.network_options.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080911140710] 
[Resolve issue1054: --no-cache option to ignore patch caches.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080911140233] 
[Remove unused variable from configure.ac.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080911132107] 
[Comment in configure.ac.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080911115840] 
[Indentation fixes in configure.ac.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080911115117] 
[Formating and minor refactoring in URL.urlThread.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080910061227] 
[insecure printfs - fix the two that I can currently hit
Steve Cotton <steve at s.cotton.clara.co.uk>**20080910230659] 
[TAG this version works.
David Roundy <droundy at darcs.net>**20080910212908] 
[Add '[DEFAULT]' to -[-no]-http-pipelining options.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080910105930] 
[remove ugly unused function appendToPath.
David Roundy <droundy at darcs.net>**20080910135159] 
[remove buggy unused function combine.
David Roundy <droundy at darcs.net>**20080910134918] 
[Make issue1057 test run on Cygwin.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080910100436] 
[move issue966 test to tests/ since it passes.
David Roundy <droundy at darcs.net>**20080909194300] 
[resolve issue1057: this was fixed in the previous patch.
David Roundy <droundy at darcs.net>**20080909155523] 
[don't inline global variables in URL.
David Roundy <droundy at darcs.net>**20080909155413] 
[fix bug in file path handling.
David Roundy <droundy at darcs.net>**20080909155325] 
[Documentation for -[-no]-http-pipelining options.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080909063743] 
[Space in Darcs.Arguments module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080909062824] 
[Move network related options to network_options.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080909062429] 
[Do no word splitting after expansion in pwd-based shell tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080908174948
 Lest darcs/Cygwin be confused by spaces in the pwd output.
] 
[don't define pipeliningLimit if we don't use it.
David Roundy <droundy at darcs.net>**20080908221625] 
[Add -[-no]-http-pipelining options, disable pipelining by default for curl < 7.19.1.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080908175726] 
[Resolve issue1063: Wrap pwd in cygpath in shell tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080908140640
 This is so that we can run the test suite under Cygwin.
 Solution by Zooko.
] 
[Apply Eric suggestions on tests/binary.sh
Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080907160645] 
[Remove old ChangeLog entries (before 2.0.2).
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080908125545] 
[Replace old ChangeLog entries for 1.0.3rc1.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080908124213
 
 I think my previous patch to avoid re-computing the ChangeLogs must
 have overwritten these hand-written (?) logs with automated ones.
 This patch ensures that the ChangeLog people see does not change.
] 
[Do not recompute ChangeLogs from darcs 2.0.2 or before.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080907145921] 
[Make binary.sh test more robust wrt spaces in filenames.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080907143929] 
[Add a test for binary patch files.
Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080907103816] 
[Update the memo about running test at record time
Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080906143815] 
[No -v option to cp(1)
Matthias Kilian <kili at outback.escape.de>**20080906121437
 
 This option isn't POSIX and doesn't exist on all operating systems.
 
] 
[Fix the gzip test for OpenBSD's gzip
Matthias Kilian <kili at outback.escape.de>**20080906115507
 
 OpenBSD's gzip(1) doesn't understand long options. Also, it doesn't
 like to deal with files that don't have a .gz extension, so let it
 read from stdin. Note: the for look isn't strictly necessary here
 (there's only one file matching), but I think it's better style.
] 
[update web page to point at both stable and unstable branches.
David Roundy <droundy at darcs.net>**20080906120322
 This is mostly a gratuitous change, so I'll have something to push in order
 to make  sure the unstable branch infrastructure is working.
] 
[bug fix for amend-cancelling.sh test
Jason Dagit <dagit at codersbase.com>**20080905194544] 
[add test for amending a depended upon patch
Jason Dagit <dagit at codersbase.com>**20080905192942
 Due to a buggy refactor of with_selected_patch_from_repository
 it is possible to make amend-record hit an impossible case.  This
 is a test for that case.
] 
[URL.hs: print debug message when wait_next_url starts.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080904133048] 
[URL.hs: fix race condition in copyUrlWithPriority and waitUrl.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080903195254] 
[Fix advice to get QuickCheck 2.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905161051] 
[revise advice to indicate darcs check over make disttest.
David Roundy <droundy at darcs.net>**20080905153056
 make disttest has the unfortunate side-effect of ruining your current
 configuration, if you happen to be using something like
 --with-libwww.
] 
[Add Repository IO monad, RIO.
Jason Dagit <dagit at codersbase.com>**20080902232331] 
[Makefile: offer advice on record --no-test
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905121952] 
[Switch test pref to make disttest.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905114335] 
[Allow make disttest to run without the configure script being present.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905114156
 This is to prepare it for use as the darcs test pref.
] 
[Resolve issue1050: Disable haskeline by default.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905113251
 We should revisit this when the Haskeline bug in question is fixed.
] 
[Resolve issue924: test for QuickCheck2 in disttest
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905111647] 
[Makefile: Tidy up disttest.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080905105921] 
[relocate issue1057.sh to bugs/.
David Roundy <droundy at darcs.net>**20080904224145] 
[Test for issue 1057: pull fails to report "Can't pull from current repository" when pulling via symbolic link
naur at post11.tele.dk**20080904212508] 
[Remove [DarcsFlag] use in (most of) HashedIO, HashedRepo API.
me at mornfall.net**20080903211833] 
[Remove a few unused [DarcsFlag] parameters from HashedRepo and  Repository.Internal.
me at mornfall.net**20080903211812] 
[Replace [DarcsFlag] with Compression in HashedIO Slurpy.
me at mornfall.net**20080903160807] 
[Add data Compression to Darcs.Flags.
me at mornfall.net**20080903154814] 
[Replace Maybe Bool with custom tri-state type in patch selection code.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080904173650
 Hopefully this makes things a bit more readable.
] 
[Roundup integration: avoid changing the bug topic.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080903221859
 
 The previous behaviour made it difficult to search the bug tracker
 because the topic would change to the patch name.  Perhaps it would
 be more useful for future searching if the topic remained untouched.
] 
[Provide DARCS_KEEP_TEMPDIR hint in testing README.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080831115908] 
[Haddock speculateFileUsingCache.
me at mornfall.net**20080904102855] 
[Remove the obsolete release/debian stuff.
me at mornfall.net**20080903143659] 
[Refactor Cache's handling of hashed paths. No functional change.
me at mornfall.net**20080902185745
 
 Factored out the filepath building to a single place. This also led to folding
 the explicit pattern matches on writability into a predicate, since the other
 components of a CacheLoc are no longer useful in the function bodies.
] 
[convert mv.pl into shell.
David Roundy <droundy at darcs.net>**20080902194056] 
[clean up ShowRepo a tad.
David Roundy <droundy at darcs.net>**20080902152652] 
[add type witnesses to new functions.
David Roundy <droundy at darcs.net>**20080902145440] 
[resolve issue1015: workaround internal API change on Windows in GHC 6.8.3
Ganesh Sittampalam <ganesh at earth.li>**20080901223420] 
[add another debug message.
David Roundy <droundy at darcs.net>**20080902144814] 
[fix bug in handling of corrupted pending file, and in test.
David Roundy <droundy at darcs.net>**20080902144450
 Our test was wrong, and our repair wasn't smart enough to find this.
 Recent fixes in repair by Petr revealed this bug, which allowed darcs
 to record a corrupt patch if users manually corrupted the pending
 file.  I fixed the test (and translated it to bash), and also fixed
 the bug by making darcs rename the pending file as soon as it notices
 it is broken.  This may not be the most robust solution (it might be
 better to just exit with failure), but it is much better than
 corrupting the recorded state.
] 
[Make clean_hashdir take a list of root hashes and use it in repair.
me at mornfall.net**20080902025040
 
 We use this functionality to keep two possibly distinct pristine trees while 
 repairing, both living in a single pristine.hashed directory.
] 
[Add HashedRepo.readHashedPristineRoot.
me at mornfall.net**20080902024943] 
[Make the "hashed" repair use pristine.hashed for its work.
me at mornfall.net**20080902024620
 
 We rely on HashedIO reliability to simplify repair to work inside the existing
 pristine.hashed. When running on old-fashioned (darcs 1) repositories, we
 temporarily create pristine.hashed, use it to check (and possibly replace) the
 old-fashioned pristine and finally we remove it again.
] 
[Add Repository.replacePristineFromSlurpy.
me at mornfall.net**20080902024254] 
[Resolve conflicts.
me at mornfall.net**20080901150324] 
[Fix checkPristineAgainst{Cwd,Slurpy}: we ignored files missing in pristine.
me at mornfall.net**20080812012720
 
 Add LookForAdds to smart_diff options to fix that and also throw in IgnoreTimes
 for a good measure and extra paranoia.
] 
[Only "update" (sync to disk) the slurpy every 100 patches.
me at mornfall.net**20080812010603] 
[First working (albeit slow) version of repair that uses hashed newpristine.
me at mornfall.net**20080812005423] 
[Add Repository.checkPristineAgainstSlurpy.
me at mornfall.net**20080812005039] 
[Haddock the {slurp,write,sync}HashedPristine functions in HashedIO.
me at mornfall.net**20080902020532] 
[Change type of subdir parameter in Cache/HashedIO functions from String to HashedDir.
me at mornfall.net**20080902010405
 
 This refactor should make calling the Cache and HashedIO functions safer: you
 should be no longer able to swap hash and subdir accidentally in the call site,
 or mistype the subdirectory name.
] 
[Rename hashSlurped, slurpHashed and syncHashed to writeHashedPristine, slurpHashedPristine and syncHashedPristine, respectively.
me at mornfall.net**20080902004402] 
[autoconf terminfo support
Ganesh Sittampalam <ganesh at earth.li>**20080901060519] 
[Optionally replace curses binding with "terminfo" from hackage.
me at mornfall.net**20080829104841] 
[Resolve issue1037: compile with -D_REENTRANT.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080901175738] 
[add makefile target "disttest" which does the script currently stored in _darcs/prefs/prefs
zooko at zooko.com**20080901164342
 This way other things such as buildbot can easily run the same tests as _darcs/prefs/prefs does.
 It is named "disttest" because it is analogous to "distclean" inasmuch as it blows away your object files and changes your ./configure.
 Also remove an obsolete .PHONY target.
] 
[add fortran .mod files to boring.
David Roundy <droundy at darcs.net>**20080901141647] 
[resolve issue1049: undo lazy patch bundle scanning.
David Roundy <droundy at darcs.net>**20080901135717] 
[tests: quote the repo variable in mv.pl so that the test will work when PWD has a space in it
zooko at zooko.com**20080831180649] 
[tests: silence unnecessary warning output from running tests
zooko at zooko.com**20080831185458] 
[ChangeLog entries: ignore a minor patch which has the string "warning" in it
zooko at zooko.com**20080901131432] 
[ChangeLog entries: ignore all patches with the string "ChangeLog entries" in them when generating ChangeLog entries
zooko at zooko.com**20080901125639
 ChangeLog entries
 :-)
] 
[ChangeLog entries: ignore a minor patch which includes the name "warning" because it makes buildbot think that the build step is emitting a compiler warning
zooko at zooko.com**20080901125526] 
[resolve issue844: darcs doesn't guarantee always to compress patches.
David Roundy <droundy at darcs.net>**20080901134631] 
[Add test case for issue844.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080830230909] 
[Fixed typo: "view this patch in *fill with the pager".
Alex Lance <alla at cyber.com.au>**20080901052559] 
[don't show ssh stderr output unless we're passed --debug.
David Roundy <droundy at darcs.net>**20080831200751
 Also fix the incorrect comment that often incorrectly declares that the
 server is running an older version of darcs.
] 
[fix bug in --list-options (tab completion).
David Roundy <droundy at darcs.net>**20080830195051] 
[fix bug in makeRelative.
David Roundy <droundy at darcs.net>**20080830174722] 
[add warning to configure about Haskell zlib speed
Ganesh Sittampalam <ganesh at earth.li>**20080830013457] 
[make use of Haskell zlib dependent on bytestring
Ganesh Sittampalam <ganesh at earth.li>**20080829221605] 
[add option to use Haskell zlib package
Ganesh Sittampalam <ganesh at earth.li>**20080829203032] 
[Remove unused FileSystem module.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080822151214] 
[Add a link to a repository browser for darcs's code.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080829144357] 
[Replace grep invocation by perl code
kili at outback.escape.de**20080829110211] 
[clean up network/get.sh test.
David Roundy <droundy at darcs.net>**20080824190916] 
[fix type of withRepository and friends.
David Roundy <droundy at darcs.net>**20080828181834] 
[fix recent bug in --list-options.
David Roundy <droundy at darcs.net>**20080828162707] 
[Check for package random on windows, used in Ssh module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080828091554] 
[Debug messages in curl module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080827222845] 
[TAG working version.
David Roundy <droundy at darcs.net>**20080828131617] 
[Use InclusiveOrExclusive instead of Bool in apply_inv_to_matcher.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080827201820] 
[add more modules to make witnesses.
David Roundy <droundy at darcs.net>**20080827201217] 
[updates to Darcs.Patch.Unit for type witnesses
Jason Dagit <dagit at codersbase.com>**20080827165445] 
[Refactor get_matcher and apply_inv_to_matcher functions from Darcs.Match module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080827105843] 
[Resolve issue966: fix apply_inv_to_matcher_inclusive.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080827091833] 
[Simplify withCurrentDirectory.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080823004712] 
[updates to Sealed.lhs to support type witness refactor in commands
Jason Dagit <dagit at codersbase.com>**20080827165357] 
[updates to Ordered.lhs to support type witness refactor in commands
Jason Dagit <dagit at codersbase.com>**20080827165053] 
[make Annotate.lhs compile with type witnesses
Jason Dagit <dagit at codersbase.com>**20080827164003] 
[fix type witnesses in Internal.
David Roundy <droundy at darcs.net>**20080827190200] 
[updates to Repository.Internal to fix conflicts and support type witness refactor in commands
Jason Dagit <dagit at codersbase.com>**20080827165327] 
[fix error in Properties due to new commuteFL
Jason Dagit <dagit at codersbase.com>**20080827044025] 
[fix minor type witness compile error with new commuteFL
Jason Dagit <dagit at codersbase.com>**20080827041344] 
[fix conflicts with get_extra changes
Jason Dagit <dagit at codersbase.com>**20080827041321] 
[improve reporting for bug in get_extra
Jason Dagit <dagit at codersbase.com>**20080825011810] 
[Finish refactor of Unrevert as well as making it pass double-unrevert.sh
Jason Dagit <dagit at codersbase.com>**20080825185907] 
[add double-unrevert.sh test
Jason Dagit <dagit at codersbase.com>**20080825183235] 
[partial type witnesses in Unrevert
Jason Dagit <dagit at codersbase.com>**20080813053837] 
[More ChangeLog entries since 2.0.2
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080826082638] 
[fix bug in defaultrepo.
David Roundy <droundy at darcs.net>**20080827152710] 
[fix accidental reversal in tentativelyAddToPending
Jason Dagit <dagit at codersbase.com>**20080826003605] 
[minor refator to get_extra improve comments
Jason Dagit <dagit at codersbase.com>**20080825170111] 
[Same ChangeLog entries since 2.0.2
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080825164844] 
[Some more globally ignored changes.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080825164814] 
[Changelog (ignore 'Add a test entries')
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080822152614] 
[Simplify filepath handling, cutting lots of hardly-used code.
David Roundy <droundy at darcs.net>**20080824173919] 
[don't bother computing path when checking prereqs (since we now can handle looking at beginning/ending working directories).
David Roundy <droundy at darcs.net>**20080823193448] 
[resolve issue950: fix fix_filepath to work with --repodir (and add test demonstrating this).
David Roundy <droundy at darcs.net>**20080823185940] 
[eliminate fix_flag.
David Roundy <droundy at darcs.net>**20080823180947] 
[add new framework for ensuring that certain arguments are converted to absolute paths.
David Roundy <droundy at darcs.net>**20080823164410
 Currently this is only used for --output, but there are a few other
 commands we can fix.  Ideally, we'll fix enough flags that fix_flag
 will become identity, and can be removed.
] 
[make Darcs.Lock functions accept FilePathLike arguments.
David Roundy <droundy at darcs.net>**20080823162940] 
[refactor maybeMkSubPath very slightly.
David Roundy <droundy at darcs.net>**20080823143505] 
[refactor repoPath very slightly.
David Roundy <droundy at darcs.net>**20080823143153] 
[make makeAbsolute behavior match comment.
David Roundy <droundy at darcs.net>**20080823121149] 
[Fix makeAbsolute to work with '../foo' paths.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080822184823
 This fixes option arguments with '../', like 'darcs send -o ../foo.dpatch'.
 Part of issue950.
] 
[move withCurrentDirectory, withTempDir and withPermDir
David Roundy <droundy at darcs.net>**20080822155100
 out of RepoPath.  This is a pretty invasive change, part of a pathetic
 attempt to allow AbsolutePath to permeate the code when we know that
 paths are absolute.  Eventually this will allow us to statically
 ensure that paths *are* absolute.  For now, it mostly just makes a few
 things more ugly.  Eventually we'd like to only use (for instance)
 Darcs.RepoPath.getCurrentDirectory, which itself witnesses that the
 resulting path must be absolute.
] 
[rewrite mkAbsolutePath to be safe.
David Roundy <droundy at darcs.net>**20080822150037] 
[resolve conflicts.
David Roundy <droundy at darcs.net>**20080822133823] 
[Resolve issue936: fix type witnesses configure check.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819193228] 
[Use forkIO in URL module as suggested by Simon Marlow.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819182648] 
[Remove HTTP.copyUrl, integrate it to URL module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819170350] 
[More URL module refactoring.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819145234] 
[Canonize Nathaniel Filardo and Simon Marlow.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080822021232] 
[Add test case for issue966 (from Dan Pascu's bug report)
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080822020616] 
[remove trailing whitespace.
David Roundy <droundy at darcs.net>**20080821224353] 
[Documentation for match touch primitive.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080821193706] 
[Resolve issue115: match patches touching given files.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080821183355] 
[fix type witnesses in with_selected_patch_from_repo.
David Roundy <droundy at darcs.net>**20080820130112] 
[clean up bugs functions (eliminate darcsBug.h).
David Roundy <droundy at darcs.net>**20080820124425] 
[Fix a bug with incorrectly specified with_selecte_patch_from_repository.
Jason Dagit <dagit at codersbase.com>**20080819233348] 
[Remove HTTP.exists, use Autoconf.have_HTTP instead.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819131617] 
[fix improper use of bug in HTTP.
David Roundy <droundy at darcs.net>**20080819211201
 In these cases failure is not a bug, it may just as well mean that the
 user has typed in a bad URL.
] 
[Do not import HTTP module in Darcs.Bug, use bug and debugFail for error reporting in HTTP module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080819124207] 
[fix incompatibility with ghc 6.6.
David Roundy <droundy at darcs.net>**20080819161540] 
[make scan_bundle create a lazy patch bundle.
David Roundy <droundy at darcs.net>**20080819154624
 The idea is to more easily catch errors in which the patch bundle is
 misused.
] 
[resolve conflicts with Darcs.Ordered change.
David Roundy <droundy at darcs.net>**20080819153558] 
[replace separate_middle_last_from_first and separate_last_from_first_middle with get_choices
Jason Dagit <dagit at codersbase.com>**20080815222635] 
[correct a bug in with_selected_patches_from_repository
Jason Dagit <dagit at codersbase.com>**20080815201125
 Fixing this bug allows w_s_p_f_r to have the expected type signature
 and also corrects a problem where the non-selected patches were returned
 in the wrong context.
] 
[refine type witnesses in SelectChanges
Jason Dagit <dagit at codersbase.com>**20080813050425] 
[make WhatsNew work with type witnesses
Jason Dagit <dagit at codersbase.com>**20080813044354] 
[major refactor of SelectChanges to work with type witnesses
Jason Dagit <dagit at codersbase.com>**20080813031625] 
[Eliminate HopefullyPrivate (fixed patch edition)
nwf at cs.jhu.edu**20080809205759] 
[Move Darcs.Patch.Ordered to Darcs.Ordered since it isn't patchy
nwf at cs.jhu.edu**20080816074429] 
[Fix use of threadWaitRead on Windows
Simon Marlow <marlowsd at gmail.com>**20080819141151
 threadWaitRead doesn't work on Windows in all GHC versions < 6.10.1
 (which isn't released yet).
 
 This means that since darcs is compiled with -threaded, when compiled
 with GHC < 6.10 on Windows, darcs will not respond to ^C when waiting
 for user input.
 
] 
[Fix Windows build
Simon Marlow <marlowsd at gmail.com>**20080819134252
 On Windows, System.Posix.Types.FileOffset is not the same as the type
 of the st_size field of the stat structure: the latter is Int64,
 whereas COff == Int32.
 
 This is almost ceratinly not the right fix, but it gets the build
 going.
 
 In general I don't recommend using System.Posix.* on Windows.  The
 right way is to either use the official platform-independent libraries
 like System.IO, System.Directory or System.Process, or to use
 System.Win32 directly.
] 
[URL module refactoring.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080817124816] 
[Do not compile curl support if libwww is enabled.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080817121834] 
[URL.hs: always import debugFail, again.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080817121101] 
[URL.hs: call debugFail when download fails.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080816070213] 
[URL.hs: debug messages.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080816070147] 
[Spacing in Darcs/Commands/Changes.lhs
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080815221245] 
[Rename catchInt to catchInterrupt, better message when get is interrupted.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080815154421] 
[Resolve issue995: changes --context : {--human-readable,--xml-output} have no effect.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080815114105] 
[Tidy up known failing shell tests.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080818102100
 
 * Keeping track of these bugs could be simpler if they were all
   associated with a ticket and a short description
 * The shell harness allows us to avoid a lot of bureaucracy in
   in the scripts.  In fact, people should be able to submit a
   bug just by sticking a shell script in bugs, no hoops to jump.
] 
[Tidy up failing test for issue1013.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080818101351
 
 We don't need to use a $DARCS variable anymore, thanks to the shell
 harness.  Also, I noticed that what used to trigger a bug now hangs.
] 
[Add failing test for issue1012 (Simon Marlow).
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080818094104] 
[Add test for issue1017 (as suggested by Bjorn Bringert)
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080818194115] 
[don't print "Wrote patch to -" when writing patch to stdout.
David Roundy <droundy at darcs.net>**20080819142537] 
[always send with context.
David Roundy <droundy at darcs.net>**20080819140729] 
[Resolve issue823: do not exit on keyboard interrupt when getting patches.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080815070943
 And give a chance for go_to_chosen_version to run.
] 
[fix buggy comments in bugs/identical-patches.sh.
David Roundy <droundy at darcs.net>**20080814135322] 
[Add Ian's identical-patch test case.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080813171032] 
[URL.hs: store only URL in waitToStart queue.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080813122246] 
[Add (failing) test for issue944.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080814055903
 
 This appears to be a reggression from darcs 1.0.9, and was submitted by
 Wolfgang Lux on the bug tracker.  Interestingly, only the old format
 repositories are affected, not the hashed ones.
] 
[add type witnesses to TouchesFiles
Jason Dagit <dagit at codersbase.com>**20080810063403] 
[add type witnesses to Patch/Choices.lhs
Jason Dagit <dagit at codersbase.com>**20080809000237] 
[Split Cache mostly out of Darsc/Repository/Prefs into its own file (take 2)
nwf at cs.jhu.edu**20080813094329] 
[Make Darcs.Repository.Prefs export the cache hash function
nwf at cs.jhu.edu**20080807094918] 
[remove a few unsightly functions
Jason Dagit <dagit at codersbase.com>**20080813061256] 
[Fix URL module bug with pipelining enabled.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080813081218] 
[Minor change to URL module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080813074218] 
[Enable pipelining by default, add --disable-pipelining option (issue838).
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080813011342] 
[Generalize HashRepo.clean_pristine to HashIO.clean_hashdir.
me at mornfall.net**20080812002708] 
[Add writeSlurpy to roll out a copy of slurpy into a filesystem.
me at mornfall.net**20080812002345] 
[fix breakage in URL.
David Roundy <droundy at darcs.net>**20080812141220] 
[Parametrize "pristine.hashed" in a bunch of functions.
me at mornfall.net**20080812002114] 
[Rework URL module for multi threading.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080811221209] 
[Add thread synchronization to URL module and resume select() if interrupted by signal in curl module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080810092810] 
[Handle error case with empty URL in URL.waitNextUrl function.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080809221755] 
[Add --debug-http flag to enable curl and libwww debug at run-time instead of compile-time.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080809154834] 
[Print a warning when the remote end does not have darcs 2.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080811100933
 
 Two reasons:
 (1) right now people get a scary warning from ssh when it can't fetch
     some non-essential files (it used to be that we would send stderr from ssh
     to /dev/null, but that has other problems...)
 (2) darcs transfer-mode more widely deployed could help a lot of people
     wrt darcs performance
] 
[Added a beware note to the unrecord command
lele at nautilus.homeip.net**20080811145756] 
[Fixed typo
lele at nautilus.homeip.net**20080801162427] 
[Better debug messages in URL module.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080809215247] 
[make Convert.lhs compile.
David Roundy <droundy at darcs.net>**20080810201725] 
[improve type safety of Darcs.Repository.Internal.
Jason Dagit <dagit at codersbase.com>**20080810051109] 
[Refactor `darcs convert' warning at kowey's request.
Trent W. Buck <trentbuck at gmail.com>**20080810110014] 
[Expand formats text based in part on suggestions from darcs-users
Max Battcher <me at worldmaker.net>**20080809184043] 
[Fixes to global cache text based on darcs-users suggestions
Max Battcher <me at worldmaker.net>**20080809181424] 
[Add user-focused documentation of repository format options
Max Battcher <me at worldmaker.net>**20080807195429] 
[Highlight the global cache as a best practice
Max Battcher <me at worldmaker.net>**20080807193918] 
[Describe best practice in `darcs convert --help'.
Trent W. Buck <trentbuck at gmail.com>**20080810110615] 
[add type witnesses to Population
Jason Dagit <dagit at codersbase.com>**20080808053252] 
[add type witnesses to CommandsAux
Jason Dagit <dagit at codersbase.com>**20080808052738] 
[Add type witnesses to more modules, rounding out Darcs/Repository/*
Jason Dagit <dagit at codersbase.com>**20080808050947] 
[fixed a bug in identity_commutes property
Jason Dagit <dagit at codersbase.com>**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.
] 
[Make Darcs.Repository.Internal compile with type witnesses.
Jason Dagit <dagit at codersbase.com>**20080808015343] 
[UF8.lhs: remove unusued functions/imports/docs
gwern0 at gmail.com**20080807221826] 
[Resolve issue974 : do not pass both -optc-g and -opta-g to GHC
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080807073620] 
[make this test more cross-platform
Simon Michael <simon at joyful.com>**20080807103433] 
[document how to run unit tests
Simon Michael <simon at joyful.com>**20080807030416] 
[move (most) failing tests to bugs for clean test output
Simon Michael <simon at joyful.com>**20080806191336] 
[fix an old spelling error
Simon Michael <simon at joyful.com>**20080806170432] 
[make searching for "test:" in makefile work
Simon Michael <simon at joyful.com>**20080805222241] 
[run only normal (expected to pass) tests by default
Simon Michael <simon at joyful.com>**20080805222108] 
[Downplay quantum mechanics link.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080806124109
 Besides, darcs has far more than 3 users by now.
] 
[Make patch theory intro more inviting to math people.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080806123411] 
[cleanup and slight rewrite of the test docs
Simon Michael <simon at joyful.com>**20080806165949] 
[make order of running tests consistent
Simon Michael <simon at joyful.com>**20080806172123] 
[small makefile refactoring: allow just the normal tests to be run, without bugs/*
Simon Michael <simon at joyful.com>**20080805203242] 
[Rectify dist help
lele at nautilus.homeip.net**20080804080322
 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 <simon at joyful.com>**20080803181216] 
[Canonize Gaetan Lehmann and Daniel Buenzli.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080730104357
 (for Daniel B, avoid an accent in his name)
] 
[configure: check for packages needed with split base.
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080730103840
 Now that all packages must be used explicitly.
] 
[fix type witness compile errors specific to ghc 6.8
Jason Dagit <dagit at codersbase.com>**20080722182729] 
[avoid import of unused function fromMaybe.
David Roundy <droundy at darcs.net>**20080729172825] 
[configure: suggest regex-compat before text
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080725095336] 
[configure: mention Haskell in 'try installing' suggestion
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080725095015] 
[Typo (Text.Regex)
Eric Kow <E.Y.Kow at brighton.ac.uk>**20080715121708] 
[Use haskeline to have a readline-like behavior when asking something to the user
gaetan.lehmann at jouy.inra.fr**20080719065033
 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 <E.Y.Kow at brighton.ac.uk>**20080604123728] 
[add configure check for Network.URI.
David Roundy <droundy at darcs.net>**20080711011914] 
[add -hide-all-packages to default GHCFLAGS.
David Roundy <droundy at darcs.net>**20080711010952] 
[add support for outputting patch numbers in darcs changes.
David Roundy <droundy at darcs.net>**20080710011211] 
[add support for matching single patches by index.
David Roundy <droundy at darcs.net>**20080710004512] 
[add support for matching ranges of patches (counting back from present).
David Roundy <droundy at darcs.net>**20080710003225] 
[Better avoid silly manpage error.
Trent W. Buck <trentbuck at gmail.com>**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 <trentbuck at gmail.com>**20080704024232] 
[darcs --overview no longer works, so don't document it.
Trent W. Buck <trentbuck at gmail.com>**20080704030804] 
[Avoid silly manpage error.
Trent W. Buck <trentbuck at gmail.com>**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
gwern0 at gmail.com**20080627192026
 'twas causing lhs/haddock difficulties where a \end{code} wasn't getting recognized.
] 
[rm haddock CPP business
gwern0 at gmail.com**20080627191413
 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 <droundy at darcs.net>**20080624170035] 
[fix makefile to remember to regenerate version information after running configure.
David Roundy <droundy at darcs.net>**20080624170001] 
[TAG 2.0.2
David Roundy <droundy at darcs.net>**20080624012041] 
Patch bundle hash:
622aa9202a5adda9f017b0bee15c448de256b189


More information about the darcs-users mailing list