Don't Apply This Yet (DATY)!

Why is this patch in your inbox if it's DATY?  Because I need help
with it of course!  I just hope my request for review doesn't drive
you batty!

My test case is as follows:
0) Get a tar ball of the linux source
1) cd linux; darcs add --recursive *
2) echo q | darcs record -m "import" +RTS -sstderr -p -hc -RTS
3) compare various modifications

(Note: -hc is just one nice profiling option, -hy is also nice but you
can only use one at a time.)

Doing the above test I have discovered that Darcs.Patch.FileName is a
very costly module.  It is costly mainly in terms of space usage.  The
space usage forces the garbage collector to run far too frequently and
this burns up CPU time, allocates a ton of virtual memory, and wastes
siginificant amounts of ram.  On my test machine, the virtual memory
usage is just over 1GB when profiling, and uses 400-500 megs of
physical ram.

Why is it so bad?  There are several reasons.  The main one is our use
of decode_white/encode_white.  These functions operate on strings and
replace white space in filenames with escaped character codes.  For
example, "hello world" becomes "hello\32world".

I'm reasonably confident that the algorithms have been preserved.
Note that the Diff module could make use of futher clean up to use
more ByteStrings and what I have there is really just enough to make
it compile.

What I need help with is the conversion functions like fp2ps, ps2fn
and so on that used encode and unpackPSfromUTF8.  I have a basic
understading of Unicode, UTF-8, bytes, and codepoints, but I'm not
familiar with the usage here and in Darcs so I could use a bit of help
from a careful eye.

Thanks!
Jason
PS I'll try to reply to this with data to quantify the
performance gains.

Wed Sep 23 19:13:50 PDT 2009  Jason Dagit <da...@codersbase.com>
  * switch Darcs.Patch.FileName to be ByteString.Char8 internally
  This switch gives significant performance gains in some use cases,
  such as recording the add of many files simultaneously.

New patches:

[switch Darcs.Patch.FileName to be ByteString.Char8 internally
Jason Dagit <da...@codersbase.com>**20090924021350
 Ignore-this: d24793cfa66a57aca7195ea32bc41f32
 This switch gives significant performance gains in some use cases,
 such as recording the add of many files simultaneously.
] hunk ./src/Darcs/Diff.hs 74
 #endif
                    )
 #ifndef GADT_WITNESSES
-import Darcs.Patch.FileName( fp2fn, breakup )
+import Darcs.Patch.FileName( fp2fn, breakup, fn2ps, ps2fn, fn2fp )
 #endif
 import System.IO ( openBinaryFile )
 import Darcs.Repository.Prefs ( FileType(..) )
hunk ./src/Darcs/Diff.hs 131
                            initialFps s1PathSlurpy s2PathSlurpy NilFL
   where pathIn1 = get_slurp (fp2fn path) s1
         pathIn2 = get_slurp (fp2fn path) s2
-        initialFps = tail $ reverse (breakup path)
+        initialFps = map (fn2fp . ps2fn) $ tail $ reverse (breakup (fn2ps . fp2fn $ path))
 
 make_nonoverlapping_path_set :: [FilePath] -> [FilePath]
hunk ./src/Darcs/Diff.hs 134
-make_nonoverlapping_path_set = map unbreakup . delete_overlapping . map breakup . sort
+make_nonoverlapping_path_set = map unbreakup . delete_overlapping . map (map (fn2fp . ps2fn)) . map (breakup . fn2ps . fp2fn) . sort
   where
     delete_overlapping :: [[FilePath]] -> [[FilePath]]
     delete_overlapping (p1:p2:ps) = if p1 `isPrefixOf` p2
hunk ./src/Darcs/Patch/FileName.hs 17
 -- along with this program; see the file COPYING.  If not, write to
 -- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
 -- Boston, MA 02110-1301, USA.
