[darcs-devel] patches to review

Eric Y. Kow eric.kow at gmail.com
Thu Dec 6 16:14:40 UTC 2007


Here are two more that were in my WAITING box

Tommy's patch is basically waiting for his go-ahead, I guess when darcs
1.1.0 comes out.  Either that or we find a nicer solution to the
problem.

I think my patch can go in.  I remember this being the kind of tricky
stuff that I always make mistakes in, so it's worth thinking about.

-- 
Eric Kow                     http://www.loria.fr/~kow
PGP Key ID: 08AC04F9         Merci de corriger mon français.
-------------- next part --------------

New patches:

[Simplify getCurrentDirectorySansDarcs out of existence.
Eric Kow <eric.kow at gmail.com>**20071119041326
 
 It was buggy and needlessly complicated.
] {
hunk ./src/Darcs/Lock.lhs 36
-import Data.List ( isPrefixOf, inits )
hunk ./src/Darcs/Lock.lhs 63
-#include "impossible.h"
hunk ./src/Darcs/Lock.lhs 175
-          look_for_tmp [] = try_directory "/tmp" getCurrentDirectorySansDarcs
+          look_for_tmp [] = try_directory "/tmp" (sansDarcs `fmap` getCurrentDirectory)
hunk ./src/Darcs/Lock.lhs 180
-getCurrentDirectorySansDarcs :: IO FilePath
-getCurrentDirectorySansDarcs = do
-  c <- getCurrentDirectory
-  case drop 5 $ reverse $ takeWhile no_darcs $ inits c of
-    []    -> impossible
-    (d:_) -> return d
-  where no_darcs x = not $ "_darcs" `isPrefixOf` x
+sansDarcs :: FilePath -> FilePath
+sansDarcs "" = ""
+sansDarcs ('/':'_':'d':'a':'r':'c':'s':_) = ""
+sansDarcs (x:xs) = x : sansDarcs xs
}

[Fix corner case in sansDarcs.
Eric Kow <eric.kow at gmail.com>**20071119174422
 Pointed out by Kevin Quick.
] {
hunk ./src/Darcs/Lock.lhs 182
-sansDarcs ('/':'_':'d':'a':'r':'c':'s':_) = ""
+sansDarcs "/_darcs" = ""
+sansDarcs ('/':'_':'d':'a':'r':'c':'s':'/':_) = ""
}

Context:

[TAG darcs unstable 2007-11-04
Eric Kow <eric.kow at loria.fr>**20071104235616] 
Patch bundle hash:
0171a949cea4cdf618c48922959a380e5acd8457
-------------- next part --------------

New patches:

[backport David's optimize --reorder bugfix to stable [issue494]
Tommy Pettersson <ptp at lysator.liu.se>**20070819153415] 
<
> {
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 32
+                             try_shrinking_inverse,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 30
-                             reorder_and_coalesce, canonize,
+                             sort_coalesceFL, canonize,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 30
-                             new_merge, mergeFL, mergeFL_FL, fancy_merge,
-                             fancy_mergeFL, fancy_mergeFL_FL, fancy_mergeFL_FL2,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 31
-                             fancy_mergeFL, fancy_mergeFL_FL, MergeResult(..),
+                             fancy_mergeFL, fancy_mergeFL_FL, fancy_mergeFL_FL2,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 31
-                             fancy_mergeFL,
+                             fancy_mergeFL, fancy_mergeFL_FL, MergeResult(..),
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 31
+                             fancy_mergeFL,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 30
-                             new_merge, mergeFL, mergeFL_FL,
+                             new_merge, mergeFL, mergeFL_FL, fancy_merge,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 30
-                             new_merge,
+                             new_merge, mergeFL, mergeFL_FL,
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 21
-module Darcs.Patch.Commute ( merge, elegant_merge,
-                      really_eq_patches, eq_patches, eq_list,
-                      compare_patches, compare_list,
-                      merger, merger_equivalent, glump, unravel,
-                      modernize_patch,
-                      resolve_conflicts, reorder_and_coalesce, canonize,
-                      commute, list_touched_files, list_conflicted_files,
-                      try_to_shrink, subcommutes,
-                      CommuteFunction, Perhaps(..),
-                      -- for PatchApply
-                      applyBinary, try_tok_internal, movedirfilename )
+#include "gadts.h"
+module Darcs.Patch.Commute ( really_eq_patches, eq_patches, eq_list,
+                             compare_patches, compare_list,
+                             merger_equivalent, modernize_patch,
+#ifndef GADT_WITNESSES
+                             merge, elegant_merge,
+                             merger, glump, unravel,
+                             resolve_conflicts,
+#endif
+                             new_merge,
+                             reorder_and_coalesce, canonize,
+                             commute, list_touched_files, list_conflicted_files,
+                             try_to_shrink, subcommutes,
+                             CommuteFunction, Perhaps(..),
+                             -- for PatchApply
+                             applyBinary, try_tok_internal, movedirfilename )
hunk ./src/Darcs/Patch/Commute.lhs 28
+                      try_shrinking_inverse,
)
)
)
)
)
)
)
)
)
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 106
-try_to_shrink psold =
+try_to_shrink x = try_to_shrink2 $ maybe x id (try_shrinking_inverse x)
+
+try_to_shrink2 :: FL Patch C(x y) -> FL Patch C(x y)
+try_to_shrink2 psold =
hunk ./src/Darcs/Patch/Commute.lhs 106
-try_to_shrink psold =
+try_to_shrink x = try_to_shrink2 $ maybe x id (try_shrinking_inverse x)
+
+try_to_shrink2 :: [Patch] -> [Patch]
+try_to_shrink2 psold =
)
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 111
-    then try_to_shrink ps_shrunk
+    then try_to_shrink2 ps_shrunk
hunk ./src/Darcs/Patch/Commute.lhs 111
-    then try_to_shrink ps_shrunk
+    then try_to_shrink2 ps_shrunk
)
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 114
+try_shrinking_inverse :: FL Patch C(x y) -> Maybe (FL Patch C(x y))
+try_shrinking_inverse (x:>:y:>:z)
+    | IsEq <- invert x =\/= y = Just z
+    | otherwise = case try_shrinking_inverse (y:>:z) of
+                  Nothing -> Nothing
+                  Just yz' -> Just $ case try_shrinking_inverse (x:>:yz') of
+                                     Nothing -> x:>:yz'
+                                     Just xyz' -> xyz'
+try_shrinking_inverse _ = Nothing
+
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 114
-shrink_a_bit :: FL Patch C(x,y) -> FL Patch C(x,y)
+shrink_a_bit :: FL Patch C(x y) -> FL Patch C(x y)
merger 0.0 (
hunk ./src/Darcs/Patch/Commute.lhs 114
-shrink_a_bit :: [Patch] -> [Patch]
-shrink_a_bit [] = []
-shrink_a_bit (p:ps) =
-    case try_one [] p ps of
-    Nothing -> p : shrink_a_bit ps
+shrink_a_bit :: FL Patch C(x,y) -> FL Patch C(x,y)
+shrink_a_bit NilFL = NilFL
+shrink_a_bit (p:>:ps) =
+    case try_one NilRL p ps of
+    Nothing -> p :>: shrink_a_bit ps
hunk ./src/Darcs/Patch/Commute.lhs 114
+try_shrinking_inverse :: [Patch] -> Maybe [Patch]
+try_shrinking_inverse (x:y:z)
+    | eq_patches (invert x) y = Just z
+    | otherwise = case try_shrinking_inverse (y:z) of
+                  Nothing -> Nothing
+                  Just yz' -> Just $ case try_shrinking_inverse (x:yz') of
+                                     Nothing -> x:yz'
+                                     Just xyz' -> xyz'
+try_shrinking_inverse _ = Nothing
+
)
)
)
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
-import Darcs.Patch.Ordered ( (:<)(..), FL(..), RL(..), lengthFL, unsafeRL )
+import Darcs.Patch.Commute ( try_shrinking_inverse )
+import Darcs.Patch.Ordered ( (:<)(..), FL(..), RL(..),
+                             lengthFL, allFL, reverseFL )
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
-import Darcs.Patch.Ordered ( (:<)(..), FL(..), lengthFL, unsafeFL, )
+import Darcs.Patch.Ordered ( (:<)(..), FL(..), RL(..), lengthFL, unsafeRL )
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 94
-                   human_friendly, showPatchInfo,
+                          showPatchInfo,
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
+import Darcs.Patch.Ordered ( (:<)(..), FL(..), lengthFL, unsafeFL, )
merger 0.0 (
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
-import Darcs.Patch.Info ( PatchInfo, make_filename, readPatchInfo,
-                   human_friendly, showPatchInfo,
-                 )
+import Darcs.Patch.Info ( PatchInfo, make_filename, readPatchInfo, showPatchInfo )
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
+import Darcs.Patch.Ordered ( (:<)(..), FL(..), lengthFL, unsafeFL, )
)
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
+import Darcs.Patch.Commute ( try_shrinking_inverse )
)
)
)
)
)
merger 0.0 (
hunk ./src/Darcs/Repository/DarcsRepo.lhs 150
-  case flatten_to_primitives $ merger_equivalent patch of
-  oldps ->
-    if all (\p -> is_addfile p || is_adddir p) oldps
-    then join_patches oldps
+ let simple_ps = flatten_to_primitivesFL $ merger_equivalent patch
+     oldps = maybe simple_ps id $ try_shrinking_inverse simple_ps
+ in if allFL (\p -> is_addfile p || is_adddir p) $ oldps
+    then join_patchesFL oldps
hunk ./src/Darcs/Repository/DarcsRepo.lhs 150
-  case flatten_to_primitives $ merger_equivalent patch of
-  oldps ->
-    if all (\p -> is_addfile p || is_adddir p) oldps
+ let simple_ps = flatten_to_primitives $ merger_equivalent patch
+     oldps = maybe simple_ps id $ try_shrinking_inverse simple_ps
+ in if all (\p -> is_addfile p || is_adddir p) oldps
)
}
[resolv conflicts (issue494)
Tommy Pettersson <ptp at lysator.liu.se>**20070819153905
 1) fix bug that revealed itself in optimize --reorder on unstable repo
 2) backport David's optimize --reorder bugfix to stable [issue494]
] 
<
> {
hunk ./src/Darcs/Patch/Commute.lhs 21
 
 \begin{code}
 {-# OPTIONS -fglasgow-exts #-}
-module Darcs.Patch.Commute ( merge, elegant_merge,
-                      really_eq_patches, eq_patches, eq_list,
-                      compare_patches, compare_list,
-                      merger, merger_equivalent, glump, unravel,
-                      modernize_patch,
-                      resolve_conflicts, reorder_and_coalesce, canonize,
-                      commute, list_touched_files, list_conflicted_files,
-                      try_to_shrink, subcommutes,
-                      CommuteFunction, Perhaps(..),
-                      -- for PatchApply
-                      applyBinary, try_tok_internal, movedirfilename )
+#include "gadts.h"
+module Darcs.Patch.Commute ( really_eq_patches, eq_patches, eq_list,
+                             compare_patches, compare_list,
+                             merger_equivalent, modernize_patch,
+#ifndef GADT_WITNESSES
+                             merge, elegant_merge,
+                             merger, glump, unravel,
+                             resolve_conflicts,
+#endif
+                             sort_coalesceFL, canonize,
+                             commute, list_touched_files, list_conflicted_files,
+                             try_shrinking_inverse,
+                             try_to_shrink, subcommutes,
+                             CommuteFunction, Perhaps(..),
+                             -- for PatchApply
+                             applyBinary, try_tok_internal, movedirfilename )
        where
 
 import Prelude hiding ( pi )
hunk ./src/Darcs/Patch/Commute.lhs 111
 
 \begin{code}
 try_to_shrink :: FL Patch C(x y) -> FL Patch C(x y)
-try_to_shrink psold =
+try_to_shrink x = try_to_shrink2 $ maybe x id (try_shrinking_inverse x)
+
+try_to_shrink2 :: FL Patch C(x y) -> FL Patch C(x y)
+try_to_shrink2 psold =
     let ps = sort_coalesceFL psold
         ps_shrunk = shrink_a_bit ps
                     in
hunk ./src/Darcs/Patch/Commute.lhs 119
     if lengthFL ps_shrunk < lengthFL ps
-    then try_to_shrink ps_shrunk
+    then try_to_shrink2 ps_shrunk
     else ps_shrunk
 
hunk ./src/Darcs/Patch/Commute.lhs 122
-shrink_a_bit :: [Patch] -> [Patch]
-shrink_a_bit [] = []
-shrink_a_bit (p:ps) =
-    case try_one [] p ps of
-    Nothing -> p : shrink_a_bit ps
+try_shrinking_inverse :: FL Patch C(x y) -> Maybe (FL Patch C(x y))
+try_shrinking_inverse (x:>:y:>:z)
+    | IsEq <- invert x =\/= y = Just z
+    | otherwise = case try_shrinking_inverse (y:>:z) of
+                  Nothing -> Nothing
+                  Just yz' -> Just $ case try_shrinking_inverse (x:>:yz') of
+                                     Nothing -> x:>:yz'
+                                     Just xyz' -> xyz'
+try_shrinking_inverse _ = Nothing
+
+shrink_a_bit :: FL Patch C(x y) -> FL Patch C(x y)
+shrink_a_bit NilFL = NilFL
+shrink_a_bit (p:>:ps) =
+    case try_one NilRL p ps of
+    Nothing -> p :>: shrink_a_bit ps
     Just ps' -> ps'
 
 try_one :: RL Patch C(w x) -> Patch C(x y) -> FL Patch C(y z)
hunk ./src/Darcs/Repository/DarcsRepo.lhs 92
                writePatch, gzWritePatch, showPatch,
                really_eq_patches
              )
