Tue Feb  5 15:53:22 GMT 2008  Eric Kow <[EMAIL PROTECTED]>
  * (Re)upgrade createPS and generatePS to Data.ByteString versions.

Tue Feb  5 15:54:20 GMT 2008  Eric Kow <[EMAIL PROTECTED]>
  * Upgrade spanEndPS and breakPS to Data.ByteString version.

Tue Feb  5 16:27:10 GMT 2008  Eric Kow <[EMAIL PROTECTED]>
  * Upgrade more FastPackedString functions.
  (!), unlinesPS (still concat . intersperse), findLastPS

Tue Feb  5 16:28:23 GMT 2008  Eric Kow <[EMAIL PROTECTED]>
  * Ratify Data.ByteString IO imports.

Tue Feb  5 16:35:41 GMT 2008  Eric Kow <[EMAIL PROTECTED]>
  * Fix 'patch cannot contain newlines' in broken-pipe.sh test.
New patches:

[(Re)upgrade createPS and generatePS to Data.ByteString versions.
Eric Kow <[EMAIL PROTECTED]>**20080205155322] {
hunk ./src/FastPackedString.hs 120
 import System.Mem ( performGC )
 import Foreign.Storable ( peekElemOff, peek )
 import Foreign.Marshal.Alloc ( free )
-import Foreign.Marshal.Array ( pokeArray, mallocArray, reallocArray,
+import Foreign.Marshal.Array ( pokeArray, mallocArray,
                                peekArray, advancePtr )
 import Foreign.Marshal.Utils ( with )
 import Foreign.C.String
hunk ./src/FastPackedString.hs 138
 
 import Foreign.Ptr ( nullPtr, plusPtr, minusPtr, Ptr )
 import Foreign.ForeignPtr( ForeignPtr, withForeignPtr, mallocForeignPtrArray,
-                           newForeignPtr,
                          )
 #if defined(__GLASGOW_HASKELL__)
 import qualified Foreign.Concurrent as FC ( newForeignPtr )
hunk ./src/FastPackedString.hs 146
 
 #ifdef DEBUG_PS
 import Foreign.ForeignPtr ( addForeignPtrFinalizer )
-#endif
 import Foreign.Ptr ( FunPtr )
hunk ./src/FastPackedString.hs 147
+#endif
 import qualified Data.ByteString.Char8 as B
 import qualified Data.ByteString.Internal as BI
 
hunk ./src/FastPackedString.hs 165
 debugForeignPtr _ _ = return ()
 #endif
 
-foreign import ccall unsafe "static stdio.h &free" c_free
-    :: FunPtr (Ptr Word8 -> IO ())
-
 mallocForeignPtr :: Int -> IO (ForeignPtr Word8)
 mallocForeignPtr l
     = do when (l > 1000000) performGC
hunk ./src/FastPackedString.hs 175
 --isn't entirely "safe", but at least it's convenient.
 
 createPS :: Int -> (Ptr Word8 -> IO ()) -> PackedString
-createPS l write_ptr =
-    unsafePerformIO $ do fp <- mallocForeignPtr l
-                         debugForeignPtr fp "createPS"
-                         withForeignPtr fp $ \p -> write_ptr p
-                         return $ BI.fromForeignPtr fp 0 l
+createPS = BI.unsafeCreate
 
 -- -----------------------------------------------------------------------------
 -- PackedString type declaration
hunk ./src/FastPackedString.hs 216
 -- function is required to return the actual size (<= the maximum size).
 
 generatePS :: Int -> (Ptr Word8 -> IO Int) -> IO PackedString
-generatePS i f
- = do p <- mallocArray i
-      i' <- f p
-      p' <- reallocArray p i'
-      fp <- newForeignPtr c_free p'
-      return $ BI.fromForeignPtr fp 0 i'
+generatePS = BI.createAndTrim
 
 -- -----------------------------------------------------------------------------
 -- Constructor functions
}
[Upgrade spanEndPS and breakPS to Data.ByteString version.
Eric Kow <[EMAIL PROTECTED]>**20080205155420] {
hunk ./src/FastPackedString.hs 298
 headPS :: PackedString -> Char
 headPS = B.head
 
-{-# INLINE unsafeHeadPS #-}
-unsafeHeadPS :: PackedString -> Char
-unsafeHeadPS ps
-  = case BI.toForeignPtr ps of
-    (x,s,_) -> BI.w2c $ unsafePerformIO $ withForeignPtr x $ \p -> peekElemOff p s
-
 -- | Extract the elements after the head of a packed string, which must be non-empty.
 {-# INLINE tailPS #-}
 tailPS :: PackedString -> PackedString
hunk ./src/FastPackedString.hs 309
 initPS :: PackedString -> PackedString
 initPS = B.init
 
-{-# INLINE unsafeTailPS #-}
-unsafeTailPS :: PackedString -> PackedString
-unsafeTailPS ps
- = case BI.toForeignPtr ps of
-   (x,s,l) | l == 1     -> nilPS
-           | otherwise  -> BI.fromForeignPtr x (s+1) (l-1)
-
 {-# INLINE nullPS #-}
 nullPS :: PackedString -> Bool
 nullPS = B.null
hunk ./src/FastPackedString.hs 341
 anyPS :: (Char -> Bool) -> PackedString -> Bool
 anyPS = B.any
 
-findWhenPS :: (Char -> Bool) -> PackedString -> Int
-findWhenPS f ps = seq f $
-    if nullPS ps then 0
-    else if f $ unsafeHeadPS ps then 0
-         else 1 + findWhenPS f (unsafeTailPS ps)
-
-findFromEndUntilPS :: (Char -> Bool) -> PackedString -> Int
-findFromEndUntilPS f ps = case BI.toForeignPtr ps of
-   (x,s,l) -> seq f $
-    if nullPS ps then 0
-    else if f $ lastPS ps then l
-         else findFromEndUntilPS f (BI.fromForeignPtr x s (l-1))
-
 {-# INLINE takeWhilePS #-}
 takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
 takeWhilePS = B.takeWhile
hunk ./src/FastPackedString.hs 377
 
 
 elemPS :: Char -> PackedString -> Bool
-elemPS c = B.elem c
+elemPS = B.elem
 
 spanPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
 spanPS =  B.span
hunk ./src/FastPackedString.hs 384
 
 
 spanEndPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
-spanEndPS  p ps = splitAtPS (findFromEndUntilPS (not.p) ps) ps
+spanEndPS  = B.spanEnd
 
 breakPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
hunk ./src/FastPackedString.hs 387
-breakPS p ps = case findWhenPS p ps of
-               n -> (takePS n ps, dropPS n ps)
+breakPS = B.break
 
 {-# INLINE breakOnPS #-}
 breakOnPS :: Char -> PackedString -> (PackedString, PackedString)
}
[Upgrade more FastPackedString functions.
Eric Kow <[EMAIL PROTECTED]>**20080205162710
 (!), unlinesPS (still concat . intersperse), findLastPS
] {
hunk ./src/FastPackedString.hs 129
 import Data.Char
 import Data.Word
 import Data.Int ( Int32 )
+import qualified Data.List as L
 import Control.Monad ( liftM, when )
 
 import System.IO.Unsafe ( unsafePerformIO, unsafeInterleaveIO )
hunk ./src/FastPackedString.hs 202
 
 {-# INLINE (!) #-}
 (!) :: PackedString -> Int -> Word8
-ps ! i
-    = case BI.toForeignPtr ps of
-      (x,s,_) -> unsafePerformIO $ withForeignPtr x $ \p -> peekElemOff p (s+i)
-  -- | i < 0 = error "Can't access negative element in PackedString."
-  -- | i >= l = error "Out of range element in PackedString."
-  -- | otherwise = unsafePerformIO $ withForeignPtr x $ \p -> peekElemOff p (s+i)
+ps ! i = BI.c2w $ B.index ps i
 
 -- -----------------------------------------------------------------------------
 -- generatePS
hunk ./src/FastPackedString.hs 459
              Nothing -> [ps]
              Just n -> takePS n ps : linesPS (dropPS (n+1) ps)
 
--- TODO: re-express in B.ByteString terms and rename
+-- TODO: rename
 unlinesPS :: [PackedString] -> PackedString
hunk ./src/FastPackedString.hs 461
-unlinesPS ss = concatPS $ intersperse_newlines ss
-    where intersperse_newlines (a:b:s) = a:newline: intersperse_newlines (b:s)
-          intersperse_newlines s = s
-          newline = packString "\n"
+unlinesPS = B.concat . L.intersperse newline
+    where newline = packString "\n"
 
 -- TODO: check if this is the same as B.words
 wordsPS :: PackedString -> [PackedString]
hunk ./src/FastPackedString.hs 510
 
 {-# INLINE findLastPS #-}
 findLastPS :: Char -> PackedString -> Maybe Int
-findLastPS c ps = wfindLastPS (BI.c2w c) ps
-
-{-# INLINE wfindLastPS #-}
-wfindLastPS :: Word8 -> PackedString -> Maybe Int
-wfindLastPS c ps =
-  case BI.toForeignPtr ps of
-   (x,s,l) ->
-    unsafePerformIO $ withForeignPtr x $ \p->
-                    findit (-1) (p `plusPtr` s) 0
-    where findit h p i = if i >= l
-                         then if h < 0
-                              then return Nothing
-                              else return $ Just h
-                         else do here <- peekElemOff p i
-                                 if c == here
-                                    then findit i p (i+1)
-                                    else findit h p (i+1)
+findLastPS = B.elemIndexEnd
 
 ------------------------------------------------------------
 
}
[Ratify Data.ByteString IO imports.
Eric Kow <[EMAIL PROTECTED]>**20080205162823] {
hunk ./src/FastPackedString.hs 553
 -- assumed to be ISO-8859-1.
 
 hGetContentsPS :: Handle -> IO PackedString
-hGetContentsPS = B.hGetContents
+hGetContentsPS = B.hGetContents -- ratify hGetContents: just a Data.ByteString import
 
 -- -----------------------------------------------------------------------------
 -- readFilePS
hunk ./src/FastPackedString.hs 567
 -- assumed to be ISO-8859-1.
 
 readFilePS :: FilePath -> IO PackedString
-readFilePS = B.readFile
+readFilePS = B.readFile -- ratify readFile: just a Data.ByteString import
 
 -- -----------------------------------------------------------------------------
 -- writeFilePS
}
[Fix 'patch cannot contain newlines' in broken-pipe.sh test.
Eric Kow <[EMAIL PROTECTED]>**20080205163541] hunk ./tests/broken-pipe.sh 24
 $DARCS add f
 $DARCS rec -am p1
 
-for i in `seq 2 20`; do
+for i in `seq 2 20 | xargs echo`; do
   echo $i > f;
   $DARCS rec -am p$i
 done

Context:

[add test for issue68.
David Roundy <[EMAIL PROTECTED]>**20080205154147
 Note that I haven't been able to reproduce this bug, but from the
 description given by Eric, I expect that this should trigger it.  Or at
 least it'll give us some sort of a hint.
] 
[use bytestring automatically where available.
David Roundy <[EMAIL PROTECTED]>**20080205150513
 configure --disable-bytestring to disable this behavior.
] 
[Stricter use of BI.toForeignPtr in FastPackedString.
Eric Kow <[EMAIL PROTECTED]>**20080205093000
 
 I don't know if this actually makes a difference.  Indeed, the intention behind
 this patch is to avoid introducing any extra laziness where none was found before.
] 
[Restore some original FastPackedString code.
Eric Kow <[EMAIL PROTECTED]>**20080205092829
 It was hanging on some tests, or running out of stack space.
] 
[Restore old FastPackedString version of linesPS and unlinesPS.
Eric Kow <[EMAIL PROTECTED]>**20080205092719
 They behave slightly differently with respect to newlines.
] 
[Add OldFastPackedString for people without the latest bytestring.
Eric Kow <[EMAIL PROTECTED]>**20080205090659
 
 Data.ByteString was included with GHC 6.6, but it seems the Data.ByteString.Internal
 part of the API was only introduced in a later version.
] 
[Start converting FastPackedString into a Data.ByteString wrapper.
Eric Kow <[EMAIL PROTECTED]>**20080203235111] 
[Use copyUrl in copyRemotesNormal.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080205002142] 
[Cleanup libwww configure check.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080205001841] 
[Cleanup curl pipelining configure check.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080205000717] 
[Fix configure check for curl_multi_timeout.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080205000109] 
[Append CPPFLAGS to GHCFLAGS in autoconf.mk.in instead of configure.ac.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080204235906] 
[Use DARCS_SSH when calling darcs transfer-mode.
Eric Kow <[EMAIL PROTECTED]>**20080205144124] 
[accept --partial instead of --lazy with warning.
David Roundy <[EMAIL PROTECTED]>**20080204175222] 
[Give a shorter help message when user supplies a bad command line.
Eric Kow <[EMAIL PROTECTED]>**20080204170119
 
   darcs failed:  Missing argument:  [REPOSITORY]
   Usage: darcs send [OPTION]... [REPOSITORY]
   Send by email a bundle of one or more patches.
 
   See darcs help send for details.
 
 As suggested by Mark Stosberg [issue495].
] 
[export information to posthooks in DARCS_PATCHES and DARCS_FILES.
David Roundy <[EMAIL PROTECTED]>**20080204160710] 
[issue572: Add Some .waf files to the default boring list.
Mark Stosberg <[EMAIL PROTECTED]>**20080203031517] 
[issue257: test for "push => incorrect return code when couldn't get lock"
Mark Stosberg <[EMAIL PROTECTED]>**20080203011036] 
[[issue633] config detection of curl_multi_timeout presence for older curl libraries.
Kevin Quick <[EMAIL PROTECTED]>**20080203035602] 
[move failing issue458 test to bugs/
David Roundy <[EMAIL PROTECTED]>**20080202202810] 
[issue496: move failing test to ./bugs
Mark Stosberg <[EMAIL PROTECTED]>**20080202162828] 
[Don't use the builtin !; it has the wrong semantics.
Trent W. Buck <[EMAIL PROTECTED]>**20080202103848] 
[Add functional sh test for issue496.
Trent W. Buck <[EMAIL PROTECTED]>**20080202103816] 
[Add functional sh test for issue458.
Trent W. Buck <[EMAIL PROTECTED]>**20080202095122] 
[Typo.
Trent W. Buck <[EMAIL PROTECTED]>**20080202083642] 
[Typo.
Trent W. Buck <[EMAIL PROTECTED]>**20080202083347] 
[clean up files we only speculatively downloaded.
David Roundy <[EMAIL PROTECTED]>**20080202164906] 
[provide nicer output when identifying repository.
David Roundy <[EMAIL PROTECTED]>**20080202164843] 
[print progress reports less frequently.
David Roundy <[EMAIL PROTECTED]>**20080202161901
 On my laptop this provides a noticeable performance improvement.  And to
 me, having less rapid jumping on the screen is also a bonus.
] 
[improved test for binaries: We now have both a positive and negative test
Mark Stosberg <[EMAIL PROTECTED]>**20080202150109] 
[issue469: test that _darcs/prefs/binaries matches against full path
Mark Stosberg <[EMAIL PROTECTED]>**20080202024805] 
[simplify speculation on patch contents.
David Roundy <[EMAIL PROTECTED]>**20080202142649] 
[use faster queue type in URL.hs.
David Roundy <[EMAIL PROTECTED]>**20080202142619] 
[refactor speculate a bit.
David Roundy <[EMAIL PROTECTED]>**20080201202752] 
[try to make speculation and pipelining help us.
David Roundy <[EMAIL PROTECTED]>**20080201181524] 
[avoid parsing all patches in darcs get.
David Roundy <[EMAIL PROTECTED]>**20080201214747] 
[add friendly interface for speculative pipelining of downloads.
David Roundy <[EMAIL PROTECTED]>**20080201154000] 
[Fix --no-ephemeral.
[EMAIL PROTECTED] 
[rename segregate{F,R}L into partition{F,R}L.
[EMAIL PROTECTED] 
[Fix darcs get --lazy (Partial was used instead of Lazy).
[EMAIL PROTECTED] 
[match absolute paths on binaries regexps.
David Roundy <[EMAIL PROTECTED]>**20080201152320] 
[avoid needless locking of hashed repositories.
David Roundy <[EMAIL PROTECTED]>**20080201150941] 
[don't display "progress" when running --list-options.  (issue635)
David Roundy <[EMAIL PROTECTED]>**20080201144458] 
[give feedback after successful push or put.
David Roundy <[EMAIL PROTECTED]>**20080131230525] 
[use System.Process when calling darcs apply
David Roundy <[EMAIL PROTECTED]>**20080131230305
 This allows us to get immediate feedback as to how the remote apply is
 proceeding.
] 
[use System.Process for running ssh and other commands.
David Roundy <[EMAIL PROTECTED]>**20080131223831] 
[fix issue 257 by not ignoring exit code of apply.
David Roundy <[EMAIL PROTECTED]>**20080131220054] 
[fix bug in whatsnew when replace is used.
David Roundy <[EMAIL PROTECTED]>**20080131201648] 
[Show a replace+whatsnew -s bug.
[EMAIL PROTECTED] 
[define segregateFL and segregateRL utility functions.
David Roundy <[EMAIL PROTECTED]>**20080131200620] 
[Fix an error message, in case of using subcommands.
[EMAIL PROTECTED] 
[default to get copying all patches.
David Roundy <[EMAIL PROTECTED]>**20080131195151
 You can use --lazy (or ^C) to get a lazy repository.
] 
[add test (failing) for issue257 (from vmiklos, thanks!)
David Roundy <[EMAIL PROTECTED]>**20080131195118] 
[fix bug in unrevert.  (issue366)
David Roundy <[EMAIL PROTECTED]>**20080131192202] 
[give progress report on initial checking of repository validity.
David Roundy <[EMAIL PROTECTED]>**20080131181249
 I'm not sure how much good this will do, since the downloading function
 probably blocks progress output.
] 
[clean up in unrevert_cancel.sh
David Roundy <[EMAIL PROTECTED]>**20080131175149] 
[issue366: test when unrevert reports a bug
Mark Stosberg <[EMAIL PROTECTED]>**20080131042313] 
[make bunchFL compile with type witnesses by adding a signature.
David Roundy <[EMAIL PROTECTED]>**20080131155718] 
[refactor convert.
David Roundy <[EMAIL PROTECTED]>**20080131155547
 This also makes convert slightly more efficient in cases where there is a
 large first patch.
] 
[make darcs get --hashed safe on case-insensitive filesystems.
David Roundy <[EMAIL PROTECTED]>**20080131155112] 
[define handy bunchFL function for grouping patches into batches.
David Roundy <[EMAIL PROTECTED]>**20080131154631] 
[fix conflict-doppleganger test to work with change in flags get accepts.
David Roundy <[EMAIL PROTECTED]>**20080131153250] 
[oops, the build of the manual broke when I hid convert...
David Roundy <[EMAIL PROTECTED]>**20080130230705
 
 rolling back:
 
 Wed Jan 30 16:39:45 EST 2008  David Roundy <[EMAIL PROTECTED]>
   * hide convert.
   Since this is a command that *must* be performed only once per group of
   related repositories, I think making it only visible in the documentation
   should reduce errors.
 
     M ./src/Darcs/TheCommands.lhs -1 +1
] 
[roll back foolish file modification time hack.
David Roundy <[EMAIL PROTECTED]>**20080130224322
 
  As it turns out, I didn't understand what "ctime" means, thinking that it
  was actually a "creation" time.  But alas, ctime changes whenver mtime
  changes, so we can't use their equality to check if the mtime has been
  set.  Ugh.  I feel silly.
 
 rolling back:
 
 Wed Jan 30 12:12:32 EST 2008  David Roundy <[EMAIL PROTECTED]>
   * employ new hack to avoid need to wait for clock to tick.
   The new hack is that if the creation time and modification time of a file
   in the pristine cache are identical, then we don't believe it's meaningful
   if the modification time happens to match that of the file in the working
   directory.
 
     M ./src/Darcs/Lock.lhs -1 +4
     M ./src/Darcs/Repository/Prefs.lhs -4 +8
     M ./src/Darcs/SlurpDirectory.lhs -12 +9
] 
[refactor readPatchInfo using Maybe monad.
David Roundy <[EMAIL PROTECTED]>**20080130220306] 
[fix issue46, parsing problem caused by wrong use of error.
David Roundy <[EMAIL PROTECTED]>**20080130220129] 
[hide convert.
David Roundy <[EMAIL PROTECTED]>**20080130213945
 Since this is a command that *must* be performed only once per group of
 related repositories, I think making it only visible in the documentation
 should reduce errors.
] 
[remove --darcs-2 from get options (issue606)
David Roundy <[EMAIL PROTECTED]>**20080130213712] 
[fix imports for win32.
David Roundy <[EMAIL PROTECTED]>**20080130212629] 
[make rollback default to a long comment indicating what was rolled back.
David Roundy <[EMAIL PROTECTED]>**20080130200814] 
[employ new hack to avoid need to wait for clock to tick.
David Roundy <[EMAIL PROTECTED]>**20080130171232
 The new hack is that if the creation time and modification time of a file
 in the pristine cache are identical, then we don't believe it's meaningful
 if the modification time happens to match that of the file in the working
 directory.
] 
[fix build failure under win32 (hopefully).  Sorry!
David Roundy <[EMAIL PROTECTED]>**20080130170953] 
[refactor issue154 test to match Eric Kow's echo_to_darcs() refactor. The test should pass.
Mark Stosberg <[EMAIL PROTECTED]>**20080129004921] 
[Update docs for echo_to_darcs() to match Eric Kow's code refactor
Mark Stosberg <[EMAIL PROTECTED]>**20080129004448] 
[Adding Test/Builder/Module.pm to the tree, unmodified.
Mark Stosberg <[EMAIL PROTECTED]>**20080129003230
     Thanks to Kevin Quick for noticing this was missing.
] 
[Test Suite: make sure to move outside of tmp repo, so it can get cleaned-up properly
Mark Stosberg <[EMAIL PROTECTED]>**20080126171642] 
[Update add_in_subdir.pl to work with updated init_tmp_repo()
Mark Stosberg <[EMAIL PROTECTED]>**20080126164158] 
[Test Suite: Improve init_tmp_repo():
Mark Stosberg <[EMAIL PROTECTED]>**20080126160916
     - Quit including random chars in the directory name (David's suggestion)
     - Allow DARCS_KEEP_TMPDIR to control whether we keep the tmp repos for inspection (default: false)
     - More reliably clean-up after ourselves then the "File::Temp" method did. 
     ***END OF DESCRIPTION***
 
 Place the long patch description above the ***END OF DESCRIPTION*** marker.
 The first line of this file will be the patch name.
 
 
 This patch contains the following changes:
 
 M ./tests/lib/perl/Test/Darcs.pm -3 +17
] 
[remove clean-up, which should now happen automatically
Mark Stosberg <[EMAIL PROTECTED]>**20080126025241] 
[Shave several minutes off test suite runs by pre-building large repos
Mark Stosberg <[EMAIL PROTECTED]>**20080126184048] 
[make sure we are outside of the tempdir so the auto-cleanup can happen.
Mark Stosberg <[EMAIL PROTECTED]>**20080124044245] 
[improved tempdir handling-- include the script name in the directory name, and better auto-cleanup
Mark Stosberg <[EMAIL PROTECTED]>**20080124044137] 
[issue154: regression test for pull with a directory removal conflict
Mark Stosberg <[EMAIL PROTECTED]>**20080127053811] 
[rollback features that apparently are needed.
David Roundy <[EMAIL PROTECTED]>**20080129203711
 These seem to be needed (at least some of them) to do
 
 darcs get http://darcs.net/repos/unstable
] 
[fix ssh connection business to work if one darcs command accesses two distinct repos on same server.
David Roundy <[EMAIL PROTECTED]>**20080129162911] 
[[issue558] Singular 'do you want to revert this change?'
Eric Kow <[EMAIL PROTECTED]>**20080129163633] 
[Refactor SelectChanges English.
Eric Kow <[EMAIL PROTECTED]>**20080129163619] 
[Add some simple English morphology.
Eric Kow <[EMAIL PROTECTED]>**20080129163613] 
[ratify use of hGetContents.
David Roundy <[EMAIL PROTECTED]>**20080129150247] 
[Fix curl version check for pipelining.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080128223731] 
[issue612: regression test demonstrates that hashed and darcs-2 formats resist a certain kind of corruption.
Mark Stosberg <[EMAIL PROTECTED]>**20080126031445
    (but the old fashioned repo format does not).  
] 
[Remove features not used in parsing patch dates.
Eric Kow <[EMAIL PROTECTED]>**20080129092401] 
[Extract external-merge from {apply,pull} conflict options.
[EMAIL PROTECTED] 
[Don't emit \r when the handle is a terminal.
[EMAIL PROTECTED] 
[Replace unpull by obliterate as much as possible.
[EMAIL PROTECTED] 
[Move rollback to another section of TheCommands.
[EMAIL PROTECTED] 
[give progress output when getting over ssh.
David Roundy <[EMAIL PROTECTED]>**20080128222133] 
[remove progress output that seems too often to be unhelpful.
David Roundy <[EMAIL PROTECTED]>**20080128221922] 
[nicer error message in ssh connection code.
David Roundy <[EMAIL PROTECTED]>**20080128221229] 
[use new ssh connection for copySSHs as well (speed my test up by 20% from the sftp code).
David Roundy <[EMAIL PROTECTED]>**20080128220858] 
[fix bug introduced by rewrite of IsoDate module.
David Roundy <[EMAIL PROTECTED]>**20080128220647
 The problem was that this module served two functions.  One was to allow
 nice date matching, and the other was to allow parsing of old patches,
 created before we moved to the simple 20080127... format.  I've split the
 latter function into a separate "frozen" module, so that we can safely
 develop more friendly date-parsing code.
] 
[Test infrastructure improvement: Add debug mode to Perl test scripts.
Mark Stosberg <[EMAIL PROTECTED]>**20080126154444
   Set this to see the output of every 'darcs' call made through this script:
   DARCS_DEBUG=1 ./bin/prove -v add.pl pull.pl
] 
[reuse ssh connection using transfer-mode.
David Roundy <[EMAIL PROTECTED]>**20080128201613] 
[try using darcs transfer-mode if available.
David Roundy <[EMAIL PROTECTED]>**20080128194406
 Note that this doesn't yet gain us any performance, it's just a step
 towards a faster connection-sharing approach.
] 
[issue227: regression test for get --context with an absolute path
Mark Stosberg <[EMAIL PROTECTED]>**20080126021139] 
[flush output in transfer-mode.
David Roundy <[EMAIL PROTECTED]>**20080128193910] 
[[issue625] Non-recursive --repodir.
Eric Kow <[EMAIL PROTECTED]>**20080128193459] 
[add transfer-mode for faster ssh access.
David Roundy <[EMAIL PROTECTED]>**20080128165256] 
[refactor SSH code into own module.
David Roundy <[EMAIL PROTECTED]>**20080128172658] 
[remove unneeded export from URL.
David Roundy <[EMAIL PROTECTED]>**20080128172534] 
[Fix optimize_relink for POSIX environment (no cp -a or du -l support; now needs perl)
Kevin Quick <[EMAIL PROTECTED]>**20080125220119] 
[Test Fix: make test pass when there is a space in the darcs repo path
Mark Stosberg <[EMAIL PROTECTED]>**20080126170531] 
[Test Fix: replace system calls with quoted function calls
Mark Stosberg <[EMAIL PROTECTED]>**20080126170253] 
[Test fix: work when darcs repo root has a space in it
Mark Stosberg <[EMAIL PROTECTED]>**20080126165818] 
[replace system call with Perl for better portability
Mark Stosberg <[EMAIL PROTECTED]>**20080124013552] 
[Remove more unneeded "--author" flags in the Perl test scripts, because the harness takes care of them
Mark Stosberg <[EMAIL PROTECTED]>**20080120010553] 
[remove now-unused perl_harness
Mark Stosberg <[EMAIL PROTECTED]>**20080120005850] 
[Merge Curl and Libwww to URL module.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080127182001] 
[Fix darcs version in libwww user agent.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080127181548] 
[Cleanup libwww module, better error handling, follow redirects (closes issue621).
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080127152710] 
[Rework libcurl module: use multi interface, support pipelining.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080127151756] 
[Do not announce recipients in send -O.
Eric Kow <[EMAIL PROTECTED]>**20080128151812] 
[Add ability to see skipped/included patches when verbose flag present.
Kevin Quick <[EMAIL PROTECTED]>**20080127190546] 
[Update patch selection feedback for messages more appropriate to the job being performed.
Kevin Quick <[EMAIL PROTECTED]>**20080126035000] 
[adding File::Temp 0.20 to tree for more consistent test results. It is GPL-licensed.
Mark Stosberg <[EMAIL PROTECTED]>**20080124033049] 
[update restrictive perms test to run a temporary directory and clean up after itself.
Mark Stosberg <[EMAIL PROTECTED]>**20080123000417
     Running in a tru temporary directory allows the potential to run tests in parallel.
] 
[ issue602: part 1: Always prefer our private copy of Test::More over the system-wide one for more consistent results
Mark Stosberg <[EMAIL PROTECTED]>**20080124005407] 
[ issue602, part 2: freshen our versions of Test::More and Test::Builder
Mark Stosberg <[EMAIL PROTECTED]>**20080123013642] 
[Test for issue625.
Eric Kow <[EMAIL PROTECTED]>**20080128150059] 
[[issue457] Check match syntax early.
Eric Kow <[EMAIL PROTECTED]>**20080128144840] 
[Add a comment for Real patches.
[EMAIL PROTECTED] 
[beautify remove_subsequenceFL.
David Roundy <[EMAIL PROTECTED]>**20080125225637] 
[beautify remove_subsequenceRL.
David Roundy <[EMAIL PROTECTED]>**20080125225440] 
[we removed --modernize-patches, so remove the test case.
David Roundy <[EMAIL PROTECTED]>**20080125225423] 
[eliminate --modernize-patches and make --uncompress work (issue620)
David Roundy <[EMAIL PROTECTED]>**20080125220624] 
[make hashed repositories respect --dont-compress.
David Roundy <[EMAIL PROTECTED]>**20080125210529] 
[Remove TimeDiff experiment.
Eric Kow <[EMAIL PROTECTED]>**20080128115307] 
[Simplify date matcher and fix tz-related bug.
Eric Kow <[EMAIL PROTECTED]>**20080128115214
 
 When matching partial dates, we should not trust the ctYear, etc on the
 CalendarTime because it may vary by timezone.  This also leads to a
 simplification in the tentative date matching.
 
 Note: subtle change in matching.  Now all matching is done
 within a range, excluding the latter date.  We check
            date <  end
 instead of date <= end
] 
[More aggressive testing of date parser.
Eric Kow <[EMAIL PROTECTED]>**20080127164254
 
 Using record --pipe to set patch dates.
] 
[Support more interactive use of echo_to_darcs in test harness.
Eric Kow <[EMAIL PROTECTED]>**20080127164241] 
[Overhaul date parsing code.
Eric Kow <[EMAIL PROTECTED]>**20080127163040
 
 - Add the ability to match on partial ISO 8601 dates, for example,
   treating 2008-08 as matching the whole month and not just the
   first day of that month
 - Fix some bugs in the parsing of fancy English dates
 - Fix bugs in the interpretation of English dates (for example,
   the interpretation of '3 days before last week' was for all
   patches since that date, and not for all patches *on* that
   date)
 - Treat user input as being in the local timezone
 - Make the matching code a bit more compact
] 
[Make documentation on dates more explicit.
Eric Kow <[EMAIL PROTECTED]>**20080127162931] 
[resolve conflict with Eric on controlMasterPath.
David Roundy <[EMAIL PROTECTED]>**20080125203903] 
[More concise backup warning.
Eric Kow <[EMAIL PROTECTED]>**20071105012930] 
[Remove now obsolete wrapper for Map (we now require GHC >= 6.4).
Eric Kow <[EMAIL PROTECTED]>**20071105192636] 
[Modernise Data.Map import.
Eric Kow <[EMAIL PROTECTED]>**20071105192530] 
[Give ssh CM socket a unique name for each darcs process.
Eric Kow <[EMAIL PROTECTED]>**20071105021956
 Delete the socket in the unlikely event that a previous darcs had a socket
 with the same name left over.
] 
[Create ssh CM socket in $HOME/.darcs if possible.
Eric Kow <[EMAIL PROTECTED]>**20071105015525] 
[Refactor y/n prompts.
Eric Kow <[EMAIL PROTECTED]>**20071019213307] 
[issue578: steve and monica test for rolling back a rollback
Mark Stosberg <[EMAIL PROTECTED]>**20080118031606] 
[eliminate lazy parsing of patches, which gives bad error messages (issue364)
David Roundy <[EMAIL PROTECTED]>**20080125191836] 
[make uniqueoptions.sh test give friendlier output.
David Roundy <[EMAIL PROTECTED]>**20080125183430] 
[fix code to avoid duplicate --verbose in --help (so tests will pass).
David Roundy <[EMAIL PROTECTED]>**20080125183420] 
[update some ChangeLog entries to also credit those who contributed through bug reporting, test writing or feedback. 
Mark Stosberg <[EMAIL PROTECTED]>**20080122235435] 
[More error messages for libwww.
Dmitry Kurochkin <[EMAIL PROTECTED]>**20080124092600] 
[issue608: a new test for 'mv', following Zooko's bug report
Mark Stosberg <[EMAIL PROTECTED]>**20080124013856] 
[[issue492] Check that context file actually exists in darcs get.
Eric Kow <[EMAIL PROTECTED]>**20080125183741] 
[[issue227] Platform-independent absolute paths in get --context
Eric Kow <[EMAIL PROTECTED]>**20080125181702] 
[Make verbosity flags advanced options universally.
Eric Kow <[EMAIL PROTECTED]>**20080125181005] 
[report progress in writing the inventory out for hashed repos.
David Roundy <[EMAIL PROTECTED]>**20080125172017] 
[make empty key case of progress reporting fast.
David Roundy <[EMAIL PROTECTED]>**20080125171859] 
[fix issue where we overwrote prompt with progress info.
David Roundy <[EMAIL PROTECTED]>**20080125164609] 
[fix bug where we used show on an exception (and thus printed "User error").
David Roundy <[EMAIL PROTECTED]>**20080125164209
 This partially addresses issue168 by improving the error message.
] 
[add gnulib sha1.c file as a faster sha1 option.
David Roundy <[EMAIL PROTECTED]>**20080123212502] 
[fix embarrassing bug in External.
David Roundy <[EMAIL PROTECTED]>**20080125152329
 (which demonstrates that I didn't compile before pushing)
] 
[for now, print progress reports to stdout.
David Roundy <[EMAIL PROTECTED]>**20080125152105
 My hope is that this will alleviate some of the issues with progress
 reports overwriting prompts.
] 
[revamp progress reporting, making it more efficient and adding more output.
David Roundy <[EMAIL PROTECTED]>**20080125151540
 Note that there is still at least one time sink that remains to be identified.
] 
[avoid creating darcs-ssh if we aren't using ControlMaster. (issue613)
David Roundy <[EMAIL PROTECTED]>**20080125150846] 
[fix bug where darcs-ssh got even worse name (issue613).
David Roundy <[EMAIL PROTECTED]>**20080125150355] 
[provide more detailed progress reports in HashedIO.
David Roundy <[EMAIL PROTECTED]>**20080124145156] 
[print additional debug data in Progress.
David Roundy <[EMAIL PROTECTED]>**20080124145114] 
[add a few more debug messages in Repository.Internal.
David Roundy <[EMAIL PROTECTED]>**20080124144829] 
[fix incorrect report that we were reading patches.
David Roundy <[EMAIL PROTECTED]>**20080124125040] 
[reenable mandatory sha1 checks, now that we can link with a faster sha1.
David Roundy <[EMAIL PROTECTED]>**20080123203104] 
[remove (broken) git support and add openssl sha1 support.
David Roundy <[EMAIL PROTECTED]>**20080123202025
 These two changes got merged together as I was introducing the configure.ac
 changes to support openssl as a sha1 alternative to our Haskell code.
 
 (Yes, I'm lazy.)
] 
[remove redundant hash checks in hashed IO code.
David Roundy <[EMAIL PROTECTED]>**20080123173022] 
[output nicer progress in convert.
David Roundy <[EMAIL PROTECTED]>**20080123170428] 
[output timings when --timings is specified.
David Roundy <[EMAIL PROTECTED]>**20080123170314] 
[remove inaccurate message in convert.
David Roundy <[EMAIL PROTECTED]>**20080123170243] 
[use debugMessage in HashedIO.
David Roundy <[EMAIL PROTECTED]>**20080123160835] 
[add --timings flag (that as yet does nothing).
David Roundy <[EMAIL PROTECTED]>**20080123154931] 
[Major Perl test suite clean-up.
Mark Stosberg <[EMAIL PROTECTED]>**20080120035651
     The primary purpose of this patch was make sure all the tests are executed in
     randomly named directories, which allows us to run Perl tests in parallel, 
     without the directory names collided. 
 
     This isn't enabled by default for "make test", but it is there to play with.
     In the test directory, you can now do:
 
     ./bin/prove -j9 *.pl 
     
     to run 9 tests in parallel. There is also "--fork"
     option which should be a win on multi-CPU computers. 
     See "perldoc ./bin/prove" for details. 
 
     As part of this, a lot of boiler-plate code at the top and bottom of the
     scripts could be eliminated, and I made few other minor style clean-ups
     while I had the files open. 
 
     There should be no functional changes to the tests. 
] 
[Take advantage of new Perl testing infrastructure by eliminating needless --ignore-time mentions
Mark Stosberg <[EMAIL PROTECTED]>**20080120005242] 
[Take advantage of updated Perl testing infrastructure by removing needless author mentions in tests
Mark Stosberg <[EMAIL PROTECTED]>**20080120004503] 
[use --ignore-time in tests instead of "sleep", for faster, more reliable results
Mark Stosberg <[EMAIL PROTECTED]>**20080118030241] 
[Issue395: avoid single letter patch names in the test suite.  
Mark Stosberg <[EMAIL PROTECTED]>**20080118020634] 
[add regression test for amend-record removed file
Tommy Pettersson <[EMAIL PROTECTED]>**20080122223231] 
[use UTC in date matching test untill match handles time zones
Tommy Pettersson <[EMAIL PROTECTED]>**20080122134322] 
[fix bug with timestamps and obliterate.
David Roundy <[EMAIL PROTECTED]>**20080122224607] 
[Test: unpull may hide changes when using timestamp optimisation.
[EMAIL PROTECTED] 
[avoid printing totals that are less than our current progress.
David Roundy <[EMAIL PROTECTED]>**20080122210546] 
[TAG 2.0.0pre3
David Roundy <[EMAIL PROTECTED]>**20080122200612] 
Patch bundle hash:
16d1f37b6fd78806f04bb82065a0922b0afab19f
_______________________________________________
darcs-devel mailing list
darcs-devel@darcs.net
http://lists.osuosl.org/mailman/listinfo/darcs-devel

Reply via email to