-
+{-# LANGUAGE OverloadedStrings #-}
 -- | FileName is an abstract type intended to facilitate the input and output of
 -- unicode filenames.
 module Darcs.Patch.FileName ( FileName( ),
hunk ./src/Darcs/Patch/FileName.hs 32
                             ) where
 
 import System.IO
-import Data.Char ( isSpace, chr, ord )
-import qualified Codec.Binary.UTF8.String as UTF8 ( encode )
-import Data.Word ( Word8( ) )
-import ByteStringUtils ( unpackPSfromUTF8 )
-import qualified Data.ByteString.Char8 as BC (unpack, pack)
-import qualified Data.ByteString       as B  (ByteString, pack)
+import qualified Data.ByteString.Char8 as BC (unpack, break, null, pack,
+                                              singleton, cons, append,
+                                              tail, breakEnd, init, head)
+import qualified Data.ByteString       as B  (ByteString)
+import Data.Char ( ord, isSpace, chr )
+
+newtype FileName = FN B.ByteString deriving ( Eq, Ord )
 
hunk ./src/Darcs/Patch/FileName.hs 40
-newtype FileName = FN FilePath deriving ( Eq, Ord )
-encode :: [Char] -> [Word8]
-encode = UTF8.encode
+-- encode :: [Char] -> [Word8]
+-- encode = UTF8.encode
 
 instance Show FileName where
    showsPrec d (FN fp) = showParen (d > app_prec) $ showString "fp2fn " . showsPrec (app_prec + 1) fp
hunk ./src/Darcs/Patch/FileName.hs 49
 
 {-# INLINE fp2fn #-}
 fp2fn :: FilePath -> FileName
-fp2fn fp = FN fp
+fp2fn = FN . BC.pack
 
 {-# INLINE fn2fp #-}
 fn2fp :: FileName -> FilePath
hunk ./src/Darcs/Patch/FileName.hs 53
-fn2fp (FN fp) = fp
+fn2fp (FN fp) = BC.unpack fp
 
 {-# INLINE niceps2fn #-}
 niceps2fn :: B.ByteString -> FileName
hunk ./src/Darcs/Patch/FileName.hs 57
-niceps2fn = FN . decode_white . BC.unpack
+niceps2fn = FN . decode_white
 
 {-# INLINE fn2niceps #-}
 fn2niceps :: FileName -> B.ByteString
hunk ./src/Darcs/Patch/FileName.hs 61
-fn2niceps (FN fp) = BC.pack $ encode_white fp
+fn2niceps (FN fp) = encode_white fp
 
 {-# INLINE fn2ps #-}
 fn2ps :: FileName -> B.ByteString
hunk ./src/Darcs/Patch/FileName.hs 65
-fn2ps (FN fp) = B.pack $ encode $ encode_white fp
+-- Hoping that we have only ASCII data in the test run
+--fn2ps (FN fp) = B.pack $ encode $ encode_white fp
+fn2ps (FN fp) = encode_white fp
 
 {-# INLINE ps2fn #-}
 ps2fn :: B.ByteString -> FileName
hunk ./src/Darcs/Patch/FileName.hs 71
-ps2fn ps = FN $ decode_white $ unpackPSfromUTF8 ps
+-- Hoping that we have only ASCII data in the test run
+--ps2fn ps = FN $ decode_white $ unpackPSfromUTF8 ps
+ps2fn ps = FN $ decode_white ps
 
 -- | 'encode_white' translates whitespace in filenames to a darcs-specific
 --   format (backslash followed by numerical representation according to 'ord').
hunk ./src/Darcs/Patch/FileName.hs 81
 --
 --   > encode_white "hello there" == "hello\32there"
 --   > encode_white "hello\there" == "hello\\there"
-encode_white :: FilePath -> String
-encode_white (c:cs) | isSpace c || c == '\\' =
-    '\\' : (show $ ord c) ++ "\\" ++ encode_white cs
-encode_white (c:cs) = c : encode_white cs
-encode_white [] = []
+encode_white :: B.ByteString -> B.ByteString
+encode_white b | BC.null b = b
+encode_white b | isSpace c || c == '\\' =
+    ('\\' `BC.cons` (BC.pack $ show $ ord c)) `BC.append` ('\\' `BC.cons` encode_white cs)
+  where
+  c = BC.head b
+  cs = BC.tail b
+encode_white b = c `BC.cons` encode_white cs
+  where
+  c = BC.head b
+  cs = BC.tail b
 
 -- | 'decode_white' interprets the Darcs-specific \"encoded\" filenames
 --   produced by 'encode_white'
hunk ./src/Darcs/Patch/FileName.hs 99
 --   > decode_white "hello\32there" == "hello there"
 --   > decode_white "hello\\there"  == "hello\there"
 --   > decode_white "hello\there"   == error "malformed filename"
-decode_white :: String -> FilePath
-decode_white ('\\':cs) =
-    case break (=='\\') cs of
-    (theord, '\\':rest) ->
-        chr (read theord) : decode_white rest
-    _ -> error "malformed filename"
-decode_white (c:cs) = c: decode_white cs
-decode_white "" = ""
+decode_white :: B.ByteString -> B.ByteString
+decode_white b | BC.null b = b
+decode_white b | c == '\\' =
+   case BC.break (=='\\') cs of
+   (theord, rest) | BC.null rest -> error "malformed filename"
+                  | c == '\\' -> chr (read (BC.unpack theord)) `BC.cons` decode_white (BC.tail rest)
+   _ -> error "malformed filename"
+ where
+ c = BC.head b
+ cs = BC.tail b
+decode_white b = (BC.head b) `BC.cons` decode_white (BC.tail b)
 
 own_name :: FileName -> FileName
 own_name (FN f) = case breakLast '/' f of Nothing -> FN f
hunk ./src/Darcs/Patch/FileName.hs 127
 norm_path :: FileName -> FileName -- remove "./"
 norm_path (FN p) = FN $ repath $ drop_dotdot $ breakup p
 
-repath :: [String] -> String
+repath :: [B.ByteString] -> B.ByteString
 repath [] = ""
 repath [f] = f
hunk ./src/Darcs/Patch/FileName.hs 130
-repath (d:p) = d ++ "/" ++ repath p
+repath (d:p) = d `BC.append` ('/' `BC.cons` repath p)
 
hunk ./src/Darcs/Patch/FileName.hs 132
-drop_dotdot :: [String] -> [String]
-drop_dotdot ("":p) = drop_dotdot p
-drop_dotdot (".":p) = drop_dotdot p
-drop_dotdot ("..":p) = ".." : (drop_dotdot p)
-drop_dotdot (_:"..":p) = drop_dotdot p
+drop_dotdot :: [B.ByteString] -> [B.ByteString]
+drop_dotdot (d:p) | BC.null d = drop_dotdot p
+                  | BC.singleton '.' == d = drop_dotdot p
+                  | BC.pack ".." == d = d : (drop_dotdot p)
+drop_dotdot (_:d:p) | BC.pack ".." == d = drop_dotdot p
 drop_dotdot (d:p) = case drop_dotdot p of
hunk ./src/Darcs/Patch/FileName.hs 138
-                    ("..":p') -> p'
+                    (d':p') | BC.pack ".." == d' -> p'
                     p' -> d : p'
 drop_dotdot [] = []
 
hunk ./src/Darcs/Patch/FileName.hs 143
 -- | Split a file path at the slashes
-breakup :: String -> [String]
-breakup p = case break (=='/') p of
-            (d,"") -> [d]
-            (d,p') -> d : breakup (tail p')
+breakup :: B.ByteString -> [B.ByteString]
+breakup p = case BC.break (=='/') p of
+            (d,p') | BC.null p' -> [d]
+                   | otherwise -> d : breakup (BC.tail p')
+
+breakFirst :: Char -> B.ByteString -> Maybe (B.ByteString, B.ByteString)
+breakFirst c l = case BC.break (c==) l of
+                 (before, after) | BC.null after -> Nothing
+                                 | otherwise -> Just (before, BC.tail after)
 
hunk ./src/Darcs/Patch/FileName.hs 153
-breakFirst :: Char -> String -> Maybe (String,String)
-breakFirst c l = bf [] l
-    where bf a (r:rs) | r == c = Just (reverse a,rs)
-                      | otherwise = bf (r:a) rs
-          bf _ [] = Nothing
-breakLast :: Char -> String -> Maybe (String,String)
-breakLast c l = case breakFirst c (reverse l) of
-                Nothing -> Nothing
-                Just (a,b) -> Just (reverse b, reverse a)
+breakLast :: Char -> B.ByteString -> Maybe (B.ByteString, B.ByteString)
+breakLast c l = case BC.breakEnd (c==) l of
+                (before, after) | BC.null before -> Nothing
+                                | otherwise -> Just (BC.init before, after)
 
 (///) :: FileName -> FileName -> FileName
 (FN "")///b = norm_path b
hunk ./src/Darcs/Patch/Prim.lhs 58
 import qualified Data.ByteString.Char8 as BC (break, pack)
 
 import Darcs.Patch.FileName ( FileName, fn2ps, fn2fp, fp2fn, norm_path,
-                              movedirfilename, encode_white )
+                              movedirfilename )
 import Darcs.Ordered
 import Darcs.Sealed ( Sealed, unseal )
 import Darcs.Patch.Patchy ( Invert(..), Commute(..) )
hunk ./src/Darcs/Patch/Prim.lhs 246
 data FileNameFormat = OldFormat | NewFormat
 formatFileName :: FileNameFormat -> FileName -> Doc
 formatFileName OldFormat = packedString . fn2ps
-formatFileName NewFormat = text . encode_white . fn2fp
+formatFileName NewFormat = packedString . fn2ps
 
 showPrim :: FileNameFormat -> Prim C(a b) -> Doc
 showPrim x (FP f AddFile) = showAddFile x f
hunk ./src/Darcs/Patch/Read.hs 33
 import qualified Data.ByteString.Char8 as BC (head, unpack, dropWhile, break)
 import qualified Data.ByteString       as B  (ByteString, null, init, tail, empty, concat)
 
-import Darcs.Patch.FileName ( FileName, fn2fp, fp2fn, ps2fn, decode_white )
+import Darcs.Patch.FileName ( FileName, fn2fp, ps2fn )
 import Darcs.Patch.Core ( Patch(..), Named(..) )
 import Darcs.Patch.Prim ( Prim(..), FileNameFormat(..),
                           DirPatchType(..), FilePatchType(..),
hunk ./src/Darcs/Patch/Read.hs 117
 
 readFileName :: FileNameFormat -> B.ByteString -> FileName
 readFileName OldFormat = ps2fn
-readFileName NewFormat = fp2fn . decode_white . BC.unpack
+readFileName NewFormat = ps2fn
 
 readHunk :: ParserM m => FileNameFormat -> m (Prim C(x y))
 readHunk x = do

Context:

[add PatchHandle type
Jason Dagit <da...@codersbase.com>**20090912205909
 Ignore-this: 300d31d76598beae3b338f13fbbf1391
] 
[add a PatchHandle module
Jason Dagit <da...@codersbase.com>**20090912040308
 Ignore-this: cda0d2d0870bba206612679d9c6f18d2
] 
[Accept issue1300: --delete-file should only delete if test succeeds.
Eric Kow <ko...@darcs.net>**20090907112620
 Ignore-this: 5a62e769b72808c9827675b2de2e6dae
] 
[Accept issue1332: darcs add -r seems to ignore --boring.
Eric Kow <ko...@darcs.net>**20090907110432
 Ignore-this: e154f5d8fb9e196a87c499c94cb33309
] 
[Test for issue942.
Eric Kow <ko...@darcs.net>**20090907105201
 Ignore-this: 2fa9be77fc31cc4958970fc09a88027f
 
 It appears to have been resolved by:
 Thu Oct 30 18:55:08 CET 2008  David Roundy <drou...@darcs.net>
   * make default be to --run-posthook and --run-prehook
] 
[Test for issue142.
Eric Kow <ko...@darcs.net>**20090904173849
 Ignore-this: 29fe1f32341d62b2582b601ca699e8a9
] 
[Subsections for posthooks and prehooks.
Eric Kow <ko...@darcs.net>**20090902072253
 Ignore-this: 85402c1fd51c99cb45e20eb0442abf53
] 
[Remove darcs.cgi contrib script.
Eric Kow <ko...@darcs.net>**20090909192413
 Ignore-this: 919bf120a9cf0256036598309a44b5e3
 Will Glozer can no longer maintain it.
] 
[More descriptive name for issue1488 test.
Eric Kow <ko...@darcs.net>**20090909192238
 Ignore-this: 6bc0dddf87b12f0b269110ae5d29796d
] 
[Accept issue1488: a 'fromJust error' in 'darcs whatsnew -l'
Marnix Klooster <marnix.kloos...@gmail.com>**20090909180046
 Ignore-this: d064a42a78efef5c327d41e425a6fefc
] 
[Make the ./tests/issue1465_ortryrunning.sh a little more foolproof.
Petr Rockai <m...@mornfall.net>**20090909144349
 Ignore-this: 2e0f7370f2e53e3c104e68a9c5aeeafe
] 
[Skip the time-stamps test on windows.
Petr Rockai <m...@mornfall.net>**20090909142844
 Ignore-this: 72b0bc3d549cab38bceda55113334dd
] 
[make an assumption in the pull code explicit
Ganesh Sittampalam <gan...@earth.li>**20090908214917
 Ignore-this: c573c45fb13012ebd28022f44508d6c8
 It seems like get_common_and_uncommon always returns a singleton list,
 which is then relied on later. This patch makes that assumption explicit,
 by erroring out if it's not true.
] 
[Print expansions of simple commands in testsuite output.
Petr Rockai <m...@mornfall.net>**20090907072337
 Ignore-this: d78e78a155da6f30ebcc592780cfd699
 
 This helps with debugging failures, since we see the exact command that was
 executed, after all shell expansion has been done. Moreover, we see exactly
 which command failed -- the existing -v will eg. print a whole "if" statement
 with body and it cannot be discerned which branch was taken or which command
 exactly has failed.
] 
[Use the correct slash in push-formerly-pl.
Petr Rockai <m...@mornfall.net>**20090906131345
 Ignore-this: b2fe686adcdccbcaf58ca839c19634c9
 
 This is usually not required, but in this particular case, the bad slash
 confuses darcs path comparison (it keeps around the mixed slashes in one of the
 paths, but has backslashes-only in the other one and wrongly concludes that the
 paths are different).
] 
[Exit 200 in abort_windows to indicate the skip to the harness.
Petr Rockai <m...@mornfall.net>**20090906131236
 Ignore-this: 18c60417b1c986eebbfddba896738ddb
] 
[Add a simple testcase for the --external-merge option.
Petr Rockai <m...@mornfall.net>**20090806063953
 Ignore-this: e848f9b8d5d926fbcc05064d85c49316
] 
[Add a rudimentary release script.
Petr Rockai <m...@mornfall.net>**20090906154343
 Ignore-this: 7ace3f8e435b04258b270dcd094b9f13
 
 This should automate most of the boring and (more importantly) error-prone work
 that needs to be done upon a darcs release. Work in progress.
] 
[Avoid relying on /dev/stdin in tests/emailformat.sh.
Petr Rockai <m...@mornfall.net>**20090903115749
 Ignore-this: 43b85a6dd1fcefeb7fd32628a5311a8c
] 
[More extensive haddocks on Darcs.Patch.Depends.get_extra.
Eric Kow <ko...@darcs.net>**20090905222525
 Ignore-this: c8e2ac70e5f61ea12afc479636d9e0cd
] 
[specify CPP globally for witnesses build
Ganesh Sittampalam <gan...@earth.li>**20090829061922] 
[missing LANGUAGE in Darcs.ProgressPatches
Ganesh Sittampalam <gan...@earth.li>**20090829061256] 
[missing LANGUAGE in Darcs.Commands.Unrevert
Ganesh Sittampalam <gan...@earth.li>**20090829061208] 
[remove some derived classes from Tag
Ganesh Sittampalam <gan...@earth.li>**20090727060203
 Ignore-this: 933bd408aff78744925ec2e6cb2475ce
 This helps to make the representation more abstract
 
] 
[couple of GADT build fixes for recent GHCs
Ganesh Sittampalam <gan...@earth.li>**20090803050514
 Ignore-this: 6c20e60426da722d0119e00be4eb6816
] 
[add a comment
Ganesh Sittampalam <gan...@earth.li>**20090803055736
 Ignore-this: aad4e733fede7c8abe552893159e0fef
] 
[Resolve issue1578: Don't put newlines in the Haskeline prompts.
Judah Jacobson <judah.jacob...@gmail.com>**20090829072733
 Ignore-this: 48a17fb0f45f3aee76aa56361bfd97df
 
 Haskeline doesn't expect to get control characters in its prompt.
 The fix is to manually print all but the last line of a prompt message
 separately, and then pass the last line as the Haskeline prompt.
 
 So far we've only seen this cause a problem when mark-conflicts is run in
 the emacs shell (see the issue for more information).
] 
[minor clean up in TouchesFiles
Jason Dagit <da...@codersbase.com>**20090830080712
 Ignore-this: dd23aa84c47234c72f14948981214960
] 
[enable -Werror for now
Jason Dagit <da...@codersbase.com>**20090830022619
 Ignore-this: 653bb524a5a252a48136c2176a07a629
 On the one had, shipping release code without treating warnings as
 errors makes a lot of pragmatic sense.  On the other hand, during
 development it would be nice if we notice and deal with warnings as
 soon as possible.  Therefore, I would like to reenable the treatment
 of warnings as errors until the next release.
] 
[silence a warning that happens when compiling witnesses
Jason Dagit <da...@codersbase.com>**20090830022548
 Ignore-this: 58f61bce80505de12ede5095d209b577
] 
[remove unused argument to readPrim
Jason Dagit <da...@codersbase.com>**20090830022354
 Ignore-this: df9164c70fa9be8f274bdb8e634956d1
] 
[use gzipFormat instead of GZip to work around deprecation warning.
Jason Dagit <da...@codersbase.com>**20090830022209
 Ignore-this: a556704bf2c974c10619a8051ebb90b4
] 
[Whoops, one more obviated line from Darcs.Repository.Checkpoint.
Trent W. Buck <trentb...@gmail.com>**20090829070738
 Ignore-this: b9aef33a8b34db9d41f8d0b83025c85b
] 
[Resolve issue1548: show contents requires at least one argument.
Trent W. Buck <trentb...@gmail.com>**20090829073643
 Ignore-this: c15286919e827a5e7fdad01c75acccfe
] 
[Add a hidden alias "darcs log" for "darcs changes".
Trent W. Buck <trentb...@gmail.com>**20090829032545
 Ignore-this: 96d8bec96c5bf39387a534fa62a79e28
 Reduces disparity with CVS, svn, hg, git &c, who all use "log".
] 
[Mark issue68 test as failing (and fix issue number).
Eric Kow <ko...@darcs.net>**20090828101717
 Ignore-this: 63c0ba22d171cefe5a0244b4ee57a991
] 
[Resolve issue1373: don't use a broken example.
Trent W. Buck <trentb...@gmail.com>**20090828062131
 Ignore-this: 35d59b69c8018f55191486c6a0175c9a
] 
[Reorder paragraphs and minor rewrite of darcs replace --help.
Trent W. Buck <trentb...@gmail.com>**20090828041241
 Ignore-this: 72137bca5de55b77173db6758445b4a7
] 
[Remove unused code from Darcs.Repository.Checkpoint.
Trent W. Buck <trentb...@gmail.com>**20090828030127
 Ignore-this: 25ab977e5ac0b735ca6ee90aea0349c9
] 
[The record-scaling test still fails.
Trent W. Buck <trentb...@gmail.com>**20090828025648
 Ignore-this: 5ca16bd011676b083cdfcd4359f4744a
] 
[Print helpful message in gzcrcs command when visiting other repos
Ganesh Sittampalam <gan...@earth.li>**20090827054315
 Ignore-this: a7f997c441f0e246c4d31d827ebc9d2b
] 
[Clean up leftover conflicts from merge with David's test suite work.
Eric Kow <ko...@darcs.net>**20090824104840
 Ignore-this: ec4ef00d4c5b4da6e24f008f854da2e8
] 
[Resolve conflicts between David and mainline test suite work.
Eric Kow <ko...@darcs.net>**20090815232335
 Ignore-this: 72f386bd5345c344f32ca2db9f5594e3
 
 Patches involved from David's end:
   * add failing test demonstrating nasty conflict markings.
   * mark check.sh test as passing.
   * mark issue27 test as passing.
   * mark issue 1043 test as passing.
   * mark nfs-failure.sh as passing (even though it might not be fixed).
   * mark dist-v as passing.
   * mark check.sh as failing.
   * clean up and mark as passing the broken-pipe.sh test.
   * mark issue 525 is no longer failing.
   * move bugs into tests/ directory.
 
 The main patch involved is the 'move bugs into tests/ directory'
 which conflicts with some new bugs we added.  I re-added these
 manually from the mainline branch of darcs along with some bugs
 we added that we later marked as passing.
 
 I also had to clean up a few tests along the way:
 - check.sh because of conflicts,
 - broken-pipe.sh because of temp dir garbage and
 - record-scaling.sh because of MacOS X incompatiblity
] 
[add failing test demonstrating nasty conflict markings.
David Roundy <drou...@darcs.net>**20090329022150
 Ignore-this: 17b0df1e2a33e5efccd92f1930850c15fbf12b1e
] 
[mark check.sh test as passing.
David Roundy <drou...@darcs.net>**20081207192451
 Ignore-this: bb0d26124eb69bb88e981d06caa88206
] 
[mark issue27 test as passing.
David Roundy <drou...@darcs.net>**20081201170526
 Ignore-this: 49c7b75f79d9bf25610162d079f7dde9
] 
[mark issue 1043 test as passing.
David Roundy <drou...@darcs.net>**20081119150515
 Ignore-this: 8b46c9feb0680f0ee9b4f95ee93eb580
] 
[mark nfs-failure.sh as passing (even though it might not be fixed).
David Roundy <drou...@darcs.net>**20081117160036
 Ignore-this: d13ebd26c2a799668068132f9c4d05bc
] 
[mark dist-v as passing.
David Roundy <drou...@darcs.net>**20081115221319
 Ignore-this: 6fbea237af32801e7207f25af032f408
] 
[mark check.sh as failing.
David Roundy <drou...@darcs.net>**20081115220504
 Ignore-this: 812ad08924c9d713646c7adc26d34b75
] 
[clean up and mark as passing the broken-pipe.sh test.
David Roundy <drou...@darcs.net>**20081115213750
 Ignore-this: db9fb0de61a4099c73e42365047dc9d2
] 
[mark issue 525 is no longer failing.
David Roundy <drou...@darcs.net>**20081115212158
 Ignore-this: 8398c09d03c2e900251f46c41106d94
] 
[move bugs into tests/ directory.
David Roundy <drou...@darcs.net>**20081115205509
 Ignore-this: 6b249e3ba90b455331ba31fee36ef5ad
] 
[Eliminate references to the autotools-based build system.
Taylor R Campbell <campb...@mumble.net>**20090826170519
 
 Now that the autotools-based build system is gone, various vestiges
 of it can be eliminated.  This patch also eliminates some text in
 src/darcs.tex about the Darcs cgi script in contrib/cgi/, which was
 built using `make install-server' and appears to have no way to be
 built now.  This does not eliminate the script, however.
 
 The following tests still refer to the old autotools- and make-based
 build system:
 
   release/darcs.spec.in
   src/Darcs/Commands/Send.lhs
   tests/README.test_maintainers.txt
   tests/run-all-tests
 
 I didn't change them because I don't know what to substitute for them.
 The sendmail options could use some clearer documentation anyway, which
 is outside the scope of this patch.
] 
[update docs for darcs mv to reflect reality
Ganesh Sittampalam <gan...@earth.li>**20090827230453
 Ignore-this: 7f5c30b5711b8bbcbec47f6217662b0d
] 
[Mark issue1317 test as failing (and note issue number).
Eric Kow <ko...@darcs.net>**20090824110437
 Ignore-this: bbecb8d3a4e60c3bc96b28b729375b6c
] 
[Regression test for issue1317.
Marco Túlio Gontijo e Silva <mar...@riseup.net>**20090811220616
 Ignore-this: 846d37873b06a70bed87afeb0fbf2d38
] 
[Explain a slightly obtuse one-liner.
Trent W. Buck <trentb...@gmail.com>**20090824033200
 Ignore-this: 8d6ed336b0a2d932eed879fc85183943
] 
[Support tests/failing-foo.sh convention for bugs.
Eric Kow <ko...@darcs.net>**20090814103659
 Ignore-this: 4729f6553910660be921af7d1199abb1
] 
[Minor style tweaks in cabal test.
Eric Kow <ko...@darcs.net>**20090814102234
 Ignore-this: 9ce3479022f3c177af3c4fa17426b177
] 
[Support command line arguments in PAGER or DARCS_PAGER
j...@elem.com**20090823011449
 Ignore-this: d979af618b5f193b58867e43dd2e0171
 For example:
   PAGER="less -is" darcs help
] 
[Rename xml_summary to xmlSummary and summarize to plainSummary.
Eric Kow <ko...@darcs.net>**20090818220119
 Ignore-this: b1e29f45f0599a406ffb6496acac2488
] 
[Cut unused imports in Darcs.Patch.Viewing.
Eric Kow <ko...@darcs.net>**20090818214432
 Ignore-this: f83f5ce55279a5b96a14770dbcb7dd0b
] 
[Simpler types for changes --summary.
Eric Kow <ko...@darcs.net>**20090818213946
 Ignore-this: 22fdc7984753eedf3d35ff88762a2eb2
] 
[Camel-case some Darcs.Patch.Viewing functions.
Eric Kow <ko...@darcs.net>**20090817153751
 Ignore-this: b3b03f3408f1097e5b476a35215ecec6
] 
[A tiny bit more separation of concerns in changes --summary core.
Eric Kow <ko...@darcs.net>**20090817230414
 Ignore-this: b9f5e9625862d19c356667dc2ce6710d
] 
[Resolve issue183: Do not sort changes --summary output.
Eric Kow <ko...@darcs.net>**20090817225814
 Ignore-this: 2749e08a69592f49bb7e2400ae89e8a6
 This adds move patches to our high-level representation of summary output.
] 
[Refactor changes --summary core code.
Eric Kow <ko...@darcs.net>**20090817225735
 Ignore-this: 1078c3bf42fa5e2acef6e6a31c81c42b
 
 This uses some custom types representing summarised changes on a higher level
 and also moves the XML and 'line' based rendering of summaries into separate
 blocks of code.
] 
[Accept issue1472: "darcs record ./foo" shouldn't open ./bar.
Trent W. Buck <trentb...@gmail.com>**20090815084306
 Ignore-this: 23d5392008872369ba9b509b75aeb5bc
 This bug was present in Darcs 2.0, but gone by 2.3.
 Thus, this patch simply adds a regression test.
] 
[Remove tabs from src/Exec.hs
Reinier Lamers <tux_roc...@reinier.de>**20090809163015
 Ignore-this: 30952fddf0ae0f60b3af442e90411ca7
] 
[Remove optimize --checkpoint cruft.
Eric Kow <ko...@darcs.net>**20090811143734
 Ignore-this: c36c818704171289ff388cdd539626d5
] 
[darcs.cabal turn on -fwarn-tabs per dupree
gwe...@gmail.com**20090807013047
 Ignore-this: c7961b5512d2f8392f3484c81ca197e0
] 
[Add script that tricks cabal into installing our build-depends only.
Petr Rockai <m...@mornfall.net>**20090805152653
 Ignore-this: 6a70f5ff464d26a944b81967606e7af0
] 
[Avoid unescaped hyphens and backslashes in manpage.
Trent W. Buck <trentb...@gmail.com>**20090803063335
 Ignore-this: 4db2b484b68590f754d36f4751e93962
 Fixes these bugs:
 
   W: darcs: manpage-has-errors-from-man darcs.1.gz:
        297: a tab character is not allowed in an escape name
   I: darcs: hyphen-used-as-minus-sign darcs.1.gz (87 times)
 
 http://lintian.debian.org/tags/manpage-has-errors-from-man.html
 http://lintian.debian.org/tags/hyphen-used-as-minus-sign.html
] 
[Typo: s/comand/command/.
Trent W. Buck <trentb...@gmail.com>**20090803042007
 Ignore-this: fcbe6f2cbcb3743872b0431b11dea10c
 Thanks to http://lintian.debian.org/tags/spelling-error-in-binary.html.
] 
[Update hpc.README to use Cabal.
Petr Rockai <m...@mornfall.net>**20090730190304
 Ignore-this: 7f63751a7daa418ffdca2ca6d20af1b1
] 
[Add a flag for enabling HPC for the darcs library.
Petr Rockai <m...@mornfall.net>**20090730185959
 Ignore-this: e0246133e84e8547e223f61b67a28066
] 
[Combine the HPC tix files after each test in ShellHarness.
Petr Rockai <m...@mornfall.net>**20090730185951
 Ignore-this: 577a6e1614aa8c5ff6f25d9df6f81554
 
 This is done when HPCTIXDIR is set, so presumably we are generating coverage
 report. We need to do this, because otherwise, a full testsuite run produces
 over a gigabyte of tixfiles, even though the combined tix is less than 200K.
] 
[Require haskell zlib, dropping the legacy internal zlib binding.
Petr Rockai <m...@mornfall.net>**20090722091325
 Ignore-this: 348c1fd005fe19900e4a9706567b4ee0
] 
[Fix link to autoconf tarball.
Eric Kow <ko...@darcs.net>**20090723135420
 Ignore-this: cfe87256fbd5af286a00fbb84ca443d0
] 
[Update web page for 2.3.0 release.
Eric Kow <ko...@darcs.net>**20090723134705
 Ignore-this: dfa04b99e5c0170448d635bf0e496a66
] 
[Resolve conflict between autoconf removal and version number updates.
Eric Kow <ko...@darcs.net>**20090723133543
 Ignore-this: efcf724bf0230243cee1e88502428ccd
] 
[Makefile: fix dependency on no longer existing distclean target.
Eric Kow <ko...@darcs.net>**20090722093438
 Ignore-this: d0f8da797e26b0c42a2da76eddd4ed31
] 
[Make utf8-string mandatory.
Eric Kow <ko...@darcs.net>**20090721194433
 Ignore-this: cd8a94b3e4e41bb938e82dffbcb27e2d
] 
[Remove UTF8 module completely.
Eric Kow <ko...@darcs.net>**20090721194220
 Ignore-this: f4ec3fe853ecbc928a8d3e3c3b9aa07c
 The utf8-string package has been the default for a while.
 Now we're wholly dependent on it.
] 
[Add support for skipping tests (exit 200).
Petr Rockai <m...@mornfall.net>**20090720095346
 Ignore-this: 133cb02e8cca03a4678068450cb150a9
] 
[Remove the --checkpoint option from the UI.
Petr Rockai <m...@mornfall.net>**20090720093634
 Ignore-this: 2fb627cd1e64bbe264fda6e19f0b085b
] 
[Remove the support for writing out new checkpoints.
Petr Rockai <m...@mornfall.net>**20090720091809
 Ignore-this: 87eb23fe7604ed0abe5c38daafb87a7e
] 
[Remove unused determine_release_state.pl.
Eric Kow <ko...@darcs.net>**20090721205227
 Ignore-this: 15331bbb258fbdeb6bd4887c8dabb8ed
] 
[Remove ununsed test/shell_harness.hs.
Eric Kow <ko...@darcs.net>**20090721192027
 Ignore-this: 7efbe97744c698beecd4f17a09868467
] 
[Remove autoconf support and cut GNUmakefile to only build manual and tags.
Petr Rockai <m...@mornfall.net>**20090717160355
 Ignore-this: 8a45c095c566172076adbe6e44b37827
] 
[Slightly refactor the run function in ShellHarness.
Petr Rockai <m...@mornfall.net>**20090714134205
 Ignore-this: 92c7f05b9c4d6973e95706f23ea27dfc
] 
[Slightly refactor test machinery in Setup.lhs.
Petr Rockai <m...@mornfall.net>**20090714134119
 Ignore-this: 32206a331658d407d9c0fb3b48405db6
] 
[Use tee in pending_has_conflicts.sh for easier debugging.
Petr Rockai <m...@mornfall.net>**20090713180404
 Ignore-this: 7b96b7f7df6358ddb0466cfe58803f71
] 
[Roll back the getSymbolicLinkStatus workaround, since it constitutes a fd leak.
Petr Rockai <m...@mornfall.net>**20090710143149
 Ignore-this: cd2aa7e13cc902852a7c5d0855d55538
 
 rolling back:
 
 Sun Jun 21 17:39:42 CEST 2009  Petr Rockai <m...@mornfall.net>
   * Avoid getSymbolicLinkStatus in mmap implementation, works around GHC 6.8.2 bug.
] 
[Note darcs 2.3 pre-release and darcs 2.2 stable versions in website.
Eric Kow <ko...@darcs.net>**20090716133323
 Ignore-this: bbe9c36213a07890816b8599f2f29aee
] 
[Remove website automation from Makefile.
Eric Kow <ko...@darcs.net>**20090716133230
 Ignore-this: f0cdb9afaa9d314321b345a08e2784bf
] 
[Rename index.html.in to index.html, forgoing website automation.
Eric Kow <ko...@darcs.net>**20090716133023
 Ignore-this: a4c62db2d3ca341e95262cd05328473f
 
 The website automation allowed us to avoid duplication of information (ie.
 version numbers), but we're in the process of changing our build and
 release system, which breaks the site.  For now, we go for simplicity and
 robustness, perhaps restoring the automation in the future when things
 have settled down somewhat.
] 
[Remove bytestring flag from darcs.cabal.
Eric Kow <ko...@darcs.net>**20090714165021
 Ignore-this: 4325773231f9679054c7d045657bdae0
 Now that we're requiring GHC 6.8 or above, we always use the external bytestring
 package.
] 
[Move email unit tests to Darcs.Test module space
Reinier Lamers <tux_roc...@reinier.de>**20090629203409
 Ignore-this: 3187d24822e7a125a46e0a273956d792
] 
[Teach cabal about new Darcs.Test modules
Reinier Lamers <tux_roc...@reinier.de>**20090629193208
 Ignore-this: c27c8398fd637e100259fdf1f4d42e0a
] 
[Move unit tests to Darcs.Test module space
Reinier Lamers <tux_roc...@reinier.de>**20090629192934
 Ignore-this: e88d9ecb7ca8f0b5679fba2cd2813ff0
] 
[Bound size of trees generated in Darcs.Patch.QuickCheck
Reinier Lamers <tux_roc...@reinier.de>**20090628134952
 Ignore-this: c499b850ad5ca15d4bada56b69ee98f3
 
 This keeps the 'Checking that tree flattenings are consistent' test from
 occasionally taking hours and hours to complete. The maximum depth of 5 was
 found by experiment.
] 
[Add some comments in Darcs.Patch.QuickCheck
Reinier Lamers <tux_roc...@reinier.de>**20090628134908
 Ignore-this: c66a386865832e75427f99febfb91a91
] 
[Avoid getSymbolicLinkStatus in mmap implementation, works around GHC 6.8.2 bug.
Petr Rockai <m...@mornfall.net>**20090621153942
 Ignore-this: 91092453d97c87edfc4e46b11e4ae208
] 
[TAG 2.3.0
Petr Rockai <m...@mornfall.net>**20090723115125
 Ignore-this: e326d4ddff92c578e8fe8a3c23d00193
] 
Patch bundle hash:
a002b50f7356181ddcdc6d542c99418e6c477717
_______________________________________________
darcs-users mailing list
darcs-users@darcs.net
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to