+import Darcs.Patch.Commute ( try_shrinking_inverse )
+import Darcs.Patch.Ordered ( (:<)(..), FL(..), RL(..),
+                             lengthFL, allFL, reverseFL )
 import Darcs.Patch.Info ( PatchInfo, make_filename, readPatchInfo,
hunk ./src/Darcs/Repository/DarcsRepo.lhs 96
-                   human_friendly, showPatchInfo,
+                          showPatchInfo,
                  )
 import Darcs.Patch.Set ( PatchSet )
 import Darcs.Patch.Depends ( is_tag )
hunk ./src/Darcs/Repository/DarcsRepo.lhs 153
 
 sift_for_pending :: Patch -> Patch
 sift_for_pending patch =
-  case flatten_to_primitives $ merger_equivalent patch of
-  oldps ->
-    if all (\p -> is_addfile p || is_adddir p) oldps
-    then join_patches oldps
+ let simple_ps = flatten_to_primitivesFL $ merger_equivalent patch
+     oldps = maybe simple_ps id $ try_shrinking_inverse simple_ps
+ in if allFL (\p -> is_addfile p || is_adddir p) $ oldps
+    then join_patchesFL oldps
     else 
       case try_to_shrink $ sfp NilFL $ reverseFL oldps of
       ps | lengthFL ps < lengthFL oldps -> sift_for_pending $ join_patchesFL ps
}

Context:

[Move conditional #include from Darcs.External to makefile.
Eric Kow <eric.kow at gmail.com>**20070807203037
   
 The GHC manual says that this is *not* the preferred option, but for some
 reason, the include pragmas seem to get ignored.  Perhaps it is because the
 requirement that the pragmas be on the top of the file conflict with the #ifdef
 statements.
 
 In any case, this patch gets rid of the warning on MacOS X:
   warning: implicit declaration of function ?tgetnum?
] 
[Pass CFLAGS to the assembler
Lennart Kolmodin <kolmodin at dtek.chalmers.se>**20070808181309
 The CFLAGS must be passed to the assembler or the build will break on some
 arches, like the -mcpu is essential on sparc.
] 
[comment out unravel checks.
David Roundy <droundy at darcs.net>**20070814000309] 
[compile unit when running check.
David Roundy <droundy at darcs.net>**20070813203540] 
[fix compile errors in unit.lhs.
David Roundy <droundy at darcs.net>**20070813203525] 
[fix Patch.Test to compile with latest code.
David Roundy <droundy at darcs.net>**20070813174442] 
[Simplify issue494 test (it's not about capitalisation).
Eric Kow <eric.kow at gmail.com>**20070812135319] 
[Add a test for issue494.
Eric Kow <eric.kow at gmail.com>**20070811211134] 
[fix bug that revealed itself in optimize --reorder on unstable repo.
David Roundy <droundy at darcs.net>**20070808005251
 I'm sure this fix doesn't make things worse, but am not convinced that it
 is a totally correct fix.  "Sifting for pending" is a subtle business,
 and in many ways this patch just works around this complexity.  On the other
 hand, I can't see another way to deal with this.  :(
] 
[fix commutation of addition and move patches.
David Roundy <droundy at darcs.net>**20070808005021
 This is potentially dangerous, but something we'll have to
 do in the long run (the new conflicts stuff assumes a property
 this patch restores).  We used to allow move patches to commute
 with add patches in one direction, so as to reduce the number
 of conflicts.  This violated the rule that if A commutes with B,
 then it will also commute with (invert B).
] 
[function to determine active/inactive patches.
David Roundy <droundy at darcs.net>**20070803000716] 
[optimize optimize --reorder.
David Roundy <droundy at darcs.net>**20070808173039] 
[eliminate reorder_coalesce and rename sort_coalesce_composite.
David Roundy <droundy at darcs.net>**20070808201609] 
[refactor coalesceHunk.
David Roundy <droundy at darcs.net>**20070808204332] 
[fix docs to match commute_nameconflict changes.
David Roundy <droundy at darcs.net>**20070808193257] 
[remove commute_nameconflict (rarely invoked and ugly)
David Roundy <droundy at darcs.net>**20070806221156
 Note: this might be able to cause trouble with existing repositories.
] 
[refactor to expand is_identity and use it to encapsulate "identitiness"
David Roundy <droundy at darcs.net>**20070806230927] 
[add allFL function to Ordered.
David Roundy <droundy at darcs.net>**20070808004826] 
[simple refactor in DarcsRepo.
David Roundy <droundy at darcs.net>**20070808004638] 
[fix ordering mistyping in sift_for_pending.
David Roundy <droundy at darcs.net>**20070806231124
 This doesn't change any behavior, but makes type correspond
 to actual order of patches in the list.
] 
[minor code cleanups.
David Roundy <droundy at darcs.net>**20070806220028] 
[minor code cleanup.
David Roundy <droundy at darcs.net>**20070806220005] 
[[issue69] Add a table of environmental variables to the manual.
Eric Kow <eric.kow at gmail.com>**20070807210622
 
 This makes it possible to support a more usage-oriented rewrite of the
 environmental variables doc.
] 
[Use System.Directory.copyFile for file copying.
Kevin Quick <quick at sparq.org>**20070723071533] 
[cut new merge code from old Commute module.
David Roundy <droundy at darcs.net>**20070801225540] 
[add new Merge module.
David Roundy <droundy at darcs.net>**20070801205859] 
[add marking of cancelled patches
David Roundy <droundy at darcs.net>**20070728000618] 
[add (unused) "cancel" patches.
David Roundy <droundy at darcs.net>**20070727193153] 
[add named primitive subpatch helpers.
David Roundy <droundy at darcs.net>**20070727185400] 
[Fixed fancy_mergeFL and fancy_mergeFL_FL
Jason Dagit <dagit at codersbase.com>**20070725215429] 
[Implemented fancy_mergeFL_FL2
Jason Dagit <dagit at codersbase.com>**20070626235249] 
[Implemented fancy_mergeFL_FL
Jason Dagit <dagit at codersbase.com>**20070626230558] 
[Added fancy_commute, still working on fancy_merge
Jason Dagit <dagit at codersbase.com>**20070623000136] 
[Use readFilePS instead of readFile for 'show contents' command.
Eric Kow <eric.kow at loria.fr>**20070805190830] 
[Fix 'show contents' documentation and help.
Eric Kow <eric.kow at loria.fr>**20070805142053] 
[[issue141] Implement darcs show contents command.
Eric Kow <eric.kow at gmail.com>**20070802040813] 
[Add test for show contents command.
Eric Kow <eric.kow at gmail.com>**20070801203053] 
[Add test for issue467.
Eric Kow <eric.kow at gmail.com>**20070801184138] 
[[issue467] changes --context --repodir
Eric Kow <eric.kow at gmail.com>**20070801184051] 
[[issue316] Prompt for confirmation if amending someone else's patch.
Eric Kow <eric.kow at gmail.com>**20070731192845] 
[Export the non-interactive part of get_author.
Eric Kow <eric.kow at gmail.com>**20070731190748] 
[Move just_dir helper function to Darcs.FilePathUtils.
Eric Kow <eric.kow at gmail.com>**20070730193703] 
[Rename fix_maybe_absolute and friends to something clearer.
Eric Kow <eric.kow at gmail.com>**20070730193603
 
 As suggested by David.
] 
[Rename (again) query/list to show.
Eric Kow <eric.kow at gmail.com>**20070730184757
 
 Clarify the online help while we're at it.
] 
[Fix conflicts between issue308 fix and amend-record metadata editing.
Eric Kow <eric.kow at gmail.com>**20070729191434] 
[Do not run test suite if amending metadata only.
Eric Kow <eric.kow at gmail.com>**20070728055505] 
[Add patchname to logfile when amending long comment.
Eric Kow <eric.kow at gmail.com>**20070728054752
 
 And simplify use of unlines (we already detect trailing newline).
] 
[Allow amend-record to edit metadata even if no changes are selected.
Eric Kow <eric.kow at gmail.com>**20070728053612] 
[[issue161] Implement amend-record --edit-long-comment, etc.
Eric Kow <eric.kow at loria.fr>**20070727205233
 
 Should also satisfy requests in issue77, issue276 and issue388.
] 
[Catch bad patch names in record --pipe.
Eric Kow <eric.kow at loria.fr>**20070727203606
 
 This appears to be a bug by which we have not yet been bitten.
] 
[[issue389] Support record -m --prompt-long-comment.
Eric Kow <eric.kow at loria.fr>**20070727203503] 
[Combine get_patchname with get_log in record command.
Eric Kow <eric.kow at loria.fr>**20070727203237
 
 This probably makes the code longer, but more explicit and with
 support for 'prior patchnames' (for amend-record).
] 
[Add some rudimentary amend-record + metadata tests.
Eric Kow <eric.kow at loria.fr>**20070725211157] 
[Fix conflict between unpull refactor and --no-deps.
Eric Kow <eric.kow at loria.fr>**20070805105818] 
[Hide darcs unpull command.
Eric Kow <eric.kow at gmail.com>**20070730181138] 
[Slightly refactor unpull (make it an alias).
Eric Kow <eric.kow at gmail.com>**20070728095057] 
[mark dangerous code with a fixme.
David Roundy <droundy at darcs.net>**20070727012503] 
[Fix typo.
Eric Kow <eric.kow at loria.fr>**20070805084445] 
[Resolve conflicts between issue353 and GUI removal patches.
Eric Kow <eric.kow at loria.fr>**20070805061431] 
[resurrect --no-deps [issue353]
Tommy Pettersson <ptp at lysator.liu.se>**20070801213028] 
[make --no-deps work with obliterate, unrecord and unpull
Tommy Pettersson <ptp at lysator.liu.se>**20070801212519] 
[make --no-deps work with push and send
Tommy Pettersson <ptp at lysator.liu.se>**20070801212256] 
[fix typo
Tommy Pettersson <ptp at lysator.liu.se>**20070729225249] 
[fix website in darcs.cgi.
David Roundy <droundy at darcs.net>**20070802220205] 
[Resolve the expected conflict with 'resolv issue490 fix'
Eric Kow <eric.kow at loria.fr>**20070730204220] 
[resolv issue490 fix in stable (will conflict with resolv in unstable)
Tommy Pettersson <ptp at lysator.liu.se>**20070729225410] 
[Add test for issue308
Kevin Quick <quick at sparq.org>**20070723062114] 
[Fix issue308: don't record empty patch with --ask-deps
Kevin Quick <quick at sparq.org>**20070728190329] 
[add cancelled patch constructor.
David Roundy <droundy at darcs.net>**20070726180243] 
[add unused Marked constructor to Patch.
David Roundy <droundy at darcs.net>**20070726003422] 
[fix filenames on conflicted patch.
David Roundy <droundy at darcs.net>**20070726002029] 
[Started fancy_merge
Jason Dagit <dagit at codersbase.com>**20070620220335] 
[Added mergeFL and mergeFL_FL
Jason Dagit <dagit at codersbase.com>**20070619025004] 
[move to pure record-access in Patch.Info.
David Roundy <droundy at darcs.net>**20070727001358] 
[improve error message when unable to access a repository.
David Roundy <droundy at darcs.net>**20070726230517] 
[Always use cloneFile for copying files.
Kevin Quick <quick at sparq.org>**20070723065621] 
[Remove more GUI code.
Eric Kow <eric.kow at loria.fr>**20070727202816] 
[Expose more PatchInfo parts and switch to record syntax.
Eric Kow <eric.kow at loria.fr>**20070725210644] 
[Refactor amend-record test.
Eric Kow <eric.kow at loria.fr>**20070725194320] 
[[issue386] Fix some --dry-run messages: "Would push" not "Pushing".
Eric Kow <eric.kow at loria.fr>**20070722211900] 
[[issue313] Ensure that logfile for record has trailing newline.
Eric Kow <eric.kow at loria.fr>**20070722053200] 
[Add a 'commit' command stub.
Eric Kow <eric.kow at loria.fr>**20070722053050] 
[Remove GUI code and stuff to build it.
Eric Kow <eric.kow at loria.fr>**20070715110324
 
 Suggested by Juliusz Chroboczek at FOSDEM 2006.  The code is pretty harmless
 in itself (it's hidden away by ifdefs), but potentially distracting.
] 
[Makes non-repository paths in DarcsFlags absolute [issue427].
Zachary P. Landau <kapheine at divineinvasion.net>**20070724013425] 
[Fix issue329: typing q for record --ask-deps records anyway with no deps.
Kevin Quick <quick at sparq.org>**20070718055426] 
[Update test suite to account for mark-conflicts command.
Eric Kow <eric.kow at loria.fr>**20070722044435] 
[Fix missing newline in inventory (issue412).
Eric Kow <eric.kow at loria.fr>**20070718210138
 
 This simplifies third party scripts that have to parse the darcs inventory.
] 
[Rename query to list; manifest to files.
Eric Kow <eric.kow at loria.fr>**20070718204703
 
   query          => list (with query as alias)
   query manifest => list files (with manifest as alias)
   query tags     => list tags
 
 Note that the list manifest and list files commands differ in that the
 former displays directories by default and the latter does not.
] 
[Refactor aliases and stubs (rm, unadd, resolve).
Eric Kow <eric.kow at loria.fr>**20070718201453] 
[Add helpers command_alias and command_stub.
Eric Kow <eric.kow at loria.fr>**20070718200940] 
[Add all pulled repos to _darcs/prefs/repos (issue368).
Eric Kow <eric.kow at loria.fr>**20070717180127] 
[Implement apply --dry-run (issue37).
Eric Kow <eric.kow at loria.fr>**20070717103257] 
[Do not set defaultrepo if --dry-run (issue186).
Eric Kow <eric.kow at loria.fr>**20070717101607] 
[Add test for issue396.
Eric Kow <eric.kow at loria.fr>**20070717054431] 
[Filter out empty filenames (issue396).
Eric Kow <eric.kow at loria.fr>**20070717054319] 
[Always use permissive disambiguation of commands.
Eric Kow <eric.kow at loria.fr>**20070717051631] 
[Use prettyException in clarify_errors (issue73).
Eric Kow <eric.kow at loria.fr>**20070717050732
 
 This solves one of three bugs in issue73, namely that we blame the user
 for darcs's own errors.
] 
[Use Control.Exception.catch in Darcs.Utils
Eric Kow <eric.kow at loria.fr>**20070717050613
 
 This affects helper functions like catchall and clarify_errors.
] 
[Tweak padding in usage_helper (mark-conflicts needs an extra space).
Eric Kow <eric.kow at loria.fr>**20070716230013] 
[Rename resolve to mark-conflicts (issue113).
Eric Kow <eric.kow at loria.fr>**20070716225635
 
 Resolve is retained as a (hidden) alias.
] 
[Make --directories the default in query manifest (issue456).
Eric Kow <eric.kow at loria.fr>**20070716220308] 
[Allow --list-options even if command cannot be run (issue297).
Eric Kow <eric.kow at loria.fr>**20070716210631
 
 If the command cannot be run, just print the possible flags, not the file args.
] 
[Implement hidden commands.
Eric Kow <eric.kow at loria.fr>**20070716204107
 
 This makes it possible to have command stubs or aliases without cluttering
 the usage info.
] 
[Implement command stubs 'rm', 'unadd', 'move' (issue127).
Eric Kow <eric.kow at loria.fr>**20070716202944
 
 These hidden commands are either stubs (they print some text and quit) or
 aliases (they do the same thing as some other command).
] 
[Distinguish between strict and permissive disambiguation (regression).
Eric Kow <eric.kow at loria.fr>**20070715203256
 
 Permissive disambiguation lets you handle the case where you supply a
 supercommand and a flag (i.e. not a subcommand).
] 
[Refactor parsing of command line arguments.
Eric Kow <eric.kow at loria.fr>**20070715200140] 
[Rewrite disambiguate_commands.
Eric Kow <eric.kow at loria.fr>**20070715200119
 
 This should make it more explicit what is going on.
] 
[Fix supercommand --help (issue282).
Eric Kow <eric.kow at loria.fr>**20070715170843] 
[Add crossref.png (issue485).
Eric Kow <eric.kow at loria.fr>**20070714230519] 
[Fix conflicts with Kevin Quick's [DarcsRepo] stuff.
Eric Kow <eric.kow at loria.fr>**20070722193223] 
[Added --nolinks option to request actual copies instead of hard-links for files.
Kevin Quick <quick at sparq.org>**20070613193742] 
[Provide [DarcsFlag] command-line options to copyLocal
Kevin Quick <quick at sparq.org>**20070612041516] 
[More concise --look-for-adds description.
Eric Kow <eric.kow at loria.fr>**20070708141727] 
[Harmonise capitalisation (etc) in flags help.
Eric Kow <eric.kow at loria.fr>**20070708122719] 
[fix repodir test cleanup
Tommy Pettersson <ptp at lysator.liu.se>**20070715183319] 
[Define datarootdir early enough in autoconf.mk.in (issue 493).
Dave Love <fx at gnu.org>**20070714165441] 
[Use listToMaybe instead of safehead.
Eric Kow <eric.kow at loria.fr>**20070708113613] 
[Fix issue490 conflicts.
Eric Kow <eric.kow at loria.fr>**20070708112618] 
[fix for issue 490
David Roundy <droundy at darcs.net>**20070629195741
 This patch ensures that we never try to use a checkpoint
 for a tag that isn't in a place where the inventory is
 broken.
 
 It's a little ugly because it also puts more of the checkpoint
 handling code in Checkpoint, which required a refactor to avoid
 import loops.
] 
[Fix Makefile bug (symlink for bigpage.tex).
Eric Kow <eric.kow at loria.fr>**20070714192500] 
[Canonize Andres Loeh and Daniel Gorin.
Eric Kow <eric.kow at loria.fr>**20070714200521] 
[Sort tags file (Vim likes it that way).
Eric Kow <eric.kow at loria.fr>**20070708213833] 
[Fix tags target in Makefile to account for mv to src.
Eric Kow <eric.kow at loria.fr>**20070708212921] 
[Fix hscurl.c conflicts.
Eric Kow <eric.kow at loria.fr>**20070714195126] 
[Fix issue420: User Agent size limit for curl gets is removed.
Kevin Quick <quick at sparq.org>**20070711225049] 
[String parameters to libcurl are kept alive to conform with the api specification
dgorin at dc.uba.ar**20070622134144] 
[work around < &lt problem in bigpage.html [issue483]
Tommy Pettersson <ptp at lysator.liu.se>**20070712233559
 latex2html seems to misunderstand the sequence "\<" in verbatim mode, so I
 split it into two verbatim sections. It appears to look the same, but it
 could probably cause an unfortunate line break.
] 
[Fix handling of --repo with relative paths.
Eric Kow <eric.kow at loria.fr>**20070714160336
   
 We did not correctly deal with the case where the user passes in a directory
 path via the --repo flag (cf --repodir).  The fix is to make findRepository
 properly aware of the --repo flag.  This way, if we have been passed a --repo
 argument, and the argument is a directory, we avoid calling seekRepo.  Note
 that we still have to keep the old code around too, to cover the case where
 --repo is a URL.
] 
[remove TODO from passing repodir.pl test
David Roundy <droundy at darcs.net>**20070530195104] 
[fix links to wiki on web page (again)
Tommy Pettersson <ptp at lysator.liu.se>**20070630080403
 (They aren't broken, but) change the /index.html/ part to /DarcsWiki/ as
 David intended it.
] 
[move URL for darcs.cgi to new server.
David Roundy <droundy at darcs.net>**20070629200757] 
[add right-arrow with new name desired by new latex2html.
droundy at darcs.net**20070620233452] 
[simplify C macro
David Roundy <droundy at darcs.net>**20070619011246] 
[Make all of Patch work with gadts.
David Roundy <droundy at darcs.net>**20070615214613] 
[Make Read work with gadts.
David Roundy <droundy at darcs.net>**20070615204731] 
[fix Jason's code to work with gadts.
David Roundy <droundy at darcs.net>**20070615194704] 
[fix type signature of ||| in Commute.lhs.
David Roundy <droundy at darcs.net>**20070615153019] 
[when using type witnesses, always compile with -fglasgow-exts.
David Roundy <droundy at darcs.net>**20070615152847] 
[Changed Patch to GADTs notation
Jason Dagit <dagit at codersbase.com>**20070615013022] 
[conflicted commute now uses filterE
Jason Dagit <dagit at codersbase.com>**20070615003757] 
[fixed conflict
Jason Dagit <dagit at codersbase.com>**20070615003733] 
[added filterE
Jason Dagit <dagit at codersbase.com>**20070615002503] 
[fixed conflicts
Jason Dagit <dagit at codersbase.com>**20070614230216] 
[Implement read/show of Conflicted patches.
Jason Dagit <dagit at codersbase.com>**20070614215509] 
[Implement Conflicted patches.
Jason Dagit <dagit at codersbase.com>**20070614205738] 
[fix gadts in Viewing
David Roundy <droundy at darcs.net>**20070615011957] 
[test gadt witnesses a bit
David Roundy <droundy at darcs.net>**20070615005140] 
[make Commute work again with witnesses.
David Roundy <droundy at darcs.net>**20070615004552] 
[cannot derive instances for gadts.
David Roundy <droundy at darcs.net>**20070615002830] 
[convert Commute to gadts.
David Roundy <droundy at darcs.net>**20070614235440] 
[make EqCheck derive Show.
David Roundy <droundy at darcs.net>**20070614212456] 
[fix bug in context of :<
David Roundy <droundy at darcs.net>**20070614011916] 
[export MyEq class
David Roundy <droundy at darcs.net>**20070614004407] 
[gadtize (File/Dir)PatchType
David Roundy <droundy at darcs.net>**20070614001425] 
[gadtize Show
David Roundy <droundy at darcs.net>**20070613211510] 
[improve type of commute_to_end
David Roundy <droundy at darcs.net>**20070613203623] 
[make gadt witnesses work with Core.
David Roundy <droundy at darcs.net>**20070613040231] 
[make Ordered compile with gadt witnesses.
David Roundy <droundy at darcs.net>**20070613030137] 
[Step 2 of gadts refactor
Jason Dagit <dagit at codersbase.com>**20070612234042] 
[Commute has arguments backwards
Jason Dagit <dagit at codersbase.com>**20070612201646] 
[clean up ordered data types
David Roundy <droundy at darcs.net>**20070530194023] 
[use more expressive types than tuples
David Roundy <droundy at darcs.net>**20070530170100] 
[start gadt stuff
David Roundy <droundy at darcs.net>**20070530011817] 
[change wiki links on webpage to wiki.darcs.net
Tommy Pettersson <ptp at lysator.liu.se>**20070617095655] 
[bump version to 1.1.0pre1
Tommy Pettersson <ptp at lysator.liu.se>**20070616202236] 
[fix bug in hashed-inventory get
David Roundy <droundy at darcs.net>**20070530172527] 
[add test to trigger yet another buggy case.
David Roundy <droundy at darcs.net>**20070422152651] 
[check for gzopen directly in zlib
mail at andres-loeh.de**20070527103908
 
 Without this change, configure will fail on systems having curl and zlib
 in different locations. Because curl depends on zlib and is already detected
 prior to zlib by the configure file, the AC_CHECK_FUNC check to curl will
 succeed. Some combinations of pkgconfig/curl versions do no longer add the
 -lz flag in its pkgconfig file, so darcs won't record -lz as a necessary
 flag, and the build will fail later.
 
 A different solution to the problem would be to move the whole check for
 zlib to *before* the check for curl.
] 
[Fix Windows build breakage.
Eric Kow <eric.kow at loria.fr>**20070520054713] 
[Modernise imports of System.IO.
Eric Kow <eric.kow at loria.fr>**20070507192521
 
 Note that some try/bracket/etc are now imported from Control.Exception.
] 
[Use System.Process under Unix.
Eric Kow <eric.kow at loria.fr>**20070426194615] 
[Remove conflictors unit tests.
Eric Kow <eric.kow at loria.fr>**20070513063537] 
[Complete conflictors code removal.
Eric Kow <eric.kow at loria.fr>**20070513061545
 
 Remove submerge_in_dir function, apparantly only used by the conflictors
 code.
] 
[remove unneeded (and unsafe) export from Patch.
David Roundy <droundy at darcs.net>**20070511005356] 
[remove (unused) conflictor code
David Roundy <droundy at darcs.net>**20070511003956] 
[Fix makefile conflict.
Eric Kow <eric.kow at loria.fr>**20070512194803] 
[fix path to completion scripts
Peter Simons <simons at cryp.to>**20070511033227] 
[Support makefile docdir/datarootdir variables.
Dave Love <fx at gnu.org>**20070507210129
 Also avoid warnings from autoconf 2.61.  The backward compatibility
 stuff should be tidied up once requiring 2.61 is acceptable.
] 
[cut unneeded pragma from SlurpDirectory.lhs
David Roundy <droundy at darcs.net>**20070505140749] 
[Added prehooks
Jason Dagit <dagit at codersbase.com>**20070505202210] 
[Use system for calling interactive cmds in Windows instead of rawSystem.
Eric Kow <eric.kow at loria.fr>**20070415132608
 
 This lets us support switches, for example, in DARCS_EDITOR.
] 
[resolve conflict.
David Roundy <droundy at darcs.net>**20070422213416] 
[make copyInventory work for all permutations of repo formats.
David Roundy <droundy at darcs.net>**20070422155344] 
[fix bug in Internal.
David Roundy <droundy at darcs.net>**20070422155324] 
[add support for different kinds of get.
David Roundy <droundy at darcs.net>**20070422152934] 
[fix strict get to a hashed repo from another.
David Roundy <droundy at darcs.net>**20070422151300
 The trouble was that my clever idea of lazily downloading patches even
 during a strict get didn't work, since we didn't have the source while
 reading the patches the second time.  One option would be to add that
 source while applying patches the second time, but that seems like it'd
 require a more tricky interface than just copying things strictly the first
 time.
] 
[don't print "partial repository" guess.
David Roundy <droundy at darcs.net>**20070422150603
 This guess is all too often inaccurate, and with the new hashed
 inventories, it'll be even more often inaccurate.
] 
[remove redundant copyInventory.
David Roundy <droundy at darcs.net>**20070422144910] 
[add tests for mixed inventories to hashed_inventory.sh.
David Roundy <droundy at darcs.net>**20070418234821] 
[rewrite --lazy to be more flexible.
David Roundy <droundy at darcs.net>**20070416154113
 This change makes it so we can handle a configured set of URLs for patch
 origins.  See the description in the Prefs.lhs documentation for details.
 In addition, I've added a new --ephemeral option, which allows the user to
 create repositories without any patch files at all (which seems a bit
 scary, but potentially handy).
] 
[fix test_scripts bug pointed out by Eric.
David Roundy <droundy at darcs.net>**20070421213635] 
[fix FIXME for handling hashed+normal inventory at the same time.
David Roundy <droundy at darcs.net>**20070418215614
 This fix also makes the tests pass with both inventory types enabled,
 so I added that to the test suite.  This was easier than I expected!
] 
[remove unused export from RepoFormat.
David Roundy <droundy at darcs.net>**20070414174933] 
[Modernise imports of Foreign.Ptr.
Eric Kow <eric.kow at loria.fr>**20070407102536] 
[Make record_editor.pl test work under Windows.
Eric Kow <eric.kow at loria.fr>**20070415132932
 
 I believe setting the PATH to '' was giving me libcurl4.dll complaints
 under Windows.
 
 Note also that this simplifies away part of a test, in that we were
 initially trying to create stuff in a directory called 'temp dir2 " "',
 but just creating the dir itself got so tricky that I just gave up and
 switched to 'temp dir2', still with a space, no quotes.
] 
[Make mv.pl test pass on Windows.
Eric Kow <eric.kow at loria.fr>**20070415114122
 
 Fixed test count mismatch, and recovery of absolute path under msys.
] 
[Include src/Darcs/Patch in makefile's SRC_DIRS.
Dave Love <fx at gnu.org>**20070415215139] 
[Re-fix MAKEMANUAL.
Dave Love <fx at gnu.org>**20070415122733] 
[Fix applyToWorking conflicts.
Eric Kow <eric.kow at loria.fr>**20070422060319
 
 Was recorded against darcs stable post 1.0.9rc2.
] 
[Fix MAKEMANUAL conflict.
Eric Kow <eric.kow at loria.fr>**20070413231608] 
[Fix MAKEMANUAL make target.
Dave Love <fx at gnu.org>**20070410192153] 
[Move packaging related stuff to its own directory (release).
Eric Kow <eric.kow at loria.fr>**20070401071845] 
[Move extras to their own directory (tools).
Eric Kow <eric.kow at loria.fr>**20070401071734
 
 Shell completion scripts, cgi.
 
] 
[Move documentation to its own directory (doc).
Eric Kow <eric.kow at loria.fr>**20070401071635] 
[Resolve Makefile conflict.
Eric Kow <eric.kow at loria.fr>**20070413231906] 
[add support for partial and lazy downloading of hashed repos.
David Roundy <droundy at darcs.net>**20070405000616] 
[add framework for lazily fetching hash files.
David Roundy <droundy at darcs.net>**20070403232223
 This patch doesn't yet actually have any effect, but prepares
 the way for changes to allow a variety of --partial that won't
 have the downside of sometimes causing darcs to fail later,
 since one can always download the patch files from the original
 server.
] 
[fix bug Eric pointed out (which has also now bitten me).
David Roundy <droundy at darcs.net>**20070404233317
 This was a bug in the Checkpoint repo, where we assumed we were
 looking at the current working directory, incorrectly.
] 
[Fix unit.lhs import.
Eric Kow <eric.kow at loria.fr>**20070331194046
 
 ...due to sloppy scripting during the hierarchical shakeup.
 
] 
[make --set-scripts-executable work with get and hashed inventories.
David Roundy <droundy at darcs.net>**20070329010828] 
[Fix conflicts; adapt QueryTag to new hierarchical structure.
Eric Kow <eric.kow at loria.fr>**20070331191925] 
[fix checkpoint handling with hashed inventories.
David Roundy <droundy at darcs.net>**20070330154325] 
[fix bug in makefile regarding manual.
David Roundy <droundy at darcs.net>**20070330154259] 
[whitespace cleanups in makefile.
David Roundy <droundy at darcs.net>**20070330152018] 
[by default test hashed inventories plus normal.
David Roundy <droundy at darcs.net>**20070329010900] 
[fail on error in get_patches_beyond_tag.
David Roundy <droundy at darcs.net>**20070328172408
 This will expose any bugs where we use this function wrongly.
 (As was the case in darcs check --partial with hashed inventories.)
] 
[Fix manual compilation errors (due to source reorganisation).
Eric Kow <eric.kow at loria.fr>**20070313214302] 
[Fix conflicts.
Eric Kow <eric.kow at loria.fr>**20070313210908] 
[Modernise imports of Data.(Char|Int|List|Maybe).
Eric Kow <eric.kow at loria.fr>**20070313210805] 
[Modernise imports of Control.Monad.
Eric Kow <eric.kow at loria.fr>**20070313205312] 
[Modernise imports of System.Directory.
Eric Kow <eric.kow at loria.fr>**20070313205200] 
[Correct compilation errors in win32 due to src reorganisation.
Eric Kow <eric.kow at loria.fr>**20070313210732] 
[Move Haskell sources to src directory with hierarchical structure.
Eric Kow <eric.kow at loria.fr>**20070313200751
 
 src
   general modules, possibly to be spun off as non-darcs libraries 
   administrative stuff (e.g., modules generated by autoconf)
 
 src/Darcs
   darcs-specific modules, catch-all for modules I didn't know what
   to do with
 
 src/Darcs/Patch
   core patch operations
 
 src/Darcs/Repository
   modules specific to the maintenance of the darcs repo, especially the _darcs
   stuff
 
 src/Darcs/Commands
   the darcs commands, e.g. pull, record, whatsnew
 
] 
[Move osx directory to src.
Eric Kow <eric.kow at loria.fr>**20070313200304] 
[Move C files to src directory.
Eric Kow <eric.kow at loria.fr>**20070313200135] 
[Add subdirectories for source files.
Eric Kow <eric.kow at loria.fr>**20070313194050] 
[Extend GHCFLAGS override mechanism to allow for subdirectories.
Eric Kow <eric.kow at loria.fr>**20070313193917] 
[In tests, don't assume diff has -u, -x flags.
Dave Love <fx at gnu.org>**20070305202838] 
[Fixes for Solaris sh in tests: no $(...), test -e, or ! pipelines.
Dave Love <fx at gnu.org>**20070311170210] 
[Fix conflicts related to --ssh-cm flag.
Eric Kow <eric.kow at loria.fr>**20070311205820] 
[Fix test/ssh.sh conflicts.
Eric Kow <eric.kow at loria.fr>**20070311205156] 
[Add changelog entries (file: quick) for pull --complement changes.
Kevin Quick <quick at sparq.org>**20070205185329] 
[In tests, don't assume grep has -q and -x flags.
Dave Love <fx at gnu.org>**20070225114022] 
[Fix bash-ism `export foo=' in tests.
Dave Love <fx at gnu.org>**20070225113216] 
[Add send --output-auto-name information to the documentation.
Zachary P. Landau <kapheine at divineinvasion.net>**20070221014555] 
[Add test for send --output-auto-name.
Zachary P. Landau <kapheine at divineinvasion.net>**20070221014501] 
[Add --output-auto-name option to Send.
Zachary P. Landau <kapheine at divineinvasion.net>**20070221014327] 
[More sed compliance on pull_compl test.
Eric Kow <eric.kow at loria.fr>**20070217073744] 
[Fix pull_compl test sed compliance.
Kevin Quick <quick at sparq.org>**20070214033347] 
[Add pull_compl test; note interesting duplicate repo elimination in docs.
Kevin Quick <quick at sparq.org>**20070206065236] 
[change "current" to (or add) "pristine" in verbose message and doc
Tommy Pettersson <ptp at lysator.liu.se>**20070211191942] 
[Resolve conflict between complement add and get_recorded_unsorted.
Kevin Quick <quick at sparq.org>**20070206071832] 
[Added --complement to pull to allow "exclusion" repos
Kevin Quick <quick at sparq.org>**20070204181301] 
[Correct test for quoted arguments in DARCS_EDITOR.
Eric Kow <eric.kow at loria.fr>**20070204211312
 
 1) On MacOS X, grep lives in /usr/bin, not /bin
 2) We shouldn't escape the double quotes because they're already protected
    by the single quotes
 
] 
[Restore working directory if no repository is found (issue385).
Zachary P. Landau <kapheine at divineinvasion.net>**20070203173440
 seekRepo continues to go further up the directory tree looking for a
 repository.  If we are not in a repository, our current working directory
 becomes /.  This causes problems with code that falls back on creating
 temporary files in the current directory.  This patch will restore the
 directory the user started in if seekRepo fails.
] 
[refactor get_unrecorded.
David Roundy <droundy at darcs.net>**20070128231405
 I've removed the [DarcsFlag] argument, and added two new functions
 get_unrecorded_unsorted, and get_unrecorded_no_look_for_adds, which do what
 they say.  I think this simplifies its use, and cleans things up a tad.  It
 doesn't scale to many different ways to get_unrecorded, but I don't think
 we want to go there.
] 
[use (empty) opts to Repository in list_authors and make_changelog
Tommy Pettersson <ptp at lysator.liu.se>**20070128165840
 They where left out in the opts Repository refactoring.
] 
[fix bug triggered in replace.sh
David Roundy <droundy at darcs.net>**20070128002206
 This bug was an annoying one that seemed to involve trouble caused by
 unsafeInterleaveIO and the order of evaluation, since we change the working
 directory.  I've simplified the code significantly.  Complicating the debug
 process was a race condition caused by the lack of --ignore-times in
 replace.sh, which was because darcs replace didn't accept that option.
] 
[refactor: add opts into Repository.
David Roundy <droundy at darcs.net>**20070128000728] 
[add test for replace that messes with unrecorded hunks
Tommy Pettersson <ptp at lysator.liu.se>**20070125153803] 
[go back to using system for edit_file/view_file instead of exec (system 'cmd "$ARG"')
Benedikt Schmidt <beschmi at cloaked.de>**20070131162811] 
[use TODO instead of pass for record_editor test
Benedikt Schmidt <beschmi at cloaked.de>**20070131161635] 
[add some tests for edit_file and DARCS_EDITOR handling
Benedikt Schmidt <beschmi at cloaked.de>**20070131011526] 
[Remove extraneous parentheses (RepoFormat).
Eric Kow <eric.kow at loria.fr>**20070127231359] 
[make write_repo_format agree with read_repo_format (use | for separating properties)
Benedikt Schmidt <beschmi at cloaked.de>**20070126143752] 
[Remove unused functions from Population.
Eric Kow <eric.kow at gmail.com>**20070107232034
 
 The functions are not shown to be used by any other part of darcs.
 Perhaps they should be restored if we ever get to work seriously on
 libdarcs.
 
] 
[Import IO.bracket instead of Control.Exception.bracket in Exec.
Eric Kow <eric.kow at loria.fr>**20070107211935
 
 This makes darcs work on *nix the same way it did before Simon Marlow's
 runProcess patch for Windows and my conflict-resolution tweaks.
 
] 
[Import bracketOnError from Workaound instead of Control.Exception.
Eric Kow <eric.kow at gmail.com>**20061225212444
   
 bracketOnError was introduced in GHC 6.6, whereas we want to support 6.4.1 and
 higher.
   
] 
[Fix conflicts and compile errors (Exec runProcess stuff).
Eric Kow <eric.kow at gmail.com>**20061225212423
 
 Side A:
   Simon Marlow: Use System.Process on Windows
 
 Side B:
   Edwin Thomson : Make Exec.lhs not import unneeded Control.Exception functions
     when compiling on Windows.
   Magnus Jonsson : Added rigorous error checking in exec
     
 Compile errors in question were just import-related issues.
 
] 
[Use System.Process on Windows
Simon Marlow <simonmar at microsoft.com>**20061129160710
 
 This was an attempt to address "[issue218] Patch bundle failed hash",
 but unfortunately it doesn't fix the problem.  Still, System.Process
 is a better way to invoke external commands these days.
 
 For now, the new code only replaces the Windows version of exec.  This
 means that GHC 6.4 will be required to build darcs on Windows.  Better
 would be to add a configure test, but I ran out of time here.
] 
[fix [issue370], darcs ignored args contained in VISUAL variable
Benedikt Schmidt <beschmi at cloaked.de>**20061220110807
 given VISUAL="emacs -nw", darcs would run "emacs file" instead of
 "emacs -nw file"
] 
[Make annotate work on files with spaces in the name
edwin.thomson at businesswebsoftware.com**20061218094210
 
] 
[Prettify exceptions in identifyRepository.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061218025453] 
[QP-encode bundles when putting to a remote repo.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061218003034] 
[fix pending bug in darcs get --tag.
David Roundy <droundy at darcs.net>**20061217225256
 This patch addresses the bug displayed in Tommy's test:
 
 Mon Dec 11 20:28:21 CET 2006  Tommy Pettersson <ptp at lysator.liu.se>
   * add test for get --tag and pending
] 
[fix issue360, with darcs mv foo foo.
David Roundy <droundy at darcs.net>**20061217212340] 
[Separate comment from OPTIONS pragma for GHC 6.4 compatibility.
Eric Kow <eric.kow at gmail.com>**20061217041212
 
] 
[Resolve conflicts in David's hashed_inventory optimize patches.
Eric Kow <eric.kow at loria.fr>**20061217031027
 
] 
[Make hashed inventories support optimize and reordering.
David Roundy <droundy at darcs.net>**20061216193913] 
[fix bug in haskell_policy check for HopefullyPrivate.
David Roundy <droundy at darcs.net>**20061210234453
 Perhaps with this test, we can rename it to CertainlyPrivate?  :)
] 
[don't use HopefullyPrivate outside of Hopefully.
David Roundy <droundy at darcs.net>**20061210231623
 The idea is to hide the Hopefully constructors, so I can hide some more
 information in there, if I like, which should be handy for the hashed
 inventories, and may also come in handy (for similar reasons) with git
 repositories.
] 
[change Maybe Patch to Hopefully Patch.
David Roundy <droundy at darcs.net>**20061210213536
 This rather pervasive change move us to using a new Hopefully type, which
 is similar to Either String for storing patches that may or may not exist.
 This should improve error reporting.  At a minimum it'll making easier to
 improve error reporting.
] 
[resolve conflict in white space.
David Roundy <droundy at darcs.net>**20061210211846] 
[fix pending bug that broke several_commands.sh.
David Roundy <droundy at darcs.net>**20061209223916] 
[make optimize less DarcsRepo-specific.
David Roundy <droundy at darcs.net>**20061209205755] 
[eliminate DarcsRepo.am_in_repo.
David Roundy <droundy at darcs.net>**20061204153128
 This patch is a Good Thing, even though repair and optimize don't yet
 properly support anything bug old-fashioned repositories, because without
 it, when using such repositories, one can find those command operating on a
 different repository than intended (e.g. the test suite runs optimize on
 the darcs repository itself).  Now they'll fail as they ought to, when run
 on a repo format they don't support.
] 
[fix hashed inventory bug in add and prevent it happening again.
David Roundy <droundy at darcs.net>**20061204020823] 
[make get and put reuse initialize code.
David Roundy <droundy at darcs.net>**20061203220833
 This patch actually fixes put to properly accept and use any flags that
 init accepts, which is a Good Thing.  It also ensures that get behaves
 consistently with init in the future.  Also a Good Thing.
] 
[make put work with hashed inventories (and test for this).
David Roundy <droundy at darcs.net>**20061203211141] 
[fix new get to not mess up pending (fixes latest hashed_inventory.sh tests).
David Roundy <droundy at darcs.net>**20061203173722] 
[add some more hashed_inventory.sh tests.
David Roundy <droundy at darcs.net>**20061203173207] 
[fix more incompatible uses of DarcsRepo.
David Roundy <droundy at darcs.net>**20061203064355] 
[make replace work with hashed inventories.
David Roundy <droundy at darcs.net>**20061203055452] 
[Make get_tag test work with hashed inventories.
David Roundy <droundy at darcs.net>**20061203055019] 
[make directory_confusion pass with hashed inventories.
David Roundy <droundy at darcs.net>**20061203035551
 I'm not sure whether there is still a bug in the pending handling here, but
 at least it doesn't crash...
] 
[resolve conflicts
Tommy Pettersson <ptp at lysator.liu.se>**20061117222757
 between 'clean up unrevert and pending handling'
 and 'ignore failure from hSetBufferin'
] 
[Resolve conflict in Resolution.lhs.
Eric Kow <eric.kow at loria.fr>**20061113032236
 
] 
[External resolution can resolve conflicting adds
edwin.thomson at businesswebsoftware.com**20061106114755] 
[Only copy files needed in external_resolution
edwin.thomson at businesswebsoftware.com**20061106114719] 
[change message in 'darcs check' from "applying" to "checking" (issue147)
Tommy Pettersson <ptp at lysator.liu.se>**20061111154259] 
[update annotate for hashed inventories
Jason Dagit <dagit at codersbase.com>**20061108033202
 Fixes test suite failure for annotate on a repository with hashed inventory.
] 
[make Get work with hashed inventory.
David Roundy <droundy at darcs.net>**20061101150901
 This is inefficient, but it uses only the pre-existing refactored
 functions, so it's the easiest approach.  Later we can write an efficient
 bit of code to do the same thing.
] 
[make darcs check use Repository framework.
David Roundy <droundy at darcs.net>**20060927024514] 
[fix parsing of hashed inventories.
David Roundy <droundy at darcs.net>**20060927024505] 
[put Repository in Show class for debugging ease.
David Roundy <droundy at darcs.net>**20060927021202] 
[add a bit of hashed inventory code.
David Roundy <droundy at darcs.net>**20060918173904] 
[resolve conflicts
Tommy Pettersson <ptp at lysator.liu.se>**20061102184834
 Merge Unrecord fix for checkpoints inventory with Repository code refactoring.
] 
[Added --store-in-memory option for diff
edwin.thomson at businesswebsoftware.com**20061006122802
 
] 
[Move RawMode into DarcsUtils to break cyclic imports on Win32
Josef Svenningsson <josef.svenningsson at gmail.com>**20061004120024] 
[remove duplicate file names in fix_filepaths (fixes issue273)
Tommy Pettersson <ptp at lysator.liu.se>**20060929145335] 
[add test for replace command with duplicated file name
Tommy Pettersson <ptp at lysator.liu.se>**20060929144008] 
[Move bug reporting code to its own module.
Eric Kow <eric.kow at loria.fr>**20060928222826
 
 Fixes circular dependency caused by David's unrevert cleanup (which moves
 edit_file to DarcsUtil, thus causing it to depend on Exec) and Tommy's
 exec patches (which add impossible.h to Exec, thus causing it to depend
 on DarcsUtil).
 
] 
[clean up unrevert and pending handling.
David Roundy <droundy at darcs.net>**20060917214136] 
[Be explicit about timezone handling (issue220); assume local by default.
Eric Kow <eric.kow at gmail.com>**20060812102034
 
 Except for the local timezone in the user interface, this patch is not
 expected to change darcs's behaviour.  It merely makes current practice
 explicit:
 
 - Assume local timezone when parsing date strings from the user
   interface (previous behaviour was assuming UTC).
 
 - Assume UTC timezone when parsing date strings from PatchInfo.
   Newer patch date strings do *not* specify the timezone, so it
   would be prudent to treat these as UTC.
  
 - Disregard timezone information altogether when reading patch
   dates (issue220).  Note that this bug was not caused by assuming local
   timezone, because legacy patch date strings explicitly tell you what
   the timezone to use.  The bug was caused by a patch that fixed
   issue173 by using timezone information correctly.  To preserve
   backwards-compatability, we deliberatly replicate the incorrect
   behaviour of overriding the timezone with UTC.
   (PatchInfo.make_filename)
  
] 
[Account for timezone offset in cleanDate  (Fixes issue173).
Eric Kow <eric.kow at gmail.com>**20060610193049
 
] 
[Fix merge conflicts.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20060906191317] 
[fix bug in pristine handling when dealing with multiple patches.
David Roundy <droundy at darcs.net>**20060731111404] 
[fix ordering of operations to call pull_first_middles properly.
David Roundy <droundy at darcs.net>**20060730111409] 
[fix bug in refactoring of get.
David Roundy <droundy at darcs.net>**20060726121655] 
[refactor Population.
David Roundy <droundy at darcs.net>**20060716034837] 
[add TODO for refactoring get_markedup_file.
David Roundy <droundy at darcs.net>**20060716034339] 
[partial refactoring in annotate.
David Roundy <droundy at darcs.net>**20060716034319] 
[don't use DarcsRepo in list_authors.
David Roundy <droundy at darcs.net>**20060716033450] 
[I've now eliminated need to export DarcsRepo.write_patch.
David Roundy <droundy at darcs.net>**20060716033109] 
[partially refactor Optimize.
David Roundy <droundy at darcs.net>**20060716032934] 
[partial refactoring of Get.
David Roundy <droundy at darcs.net>**20060716031605] 
[refactor amend-record.
David Roundy <droundy at darcs.net>**20060716021003] 
[add TODO to refactor unrevert handling.
David Roundy <droundy at darcs.net>**20060716020247] 
[refactor Unrecord, adding tentativelyRemovePatches.
David Roundy <droundy at darcs.net>**20060716015150] 
[refactor tag.
David Roundy <droundy at darcs.net>**20060716011853] 
[refactor Repository to allow truly atomic updates.
David Roundy <droundy at darcs.net>**20060716011245] 
[TAG 1.0.9
Tommy Pettersson <ptp at lysator.liu.se>**20070603213706] 
[make 1.0.9 latest stable release on web page
Tommy Pettersson <ptp at lysator.liu.se>**20070603203451] 
[fix spelling error in changelog
Tommy Pettersson <ptp at lysator.liu.se>**20070603203437] 
[fix scp whitespace
Misha Aizatulin <avatar at hot.ee>*-20070523234232
 
 see http://bugs.darcs.net/issue454
] 
[bump version to 1.0.9
Tommy Pettersson <ptp at lysator.liu.se>**20070530071054] 
[fix error in changelog
Tommy Pettersson <ptp at lysator.liu.se>**20070530070723
 I got the attribution wrong. Apologies to Georg.
] 
[fix scp whitespace
Misha Aizatulin <avatar at hot.ee>**20070523234232
 
 see http://bugs.darcs.net/issue454
] 
[TAG 1.0.9rc3
Tommy Pettersson <ptp at lysator.liu.se>**20070517090113] 
[add some changelog entries
Tommy Pettersson <ptp at lysator.liu.se>**20070517090106] 
[bump version to 1.0.9rc3
Tommy Pettersson <ptp at lysator.liu.se>**20070517084513] 
[Make shell harness failures fatal in Makefile.
Eric Kow <eric.kow at loria.fr>**20070428200237] 
[remove write protected directory after workingdir.pl test
Tommy Pettersson <ptp at lysator.liu.se>**20070506232847
 Move to parent directory after last test, so reset_chmod finds the dirs and
 actually does its work.
 They were silently ignored
] 
[fix bug where we add a file but not its boring parent directory.
David Roundy <droundy at darcs.net>**20070505143330] 
[Renable --quiet test for rmdir.
Eric Kow <eric.kow at loria.fr>**20070422072009] 
[add test (but don't do it) for both sorts of inventories.
David Roundy <droundy at darcs.net>**20070418175214] 
[Modify match test for escaping quotes in match strings.
Dave Love <fx at gnu.org>**20070415170419] 
[Allow escaped quotes in `quoted' for match text.
Dave Love <fx at gnu.org>**20070415180132] 
[Make revert_interactive.sh test work under Windows.
Eric Kow <eric.kow at loria.fr>**20070415140652] 
[Make set_scripts_executable.pl test work under Windows.
Eric Kow <eric.kow at loria.fr>**20070415133233] 
[Make external.pl test work on Windows.
Eric Kow <eric.kow at loria.fr>**20070414212029
 
 One of the tests in this script is to see if darcs calls ssh correctly.
 We create a fake ssh program in the form of a shell script (it just
 creates a file 'fakessh' to let us know it ran).  Windows got confused
 by this, so we (1) made sure the script also works as a DOS batch file
 (2) gave it a .bat extension so that Windows knows how to run it.
] 
[Abuse test counter to get a pull_many_files.pl progress meter.
Eric Kow <eric.kow at loria.fr>**20070415142352] 
[don't exit with failure when there are no perl tests.
David Roundy <droundy at darcs.net>**20070418233016
 This happens when tests_to_run is used.
] 
[revamp TolerantIO to be simpler.
David Roundy <droundy at darcs.net>**20070421224551] 
[reenable --quiet mode in apply.
David Roundy <droundy at darcs.net>**20070421001933] 
[Apply patches 'tolerantly' to the working directory (issue434).
Eric Kow <eric.kow at loria.fr>**20070419200558
 
 If there are any exceptions applying a patch to the working directory, catch
 the exceptions, emit a pretty warning and move on.  This is meant to ease
 the scenario where the user is pulling in a large patch, but there is a
 permissions error (or something similar) in the working directory.
 
 Without this patch, darcs typically dies and leaves the working directory in
 a 'corrupted' state.  The corruption is relatively minor in that patches and
 pristine are perfectly fine.  The problem is that the user has large portions
 of the patch still upapplied and when he does a darcs whatsnew, gets a mass
 of seemingly incomprehensible goop (the inverse of the unapplied changes)
 mixed in with his changes.  We reduce the incomprehensible goop effect by
 catching exceptions so that darcs can continue to apply as much of the patch
 as it can.
] 
[Add tests specifically for applying patches to the working dir (issue434).
Eric Kow <eric.kow at loria.fr>**20070419200048] 
[Generalise HACKING file into a README (issue287).
Eric Kow <eric.kow at loria.fr>**20070401063734
 
 The README parts are largely inspired from GHC.
 
] 
[Remove unused bugs directory.
Eric Kow <eric.kow at loria.fr>**20070314203416] 
[Exit with error if any Perl tests fail (Makefile).
Eric Kow <eric.kow at loria.fr>**20070406062704] 
[Mention the query tags command in the tag documentation
Florian Weimer <fw at deneb.enyo.de>**20070325171247] 
[Add the query tags command
Florian Weimer <fw at deneb.enyo.de>**20070325170617] 
[Implement PatchInfo.pi_tag
Florian Weimer <fw at deneb.enyo.de>**20070325160343] 
[Include the query commands in the manual
Florian Weimer <fw at deneb.enyo.de>**20070325170019] 
[fix unrecord.sh to use proper darcs.
David Roundy <droundy at darcs.net>**20070328181345] 
[Fix date.t pathname construction in whatsnew test.
Dave Love <fx at gnu.org>**20070305203305] 
[Flip ssh test to accept a --ssh-cm argument.
Eric Kow <eric.kow at loria.fr>**20070310063327] 
[Add a --ssh-cm flag with --no-ssh-cm as the default.
Eric Kow <eric.kow at loria.fr>**20070310063132
 
 Previously, darcs would launch the ControlMaster by default, but it seems to
 hang on some large repositories and cause pain.  The user can always add
 --ssh-cm if s/he wants it on.
 
] 
[Rename --disable-ssh-cm to --no-ssh-cm.
Eric Kow <eric.kow at loria.fr>**20070310061124
 
 This appears to be more consistent with other darcs flags.
] 
[Do not append a colon to hostname when calling sftp (issue362).
Eric Kow <eric.kow at loria.fr>**20070308201844
 
 This does not solve all of issue362, just a minor annoyance along its way.
 
] 
[Don't depend on `seq' in tests.
Dave Love <fx at gnu.org>**20070225113255] 
[Get `open' and `psignal' declared on Solaris.
Dave Love <fx at gnu.org>**20070225113041
 The header requirements for open are actually as documented for glibc.
] 
[Make test harnesses define PWD in environment in case shell doesn't.
Dave Love <fx at gnu.org>**20070225112124] 
[Zsh completion: support repos that use _darcs/pristine
Georg Neis <gn at oglaroon.de>**20070301103113] 
[Use LaTeX for ISO 8601 hyperlink.
Eric Kow <eric.kow at loria.fr>**20070217071601] 
[Documentation only: add link for ISO 8601 format
Kirsten Chevalier <chevalier at alum.wellesley.edu>**20070216004007
 
 In the documentation, make "ISO 8601 format" a link to the official
 W3C page describing the format (for those who don't know it by heart).
] 
[fix some changelog entries
Tommy Pettersson <ptp at lysator.liu.se>**20061231210024] 
[fix bugs in replace.sh script--running wrong darcs.
David Roundy <droundy at darcs.net>**20070128001826] 
[add documentation for DARCS_PAGER
Benedikt Schmidt <beschmi at cloaked.de>**20070126142649] 
[Fix issue383 - allow --disable-ssh-cm for 'darcs changes'.
Georg Neis <gn at oglaroon.de>**20070121224417] 
[(add a + mv a b = add b) and (mv a b + remove b = remove a)
malebria at riseup.net**20070108160933] 
[update web page for new mailing list server.
David Roundy <droundy at darcs.net>**20070116162930] 
[Canonize Marco Túlio Gontijo e Silva.
Eric Kow <eric.kow at loria.fr>**20070113231736
 
 Sorry for stripping off the accent.
 
] 
[Redundant noncomments
malebria at riseup.net**20070109125519
 
 noncomments was already called by get_preffile via get_lines.
] 
[Add Workaround.bracketOnError (introduced in GHC 6.6).
Eric Kow <eric.kow at gmail.com>**20061225201830
 
 This is to compensate for the missing Control.Exception.bracketOnError
 in GHC 6.4.2
 
] 
[Fix issue376 - inconsistent punctuation in darcs get.
Eric Kow <eric.kow at gmail.com>**20061231180024
 
] 
[Fix issue367 - pull help message.
Eric Kow <eric.kow at gmail.com>**20061231174322] 
[fix spelling errors in comments
Benedikt Schmidt <beschmi at cloaked.de>**20061222020037] 
[fix link error with gcc 4.12/glibc 2.4
Benedikt Schmidt <beschmi at cloaked.de>**20061220091436
 errno is a C macro that expands to a function call in
 some versions of glibc, so it can't be treated like
 a CInt there
] 
[Fix includes in External.hs.
Dave Love <fx at gnu.org>**20061218224158
 You can't put comments before {-# INCLUDE ...
] 
[Fix ssh.sh test.
Dave Love <fx at gnu.org>**20061218223442] 
[Implement prettyException.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061218025440] 
[Simplify common libcurl errors.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061218025419] 
[fix issue369 by failing if quickcheck isn't available
David Roundy <droundy at darcs.net>**20061218021545] 
[Don't QP-encode bundles when pushing locally.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061218002533] 
[Make darcs push QP-encode the bundle before transferring.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061217234635
 This should hopefully fix issues with scp/sftp corrupting bundles in transit.
] 
[Adapt callers to new calling convention for make_email.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061217234608
 Use Just at the right places.
] 
[Make arguments to make_email optional.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20061217234501
 Makes contents and filename optional.  If they are omitted, we still
 generate a conforming MIME message.
] 
[add warning about ALL and obliterate --all to documentation
Tommy Pettersson <ptp at lysator.liu.se>**20061219180302] 
[add test for get --tag and pending
Tommy Pettersson <ptp at lysator.liu.se>**20061211192821] 
[add new test related to issue262.
David Roundy <droundy at darcs.net>**20061217221041
 This issue seems to already have been fixed.
] 
[Canonize Kirsten Chevalier.
Kirsten Chevalier <chevalier at alum.wellesley.edu>**20061217025004
 
 Added my name to the list of authors who originally only submitted an email
 address.
 
] 
[Documentation only - clarify meaning of --from and --author
Kirsten Chevalier <chevalier at alum.wellesley.edu>**20061217024927
   
 Clarified the meaning of --from and --author. I had assumed that these
 options also set the From: address on the email sent by "darcs sent".  Of
 course they don't, but it's better to make this clear.
 
] 
[Added test for reverting an unrecorded add
edwin.thomson at businesswebsoftware.com**20061215180047] 
[add test for reverting removed directory
Tommy Pettersson <ptp at lysator.liu.se>**20061108202344] 
[allow commented tests in tests_to_run.
David Roundy <droundy at darcs.net>**20061211000322] 
[remove link to obsolete mirror of kernel repo.
David Roundy <droundy at darcs.net>**20061212012644] 
[add test that sigPIPE doesn't make darcs fail.
David Roundy <droundy at darcs.net>**20061209230155] 
[Hard link support on Windows
Simon Marlow <simonmar at microsoft.com>*-20061204162040
 This works only on NTFS filesystems.  Also it requires Windows 2000 or
 later; this may or may not be acceptable, I'll leave that up to the
 darcs maintainers to decide.
] 
[make it an error to "put" into a preexisting directory.
David Roundy <droundy at darcs.net>**20061203205826
 This changes darcs' behavior I believe for the better.  Often one could be
 tempted to try to put into a directory, expecting to have the repository
 created as a subdirectory there, and it seems confusing (confused me) to
 have instead the repository contents mingled with whatever was already in
 that directory.  Put should behave like get in this regard, in that it
 shouldn't mix the new repo with a preexisting directory.
] 
[catch exceptions in stdout_is_a_pipe
Simon Marlow <simonmar at microsoft.com>**20061129160620] 
[hFlush after "waiting for lock" message
Simon Marlow <simonmar at microsoft.com>**20061129160342
 On Windows, stdout isn't always in line-buffered mode, but we really
 want to see the message about waiting for a lock quickly.  Mostly
 because ^C isn't always caught properly on Windows and lock files are
 often left behind, but that's another storey...
 
] 
[add explicit import list
Simon Marlow <simonmar at microsoft.com>**20061129160144] 
[Improve error messages in push_cmd
chevalier at alum.wellesley.edu**20061207040701
 
 I ran into this because MSYS was munging my repository directory in a
 horrible way. This resulted in a bad repo directory getting passed into
 darcs, which resulted in a fromJust error, which we all know makes the
 baby Jesus cry. So, I at least refactored the code to give a better
 error message, though there may well be a better solution.
] 
[Hard link support on Windows
Simon Marlow <simonmar at microsoft.com>**20061204162040
 This works only on NTFS filesystems.  Also it requires Windows 2000 or
 later; this may or may not be acceptable, I'll leave that up to the
 darcs maintainers to decide.
] 
[adapt test sametwice to new obliterate --all feature
Tommy Pettersson <ptp at lysator.liu.se>**20061130132058] 
[Adapt test perms.sh to obliterate --all feature.
Eric Kow <eric.kow at gmail.com>**20061209200625] 
[fix for Issue111, obliterate --all
David Roundy <droundy at darcs.net>**20061129164016
 This is a patch to implement the wishless item Issue111,
 which asks for an --all option to obliterate.  The idea is
 that you might use the --patches flag to select a bunch of
 patches and not want to have to say yess to all of them.
 
 For good measure, I also added it to unpull and unrecord.
] 
[use impossible to document impossible case in Repair.
David Roundy <droundy at darcs.net>**20061204152854] 
[use variable TEST_FILTER_FILE in makefile.
David Roundy <droundy at darcs.net>**20061204151217] 
[configure should fail if a required module isn't present.
David Roundy <droundy at darcs.net>**20061128024557] 
[Remove raw_mode functions from atomic_create.h.
Eric Kow <eric.kow at gmail.com>**20061008202738
 
 It seems these were once implemented in compat.c and have since been
 reimplemented in Haskell by Ian Lynagh on 2005-07-30.  These appear to
 just be leftover declarations in the C header.
 
] 
[ignore failure from hSetBuffering
Tommy Pettersson <ptp at lysator.liu.se>**20061117221424
 This affects:
   issue41	Doesn't like pasted text.
   issue94	Crash on bogus input
   issue146	hSetBuffering: invalid argument
   issue318	buffering error of darcs record under bash/cmd.exe
 It doesn't necessarily "fix" anything. It prevents darcs from quiting,
 instead continuing with perhaps an undesirable buffering mode, which may or
 may not be better ... or worse.
] 
[Fix curses stuff, especially on Solaris 10.
Dave Love <fx at gnu.org>**20061120171211] 
[Define infodepspatch locally in AmendRecord instead of exporting it from Patch
edwin.thomson at businesswebsoftware.com**20061121093332
 
] 
[Make libcurl use any http authentication.
Tobias Gruetzmacher <darcs at portfolio16.de>**20061118230406
 This let darcs use repositories protected with digest authentication.
] 
[Redirect stderr to Null when exiting SSH control master.
Eric Kow <eric.kow at loria.fr>**20061118212115
 
 This suppresses the output
 * Pseudo-terminal will not be allocated because stdin is not a terminal.
   (result of redirecting stdin from /dev/null)
 * Exit request sent.
   (seems to be normal output. Seems also that there is no way to suppress
    this; -q does not do the job, for example)
 
] 
[Overhaul and improve automation of ssh_test.
Eric Kow <eric.kow at gmail.com>**20061121141802
 
 * Now quits if you don't supply REMOTE; does not have any
   silly default values
 * Options now passed in through environment variables, so:
     NO_CONTROL_MASTER=1 REMOTE=me at 192.168.2.12 ./ssh_test
 * Performs some automated success checks (which means that
   it should be possible to use this from the harness if you
   have ssh-agent running)
 * Performs darcs send test
 * Does not try to pass darcs-ssh flags (like --disable-ssh-cm)
   to non-ssh-using commands like record
 
] 
[Rename ssh_test to ssh.sh (for shell harness).
Eric Kow <eric.kow at gmail.com>**20061121141101
 
 Note that you must set environment variables for it do anything
 useful (namely REMOTE=you at someserver); something like the following
 should work:
   REMOTE=me at 192.168.2.3 make test
 
 You need to be using public key authentication to have a fully
 automated test.
 
] 
[Support darcs send --disable-ssh-cm.
Eric Kow <eric.kow at loria.fr>**20061121134158] 
[Canonize Edwin Thomson.
Eric Kow <eric.kow at gmail.com>**20061118174454] 
[Make Exec.lhs not import unneeded Control.Exception functions when compiling on Windows.
edwin.thomson at businesswebsoftware.com**20061114182952
 
] 
[Annotate various boring patterns.
Dave Love <fx at gnu.org>**20061113225701] 
[Add make rules for tags files.
Dave Love <fx at gnu.org>**20061113213923] 
[Amending a patch doesn't remove explicit dependencies
edwin.thomson at gmail.com**20061110222837] 
[look for --disable-ssh-cm in defaults files (issue351)
Tommy Pettersson <ptp at lysator.liu.se>**20061117180942] 
[Add a semi-automated test for SSH-related things.
Eric Kow <eric.kow at gmail.com>**20061110110801
 
 Testing SSH stuff is tricky in that (1) you need some place to connect
 to and (2) you often want to make sure that the user interactions work
 out right.  But it can't hurt to script away the boring stuff so that
 you are naturally encouraged to test things out more thoroughly.
] 
[add test target for testing hashed inventories.
David Roundy <droundy at darcs.net>**20060927020127] 
[Do _not_ allow escaped quotes in `quoted'.
Eric Kow <eric.kow at loria.fr>**20061030064531
 
 This undoes the patch by Dave Love: Allow escaped quotes in `quoted'.
 The immediate problem is that it breaks make_changelog (because one of
 Tommy's entries matches on a backslash).  This feature might need more
 discussion before we include it (or not).
 
] 
[Tidy filenames before invoking tar 
Wim Lewis <wiml at hhhh.org>**20061026035535
 Only use the last path component of --dist-name for the distribution
 name; the rest is still used when creating the final tar file. (issue323)
] 
[Replace tabs with spaces (escaped quotes in PatchMatch).
Eric Kow <eric.kow at loria.fr>**20061023192003] 
[Allow escaped quotes in `quoted'.
Dave Love <fx at gnu.org>**20060716193940] 
[Added rigorous error checking in exec
Magnus Jonsson <magnus at smartelectronix.com>**20061006222630
 All lowlevel C return values are checked and turned into
 exceptions if they are error codes. In darcs main
 ExecExceptions are caught and turned into error messages
 to help the user.
] 
[redirect errors to stderr where exec output is used
Tommy Pettersson <ptp at lysator.liu.se>**20060916005651
 Error messages would destroy the result if they ended up in the output.
 If the external command fails, darcs should (but does not always) fail.
] 
[TAG 1.0.9rc2
Tommy Pettersson <ptp at lysator.liu.se>**20061116140351] 
[add some changelog entries
Tommy Pettersson <ptp at lysator.liu.se>**20061116135447] 
[refactor is_malicious_path (for easier reading)
Tommy Pettersson <ptp at lysator.liu.se>**20061113191040] 
[really use new malicious file path check in pull (not in changes)
Tommy Pettersson <ptp at lysator.liu.se>**20061113182628] 
[Pass -q flag to scp only, not ssh and scp.
Eric Kow <eric.kow at gmail.com>**20061108225137
 
 Putty's SSH (plink) does not recognise the -q flag.
 
] 
[remove old malicious_filename check (issue177)
Tommy Pettersson <ptp at lysator.liu.se>**20061110211757] 
[Update FSF address in DarcsCommandsAux.lhs.
Eric Kow <eric.kow at loria.fr>**20061113032907] 
[use new malicious file path check in pull and apply (issue177)
Tommy Pettersson <ptp at lysator.liu.se>**20061110211702] 
[fix latex markup error
Tommy Pettersson <ptp at lysator.liu.se>**20061110205511] 
[add new malicious file path check system
Tommy Pettersson <ptp at lysator.liu.se>**20061110132338
 Adds a new module DarcsCommandsAux for auxiliary functionality common to
 more than one darcs command.
] 
[add function for finding all file names in a patch
Tommy Pettersson <ptp at lysator.liu.se>**20061109144144] 
[add missing space in print_version (issue283)
Tommy Pettersson <ptp at lysator.liu.se>**20061111132808] 
[Extra boring patterns.
Dave Love <fx at gnu.org>**20061109004620] 
[really dump generated darcs.ps in subdir manual/
Tommy Pettersson <ptp at lysator.liu.se>**20061108175122
 Now with working makefile!
] 
[Update FSF address in copyright headers.
Dave Love <fx at gnu.org>**20061104180508] 
[Add COPYING.LIB for fpstring.c.
Dave Love <fx at gnu.org>**20061104180121] 
[Pass email address only for %t in --sendmail-command.
Eric Kow <eric.kow at gmail.com>**20061029112604
 
 Given an address like Bubba Dupont <bubba at jonescollege.edu>, pass
 bubba at jonescollege.edu to the %t argument.  Msmtp seems to require this
 at least.  Note that the full address (Bubba Dupont etc) is already
 encoded in the message body anyway.
 
] 
[Refactor sendEmail and sendEmailDoc.
Eric Kow <eric.kow at gmail.com>**20061029105048] 
[Make Send code slightly easier to understand.
Eric Kow <eric.kow at gmail.com>**20061029100316] 
[make darcs.cgi look for both pristine and current
Dan <greenash at yahoo.com>**20061101222005] 
[Don't lock the repo during `query manifest' (issue315).
Dave Love <fx at gnu.org>**20061105125701] 
[Include curses.h with term.h (issue326).
Dave Love <fx at gnu.org>**20061105123851] 
[I fixed up a bit of bad grammars.
Bill Trost <trost at cloud.rain.com>**20061102033207] 
[bumb version to 1.0.9rc2
Tommy Pettersson <ptp at lysator.liu.se>**20061009204226] 
[dump generated darcs.ps in subdir manual/
Tommy Pettersson <ptp at lysator.liu.se>**20061102152516] 
[remove unrecorded tags from the checkpoint inventory (issue281)
Tommy Pettersson <ptp at lysator.liu.se>**20061031220157
 The commands Check, Get and Repair all can make use of the checkpoint
 inventory. Unrecord, Unpull and Obliterate forgot to remove deleted patches
 from that inventory.
] 
[add test that unrecord of tag removes checkpoint
Tommy Pettersson <ptp at lysator.liu.se>**20061007152648] 
[English and markup fixes.
Dave Love <fx at gnu.org>**20061104153036] 
[add HACKING file
Jason Dagit <dagit at codersbase.com>**20061104214749] 
[Add hi-boot and o-boot extensions in default boring file.
Eric Kow <eric.kow at gmail.com>**20061019071304
 
 These are automatically generated from hs-boot.
 Suggested by Bulat Ziganshin.
 
] 
[Fix some obsolete autoconf stuff.
Dave Love <fx at gnu.org>**20061015155914] 
[TAG 1.0.9rc1
Tommy Pettersson <ptp at lysator.liu.se>**20061008175207] 
[bump version to 1.0.9rc1
Tommy Pettersson <ptp at lysator.liu.se>**20061008175156] 
[Look for Text.Regex in package regex-compat. Needed for GHC 6.6
Josef Svenningsson <josef.svenningsson at gmail.com>**20061004123158] 
[Require 'permission denied' test for MacOS X again.
Eric Kow <eric.kow at gmail.com>**20060930121032
 
 This removes a workaround that had demoted a pull.pl test to a mere TODO under
 MacOS X. For some reason, under MacOS X, we would occasionally get "Unexpected
 error: 0" instead of "permission denied".  The error was first reported on
 2005-11-06 by Erik Schnetter.  We still don't know why it does this, but now
 test seems to systematically "unexpectedly succeed" under MacOS X 10.4.7.
 Perhaps something in MacOS X that was fixed since the error was reported?
 
] 
[In procmail examples, don't use a lock file
era+darcs at iki.fi**20060924111522] 
[add some changelog entries
Tommy Pettersson <ptp at lysator.liu.se>**20060930120140] 
[remove some tabs from darcs source
Tommy Pettersson <ptp at lysator.liu.se>**20060929211203] 
[--matches now accepts logical 'and' 'or' '!' in addition to '&&' '||' 'not'.
Pekka Pessi <ppessi at gmail.com>**20060915140406] 
[Canonize Era Eriksson.
Eric Kow <eric.kow at loria.fr>**20060928223224] 
[Reword paragraph about Procmail's umask handling
era+darcs at iki.fi**20060924114546
 
 The explanation now helpfully hints that similar tricks may be necessary
 in other mail programs, too
] 
[Wrap .muttrc example so it doesn't bleed into margin in PostScript version
era+darcs at iki.fi**20060924111313] 
["Granting access to a repository": remove odd orphaned? sentence
era+darcs at iki.fi**20060924111142] 
[era's trivial typo fixes
era+darcs at iki.fi**20060924110945
 	* best_practices.tex (subsection{Conflicts}): \emph pro \verb
 	  around emphasized word "only"
 
 	* DarcsArguments.lhs (intersection_or_union): uppercase "[DEFAULT]";
 	  (disable_ssh_cm docs): remove duplicate "which"
 
 	* Help.lhs: Missing full stop in description of --extended-help
 
 	* Mv.lhs (mv_description): Missing apostrophe in "Apple's"
 
 	* PatchShow.lhs (showHunk): Replace "that the white space must not"
 	  with "that whitespace must not"
] 
[show error messages when starting and stoping the ssh control master
Tommy Pettersson <ptp at lysator.liu.se>**20060916010645] 
[redirect errors to null where exec output is used but failure is not fatal
Tommy Pettersson <ptp at lysator.liu.se>**20060916010116
 Error messages in the output would destroy the result, but if the command
 fails some other action is taken, so error messages shall not be displayed
 to the user.
] 
[redirect errors to stderr where exec is checked and darcs fails
Tommy Pettersson <ptp at lysator.liu.se>**20060916004407
 In these situations the user will get both the error message from the
 failing external command and a message from darcs about what action it
 could not perform.
] 
[simplify helper function stupidexec in copyRemoteCmd
Tommy Pettersson <ptp at lysator.liu.se>**20060915222923] 
[reindent some long lines
Tommy Pettersson <ptp at lysator.liu.se>**20060915222654] 
[update calls to exec and exec_fancy to new interface
Tommy Pettersson <ptp at lysator.liu.se>**20060915222226] 
[fix typo
Tommy Pettersson <ptp at lysator.liu.se>**20060915164446] 
[rewrite Exec.lhs, new exec interface with Redirects
Tommy Pettersson <ptp at lysator.liu.se>**20060911102933
 Make the code structure a bit simpler and easier to understand.
 Only one (fancy) version of exec.
] 
[Fix Windows stderr non-redirection.
Eric Kow <eric.kow at gmail.com>**20060909055204
 
 (It was consistently redirecting to stdout.)
 
 Also make the exec code more readable/transparent.
 
] 
[whatsnew --look-for-adds doesn't read unadded files (fix for issue79)
Jason Dagit <dagit at codersbase.com>**20060910193803
 The default mode for whatsnew --look-for-adds is summary mode.  In summary
 mode full patches are not needed.  This fix changes whatsnew
 --look-for-adds to stop computing the full patch for a file when the
 file is not managed by darcs.
] 
[Correct canonical email for Kirill Smelkov
Kirill Smelkov <kirr at landau.phys.spbu.ru>**20060912080004] 
[move test for tabs from makefile to haskell_policy test
Tommy Pettersson <ptp at lysator.liu.se>**20060730122348] 
[add test for haskell policy
Tommy Pettersson <ptp at lysator.liu.se>**20060730121404] 
[ratify some uses of readFile and hGetContents
Tommy Pettersson <ptp at lysator.liu.se>**20060730121158] 
[Remove direct dependency to mapi32.dll; Improve MAPI compatibility.
Esa Ilari Vuokko <ei at vuokko.info>**20051130000915] 
[Canonize Kirill Smelkov and Anders Hockersten.
Eric Kow <eric.kow at gmail.com>**20060910052541] 
[Correct 'one one' in web page.
Eric Kow <eric.kow at loria.fr>**20060908191241] 
[make amend-record.pl test a bit pickier.
David Roundy <droundy at darcs.net>**20060730103854] 
[simplify code a tad in get.
David Roundy <droundy at darcs.net>**20060726121737] 
[Do not redirect to or from /dev/null when calling ssh.
Eric Kow <eric.kow at loria.fr>**20060903214831
 
 Redirection of stdin and stdout breaks putty, which uses these to
 interact with the user.  Quiet mode, and redirecting stderr are good
 enough for making ssh silent.
 
] 
[Exec improvements : Windows redirection, and more redirection control.
Eric Kow <eric.kow at gmail.com>**20060707054134
 
 - Implement ability to redirect to /dev/null under Windows
   (eivuokko on #darcs points out that it is NUL under Windows)
 
 - Add exec_ function, which does the same thing as exec,
   but allows redirection on stderr, and also allows us
   to NOT redirect stdin/stderr
 
] 
[Ignore .git if _darcs found.
Juliusz Chroboczek <jch at pps.jussieu.fr>**20060831231933] 
[overhaul the darcs.net front page.
Mark Stosberg <mark at summersault.com>**20060820191415
 
 The themes to this change are:
 
 - Focus on the key benefits of darcs:
     Distributed. Interactive. Smart.
 
 - Recognize that the wiki is the central resource,
    and remove some information that is duplicated here
    and reference the wik instead. 
 
 I can post a demo of this HTML for easy comparison if you'd like.
 
     Mark
] 
[Reimplement --disable-ssh-cm flag (issue239).
Eric Kow <eric.kow at gmail.com>**20060812134856
 
 My patch to "Only launch SSH control master on demand" accidentally
 removed the ability to disable use of SSH ControlMaster.  Also, the
 way it was implemented is not compatible with launching on demand.
 This implementation relies on a notion of global variables using
 unsafe IORefs.
 
] 
[Compile Global.lhs in place of AtExit.lhs.
Eric Kow <eric.kow at gmail.com>**20060812121943] 
[Rename AtExit module to Global.
Eric Kow <eric.kow at gmail.com>**20060812121925
 
 The goal is to capture some broad "global" notions like exit handlers
 and global variables.  Note the GPL header thrown in for good measure.
 
] 
[Raise exception if unable to open logfile (issue142).
Zachary P. Landau <kapheine at divineinvasion.net>**20060810034035] 
[Make the pull 'permission test' work when run as root
Jon Olsson <jon at vexed.se>**20060831193834] 
[TAG darcs-unstable-20060831
Juliusz Chroboczek <jch at pps.jussieu.fr>**20060831191554] 
Patch bundle hash:
c037b08f00f7fcc122ef5cb8d0d21269640633d7
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 186 bytes
Desc: not available
Url : http://lists.osuosl.org/pipermail/darcs-devel/attachments/20071206/93efa59f/attachment-0001.pgp 


More information about the darcs-devel mailing list