darcs

Patch 374 adventure branch

Title adventure branch
Superseder Nosy List mndrix, mornfall
Related Issues
Status obsoleted Assigned To
Milestone

Created on 2010-08-30.08:43:30 by mornfall, last changed 2013-02-18.09:36:07 by gh. Tracked on DarcsWatch.

Files
File name Status Uploaded Type Edit Remove
first-stab-at-a-hashed_storage-0_6-port_.dpatch mornfall, 2010-09-04.15:17:26 text/x-darcs-patch
move-the-preferences-system-into-io-where-it-belongs_.dpatch mornfall, 2010-09-07.23:44:35 text/x-darcs-patch
move-the-preferences-system-into-io-where-it-belongs_.dpatch ganesh, 2010-10-04.18:51:31 text/x-darcs-patch
unnamed mornfall, 2010-08-30.08:43:29
unnamed mornfall, 2010-09-02.16:33:35
unnamed mornfall, 2010-09-03.02:53:14
unnamed mornfall, 2010-09-04.15:17:26
unnamed mornfall, 2010-09-07.23:44:35
unnamed ganesh, 2010-10-04.18:51:31
wibble-path-building-in-repository_prefs_.dpatch mornfall, 2010-08-30.08:43:29 text/x-darcs-patch
wibble-path-building-in-repository_prefs_.dpatch mornfall, 2010-09-02.16:33:35 text/x-darcs-patch
wibble-path-building-in-repository_prefs_.dpatch mornfall, 2010-09-03.02:53:14 text/x-darcs-patch
See mailing list archives for discussion on individual patches.
Messages
msg12375 (view) Author: mornfall Date: 2010-08-30.08:43:29
Hi!

In between the discussions about how to actually organise the adventure branch,
I have taken the liberty to start hacking on it.

The first pile of patches is a *bit* of a powerplant maybe, on the other hand
it also contains a couple of previously submitted bundles that are blocking
somewhere in review, partially due to their adventure-appropriateness. It would
be good if people could take it apart and start applying the easier part and
maybe discuss the harder (the latter group mostly contains the new annotate
code).

In effect, patch 351 (optimize diff) and 343 (hashed-storage 0.6 aka path
refactor) are obsoleted by this patch. They will hopefully get to mainline
through the adventure branch at some point.

I have also cloned HEAD as darcs-unstable@darcs.net:adventure (also available
as http://darcs.net/adventure) where I imagine these patches would go. I'll set
up a buildbot waterfall for it when people start pushing patches there.

As a sneak preview, you can find the new annotate in action. However please
note, that it is common that the speedup is just a factor of 3 - 10, in this
case the difference is fairly extreme.

Yours,
   Petr.

61 patches for repository http://darcs.net:

Wed Jul 14 19:52:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Wibble path building in Repository.Prefs.

Thu Jul 15 10:59:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use more meaningful names for seal_up_patches' parameters.

Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update haddock.

Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Thu Aug 12 00:16:21 CEST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Thu Aug 12 01:31:25 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Thu Aug 12 01:32:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Wed Aug 18 22:53:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Sun Aug 29 18:30:19 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve hashed-storage dependency conflicts.

Sun Aug 29 18:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Sun Aug 29 18:30:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Sun Aug 29 18:31:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Sun Aug 29 18:31:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Darcs.Patch.*.

Fri Aug 27 22:44:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement a test-framework-based shell harness.
  
  This merges the two test drivers we previously had, "unit" and
  Distribution.ShellHarness (used directly by Setup), into a single "darcs-test"
  binary. This patch only goes half the way, though: the new shell harness is not
  used by "cabal test" yet. That will come as a separate patch.

Sat Aug 28 00:03:53 CEST 2010  Petr Rockai <me@mornfall.net>
  * Couple of improvements in the new shell test runner.

Sat Aug 28 00:04:14 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a --network option to darcs-test to run the network shell tests.

Sat Aug 28 00:04:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Flip "cabal test" over to use darcs-test to run the shell tests.

Sun Aug 29 15:47:47 CEST 2010  Petr Rockai <me@mornfall.net>
  * Bump shellish dependency to >= 0.1.1, to avoid the infinite loop in rm_rf problem.

Sun Aug 29 15:56:23 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop the "test" cabal flag and build darcs-test unconditionally.

Sun Aug 29 18:45:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make it possible to pass "threads=N" to cabal test.

Sun Aug 29 18:46:13 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve a (bogus?) conflict in darcs.cabal.

Sun Aug 29 18:51:11 CEST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Sun Aug 29 18:53:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Sun Aug 29 18:54:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 19:14:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Set a $format variable in lib, depending on current repo format under test.

Sun Aug 29 19:15:01 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests a bit less verbose (do not print all of lib every time).

Sun Aug 29 19:15:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 19:15:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug in cabal test argument parsing.

Sun Aug 29 19:16:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix up the module list in darcs.cabal.

Sun Aug 29 19:16:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 19:43:58 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Sun Aug 29 19:44:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a tarball of a small oldfashioned repository for testing purposes.

Sun Aug 29 19:57:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 19:57:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 19:58:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 19:58:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Sun Aug 29 21:14:09 CEST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Sun Aug 29 21:14:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 21:15:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Sun Aug 29 21:17:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-defunct Distribution directory.

Mon Aug 30 01:09:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Mon Aug 30 01:16:51 CEST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Mon Aug 30 01:22:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Mon Aug 30 01:24:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Mon Aug 30 09:46:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Mon Aug 30 09:47:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Mon Aug 30 10:17:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Mon Aug 30 10:24:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Mon Aug 30 10:29:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

darcs annotate src/test.hs 8,69s user 0,46s system 99% cpu 9,199 total

[snip]

darcs-ADV annotate src/test.hs 0,08s user 0,01s system 93% cpu 0,102 total

1: Wed Jul  7 20:06:00 CEST 2010  Ganesh Sittampalam <ganesh@earth.li>
  * move main unit testing code into module with proper name (not Main)
  This is enable other things than the unit executable to import it
  
2: Fri Aug 27 22:44:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement a test-framework-based shell harness.
  
  This merges the two test drivers we previously had, "unit" and
  Distribution.ShellHarness (used directly by Setup), into a single "darcs-test"
  binary. This patch only goes half the way, though: the new shell harness is not
  used by "cabal test" yet. That will come as a separate patch.
3: Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.
4: Sat Aug 28 00:03:53 CEST 2010  Petr Rockai <me@mornfall.net>
  * Couple of improvements in the new shell test runner.
5: Sat Aug 28 00:04:14 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a --network option to darcs-test to run the network shell tests.
 
     ganesh@earth.li   #1 | module Main ( main ) where
     me@mornfall.net   #2 | import Test.Framework.Runners.Console ( defaultMain )
                          | import qualified Darcs.Test.Unit as Unit
                          | import Data.List ( isPrefixOf, isSuffixOf, sort )
                          | import qualified Data.ByteString.Char8 as B
                          | import System.Console.CmdLib hiding ( run )
                          | import qualified System.Console.CmdLib as CmdLib
                          | import System.FilePath( takeDirectory )
     me@mornfall.net   #3 | import Control.Concurrent.MVar
                          | import Control.Exception( finally )
     ganesh@earth.li   #1 | 
     me@mornfall.net   #2 | import Test.Framework.Providers.API
                          | import Test.Framework
                          | import Shellish hiding ( liftIO )
     me@mornfall.net   #3 | import qualified Control.Monad.Trans as Trans
     me@mornfall.net   #2 | 
                          | data Format = Hashed | Darcs2 | OldFashioned deriving Show
                          | data Running = Running deriving Show
                          | data Result = Success | Skipped | Failed String
                          | 
                          | instance Show Result where
                          |   show Success = "Success"
                          |   show Skipped = "Skipped"
                          |   show (Failed f) = unlines (map ("| " ++) $ lines f)
                          | 
                          | instance TestResultlike Running Result where
                          |   testSucceeded Success = True
                          |   testSucceeded Skipped = True
                          |   testSucceeded _ = False
                          | 
                          | data ShellTest = ShellTest { format :: Format
                          |                            , file :: FilePath
     me@mornfall.net   #3 |                            , darcspath :: FilePath
                          |                            , failedlist :: MVar [String] }
                          | 
                          | fmtstr Darcs2 = "darcs-2"
                          | fmtstr Hashed = "hashed"
                          | fmtstr OldFashioned = "old-fashioned-inventory"
     me@mornfall.net   #2 | 
     me@mornfall.net   #4 | runtest' :: ShellTest -> FilePath -> ShIO Result
     me@mornfall.net   #3 | runtest' (ShellTest fmt file dp ref) srcdir =
     me@mornfall.net   #2 |   do wd <- pwd
                          |      setenv "HOME" wd
                          |      setenv "TESTDATA" (srcdir </> "tests" </> "data")
                          |      setenv "TESTBIN" (srcdir </> "tests" </> "bin")
                          |      setenv "DARCS_TESTING_PREFS_DIR" $ wd </> ".darcs"
                          |      setenv "EMAIL" "tester"
                          |      setenv "DARCS_DONT_COLOR" "1"
                          |      setenv "DARCS_DONT_ESCAPE_ANYTHING" "1"
                          |      getenv "PATH" >>= setenv "PATH" . ((takeDirectory dp ++ ":") ++)
                          |      setenv "DARCS" dp
                          |      mkdir ".darcs"
                          |      writefile ".darcs/defaults" defaults
                          |      run "bash" [ "test" ]
                          |      return Success
                          |    `catch_sh` \e -> case e of
                          |       RunFailed _ 200 _ -> return Skipped
     me@mornfall.net   #3 |       RunFailed _ n _ -> do
                          |         Trans.liftIO $ modifyMVar_ ref $ \bad -> return $ (fmtstr fmt ++ ": " ++ file) : bad
                          |         Failed <$> B.unpack <$> lastOutput
                          |   where defaults = unlines ["ALL " ++ fmtstr fmt, "send no-edit-description", "ALL ignore-times"]
     me@mornfall.net   #2 | 
                          | runtest :: ShellTest -> ShIO Result
                          | runtest t = withTmpDir $ \dir -> do
                          |   cp "tests/lib" dir
                          |   cp ("tests" </> file t) (dir </> "test")
                          |   srcdir <- pwd
     me@mornfall.net   #4 |   silently $ sub $ cd dir >> runtest' t srcdir
     me@mornfall.net   #2 | 
                          | instance Testlike Running Result ShellTest where
                          |   testTypeName _ = "Shell"
     me@mornfall.net   #4 |   runTest topts test = runImprovingIO $ do yieldImprovement Running
                          |                                            liftIO (shellish $ runtest test)
     me@mornfall.net   #2 | 
     me@mornfall.net   #3 | shellTest :: FilePath -> Format -> String -> MVar [String] -> Test
                          | shellTest dp fmt file ref =
                          |   Test (fmtstr fmt ++ ": " ++ file) $ ShellTest fmt file dp ref
     me@mornfall.net   #2 | 
     me@mornfall.net   #3 | findShell :: FilePath -> Bool -> ShIO ([Test], MVar [String])
     me@mornfall.net   #2 | findShell dp failing =
                          |   do files <- sort <$> grep relevant <$> grep (".sh" `isSuffixOf`) <$> ls "tests"
     me@mornfall.net   #3 |      ref <- Trans.liftIO $ newMVar []
                          |      return ([ shellTest dp format file ref
                          |              | format <- [ Darcs2, Hashed ]
                          |              , file <- files ], ref)
     me@mornfall.net   #2 |   where relevant = (if failing then id else not) . ("failing-" `isPrefixOf`)
                          | 
     me@mornfall.net   #5 | findNetwork :: FilePath -> ShIO [Test]
                          | findNetwork dp = do files <- sort <$> grep (".sh" `isSuffixOf`) <$> ls "tests/network"
     me@mornfall.net   #3 |                     ref <- Trans.liftIO $ newMVar []
                          |                     return [ shellTest dp Darcs2 ("network" </> file) ref | file <- files ]
     me@mornfall.net   #5 | 
     me@mornfall.net   #2 | data Config = Config { failing :: Bool
                          |                      , shell :: Bool
     me@mornfall.net   #5 |                      , network :: Bool
     me@mornfall.net   #2 |                      , unit :: Bool
                          |                      , darcs :: String
                          |                      , tests :: [String]
                          |                      , threads :: Int }
                          |             deriving (Data, Typeable, Eq)
                          | 
                          | instance Attributes Config where
                          |   attributes _ = group "Options"
                          |     [ failing %> Help "Run the failing (shell) tests."
     me@mornfall.net   #5 |     , shell %> Help "Run the passing, non-network shell tests." %+ Default True
                          |     , network %> Help "Run the network shell tests."
     me@mornfall.net   #2 |     , unit %> Help "Run the unit tests." %+ Default True
                          |     , tests %> Help "Pattern to limit the tests to run." %+ short 't'
                          |     , threads %> Default (1 :: Int) %+ short 'j' ]
                          | 
                          | data DarcsTest = DarcsTest deriving Typeable
                          | instance Command DarcsTest (Record Config) where
                          |   run _ conf _ = do
                          |     let args = [ "-j", show $ threads conf ] ++ concat [ ["-t", x ] | x <- tests conf ]
     me@mornfall.net   #3 |     nullref <- newMVar []
                          |     (ftests, _) <- shellish $ if failing conf then findShell (darcs conf) True
                          |                                               else return ([], nullref)
                          |     (stests, sfail) <- shellish $ if shell conf then findShell (darcs conf) False
                          |                                                 else return ([], nullref)
     me@mornfall.net   #2 |     utests <- if unit conf then Unit.unit else return []
     me@mornfall.net   #5 |     ntests <- shellish $ if network conf then findNetwork (darcs conf) else return []
     me@mornfall.net   #3 |     defaultMainWithArgs (ftests ++ stests ++ utests ++ ntests) args `finally`
                          |      (readMVar sfail >>= \x -> case x of
                          |          [] -> return ()
                          |          bad -> putStr $ "The following Shell tests failed:\n" ++ unlines bad)
     me@mornfall.net   #2 | 
                          | main :: IO ()
                          | main = getArgs >>= execute DarcsTest
Attachments
msg12383 (view) Author: kowey Date: 2010-08-31.12:53:45
On Mon, Aug 30, 2010 at 08:43:30 +0000, Petr Ročkai wrote:
> I have also cloned HEAD as darcs-unstable@darcs.net:adventure (also available
> as http://darcs.net/adventure) where I imagine these patches would go. I'll set
> up a buildbot waterfall for it when people start pushing patches there.

Nice work.  But you moved too fast (I would have waited until the
adventure branch discussion made progress before actually creating
the branch, but no harm done).  Anyway Let's hold off on pushing patches
to this adventure branch until we've made more progress on the
discussion.  Consensus building is slow, patient and sometimes
frustrating work, but it's worth it in the end.

That said, just because consensus building is slow doesn't mean we can't
get some work done while we're trying to build consensus.  I don't see
any reason folks can't review review patches for efficiency while
the adventure branch thread converges...  trying my hand at a little bit
of high-level review (sorry, this really is a token effort):

> Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
>   * First stab at a hashed-storage 0.6 port.

I mostly skipped as it was a big one, and also because I didn't really
know how to review a replace-this-bit-hs-use-with-this-other-bit
patch.

> Wed Jul 14 19:52:08 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Wibble path building in Repository.Prefs.
> 
> Thu Jul 15 10:59:38 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Use more meaningful names for seal_up_patches' parameters.
> 
> Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Update haddock.
 
> Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Move the preferences system into IO where it belongs.
> 
> Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Make FileName an alias to Relative (from Hashed.Storage.Path).
> 
> Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Fix annotate that got broken due to path format change.
> 
> Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Replace FilePath with FileName in SelectChanges and ChooseTouching.
> 
> Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Make SubPath just another alias for Relative.

I only got up to here... and hmm, it took me a couple of hours
of review, so I don't know if I'm doing something wrong or just
being slow.

[snip remaining 52 patches :-/]

Hmm, so if this adventure branch thing is going to work, we're going to
need to learn how to review it.

Wibble path building in Repository.Prefs.
-----------------------------------------
Wibble acknowledged

Use more meaningful names for seal_up_patches' parameters.
----------------------------------------------------------
> -          seal_up_patches xxx yyy =
> +          seal_up_patches patches context =

Better

Update haddock.
---------------
Slightly more precise patch names please

>  -- | Sets scripts in or below the current directory executable. A script is any file that starts
> ---   with the bytes '#!'. This is used sometimes for --set-scripts-executable, but at other times
> ---   --set-scripts-executable is handled by the hunk patch case of applyFL.
> +--   with the bytes '#!'. This is used for --set-scripts-executable.

Thanks

First stab at a hashed-storage 0.6 port.
----------------------------------------
Seems to replace anchorPath (old stuff)

> -       return $ map (anchorPath "" . fst) $ list recorded
> +       return $ map (pathToString . fst) $ list recorded

I'm going to just have to guess anchorPath "" and pathToString
both from hashed-storage are equivalent

>  filesDirs :: Bool -> Bool -> Tree m -> [FilePath]
>  filesDirs False False _ = []
> -filesDirs False True  t = "." : [ anchorPath "." p | (p, SubTree _) <- list t ]
> +filesDirs False True  t = "." : [ pathToString p | (p, SubTree _) <- list t ]
> -filesDirs True  False t = [ anchorPath "." p | (p, File _) <- list t ]
> +filesDirs True  False t = [ pathToString p | (p, File _) <- list t ]
> -filesDirs True  True  t = "." : (map (anchorPath "." . fst) $ list t)
> +filesDirs True  True  t = "." : (map (pathToString . fst) $ list t)

What was the difference between anchorPath "." and anchorPath ""?
Seems to be none according to this block of code.

> -import Storage.Hashed( floatPath )
> +import Storage.Hashed.Path( unsafePathFromString )

And I guess I have to assume these do the same thing

> conflictor [
> hunk ./src/Darcs/Diff.hs 56
> -    where diff :: Gap w
> -               => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)
> -               -> IO (w (FL Prim))
> +    where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m)
> +               -> m (w (FL Prim))
> hunk ./src/Darcs/Diff.hs 56
> -    where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m)
> -               -> m (w (FL Prim))
> -          diff _ (Just (SubTree _)) (Just (SubTree _)) = return (emptyGap NilFL)
> -          diff p (Just (SubTree _)) Nothing =
> +    where
> +          -- sort into removes, changes, adds, with removes in reverse-path order
> +          -- and everything else in forward order
> +          organise :: (AnchoredPath, Diff m) -> (AnchoredPath, Diff m) -> Ordering
> +
> +          organise (p1, Changed _ _ ) (p2, Changed _ _) = compare p1 p2
> +          organise (p1, Added _)      (p2, Added _)   = compare p1 p2
> +          organise (p1, Removed _)    (p2, Removed _) = compare p2 p1
> +
> +          organise (p1, Removed _) _ = LT
> +          organise _ (p1, Removed _) = GT
> +
> +          organise (p1, Changed _ _) _ = LT
> +          organise _ (p1, Changed _ _) = GT
> +
> +          diff :: AnchoredPath -> Diff m -> m (w (FL Prim))
> +          diff _ (Changed (SubTree _) (SubTree _)) = return (emptyGap NilFL)
> +          diff p (Removed (SubTree _)) =
> hunk ./src/Darcs/Diff.hs 65
> -          organise (p1, Removed _) _ = LT
> -          organise _ (p1, Removed _) = GT
> +          organise (_, Removed _) _ = LT
> +          organise _ (_, Removed _) = GT
> hunk ./src/Darcs/Diff.hs 68
> -          organise (p1, Changed _ _) _ = LT
> -          organise _ (p1, Changed _ _) = GT
> +          organise (_, Changed _ _) _ = LT
> +          organise _ (_, Changed _ _) = GT
> ]
> :
> hunk ./src/Darcs/Diff.hs 57
> -               => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)
> +               => Relative -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)

Hmm, not sure how to react to a conflictor like this.

> +pathFromFileName :: FileName -> Relative
> +pathFromFileName x = y -- trace ("pathFromFileName: " ++ show x ++ " -> " ++ show y) y
> +  where y = unsafePathFromString $ fix $ fn2fp x
> +        fix p | "./" `isPrefixOf` p = drop 2 p
> +              | otherwise = p

I'm not going to worry about this  because it's going away in a future
patch

Skipped treeHasAnyCase = treeHas anyCase refactor

Move the preferences system into IO where it belongs.
-----------------------------------------------------
> +import System.IO.Unsafe( unsafePerformIO )

What was wrong with using ReadableDirectory and WriteableDirectory?

> hunk ./src/Darcs/Patch/Apply.lhs 145
>      apply (Move f f') = mRename f f'
>      apply (ChangePref p f t) =
>          do b <- mDoesDirectoryExist (fp2fn $ darcsdir++"/prefs")
> -           when b $ changePrefval p f t
> +           when b $ return $! unsafePerformIO (changePrefval p f t) -- fuck you.

No fucking profanity, please. I'm not so much worried about protecting
people's delicate eyes, as about keeping things
simple/minimal/professional.

Surely you have a more meaningful comment to make.

Make FileName an alias to Relative (from Hashed.Storage.Path).
--------------------------------------------------------------
> hunk ./src/Darcs/Patch/FileName.hs 41
> -newtype FileName = FN FilePath deriving ( Eq, Ord )
> +type FileName = Relative

How do we know that FileName and Relative behave the same ways where it
counts?  We want to be very very careful here. I realise the whole point
of this work is that we replace our braindead path representation with
something far saner, but we have to be super careful about backwards
compatibility.  No surprises.

Also how do we know that Storage.Hashed.Path has sane behaviour in the
first place?  It seems like Storage.Hashed.Path is a module that lends
itself fairly well to testing, some examples being:

 - path/unpath roundtrips
 - properties on isPrefix is reflexivity, antisymmetry, transitivity
 - crazy things with ..
 - maybe just ideas taken from the System.FilePath test suite

Does Storage.Hashed.Path.Absolute behave sanely on Windows (consider
paths starting with \\).  Yeah OK all this stuff is a pain in the ass
but we're going to have deal with it someday

So I'm picking on the path stuff for two reasons: first that we count
on it so much, and second that it seems to be fairly self-contained, so
it could be easy as a way to help us learn to test.  I think I can work
on this if I have some time, but I hope we can agree on the principle
that it's not safe to merge adventure until we at least how the path
stuff really behaves.

> -encodeWhite :: FilePath -> String
> -encodeWhite (c:cs) | isSpace c || c == '\\' =
> -    '\\' : (show $ ord c) ++ "\\" ++ encodeWhite cs
> -encodeWhite (c:cs) = c : encodeWhite cs
> -encodeWhite [] = []
> +encodeWhite :: B.ByteString -> B.ByteString
> +encodeWhite = BC.concatMap encode
> +  where encode c
> +          | isSpace c || c == '\\' = B.concat [ "\\", BC.pack $ show $ ord c, "\\" ]
> +          | otherwise = BC.singleton c

Looks like the FilePath -> String representation should have been
written this way.  This and decodeWhite are the sort of function where
we have haddocks that show examples of what this does for clarity.  Said
haddocks should also be tests, IMHO.

> -ownName :: FileName -> FileName
> -ownName (FN f) =  case breakLast '/' f of Nothing -> FN f
> -                                          Just (_,f') -> FN f'
> -superName :: FileName -> FileName
> -superName fn = case normPath fn of
> -                FN f -> case breakLast '/' f of
> -                        Nothing -> FN "."
> -                        Just (d,_) -> FN d
> -breakOnDir :: FileName -> Maybe (FileName,FileName)
> -breakOnDir (FN p) = case breakFirst '/' p of
> -                      Nothing -> Nothing
> -                      Just (d,f) | d == "." -> breakOnDir $ FN f
> -                                 | otherwise -> Just (FN d, FN f)

> -dropDotdot :: [String] -> [String]
> -dropDotdot ("":p) = dropDotdot p
> -dropDotdot (".":p) = dropDotdot p
> -dropDotdot ("..":p) = ".." : (dropDotdot p)
> -dropDotdot (_:"..":p) = dropDotdot p
> -dropDotdot (d:p) = case dropDotdot p of
> -                    ("..":p') -> p'
> -                    p' -> d : p'
> -dropDotdot [] = []

This is the kind of thing which I expect is easy for us get wrong.  How
does the hashed-storage version compare?

> hunk ./src/Darcs/Patch/FileName.hs 102
> -movedirfilename :: FileName -> FileName -> FileName -> FileName
> -movedirfilename old new name =
> -    if name' == old' then new
> -                     else if length name' > length old' &&
> -                             take (length old'+1) name' == old'++"/"
> -                          then fp2fn ("./"++new'++drop (length old') name')
> -                          else name
> -    where old' = fn2fp $ normPath old
> -          new' = fn2fp $ normPath new
> -          name' = fn2fp $ normPath name

> +movedirfilename :: FileName -> FileName -> FileName -> FileName
> +movedirfilename old new name
> +  | old == name = new
> +  | old `isPrefix` name = new +/+ (suffix old name)
> +  | otherwise = name

I can believe the new one is cleaner/safer but it really could stand to
be checked.

[skimmed the rest of this]

Fix annotate that got broken due to path format change.
-------------------------------------------------------
I didn't really understand what broke here, so I didn't really
look at this much.

Replace FilePath with FileName in SelectChanges and ChooseTouching.
-------------------------------------------------------------------
Making a point of high-level only reviewing this was useful.  I imagine
that the idea is that SelectChanges and ChooseTouching are really
repo-local operations.  When working on the adventure branch, I might
suggest targeting certain local changes like this for mainline.

The rest of this was just a cursory look.

> -isMaliciousPath :: String -> Bool
> -isMaliciousPath fp =
> -    splitDirectories fp `contains_any` [ "..", darcsdir ]
> - where
> -    contains_any a b = not . null $ intersect a b
> +isMaliciousPath :: FileName -> Bool
> +isMaliciousPath fp = not $ nodarcs fp
> + where nodarcs (directory -> dir :/: rest) = dir /= "_darcs" && nodarcs rest
> +       nodarcs _ = True

Again the sort of thing we should really be careful with.
(I dimly recall seeing another patch that fixes this later)

Also, why is this "not . nodarcs" when it could be just "hasDarcs"?

> hunk ./src/Darcs/External.hs 108
> -backupByCopying :: FilePath -> IO ()
> +backupByCopying :: FileName -> IO ()

This also looks like a good idea, but perhaps it's a separate patch.

> -applyToFilepaths :: Apply p => p C(x y) -> [FilePath] -> [FilePath]
> +applyToFilepaths :: Apply p => p C(x y) -> [FileName] -> [FileName]
>  applyToFilepaths pa fs = withFilePaths fs (apply pa)

> -fix :: FilePath -> FilePath
> -fix f | "/" `isSuffixOf` f = fix $ init f
> -fix "" = "."
> -fix "." = "."
> -fix f = "./" ++ f

Hooray?  This seems to be just tidying up trailing dots and slashes
and I'm glad to see it go


Make SubPath just another alias for Relative.
---------------------------------------------
Yes, I like the idea that FileName and SubPath get consolidated.

I don't mean to bang on the testing drum again, but the fact that
we're sweeping it all into one central pile means it should be
even easier to have some tests.

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg12412 (view) Author: kowey Date: 2010-09-02.12:25:45
On Mon, Aug 30, 2010 at 08:43:30 +0000, Petr Ročkai wrote:
> 61 patches for repository http://darcs.net:

Continuing to chip away at this bundle and trying to learn how to
review more efficiently.

> Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Update haddock.
> 
> Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
>   * First stab at a hashed-storage 0.6 port.
> 
> Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Move the preferences system into IO where it belongs.
> 
> Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Make FileName an alias to Relative (from Hashed.Storage.Path).
> 
> Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Fix annotate that got broken due to path format change.
> 
> Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Replace FilePath with FileName in SelectChanges and ChooseTouching.
> 
> Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Make SubPath just another alias for Relative.
> 
> Thu Aug 12 00:16:21 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Introduce a new Darcs.Path module to centralise path handling.

Covered in last review.

> Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Merge Darcs.Patch.FileName into Darcs.Path.
> 
> Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Remove the now-redundant sp2fn.
> 
> Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).
> 
> Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Restore the ".." check in isMaliciousPath.
> 
> Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Fix a subtle bug in onlyHunks with rather curious side-effects.

I stopped here.

> Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Merge Darcs.RepoPath into Darcs.Path.

More to go!

Merge Darcs.Patch.FileName into Darcs.Path.
-------------------------------------------
> -     then do has_target <- treeHasDir cur (fn2fp $ superName $ fp2fn new)
> +     then do has_target <- treeHasDir cur (fn2fp $ parent $ fp2fn new)

Getting some sort of notion that we a get little renames like this

> -                             result <- foldM removeOnePath (ftf,recorded,unrecorded, []) $
> -                                           map pathFromSubPath files
> +                             result <- foldM removeOnePath (ftf,recorded,unrecorded, []) files

And less need for conversions like this.
(Presumably because we're accepting more FileName and fewer FilePath)

> hunk ./src/Darcs/Patch/Named.lhs 42
> -import Darcs.Witnesses.Eq ( EqCheck(..) )
> -import Darcs.Witnesses.Ordered ( FL(..), RL(..), mapFL, concatFL
> -                               , mapFL_FL )
> -import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL), nFn )
> -#include "impossible.h"
> -
> -data Patch C(x y) where
> -    PP :: Prim C(x y) -> Patch C(x y)
> -    ComP :: FL Patch C(x y) -> Patch C(x y)
> -    Merger :: Patch C(x y)
> -           -> RL Patch C(x b)
> -           -> Patch C(c b)
> -           -> Patch C(c d)
> -           -> Patch C(x y)
> -    Regrem :: Patch C(x y)
> -           -> RL Patch C(x b)
> -           -> Patch C(c b)
> -           -> Patch C(c a)
> -           -> Patch C(y x)
> -
> -instance FromPrim Patch where
> -    fromPrim = PP
> +import Darcs.Witnesses.Ordered ( concatFL )
> +import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn )
> hunk ./src/Darcs/Patch/Named.lhs 42
> -import Darcs.Witnesses.Ordered ( concatFL )
> hunk ./src/Darcs/Patch/Named.lhs 40
> -import Darcs.Patch.Info ( PatchInfo, patchinfo, makeFilename )
> -import Darcs.Patch.Patchy ( Patchy )
> -import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn )
> +import Darcs.Patch.Info ( PatchInfo, patchinfo, makeFilename, invertName, idpatchinfo )
> +import Darcs.Patch.Patchy ( Patchy, Commute(..), Invert(..) )
> +import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn, Conflict(..) )
> +import Darcs.Witnesses.Eq ( MyEq(..) )
> +import Darcs.Witnesses.Ordered ( (:>)(..), (:\/:)(..), (:/\:)(..) )
> hunk ./src/Darcs/Patch/Named.lhs 41
> -import Darcs.Patch.Patchy ( Patchy, Commute(..), Invert(..) )
> +import Darcs.Patch.Patchy ( Patchy, Commute(..), Merge(..), PatchInspect(..), Invert(..) )
> ]
> :
> hunk ./src/Darcs/Patch/Named.lhs 45
> -import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL), nFn )
> +import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL) )

> hunk ./src/Darcs/Patch/FileName.hs 1

Module is nuked.  I'm assuming that the code moved in Darcs.Path is only
hunk-moved.

I'll just restate my reservations about the future stability of
Darcs.Path, that we'll need to make it sure that should Darcs.Path
change in the future our behaviour with respect to pre-existing patches
does not also change.  Our of the challenges in the Darcs hacking
context is that correctness for Darcs is partly defined by historical
precedent, ie.  "does not behave like it used to" can be considered a
bug. :-/ [I guess folks working on browser etc have similar problems,
cf. quirks mode, just with somewhat lower stakes]

> -pathFromSubPath :: SubPath -> Relative
> -pathFromSubPath x = y -- trace ("pathFromSubPath: " ++ show x ++ " -> " ++ show y) y

No longer needed because they are the same.

Remove the now-redundant sp2fn.
-------------------------------
Skipping this and just assuming that it's a natural consequence of
the new consolidated FileName == SubPath == Storage.Hashed.Relative

Fix announceFiles in WhatsNew (abolish unsafePathFrom*).
--------------------------------------------------------
> -      let paths = map toFilePath files
> -          check = virtualTreeIO (mapM exists $ map unsafePathFromString paths)
> +      let check = virtualTreeIO (mapM exists files)

Seems nice, but it's not clear to me what the fix actually is.

Restore the ".." check in isMaliciousPath.
------------------------------------------
> +isMaliciousPath = forbidden [ "_darcs", ".." ]
> + where forbidden bad (directory -> dir :/: rest) = dir `elem` bad || forbidden bad rest
> +       forbidden _ _ = False

This is one of those functions where you don't need to check old
behaviour, just the new one.

forbidden: Nice use of English for clarity.

Unless I misunderstand the (foo -> pattern) syntax, this is just
recursively walking the path elements and checking to see if any of the
elements are forbidden.  Why have explicit recursion when we can just
convert to a list and use any?

Fix a subtle bug in onlyHunks with rather curious side-effects.
---------------------------------------------------------------
>  onlyHunks :: [Sealed (FL Prim C(x))] -> Bool
>  onlyHunks [] = False
> -onlyHunks pss = fn2fp f /= "" && all oh pss
> +onlyHunks pss = fn2fp f /= "." && all oh pss
>      where f = getAFilename pss
>            oh :: Sealed (FL Prim C(x)) -> Bool
>            oh (Sealed (p:>:ps)) = primIsHunk p &&

So we have a problem with assumptions about the representation of "."
Perhaps we need to introduce some sort of "isRelativeRoot" function and
abolish explicit checking on "."/"" instead?

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg12421 (view) Author: mornfall Date: 2010-09-02.16:33:35
Hi,

I know we still haven't worked out the adventure process, but I have worked a
bit more on this. The news is that I managed to ditch a lot more obsolete code
without compromising functionality. Most code in Darcs.Repository.HashedIO is
gone, I have replaced (Readable/Writeable) Directory monad classes with a
simpler ApplyMonad which actually reflects what it is used for, FilePathMonad
is rewritten (it still does the same thing, it's just using State monad from
mtl instead of hand-rolled version). The last had the side-effect of making the
annotate monad a bit nicer.

The near-term plan is to add a restricted apply monad, that'll work on a list
of files (with contents, as opposed to FilePathMonad) so we can improve the
performance of darcs show contents (which is now officially slower than
annotate on some files).

The other near-term thing is directory annotate, since that is currently what
stands between me and passing tests.

Yours,
   Petr.

PS: I know I am owing some responses to the review that's in progress. I'll
look into that a bit later, either tonight or tomorrow, time permitting.

65 patches for repository http://darcs.net:

Wed Jul 14 19:52:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Wibble path building in Repository.Prefs.

Thu Jul 15 10:59:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use more meaningful names for seal_up_patches' parameters.

Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update haddock.

Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Thu Aug 12 00:16:21 CEST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Thu Aug 12 01:31:25 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Thu Aug 12 01:32:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Wed Aug 18 22:53:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Sun Aug 29 18:30:19 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve hashed-storage dependency conflicts.

Sun Aug 29 18:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Sun Aug 29 18:30:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Sun Aug 29 18:31:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Sun Aug 29 18:31:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Darcs.Patch.*.

Sun Aug 29 18:46:13 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve a (bogus?) conflict in darcs.cabal.

Sun Aug 29 18:51:11 CEST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Sun Aug 29 18:53:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Sun Aug 29 18:54:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 19:14:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Set a $format variable in lib, depending on current repo format under test.

Sun Aug 29 19:15:01 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests a bit less verbose (do not print all of lib every time).

Sun Aug 29 19:15:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 19:16:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix up the module list in darcs.cabal.

Sun Aug 29 19:16:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 19:43:58 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Sun Aug 29 19:44:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a tarball of a small oldfashioned repository for testing purposes.

Sun Aug 29 19:57:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 19:57:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 19:58:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 19:58:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Sun Aug 29 21:14:09 CEST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Sun Aug 29 21:14:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 21:15:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Sun Aug 29 21:17:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-defunct Distribution directory.

Mon Aug 30 01:09:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Mon Aug 30 01:16:51 CEST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Mon Aug 30 01:22:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Mon Aug 30 01:24:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Mon Aug 30 09:46:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Mon Aug 30 09:47:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Mon Aug 30 10:17:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Mon Aug 30 10:24:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Mon Aug 30 10:29:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

Thu Sep  2 13:20:06 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a redundant readRecorded in readRecordedAndPending.

Thu Sep  2 13:45:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug with following indirect renames in annotate.

Thu Sep  2 13:45:31 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace (Readable/Writeable)Directory with ApplyMonad.

Thu Sep  2 16:19:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Break away textDiff out of treeDiff.

Thu Sep  2 16:21:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use lib in tests/issue257.sh.

Thu Sep  2 16:23:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Re-implement create(Partials)PristineDirectoryTree in terms of readRecorded.

Thu Sep  2 16:25:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a pile of virtually unused HashedIO code.

Thu Sep  2 18:03:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid useless expansion of recorded in Commands.Add.

Thu Sep  2 18:19:52 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add missed mReadFilePS to Storage.Hashed.Monad implementation of ApplyMonad.

Thu Sep  2 18:20:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Do not try to replayRepository in optimize --upgrade (redundant, broken).

Thu Sep  2 18:20:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * (Nearly) make it possible to thread fetchFileUsingCache into Storage.Hashed.Darcs.

Thu Sep  2 18:27:12 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix withTentative (needs to run the copy from inside the repo).
Attachments
msg12424 (view) Author: mornfall Date: 2010-09-02.17:56:56
Hi,

second part of the reaction.

Eric Kow <kowey@darcs.net> writes:

>> Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Merge Darcs.Patch.FileName into Darcs.Path.
>> 
>> Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Remove the now-redundant sp2fn.
>> 
>> Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).
>> 
>> Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Restore the ".." check in isMaliciousPath.
>> 
>> Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Fix a subtle bug in onlyHunks with rather curious side-effects.
>
> I stopped here.
>
>> Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Merge Darcs.RepoPath into Darcs.Path.
>
> More to go!
And even more now...

> Merge Darcs.Patch.FileName into Darcs.Path.
> -------------------------------------------
>> -     then do has_target <- treeHasDir cur (fn2fp $ superName $ fp2fn new)
>> +     then do has_target <- treeHasDir cur (fn2fp $ parent $ fp2fn new)
>
> Getting some sort of notion that we a get little renames like this
>
>> -                             result <- foldM removeOnePath (ftf,recorded,unrecorded, []) $
>> -                                           map pathFromSubPath files
>> +                             result <- foldM removeOnePath (ftf,recorded,unrecorded, []) files
>
> And less need for conversions like this.
> (Presumably because we're accepting more FileName and fewer FilePath)

At this point I think we work with FileName (Relative) most of the
time. Although actual filesystem access is still using FilePath. That
will come in later.

>> hunk ./src/Darcs/Patch/Named.lhs 42
>> -import Darcs.Witnesses.Eq ( EqCheck(..) )
>> -import Darcs.Witnesses.Ordered ( FL(..), RL(..), mapFL, concatFL
>> -                               , mapFL_FL )
>> -import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL), nFn )
>> -#include "impossible.h"
>> -
>> -data Patch C(x y) where
>> -    PP :: Prim C(x y) -> Patch C(x y)
>> -    ComP :: FL Patch C(x y) -> Patch C(x y)
>> -    Merger :: Patch C(x y)
>> -           -> RL Patch C(x b)
>> -           -> Patch C(c b)
>> -           -> Patch C(c d)
>> -           -> Patch C(x y)
>> -    Regrem :: Patch C(x y)
>> -           -> RL Patch C(x b)
>> -           -> Patch C(c b)
>> -           -> Patch C(c a)
>> -           -> Patch C(y x)
>> -
>> -instance FromPrim Patch where
>> -    fromPrim = PP
>> +import Darcs.Witnesses.Ordered ( concatFL )
>> +import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn )
>> hunk ./src/Darcs/Patch/Named.lhs 42
>> -import Darcs.Witnesses.Ordered ( concatFL )
>> hunk ./src/Darcs/Patch/Named.lhs 40
>> -import Darcs.Patch.Info ( PatchInfo, patchinfo, makeFilename )
>> -import Darcs.Patch.Patchy ( Patchy )
>> -import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn )
>> +import Darcs.Patch.Info ( PatchInfo, patchinfo, makeFilename, invertName, idpatchinfo )
>> +import Darcs.Patch.Patchy ( Patchy, Commute(..), Invert(..) )
>> +import Darcs.Patch.Prim ( Effect(effect, effectRL), nFn, Conflict(..) )
>> +import Darcs.Witnesses.Eq ( MyEq(..) )
>> +import Darcs.Witnesses.Ordered ( (:>)(..), (:\/:)(..), (:/\:)(..) )
>> hunk ./src/Darcs/Patch/Named.lhs 41
>> -import Darcs.Patch.Patchy ( Patchy, Commute(..), Invert(..) )
>> +import Darcs.Patch.Patchy ( Patchy, Commute(..), Merge(..), PatchInspect(..), Invert(..) )
>> ]
>> :
>> hunk ./src/Darcs/Patch/Named.lhs 45
>> -import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL), nFn )
>> +import Darcs.Patch.Prim ( Prim(..), FromPrim(..), Effect(effect, effectRL) )
>
>> hunk ./src/Darcs/Patch/FileName.hs 1
>
> Module is nuked.  I'm assuming that the code moved in Darcs.Path is only
> hunk-moved.
Yes, should be the case.

> I'll just restate my reservations about the future stability of
> Darcs.Path, that we'll need to make it sure that should Darcs.Path
> change in the future our behaviour with respect to pre-existing patches
> does not also change.  Our of the challenges in the Darcs hacking
> context is that correctness for Darcs is partly defined by historical
> precedent, ie.  "does not behave like it used to" can be considered a
> bug. :-/ [I guess folks working on browser etc have similar problems,
> cf. quirks mode, just with somewhat lower stakes]

I keep that in mind, don't worry. Fortunately, darcs is not writing out
particularly stupid filenames into patches, so it should not really
matter much. If the path code breaks on paths as canonic as those in
darcs patches, we will see that right away.

> Remove the now-redundant sp2fn.
> -------------------------------
> Skipping this and just assuming that it's a natural consequence of
> the new consolidated FileName == SubPath == Storage.Hashed.Relative
Indeed.

> Fix announceFiles in WhatsNew (abolish unsafePathFrom*).
> --------------------------------------------------------
>> -      let paths = map toFilePath files
>> -          check = virtualTreeIO (mapM exists $ map unsafePathFromString paths)
>> +      let check = virtualTreeIO (mapM exists files)
>
> Seems nice, but it's not clear to me what the fix actually is.

Because toFilePath was producing a non-canonic path, which then broke
the Path invariants (which is what is unsafe about unsafePathFromString
-- it allows you to build an invariant-breaking path). The type of
"files" and argument type of exists is now the same, so this was a
redundant roundtrip, too.

> Restore the ".." check in isMaliciousPath.
> ------------------------------------------
>> +isMaliciousPath = forbidden [ "_darcs", ".." ]
>> + where forbidden bad (directory -> dir :/: rest) = dir `elem` bad || forbidden bad rest
>> +       forbidden _ _ = False
>
> This is one of those functions where you don't need to check old
> behaviour, just the new one.
>
> forbidden: Nice use of English for clarity.
>
> Unless I misunderstand the (foo -> pattern) syntax, this is just
> recursively walking the path elements and checking to see if any of the
> elements are forbidden.  Why have explicit recursion when we can just
> convert to a list and use any?

For now, I am not allowing a Path to be converted to a list. It will
need a bit of thought whether this is desirable and whether it could
open a loophole in the API.

> Fix a subtle bug in onlyHunks with rather curious side-effects.
> ---------------------------------------------------------------
>>  onlyHunks :: [Sealed (FL Prim C(x))] -> Bool
>>  onlyHunks [] = False
>> -onlyHunks pss = fn2fp f /= "" && all oh pss
>> +onlyHunks pss = fn2fp f /= "." && all oh pss
>>      where f = getAFilename pss
>>            oh :: Sealed (FL Prim C(x)) -> Bool
>>            oh (Sealed (p:>:ps)) = primIsHunk p &&
>
> So we have a problem with assumptions about the representation of "."
> Perhaps we need to introduce some sort of "isRelativeRoot" function and
> abolish explicit checking on "."/"" instead?

We actually have isRoot which we should probably use here. Any use of
fn2fp is unsafe when it comes to path representation (as opposed to
actually looking up files in the filesystem).

Yours,
   Petr.
msg12425 (view) Author: mornfall Date: 2010-09-02.17:57:48
Hi,

the promised review reaction...

Eric Kow <kowey@darcs.net> writes:

> Nice work.  But you moved too fast (I would have waited until the
> adventure branch discussion made progress before actually creating
> the branch, but no harm done).  Anyway Let's hold off on pushing patches
> to this adventure branch until we've made more progress on the
> discussion.  Consensus building is slow, patient and sometimes
> frustrating work, but it's worth it in the end.
I hope you are right. :)

> That said, just because consensus building is slow doesn't mean we can't
> get some work done while we're trying to build consensus.  I don't see
> any reason folks can't review review patches for efficiency while
> the adventure branch thread converges...  trying my hand at a little bit
> of high-level review (sorry, this really is a token effort):
>
>> Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * First stab at a hashed-storage 0.6 port.
>
> I mostly skipped as it was a big one, and also because I didn't really
> know how to review a replace-this-bit-hs-use-with-this-other-bit
> patch.

Unless you spotted something really hideous, I guess you could take my
word on it. (I have hopefully fixed all the actual hideous bits in later
patches.)

>> Wed Jul 14 19:52:08 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Wibble path building in Repository.Prefs.
>> 
>> Thu Jul 15 10:59:38 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Use more meaningful names for seal_up_patches' parameters.
>> 
>> Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Update haddock.

I think you could maybe cherry-pick those for mainline, so they would
disappear from the radar and shrink future resends of this bundle.

>> Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Move the preferences system into IO where it belongs.
More about this below.

>> Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Make FileName an alias to Relative (from Hashed.Storage.Path).
>> 
>> Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Fix annotate that got broken due to path format change.
>> 
>> Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Replace FilePath with FileName in SelectChanges and ChooseTouching.
>> 
>> Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
>>   * Make SubPath just another alias for Relative.
>
> I only got up to here... and hmm, it took me a couple of hours
> of review, so I don't know if I'm doing something wrong or just
> being slow.
>

> Update haddock.
> ---------------
> Slightly more precise patch names please
Next time. :)

> First stab at a hashed-storage 0.6 port.
> ----------------------------------------
> Seems to replace anchorPath (old stuff)
>
>> -       return $ map (anchorPath "" . fst) $ list recorded
>> +       return $ map (pathToString . fst) $ list recorded
>
> I'm going to just have to guess anchorPath "" and pathToString
> both from hashed-storage are equivalent
Yes, anchorPath "" is same as anchorPath "." which is same as
pathToString.

>>  filesDirs :: Bool -> Bool -> Tree m -> [FilePath]
>>  filesDirs False False _ = []
>> -filesDirs False True  t = "." : [ anchorPath "." p | (p, SubTree _) <- list t ]
>> +filesDirs False True  t = "." : [ pathToString p | (p, SubTree _) <- list t ]
>> -filesDirs True  False t = [ anchorPath "." p | (p, File _) <- list t ]
>> +filesDirs True  False t = [ pathToString p | (p, File _) <- list t ]
>> -filesDirs True  True  t = "." : (map (anchorPath "." . fst) $ list t)
>> +filesDirs True  True  t = "." : (map (pathToString . fst) $ list t)
>
> What was the difference between anchorPath "." and anchorPath ""?
> Seems to be none according to this block of code.
Indeed. See above.

>> -import Storage.Hashed( floatPath )
>> +import Storage.Hashed.Path( unsafePathFromString )
>
> And I guess I have to assume these do the same thing

They don't and that was a bug that I fixed up somewhere later. The more
reasonable counterpart to floatPath is parsePath. It is not equivalent
either, but parsePath is supposed to handle all kinds of mess (like
foo/../bar, foo/./bar etc.).

>> conflictor [
>> hunk ./src/Darcs/Diff.hs 56
>> -    where diff :: Gap w
>> -               => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)
>> -               -> IO (w (FL Prim))
>> +    where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m)
>> +               -> m (w (FL Prim))
>> hunk ./src/Darcs/Diff.hs 56
>> -    where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m)
>> -               -> m (w (FL Prim))
>> -          diff _ (Just (SubTree _)) (Just (SubTree _)) = return (emptyGap NilFL)
>> -          diff p (Just (SubTree _)) Nothing =
>> +    where
>> +          -- sort into removes, changes, adds, with removes in reverse-path order
>> +          -- and everything else in forward order
>> +          organise :: (AnchoredPath, Diff m) -> (AnchoredPath, Diff m) -> Ordering
>> +
>> +          organise (p1, Changed _ _ ) (p2, Changed _ _) = compare p1 p2
>> +          organise (p1, Added _)      (p2, Added _)   = compare p1 p2
>> +          organise (p1, Removed _)    (p2, Removed _) = compare p2 p1
>> +
>> +          organise (p1, Removed _) _ = LT
>> +          organise _ (p1, Removed _) = GT
>> +
>> +          organise (p1, Changed _ _) _ = LT
>> +          organise _ (p1, Changed _ _) = GT
>> +
>> +          diff :: AnchoredPath -> Diff m -> m (w (FL Prim))
>> +          diff _ (Changed (SubTree _) (SubTree _)) = return (emptyGap NilFL)
>> +          diff p (Removed (SubTree _)) =
>> hunk ./src/Darcs/Diff.hs 65
>> -          organise (p1, Removed _) _ = LT
>> -          organise _ (p1, Removed _) = GT
>> +          organise (_, Removed _) _ = LT
>> +          organise _ (_, Removed _) = GT
>> hunk ./src/Darcs/Diff.hs 68
>> -          organise (p1, Changed _ _) _ = LT
>> -          organise _ (p1, Changed _ _) = GT
>> +          organise (_, Changed _ _) _ = LT
>> +          organise _ (_, Changed _ _) = GT
>> ]
>> :
>> hunk ./src/Darcs/Diff.hs 57
>> -               => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)
>> +               => Relative -> Maybe (TreeItem IO) -> Maybe (TreeItem IO)
>
> Hmm, not sure how to react to a conflictor like this.

Me neither. The actual change on my end was to just replace AnchoredPath
with Relative on the piece of code. In retrospect, darcs replace could
have worked better. (We could really use some smarter diff that would
notice these kinds of thing... or something.)

>> +pathFromFileName :: FileName -> Relative
>> +pathFromFileName x = y -- trace ("pathFromFileName: " ++ show x ++ " -> " ++ show y) y
>> +  where y = unsafePathFromString $ fix $ fn2fp x
>> +        fix p | "./" `isPrefixOf` p = drop 2 p
>> +              | otherwise = p
>
> I'm not going to worry about this  because it's going away in a future
> patch
Indeed.

> Move the preferences system into IO where it belongs.
> -----------------------------------------------------
>> +import System.IO.Unsafe( unsafePerformIO )
>
> What was wrong with using ReadableDirectory and WriteableDirectory?

It was a rampant API abuse. The problem is that the changepref patch
does not apply to things in the repository. The FooDirectory abstraction
is broken 

>> hunk ./src/Darcs/Patch/Apply.lhs 145
>>      apply (Move f f') = mRename f f'
>>      apply (ChangePref p f t) =
>>          do b <- mDoesDirectoryExist (fp2fn $ darcsdir++"/prefs")
>> -           when b $ changePrefval p f t
>> +           when b $ return $! unsafePerformIO (changePrefval p f t) -- fuck you.
>
> No fucking profanity, please. I'm not so much worried about protecting
> people's delicate eyes, as about keeping things
> simple/minimal/professional.

Sorry. I'll fix that. I was a bit frustrated with the whole changepref
mess.

> Surely you have a more meaningful comment to make.
Well, not really. The changepref patch implementation does not make any
sense. We really need to gut it and go about it differently. The idea is
to just make apply (ChangePref ...) a noop and handle this like we
handle setScriptsExecutable nowadays, externally. It's going to slow
things down slightly, but it will also further un-mess the patch
application code.

> Make FileName an alias to Relative (from Hashed.Storage.Path).
> --------------------------------------------------------------
>> hunk ./src/Darcs/Patch/FileName.hs 41
>> -newtype FileName = FN FilePath deriving ( Eq, Ord )
>> +type FileName = Relative
>
> How do we know that FileName and Relative behave the same ways where it
> counts?  We want to be very very careful here. I realise the whole point
> of this work is that we replace our braindead path representation with
> something far saner, but we have to be super careful about backwards
> compatibility.  No surprises.

> Also how do we know that Storage.Hashed.Path has sane behaviour in the
> first place?  It seems like Storage.Hashed.Path is a module that lends
> itself fairly well to testing, some examples being:
>
>  - path/unpath roundtrips
>  - properties on isPrefix is reflexivity, antisymmetry, transitivity
>  - crazy things with ..
>  - maybe just ideas taken from the System.FilePath test suite
>
> Does Storage.Hashed.Path.Absolute behave sanely on Windows (consider
> paths starting with \\).  Yeah OK all this stuff is a pain in the ass
> but we're going to have deal with it someday
Not yet -- the path code as it is now is a prototype and there is no
win32 trapping. I will add that a bit later, as well as a testsuite. I
have also seriously considered splitting the path code away into a
separate library. Hopefully it won't be interpreted as me picking on
Neil...

> So I'm picking on the path stuff for two reasons: first that we count
> on it so much, and second that it seems to be fairly self-contained, so
> it could be easy as a way to help us learn to test.  I think I can work
> on this if I have some time, but I hope we can agree on the principle
> that it's not safe to merge adventure until we at least how the path
> stuff really behaves.
That would be great. The Path module in h-s is closed enough that you
can pick it out and write tests as you have time. I'll get to that at
some point too, so hopefully in the end we are fairly well-covered.

>> -encodeWhite :: FilePath -> String
>> -encodeWhite (c:cs) | isSpace c || c == '\\' =
>> -    '\\' : (show $ ord c) ++ "\\" ++ encodeWhite cs
>> -encodeWhite (c:cs) = c : encodeWhite cs
>> -encodeWhite [] = []
>> +encodeWhite :: B.ByteString -> B.ByteString
>> +encodeWhite = BC.concatMap encode
>> +  where encode c
>> +          | isSpace c || c == '\\' = B.concat [ "\\", BC.pack $ show $ ord c, "\\" ]
>> +          | otherwise = BC.singleton c
>
> Looks like the FilePath -> String representation should have been
> written this way.  This and decodeWhite are the sort of function where
> we have haddocks that show examples of what this does for clarity.  Said
> haddocks should also be tests, IMHO.

>> -ownName :: FileName -> FileName
>> -ownName (FN f) =  case breakLast '/' f of Nothing -> FN f
>> -                                          Just (_,f') -> FN f'
>> -superName :: FileName -> FileName
>> -superName fn = case normPath fn of
>> -                FN f -> case breakLast '/' f of
>> -                        Nothing -> FN "."
>> -                        Just (d,_) -> FN d
>> -breakOnDir :: FileName -> Maybe (FileName,FileName)
>> -breakOnDir (FN p) = case breakFirst '/' p of
>> -                      Nothing -> Nothing
>> -                      Just (d,f) | d == "." -> breakOnDir $ FN f
>> -                                 | otherwise -> Just (FN d, FN f)
>
>> -dropDotdot :: [String] -> [String]
>> -dropDotdot ("":p) = dropDotdot p
>> -dropDotdot (".":p) = dropDotdot p
>> -dropDotdot ("..":p) = ".." : (dropDotdot p)
>> -dropDotdot (_:"..":p) = dropDotdot p
>> -dropDotdot (d:p) = case dropDotdot p of
>> -                    ("..":p') -> p'
>> -                    p' -> d : p'
>> -dropDotdot [] = []
>
> This is the kind of thing which I expect is easy for us get wrong.  How
> does the hashed-storage version compare?

(</>) :: forall p. (Show p, Path p) => p -> Name -> p
(unpath -> p) </> n
  | n == BS.pack "." = path p
  | n == BS.pack ".." = parent (path p :: p)
(...)

(We disallow non-leading .. and all . components as an invariant on the
Path types.)

>> hunk ./src/Darcs/Patch/FileName.hs 102
>> -movedirfilename :: FileName -> FileName -> FileName -> FileName
>> -movedirfilename old new name =
>> -    if name' == old' then new
>> -                     else if length name' > length old' &&
>> -                             take (length old'+1) name' == old'++"/"
>> -                          then fp2fn ("./"++new'++drop (length old') name')
>> -                          else name
>> -    where old' = fn2fp $ normPath old
>> -          new' = fn2fp $ normPath new
>> -          name' = fn2fp $ normPath name
>
>> +movedirfilename :: FileName -> FileName -> FileName -> FileName
>> +movedirfilename old new name
>> +  | old == name = new
>> +  | old `isPrefix` name = new +/+ (suffix old name)
>> +  | otherwise = name
>
> I can believe the new one is cleaner/safer but it really could stand to
> be checked.
Well, it took a while to figure. If it comforts you any, a buggy version
made the shell tests explode quite colourfully.

> Fix annotate that got broken due to path format change.
> -------------------------------------------------------
> I didn't really understand what broke here, so I didn't really
> look at this much.

Obsoleted by new annotate anyway. I just wanted to keep a working
midpoint here.

>
> Replace FilePath with FileName in SelectChanges and ChooseTouching.
> -------------------------------------------------------------------
> Making a point of high-level only reviewing this was useful.  I imagine
> that the idea is that SelectChanges and ChooseTouching are really
> repo-local operations.  When working on the adventure branch, I might
> suggest targeting certain local changes like this for mainline.
>
> The rest of this was just a cursory look.
>
>> -isMaliciousPath :: String -> Bool
>> -isMaliciousPath fp =
>> -    splitDirectories fp `contains_any` [ "..", darcsdir ]
>> - where
>> -    contains_any a b = not . null $ intersect a b
>> +isMaliciousPath :: FileName -> Bool
>> +isMaliciousPath fp = not $ nodarcs fp
>> + where nodarcs (directory -> dir :/: rest) = dir /= "_darcs" && nodarcs rest
>> +       nodarcs _ = True
>
> Again the sort of thing we should really be careful with.
> (I dimly recall seeing another patch that fixes this later)
>
> Also, why is this "not . nodarcs" when it could be just "hasDarcs"?
Redone in a later patch.

>
>> hunk ./src/Darcs/External.hs 108
>> -backupByCopying :: FilePath -> IO ()
>> +backupByCopying :: FileName -> IO ()
>
> This also looks like a good idea, but perhaps it's a separate patch.
>
>> -applyToFilepaths :: Apply p => p C(x y) -> [FilePath] -> [FilePath]
>> +applyToFilepaths :: Apply p => p C(x y) -> [FileName] -> [FileName]
>>  applyToFilepaths pa fs = withFilePaths fs (apply pa)
>
>> -fix :: FilePath -> FilePath
>> -fix f | "/" `isSuffixOf` f = fix $ init f
>> -fix "" = "."
>> -fix "." = "."
>> -fix f = "./" ++ f
>
> Hooray?  This seems to be just tidying up trailing dots and slashes
> and I'm glad to see it go

Again, invariants on the new Path types prevent such things from
existing.

> Make SubPath just another alias for Relative.
> ---------------------------------------------
> Yes, I like the idea that FileName and SubPath get consolidated.
>
> I don't mean to bang on the testing drum again, but the fact that
> we're sweeping it all into one central pile means it should be
> even easier to have some tests.

Yours,
   Petr.
msg12431 (view) Author: mornfall Date: 2010-09-03.02:53:14
Hi once again...

The news since the last update:

1) directory annotate works now
2) -p/-m works with file & directory annotate
3) darcs show contents -m is a lot faster for deeper changes (~3x on ~300
   patches deep match, with src/test.hs in darcs repo)
4) the unsafePerformIO for ChangePref is gone (changeprefs are now applied
   separately)
5) the tests pass, although I had to remove one --xml

For point 5, I don't think we should really retain annotate --xml. My guess is
that a simple regular language would be much better for both us and darcs-using
tools. At least Lele (tracdarcs) agrees. The proposed format (to be
implemented) is

<patch-hash> | line of text
<patch-hash> | another line
...

which is much easier to parse than the XML and also avoids the validity issues
(since we currently don't have code that'd enable us to generate actual valid
XML).

As for point 3, this is what darcs-benchmark says (I guess the 50 and 500 are a
bit overshot, but I'll fix that later):

=================  ================  ========  ===============  =======
                   HEAD / darcs2-op      sdev  ADV / darcs2-op     sdev
=================  ================  ========  ===============  =======
 show contents 50         ?7399.3ms  (48.9ms)        ~1751.5ms  (6.5ms)
show contents 500         ?7369.9ms  (33.0ms)        ~1740.7ms  (5.4ms)
=================  ================  ========  ===============  =======

Latest hashed-storage is required, as usual.

I think the last time I forgot to mention that I have improved darcs add,
although it's still not as fast as it should and it's not completely clear how
to achieve that.

=======  ================  =======  ===============  =======
         HEAD / darcs2-op     sdev  ADV / darcs2-op     sdev
=======  ================  =======  ===============  =======
add 100           471.5ms  (3.6ms)          123.4ms  (2.2ms)
=======  ================  =======  ===============  =======

For 4, even though this is a lot less efficient (another pass through the
patches is required), things aren't looking too bad either (the improvement is
from other changes on ADV/h-s 0.6)...

========  ================  ========  ===============  =======
          HEAD / darcs2-op      sdev  ADV / darcs2-op     sdev
========  ================  ========  ===============  =======
pull 100           456.8ms  (22.9ms)          403.0ms  (8.2ms)
========  ================  ========  ===============  =======

Finally, as for 1, I had to make the annotate code a bit more generic, but it
still seems to be give very reasonable efficiency compared to HEAD.

========  ================  ========  ===============  =======
          HEAD / darcs2-op      sdev  ADV / darcs2-op     sdev
========  ================  ========  ===============  =======
annotate        ?15645.7ms  (43.8ms)        ~1681.1ms  (7.8ms)
========  ================  ========  ===============  =======

Yours,
   Petr.

PS: All benchmarks are on the darcs darcs repo, from the standard suite (in
darcs-benchmark HEAD).

77 patches for repository http://darcs.net:

Wed Jul 14 19:52:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Wibble path building in Repository.Prefs.

Thu Jul 15 10:59:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use more meaningful names for seal_up_patches' parameters.

Sat Jul 17 10:40:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update haddock.

Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Thu Aug 12 00:16:21 CEST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Thu Aug 12 01:31:25 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Thu Aug 12 01:32:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Wed Aug 18 22:53:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Sun Aug 29 18:30:19 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve hashed-storage dependency conflicts.

Sun Aug 29 18:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Sun Aug 29 18:30:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Sun Aug 29 18:31:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Sun Aug 29 18:31:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Darcs.Patch.*.

Sun Aug 29 18:46:13 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve a (bogus?) conflict in darcs.cabal.

Sun Aug 29 18:51:11 CEST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Sun Aug 29 18:53:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Sun Aug 29 18:54:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 19:14:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Set a $format variable in lib, depending on current repo format under test.

Sun Aug 29 19:15:01 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests a bit less verbose (do not print all of lib every time).

Sun Aug 29 19:15:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 19:16:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix up the module list in darcs.cabal.

Sun Aug 29 19:16:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 19:43:58 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Sun Aug 29 19:44:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a tarball of a small oldfashioned repository for testing purposes.

Sun Aug 29 19:57:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 19:57:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 19:58:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 19:58:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Sun Aug 29 21:14:09 CEST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Sun Aug 29 21:14:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 21:15:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Sun Aug 29 21:17:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-defunct Distribution directory.

Mon Aug 30 01:09:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Mon Aug 30 01:16:51 CEST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Mon Aug 30 01:22:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Mon Aug 30 01:24:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Mon Aug 30 09:46:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Mon Aug 30 09:47:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Mon Aug 30 10:17:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Mon Aug 30 10:24:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Mon Aug 30 10:29:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

Thu Sep  2 13:20:06 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a redundant readRecorded in readRecordedAndPending.

Thu Sep  2 13:45:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug with following indirect renames in annotate.

Thu Sep  2 13:45:31 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace (Readable/Writeable)Directory with ApplyMonad.

Thu Sep  2 16:19:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Break away textDiff out of treeDiff.

Thu Sep  2 16:21:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use lib in tests/issue257.sh.

Thu Sep  2 16:23:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Re-implement create(Partials)PristineDirectoryTree in terms of readRecorded.

Thu Sep  2 16:25:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a pile of virtually unused HashedIO code.

Thu Sep  2 18:03:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid useless expansion of recorded in Commands.Add.

Thu Sep  2 18:19:52 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add missed mReadFilePS to Storage.Hashed.Monad implementation of ApplyMonad.

Thu Sep  2 18:20:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Do not try to replayRepository in optimize --upgrade (redundant, broken).

Thu Sep  2 18:20:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * (Nearly) make it possible to thread fetchFileUsingCache into Storage.Hashed.Darcs.

Thu Sep  2 18:27:12 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix withTentative (needs to run the copy from inside the repo).

Thu Sep  2 23:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the useless MonadPlus AnnotatedM instance.

Fri Sep  3 01:24:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement directory annotate.

Fri Sep  3 01:56:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a forgotten trace.

Fri Sep  3 02:11:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update annotate.sh (no --xml).

Fri Sep  3 02:12:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update changes_with_move for differences in annotate.

Fri Sep  3 02:13:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant set -ev from tentative_revert.sh.

Fri Sep  3 02:13:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix create(Partials)Pristine... with relative paths.

Fri Sep  3 02:35:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a RestrictedApply monad, and withFiles as its entrypoint.

Fri Sep  3 02:36:03 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs show contents --match.

Fri Sep  3 02:56:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Give up some progress feedback to generalise the type of getNonrangeMatchS.

Fri Sep  3 02:57:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement darcs annotate -p/-m for files & directories.

Fri Sep  3 04:07:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Apply ChangePref patches ex-post, restoring purity of apply.
Attachments
msg12435 (view) Author: mornfall Date: 2010-09-03.08:57:41
Petr Ročkai <bugs@darcs.net> writes:

> ========  ================  ========  ===============  =======
>           HEAD / darcs2-op      sdev  ADV / darcs2-op     sdev
> ========  ================  ========  ===============  =======
> pull 100           456.8ms  (22.9ms)          403.0ms  (8.2ms)
> ========  ================  ========  ===============  =======

Huh, I wish I knew how these numbers came to be. I am consistently
getting ~1s now on the same repo, with the same HEAD binary (different
ADV binary) and same darcs-benchmark command.

I have checked the above exists in my scrollback, so apparently I wasn't
hallucinating last night.

Yours,
   Petr.
msg12461 (view) Author: mornfall Date: 2010-09-04.15:17:26
I have re-done the ChangePref patch since the last time, should be sane
now. Other than that, there aren't many new patches here, but I have worked a
lot on Storage.Hashed.Path. Please look in the h-s HEAD repo. There's a number
of QC properties now. Eric, if you had a bit of time for this, you could maybe
look at that part?

I have also flipped over darcs's absolute path handling to S.H.Path. The tests
still pass.

Anyway, I have started to work on a Repository typeclass. More news on that
later.

Yours,
   Petr.

79 patches for repository http://darcs.net:

Wed Aug 11 17:39:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 21:45:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 00:02:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Thu Aug 12 00:09:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Thu Aug 12 00:16:21 CEST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Thu Aug 12 00:36:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Thu Aug 12 00:47:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Thu Aug 12 01:05:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Thu Aug 12 01:06:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Thu Aug 12 01:31:25 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Thu Aug 12 01:32:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Wed Aug 18 22:53:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Sun Aug 29 18:30:19 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve hashed-storage dependency conflicts.

Sun Aug 29 18:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Sun Aug 29 18:30:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Sun Aug 29 18:31:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Sun Aug 29 18:31:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Darcs.Patch.*.

Sun Aug 29 18:46:13 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve a (bogus?) conflict in darcs.cabal.

Sun Aug 29 18:51:11 CEST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Sun Aug 29 18:53:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Sun Aug 29 18:54:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 19:14:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Set a $format variable in lib, depending on current repo format under test.

Sun Aug 29 19:15:01 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests a bit less verbose (do not print all of lib every time).

Sun Aug 29 19:15:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 19:16:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix up the module list in darcs.cabal.

Sun Aug 29 19:16:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 19:43:58 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Sun Aug 29 19:57:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 19:57:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 19:58:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 19:58:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Sun Aug 29 21:14:09 CEST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Sun Aug 29 21:14:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 21:15:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Mon Aug 30 01:09:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Mon Aug 30 01:16:51 CEST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Mon Aug 30 01:22:17 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Mon Aug 30 01:24:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Mon Aug 30 09:46:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Mon Aug 30 09:47:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Mon Aug 30 10:17:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Mon Aug 30 10:24:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Mon Aug 30 10:29:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

Thu Sep  2 13:20:06 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a redundant readRecorded in readRecordedAndPending.

Thu Sep  2 13:45:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug with following indirect renames in annotate.

Thu Sep  2 13:45:31 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace (Readable/Writeable)Directory with ApplyMonad.

Thu Sep  2 16:19:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Break away textDiff out of treeDiff.

Thu Sep  2 16:23:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Re-implement create(Partials)PristineDirectoryTree in terms of readRecorded.

Thu Sep  2 16:25:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a pile of virtually unused HashedIO code.

Thu Sep  2 18:03:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid useless expansion of recorded in Commands.Add.

Thu Sep  2 18:19:52 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add missed mReadFilePS to Storage.Hashed.Monad implementation of ApplyMonad.

Thu Sep  2 18:20:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Do not try to replayRepository in optimize --upgrade (redundant, broken).

Thu Sep  2 18:20:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * (Nearly) make it possible to thread fetchFileUsingCache into Storage.Hashed.Darcs.

Thu Sep  2 18:27:12 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix withTentative (needs to run the copy from inside the repo).

Thu Sep  2 23:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the useless MonadPlus AnnotatedM instance.

Fri Sep  3 01:24:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement directory annotate.

Fri Sep  3 01:56:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a forgotten trace.

Fri Sep  3 02:11:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update annotate.sh (no --xml).

Fri Sep  3 02:12:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update changes_with_move for differences in annotate.

Fri Sep  3 02:13:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant set -ev from tentative_revert.sh.

Fri Sep  3 02:13:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix create(Partials)Pristine... with relative paths.

Fri Sep  3 02:35:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a RestrictedApply monad, and withFiles as its entrypoint.

Fri Sep  3 02:36:03 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs show contents --match.

Fri Sep  3 02:56:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Give up some progress feedback to generalise the type of getNonrangeMatchS.

Fri Sep  3 02:57:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement darcs annotate -p/-m for files & directories.

Fri Sep  3 09:29:59 CEST 2010  Petr Rockai <me@mornfall.net>
  * Model ChangePref in ApplyMonad (by ignoring it, outside of the IO instance).

Fri Sep  3 09:30:35 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut an overlooked bit of debug code.

Fri Sep  3 09:30:47 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use a strict State monad for FilePathMonad/RestrictedApply.

Sat Sep  4 05:09:47 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve issue1942: Fix an IO interleaving bug in old-fashioned readRepo.

Sat Sep  4 05:10:04 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use currentTree from S.H.Monad instead of gets tree.

Sat Sep  4 05:10:32 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix compile of ApplyPatches (missed instance import).

Sat Sep  4 16:51:20 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt Darcs.Path and couple other use sites to S.H.Path API changes.

Sat Sep  4 16:53:05 CEST 2010  Petr Rockai <me@mornfall.net>
  * Flip handling of absolute paths over to S.H.Path as well.

Sat Sep  4 17:01:11 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a machineFormat implementation to Darcs.Annotate (not yet used).
Attachments
msg12479 (view) Author: kowey Date: 2010-09-06.15:04:15
> Other than that, there aren't many new patches here, but I have worked a
> lot on Storage.Hashed.Path. Please look in the h-s HEAD repo. There's a number
> of QC properties now. Eric, if you had a bit of time for this, you could maybe
> look at that part?

Yay! But sorry, I didn't give you very much time.  I hope these off-the-cuff
glanced-at-the-code-and-ran-some-tests comments are useful anyway.

I hope Jason sees this thread, because I think it's something he could
provide some useful insights on.

I got a cabal error without -ftest.  I think you ran into the same problem I
did, which was that baking tests into code modules, means you have to include
test-framework in the dependencies as well.

| class Cook raw cooked | raw -> cooked, raw -> cooked where
|   cook :: raw -> cooked

Hmm, I think I'm looking at a functional dependency.

If nothing else, working on Darcs is helping me to learn more functional
programming concepts, by giving me concrete examples I find naturally
compelling.

| newtype RawAbsPath = RawAbsPath BS.ByteString deriving (Eq)
| newtype RawRelPath = RawRelPath BS.ByteString deriving (Eq)
| newtype Component = Component BS.ByteString deriving (Eq, Show)
| 
|  instance Cook RawAbsPath Absolute where
|    cook (RawAbsPath x) = case parsePathBS x of
|      Nothing -> error $ "Parse failed on path: " ++ show x
|      Just y -> y
|  instance Cook RawRelPath Relative where
|    cook (RawRelPath x) = case parsePathBS x of
|      Nothing -> error $ "Parse failed on path: " ++ show x
|      Just y -> y

Are these errors OK to have because you assume random path generators
that give you valid paths to begin with?

Should there be more testing on bad path inputs, of the
we-should-refuse-X variety?

I like how to seem to have a lot of code reuse, testing the same
invariants on all sorts of operations you can do with paths, and
also making sure you're testing both relative and absolute paths
the same way.

I wonder if it would be useful to:

1. copy tests from from System.FilePath.
2. randomly test combinations of operations, like "any random sequence
   of Storage.Hashed.Path operations should result in a valid path"
3. worry about portability for AbsolutePath - do we need lots of HUnit
   cases detailing all the fun things that Windows paths can do?
4. be more formal about testing for mathy properties, like "I think
   this relation should be symmetrical", and so on.  The reason why
   the formality may help is simply so that folks trained to think
   in those terms can recognise our tests more easily and just say
   "oh, yeah, that's an antisymmetry test"

Eric

PS: A bit off-topic, but how about adding a cabal haddock to
    repos.mornfall.net/hashed-storage?
    
    I'm partly interested because I'd like darcs.net/api-doc to be
    clever about linking to it as needed (pony request by Ganesh), and
    also because I think it will help us to see the current state of
    documentation.  Two birds, one stone.

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg12480 (view) Author: kowey Date: 2010-09-06.17:56:13
On Sat, Sep 04, 2010 at 15:17:26 +0000, Petr Ročkai wrote:
> Thu Aug 12 01:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
>   * Merge Darcs.RepoPath into Darcs.Path.

Petr later worked out why we have SubPath and not Relative (which I'd
completely forgotten about in my review, oops).

The point of SubPath is that it has no initial ".." (or anything that
could lead to one)

>   * Drop unused and redundant pathFromFileName.
>   * Make the tests pass (mostly ./foo versus foo in user-visible output).

Quick look at these

>   * Optimize darcs diff.

Reviewed by time machine

>   * Resolve hashed-storage dependency conflicts.
>   * Resolve conflict in Commands.Diff imports.
>   * Resolve conflicts in Commands.WhatsNew imports.
>   * Fix conflicts in Darcs.Diff.
>   * Resolve conflicts in Darcs.Patch.*.
>   * Resolve a (bogus?) conflict in darcs.cabal.

Ignored on the grounds of boringness. :-)

>   * First round of OF removal.
>   * Also remove support for getting old-fashioned (to hashed).
>   * Only test Darcs2 and Hashed (and not OF).

Blazed through these as they looked easy

>   * Set a $format variable in lib, depending on current repo format under test.
>   * Make the tests a bit less verbose (do not print all of lib every time).

Cherry picked these

>   * Modernize the conflict-doppleganger test.
>   * Fix up the module list in darcs.cabal.
>   * Update couple more tests for absence of OF.

Kind of ignored these....

More to go! If anybody wants to help chip away at this bundle, could be
good, or maybe we should focus on getting fast-patch-production
logistics settled.

Drop unused and redundant pathFromFileName.
-------------------------------------------
OK

Make the tests pass (mostly ./foo versus foo in user-visible output).
---------------------------------------------------------------------
> +cat _darcs/patches/pending

Quite a few of these debugging statements thrown in, same old
yada-yada about separate patches.

> -echo 'M ./foo +1' > correct_summary
> +echo 'M foo +1' > correct_summary

OK so I see that this is main change of the patch.

Is this user interface change going to pose a backwards compatibility
problem for people who are scrape-parsing our human readable output, and
should if so, to what extent should we care? Enough to post an advisory
in release notes? Enough to try to preserve existing behaviour?

Maybe now that we remember the SubPath/RelativePath distinction, it
could be worth revisiting this question.

Optimize darcs diff.
--------------------
Previously reviewed.  I remember pointing out some file move problems in
the command line arguments.

--------------------------------------------
Resolve hashed-storage dependency conflicts.
Resolve conflict in Commands.Diff imports.
Resolve conflicts in Commands.WhatsNew imports.
Fix conflicts in Darcs.Diff.
Resolve conflicts in Darcs.Patch.*.
Resolve a (bogus?) conflict in darcs.cabal.
--------------------------------------------
Given that I'm reviewing a Review Team patch, I can just assume these
are boring and ignore

----------------------------------------------------------------------
First round of OF removal.
Also remove support for getting old-fashioned (to hashed).
Only test Darcs2 and Hashed (and not OF).
----------------------------------------------------------------------
I blew through these three patches because they look like fairly
straightforward machete operation, basically removing
  if foo then hashedStuff else oldStuff
with
  hashedStuff

I'm also going to ignore the problem of how to make optimize
--upgrade work again when all the infrastructure has been blown
away.

Chopping through the jungle, whee!  I'm more much enthusiastic about
this work because I feel like we've made our attempt to be responsible
about it and do our darcs-users homework first:
http://lists.osuosl.org/pipermail/darcs-users/2010-August/024941.html

>                                                 $$ text "the maintainer to run darcs optimize --upgrade with darcs 2.4.0 or higher?"
>                                                 $$ text "*******************************************************************************"

Looks like warning text that could go too, but I'll bet you got rid of
this later.

> -copyRepoOldFashioned :: RepoPatch p => Repository p C(r u t) -> [DarcsFlag] -> String -> IO ()
> -copyRepoOldFashioned repository opts repodir = do

This one feels particularly nice to be rid of.  Checkpoints, partial
repositories, a whole lot of mess we can get rid of.

> rmfile ./src/Darcs/Repository/Checkpoint.hs
> rmfile ./src/Darcs/Repository/Pristine.hs

Rah!

-----------------------------------------------------------------------
Set a $format variable in lib, depending on current repo format under test.
Make the tests a bit less verbose (do not print all of lib every time).
---------------------------------------------------------------------------

Cherry picking these patches to the test suite which look like good
ideas.

Modernize the conflict-doppleganger test.
---------------------------------------------------------------------------
Didn't line-by-line this, as it looks like just some refactoring (we do
still have advice to avoid functions in test scripts, perhaps worth
revisiting) and removing any old-fashioned bits from the test.

Fix up the module list in darcs.cabal.
--------------------------------------
> -                      Darcs.Repository.DarcsRepo
> +                      Darcs.Repository.Old

Was just a rename in your first round of OF removal patch


Update couple more tests for absence of OF.
-------------------------------------------
Treating as boring.

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg12501 (view) Author: mornfall Date: 2010-09-07.23:44:35
Hi!

NB: This is a rebase. You need to unpull any previous versions of this bundle
before applying this one. Unfortunately, the patches ended up in a fairly mixed
order due to the rebase, which will probably make reviewers' lives even harder
:(.

I have pushed Ganesh's Darcs.Patch refactors and rebased adventure against
that. That also means that all conflictors should be gone from this
set. Hopefully that offsets somewhat the above unfortunateness for the
reviewer(s).

As for contents of the set:

(a) I have ported over hashed-storage, and consequently also adventure, to
pathlib: (darcs get) http://repos.mornfall.net/pathlib/ , also see
http://repos.mornfall.net/pathlib/dist/doc/html/pathlib/

The library is a work in progress, and is based on previous Storage.Hashed.Path
work. I have added optional type witnesses for object type (they are not used
by hashed-storage or darcs, but are used by the implementation of pathlib
itself), after pathtype. I have also improved the testsuite somewhat, and added
a SubPath type that is a Relative with no .. allowed. Switching hashed-storage
and darcs itself to SubPath (where appropriate) is still pending, and I'll do
that in the near-term.

Note that the Data.Path.Witnessed API is by far not complete yet, with regards
to (unwitnessed) Data.Path. I'll get to that later (but before releasing
pathlib to Hackage, presumably). Nevertheless, the priority is the basic (no
witnesses) API. Maybe more importantly, there is currently no (real) support
for windows paths, although the way is more or less paved (there is a Posix/W32
split in the types). I have also beaten a bit of a trail for eventual URL
support (no paving yet).

(b) I have added, but not made any use of, Darcs.Repository.Class and
Darcs.Repository.Hashed. These will eventually replace the existing
Darcs.Repository interface (hopefully). They currently fail to compile, but I
figured I could use some version control when working on them, and why not keep
them around in the branch in the meantime.

The new interface is using the tentative state pervasively for all
operations. The only operation that manipulates the recorded state is "commit"
(this should be captured by the type witnesses as well, although I haven't
gotten to actually running them through GHC).

I'll work more on this, the expected course of action is to get the new API to
compile and then probably try to write some tests for it, before starting to
port the rest of darcs. At that point, I'll need to add some HUnit
infrastructure (the unit tests will need a working directory to run in,
etc.). I don't think QC is very well suited for this (mostly everything
interesting lives in IO and doesn't come with the kind of general properties QC
is good for).

(c) There's now annotate --machine flag to get the machine-readable output.

That's it, I think.

Yours,
   Petr.

81 patches for repository http://darcs.net:

Wed Aug 11 21:25:55 CEST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 22:12:49 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 01:29:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 01:32:08 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Sun Aug 29 18:54:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 19:14:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * Set a $format variable in lib, depending on current repo format under test.

Sun Aug 29 19:15:01 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests a bit less verbose (do not print all of lib every time).

Sun Aug 29 19:15:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 19:16:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 19:57:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 19:57:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 19:58:18 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 21:15:00 CEST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 21:15:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Mon Aug 30 10:17:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Thu Sep  2 13:20:06 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a redundant readRecorded in readRecordedAndPending.

Thu Sep  2 18:03:15 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid useless expansion of recorded in Commands.Add.

Thu Sep  2 18:20:24 CEST 2010  Petr Rockai <me@mornfall.net>
  * Do not try to replayRepository in optimize --upgrade (redundant, broken).

Fri Sep  3 02:11:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update annotate.sh (no --xml).

Fri Sep  3 02:12:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Update changes_with_move for differences in annotate.

Fri Sep  3 02:13:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant set -ev from tentative_revert.sh.

Fri Sep  3 02:56:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Give up some progress feedback to generalise the type of getNonrangeMatchS.

Sat Sep  4 05:10:32 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix compile of ApplyPatches (missed instance import).

Tue Sep  7 22:57:14 CEST 2010  Petr Rockai <me@mornfall.net>
  * Tweak the haddock for readWorking.

Tue Sep  7 23:49:28 CEST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Tue Sep  7 23:49:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use currentTree from S.H.Monad instead of gets tree.

Tue Sep  7 23:49:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Tue Sep  7 23:49:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Break away textDiff out of treeDiff.

Tue Sep  7 23:52:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Tue Sep  7 23:52:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a machineFormat implementation to Darcs.Annotate (not yet used).

Tue Sep  7 23:52:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug with following indirect renames in annotate.

Tue Sep  7 23:52:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Tue Sep  7 23:52:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Tue Sep  7 23:52:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Tue Sep  7 23:52:44 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

Tue Sep  7 23:52:46 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Tue Sep  7 23:52:47 CEST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Tue Sep  7 23:52:48 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Tue Sep  7 23:58:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Wed Sep  8 00:21:20 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the type of listTouchedFiles to -> [FileName].

Wed Sep  8 00:30:27 CEST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Wed Sep  8 00:30:29 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Wed Sep  8 00:30:31 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a forgotten trace.

Wed Sep  8 00:30:32 CEST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Wed Sep  8 00:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Wed Sep  8 00:30:33 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Wed Sep  8 00:30:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Wed Sep  8 00:30:35 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove bad import (no longer exists).

Wed Sep  8 00:30:35 CEST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Wed Sep  8 00:30:36 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Wed Sep  8 00:30:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Wed Sep  8 00:30:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Cut an overlooked bit of debug code.

Wed Sep  8 00:30:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Wed Sep  8 00:30:41 CEST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Wed Sep  8 00:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement directory annotate.

Wed Sep  8 00:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Adapt Darcs.Path and couple other use sites to S.H.Path API changes.

Wed Sep  8 00:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Implement darcs annotate -p/-m for files & directories.

Wed Sep  8 00:30:42 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add and implement --machine for annotate.

Wed Sep  8 00:30:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Wed Sep  8 00:30:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Re-implement create(Partials)PristineDirectoryTree in terms of readRecorded.

Wed Sep  8 00:30:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove a pile of virtually unused HashedIO code.

Wed Sep  8 00:30:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix withTentative (needs to run the copy from inside the repo).

Wed Sep  8 00:30:43 CEST 2010  Petr Rockai <me@mornfall.net>
  * (Nearly) make it possible to thread fetchFileUsingCache into Storage.Hashed.Darcs.

Wed Sep  8 00:30:44 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix create(Partials)Pristine... with relative paths.

Wed Sep  8 00:30:50 CEST 2010  Petr Rockai <me@mornfall.net>
  * Flip handling of absolute paths over to S.H.Path as well.

Wed Sep  8 00:30:51 CEST 2010  Petr Rockai <me@mornfall.net>
  * Port over to pathlib-based hashed-storage.

Wed Sep  8 00:30:52 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Wed Sep  8 00:30:52 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Wed Sep  8 00:30:53 CEST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Wed Sep  8 00:30:53 CEST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Wed Sep  8 00:30:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Wed Sep  8 00:30:54 CEST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Wed Sep  8 00:33:34 CEST 2010  Petr Rockai <me@mornfall.net>
  * Replace (Readable/Writeable)Directory with ApplyMonad.

Wed Sep  8 00:33:37 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add missed mReadFilePS to Storage.Hashed.Monad implementation of ApplyMonad.

Wed Sep  8 00:33:38 CEST 2010  Petr Rockai <me@mornfall.net>
  * Remove the useless MonadPlus AnnotatedM instance.

Wed Sep  8 00:33:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a RestrictedApply monad, and withFiles as its entrypoint.

Wed Sep  8 00:33:39 CEST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs show contents --match.

Wed Sep  8 00:33:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Model ChangePref in ApplyMonad (by ignoring it, outside of the IO instance).

Wed Sep  8 00:33:40 CEST 2010  Petr Rockai <me@mornfall.net>
  * Use a strict State monad for FilePathMonad/RestrictedApply.

Wed Sep  8 00:56:45 CEST 2010  Petr Rockai <me@mornfall.net>
  * Add a first stab at Darcs.Repository.Class (and a Hashed implementation).

Wed Sep  8 01:06:56 CEST 2010  Petr Rockai <me@mornfall.net>
  * Resolve issue1942: fix the fix which ended up too strict due to unsealing.
Attachments
msg12636 (view) Author: ganesh Date: 2010-10-04.18:51:31
Petr has given up working on adventure for the time being:
http://lists.osuosl.org/pipermail/darcs-users/2010-October/025413.html

So we won't push these to screened. I'm just sending in some minor fixups I
made to them to make the witnesses build and test harness compile properly,
for archival purposes.

81 patches for repository http://darcs.net:

Wed Aug 11 20:25:55 BST 2010  Petr Rockai <me@mornfall.net>
  * Move the preferences system into IO where it belongs.

Wed Aug 11 21:12:49 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix annotate that got broken due to path format change.

Thu Aug 12 00:29:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix a subtle bug in onlyHunks with rather curious side-effects.

Thu Aug 12 00:32:08 BST 2010  Petr Rockai <me@mornfall.net>
  * Make the tests pass (mostly ./foo versus foo in user-visible output).

Sun Aug 29 17:54:41 BST 2010  Petr Rockai <me@mornfall.net>
  * Only test Darcs2 and Hashed (and not OF).

Sun Aug 29 18:15:18 BST 2010  Petr Rockai <me@mornfall.net>
  * Modernize the conflict-doppleganger test.

Sun Aug 29 18:16:18 BST 2010  Petr Rockai <me@mornfall.net>
  * Update couple more tests for absence of OF.

Sun Aug 29 18:57:34 BST 2010  Petr Rockai <me@mornfall.net>
  * Adapt bad-format to the current OF-less situation.

Sun Aug 29 18:57:50 BST 2010  Petr Rockai <me@mornfall.net>
  * Adapt issue1248 test to current OF-less situation.

Sun Aug 29 18:58:18 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove parts of the hashed_inventory that require conversion to OF.

Sun Aug 29 20:15:00 BST 2010  Petr Rockai <me@mornfall.net>
  * Print a list of (shell) tests that have failed after a test run.

Sun Aug 29 20:15:37 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix a few more tests since the OF support removal.

Mon Aug 30 09:17:54 BST 2010  Petr Rockai <me@mornfall.net>
  * Cut the old annotate code from Commands.Annotate.

Thu Sep  2 12:20:06 BST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a redundant readRecorded in readRecordedAndPending.

Thu Sep  2 17:03:15 BST 2010  Petr Rockai <me@mornfall.net>
  * Avoid useless expansion of recorded in Commands.Add.

Thu Sep  2 17:20:24 BST 2010  Petr Rockai <me@mornfall.net>
  * Do not try to replayRepository in optimize --upgrade (redundant, broken).

Fri Sep  3 01:11:37 BST 2010  Petr Rockai <me@mornfall.net>
  * Update annotate.sh (no --xml).

Fri Sep  3 01:12:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Update changes_with_move for differences in annotate.

Fri Sep  3 01:13:27 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant set -ev from tentative_revert.sh.

Fri Sep  3 01:56:34 BST 2010  Petr Rockai <me@mornfall.net>
  * Give up some progress feedback to generalise the type of getNonrangeMatchS.

Sat Sep  4 04:10:32 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix compile of ApplyPatches (missed instance import).

Tue Sep  7 21:57:14 BST 2010  Petr Rockai <me@mornfall.net>
  * Tweak the haddock for readWorking.

Tue Sep  7 22:49:28 BST 2010  Petr Rockai <me@mornfall.net>
  * First stab at a hashed-storage 0.6 port.

Tue Sep  7 22:49:38 BST 2010  Petr Rockai <me@mornfall.net>
  * Use currentTree from S.H.Monad instead of gets tree.

Tue Sep  7 22:49:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix conflicts in Darcs.Diff.

Tue Sep  7 22:49:41 BST 2010  Petr Rockai <me@mornfall.net>
  * Break away textDiff out of treeDiff.

Tue Sep  7 22:52:36 BST 2010  Petr Rockai <me@mornfall.net>
  * A new implementation of per-file annotate, part one.

Tue Sep  7 22:52:37 BST 2010  Petr Rockai <me@mornfall.net>
  * Add a machineFormat implementation to Darcs.Annotate (not yet used).

Tue Sep  7 22:52:38 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix a bug with following indirect renames in annotate.

Tue Sep  7 22:52:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix the annotation of the first line.

Tue Sep  7 22:52:42 BST 2010  Petr Rockai <me@mornfall.net>
  * Avoid a bogus trailing empty line in annotate output.

Tue Sep  7 22:52:43 BST 2010  Petr Rockai <me@mornfall.net>
  * Use fluffier and more readable formatting for annotate.

Tue Sep  7 22:52:44 BST 2010  Petr Rockai <me@mornfall.net>
  * Make the annotate formatting ever so fluffier.

Tue Sep  7 22:52:46 BST 2010  Petr Rockai <me@mornfall.net>
  * Use linesPS in patch application -- the trailing empty line is significant.

Tue Sep  7 22:52:47 BST 2010  Petr Rockai <me@mornfall.net>
  * A slight improvement to file annotate performance.

Tue Sep  7 22:52:48 BST 2010  Petr Rockai <me@mornfall.net>
  * Make SubPath just another alias for Relative.

Tue Sep  7 22:58:41 BST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflicts in Commands.WhatsNew imports.

Tue Sep  7 23:21:20 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix the type of listTouchedFiles to -> [FileName].

Tue Sep  7 23:30:27 BST 2010  Petr Rockai <me@mornfall.net>
  * Make FileName an alias to Relative (from Hashed.Storage.Path).

Tue Sep  7 23:30:29 BST 2010  Petr Rockai <me@mornfall.net>
  * Replace FilePath with FileName in SelectChanges and ChooseTouching.

Tue Sep  7 23:30:31 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove a forgotten trace.

Tue Sep  7 23:30:32 BST 2010  Petr Rockai <me@mornfall.net>
  * Restore the ".." check in isMaliciousPath.

Tue Sep  7 23:30:33 BST 2010  Petr Rockai <me@mornfall.net>
  * Introduce a new Darcs.Path module to centralise path handling.

Tue Sep  7 23:30:33 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix announceFiles in WhatsNew (abolish unsafePathFrom*).

Tue Sep  7 23:30:34 BST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.Patch.FileName into Darcs.Path.

Tue Sep  7 23:30:35 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove bad import (no longer exists).

Tue Sep  7 23:30:35 BST 2010  Petr Rockai <me@mornfall.net>
  * Drop unused and redundant pathFromFileName.

Tue Sep  7 23:30:36 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove the now-redundant sp2fn.

Tue Sep  7 23:30:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs diff.

Tue Sep  7 23:30:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Cut an overlooked bit of debug code.

Tue Sep  7 23:30:41 BST 2010  Petr Rockai <me@mornfall.net>
  * Resolve conflict in Commands.Diff imports.

Tue Sep  7 23:30:41 BST 2010  Petr Rockai <me@mornfall.net>
  * Merge Darcs.RepoPath into Darcs.Path.

Tue Sep  7 23:30:42 BST 2010  Petr Rockai <me@mornfall.net>
  * Implement directory annotate.

Tue Sep  7 23:30:42 BST 2010  Petr Rockai <me@mornfall.net>
  * Adapt Darcs.Path and couple other use sites to S.H.Path API changes.

Tue Sep  7 23:30:42 BST 2010  Petr Rockai <me@mornfall.net>
  * Implement darcs annotate -p/-m for files & directories.

Tue Sep  7 23:30:42 BST 2010  Petr Rockai <me@mornfall.net>
  * Add and implement --machine for annotate.

Tue Sep  7 23:30:43 BST 2010  Petr Rockai <me@mornfall.net>
  * First round of OF removal.

Tue Sep  7 23:30:43 BST 2010  Petr Rockai <me@mornfall.net>
  * Re-implement create(Partials)PristineDirectoryTree in terms of readRecorded.

Tue Sep  7 23:30:43 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove a pile of virtually unused HashedIO code.

Tue Sep  7 23:30:43 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix withTentative (needs to run the copy from inside the repo).

Tue Sep  7 23:30:43 BST 2010  Petr Rockai <me@mornfall.net>
  * (Nearly) make it possible to thread fetchFileUsingCache into Storage.Hashed.Darcs.

Tue Sep  7 23:30:44 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix create(Partials)Pristine... with relative paths.

Tue Sep  7 23:30:50 BST 2010  Petr Rockai <me@mornfall.net>
  * Flip handling of absolute paths over to S.H.Path as well.

Tue Sep  7 23:30:51 BST 2010  Petr Rockai <me@mornfall.net>
  * Port over to pathlib-based hashed-storage.

Tue Sep  7 23:30:52 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove the Population code (part of the old annotate implementation).

Tue Sep  7 23:30:52 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove redundant imports from Commands.Get.

Tue Sep  7 23:30:53 BST 2010  Petr Rockai <me@mornfall.net>
  * Getting OF repos is not supported, reflect that in Commands.Get.

Tue Sep  7 23:30:53 BST 2010  Petr Rockai <me@mornfall.net>
  * Correctly fail on encountering unsupported repository format in Commands.Get.

Tue Sep  7 23:30:54 BST 2010  Petr Rockai <me@mornfall.net>
  * Fix the optimize --upgrade functionality.

Tue Sep  7 23:30:54 BST 2010  Petr Rockai <me@mornfall.net>
  * Also remove support for getting old-fashioned (to hashed).

Tue Sep  7 23:33:34 BST 2010  Petr Rockai <me@mornfall.net>
  * Replace (Readable/Writeable)Directory with ApplyMonad.

Tue Sep  7 23:33:37 BST 2010  Petr Rockai <me@mornfall.net>
  * Add missed mReadFilePS to Storage.Hashed.Monad implementation of ApplyMonad.

Tue Sep  7 23:33:38 BST 2010  Petr Rockai <me@mornfall.net>
  * Remove the useless MonadPlus AnnotatedM instance.

Tue Sep  7 23:33:39 BST 2010  Petr Rockai <me@mornfall.net>
  * Add a RestrictedApply monad, and withFiles as its entrypoint.

Tue Sep  7 23:33:39 BST 2010  Petr Rockai <me@mornfall.net>
  * Optimize darcs show contents --match.

Tue Sep  7 23:33:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Model ChangePref in ApplyMonad (by ignoring it, outside of the IO instance).

Tue Sep  7 23:33:40 BST 2010  Petr Rockai <me@mornfall.net>
  * Use a strict State monad for FilePathMonad/RestrictedApply.

Tue Sep  7 23:56:45 BST 2010  Petr Rockai <me@mornfall.net>
  * Add a first stab at Darcs.Repository.Class (and a Hashed implementation).

Wed Sep  8 00:06:56 BST 2010  Petr Rockai <me@mornfall.net>
  * Resolve issue1942: fix the fix which ended up too strict due to unsealing.

Sat Oct  2 19:38:45 BST 2010  Ganesh Sittampalam <ganesh@earth.li>
  * fix witnesses build by enabling TypeSynonymInstances

Mon Oct  4 17:42:41 BST 2010  Ganesh Sittampalam <ganesh@earth.li>
  * compile fixes for test harness
Attachments
msg12639 (view) Author: mornfall Date: 2010-10-04.19:45:51
Ganesh Sittampalam <bugs@darcs.net> writes:

> Petr has given up working on adventure for the time being:
> http://lists.osuosl.org/pipermail/darcs-users/2010-October/025413.html
>
> So we won't push these to screened. I'm just sending in some minor fixups I
> made to them to make the witnesses build and test harness compile properly,
> for archival purposes.

Thanks Ganesh.

I will keep you updated about my status. Things may still turn out the
better way, but I won't know for a few more weeks. Hopefully the things
that fell out of adventure will be useful for darcs in the long run,
regardless of how this turns out. All I can do for now is hope that I
didn't waste too much of anyone's time...

Yours,
   Petr.

PS: I will still read darcs-users@ and review patches as time allows.
msg13353 (view) Author: gh Date: 2010-12-16.16:30:01
I have resubmitted the "Do not try to replayRepository in optimize
--upgrade" patch with a small followup patch at:

http://bugs.darcs.net/patch507

And I have submitted OF removal patches based on "First round of OF
removal":

http://bugs.darcs.net/patch510

What remains to be submitted again from this bundle, probably after the
2 bundles above are screened, are:

* disable tests for OF
* tests for OF upgrade with ``optimize --upgrade``
* update to hashed-storage 0.6
* annotate optimization
* diff optimization (not for OF)
* annotate  git-like format
* new Darcs.Path module to centralise path handling.
* Optimize darcs show contents --match
* and various patches that follow OF deprecation but that I have not
checked in detail.
msg15316 (view) Author: gh Date: 2012-03-14.15:46:01
As of now, the main features/changes that are in this bundle and that
aren't yet in HEAD are:

* update to hashed-storage 0.6
* diff optimization
* new Darcs.Path module to centralise path handling.
* Optimize darcs show contents --match

What are we doing with that? Is there one of these items or more that
deserves to be ported (manually, I guess) into HEAD?
msg15318 (view) Author: mndrix Date: 2012-03-14.17:57:24
> * diff optimization

I'd like to see this ported.  I'm glad to work on the port myself, but 
will probably be slower than others as I come up to speed on the necessary 
internals.

For the record, there's background discussion on the general optimization 
in patch351
msg15319 (view) Author: gh Date: 2012-03-14.18:24:42
Thanks Michael, I forgot about that patch! It has been marked as
obsoleted, but I'm going to reopen it so that we can discuss this
proposed change and its implementation. (Althought everything is a
little entangled since the diff optimization relies on the
hashed-storage 6.0 port).

g.
msg15669 (view) Author: gh Date: 2012-05-11.19:28:05
Update: the diff optimization has been ported to HEAD.

As of now, the main features/changes that are in this bundle and that
aren't yet in HEAD are:

* update to hashed-storage 0.6
* new Darcs.Path module to centralise path handling.
* Optimize darcs show contents --match

What are we doing with that? Is there one of these items or more that
deserves to be ported (manually, I guess) into HEAD?
msg15807 (view) Author: gh Date: 2012-06-11.22:45:12
mornfall, I recently did some refactoring in the darcs codebase.

Among these changes are the introduction of Darcs.Path, that replaces 
both Darcs.Patch.FileName and Darcs.RepoPath, and also contains a few 
malicious path test functions that were elsewhere before. That pretty 
much follows what you did in your adventure branch, except that there is 
no switch to hashed-storage 0.6.

Do you think you can work on this current codebase so that darcs can rely 
on the pathlib library you did during the last summer of code?
msg16692 (view) Author: gh Date: 2013-02-18.09:36:07
Closing this as the remaining code is probably too different to be 
adapted to current HEAD.
History
Date User Action Args
2010-08-30 08:43:30mornfallcreate
2010-08-30 08:44:54darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-f1f0b5c76c92e42cc6f6f81cca9b3bde1a0a38b4
2010-08-31 09:52:22koweylinkpatch351 superseder
2010-08-31 09:52:57koweylinkpatch343 superseder
2010-08-31 12:53:47koweysetmessages: + msg12383
2010-09-02 12:25:45koweysetmessages: + msg12412
2010-09-02 16:33:35mornfallsetfiles: + wibble-path-building-in-repository_prefs_.dpatch, unnamed
messages: + msg12421
title: ADV: the initial pile -> the state of the adventure
2010-09-02 16:35:45darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-f1f0b5c76c92e42cc6f6f81cca9b3bde1a0a38b4 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-b342e4fa100e8818ad013d6b2b8f30d0e64cf714
2010-09-02 17:56:57mornfallsetmessages: + msg12424
title: the state of the adventure -> ADV: the initial pile
2010-09-02 17:57:49mornfallsetmessages: + msg12425
2010-09-03 02:53:14mornfallsetfiles: + wibble-path-building-in-repository_prefs_.dpatch, unnamed
messages: + msg12431
title: ADV: the initial pile -> the state of the adventure
2010-09-03 02:56:22darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-b342e4fa100e8818ad013d6b2b8f30d0e64cf714 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-3f0e2878d2af724e06b12324966901f4701d004c
2010-09-03 08:57:41mornfallsetmessages: + msg12435
2010-09-04 15:17:26mornfallsetfiles: + first-stab-at-a-hashed_storage-0_6-port_.dpatch, unnamed
messages: + msg12461
2010-09-06 15:04:16koweysetmessages: + msg12479
2010-09-06 17:56:13koweysetmessages: + msg12480
2010-09-06 19:30:52darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-3f0e2878d2af724e06b12324966901f4701d004c -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-596c22435a44e22635b52e418bd25d569563bf5d
2010-09-07 23:44:36mornfallsetfiles: + move-the-preferences-system-into-io-where-it-belongs_.dpatch, unnamed
messages: + msg12501
2010-09-07 23:50:15darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-596c22435a44e22635b52e418bd25d569563bf5d -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-b89701bb59446d00129b18631b8ed895e528ef48
2010-09-15 10:44:24koweysetstatus: needs-review -> needs-screening
2010-10-04 18:51:33ganeshsetfiles: + move-the-preferences-system-into-io-where-it-belongs_.dpatch, unnamed
messages: + msg12636
title: the state of the adventure -> compile fixups
2010-10-04 18:52:26ganeshsetstatus: needs-screening -> followup-in-progress
2010-10-04 19:30:40darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-b89701bb59446d00129b18631b8ed895e528ef48 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-44d4246aa13627cce748719df9f7f69e67084bea
2010-10-04 19:45:51mornfallsetmessages: + msg12639
2010-10-04 22:12:00ganeshsettitle: compile fixups -> adventure branch
2010-12-16 16:30:01ghsetmessages: + msg13353
2011-05-10 17:36:32darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-44d4246aa13627cce748719df9f7f69e67084bea -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-b89701bb59446d00129b18631b8ed895e528ef48
2011-05-10 18:06:19darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-b89701bb59446d00129b18631b8ed895e528ef48 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-3f0e2878d2af724e06b12324966901f4701d004c
2011-05-10 19:05:44darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-3f0e2878d2af724e06b12324966901f4701d004c -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-44d4246aa13627cce748719df9f7f69e67084bea
2011-05-10 19:36:56darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-44d4246aa13627cce748719df9f7f69e67084bea -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-f1f0b5c76c92e42cc6f6f81cca9b3bde1a0a38b4
2011-05-10 19:37:46darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-f1f0b5c76c92e42cc6f6f81cca9b3bde1a0a38b4 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-b342e4fa100e8818ad013d6b2b8f30d0e64cf714
2011-05-10 22:06:56darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-b342e4fa100e8818ad013d6b2b8f30d0e64cf714 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-596c22435a44e22635b52e418bd25d569563bf5d
2012-03-14 15:46:01ghsetmessages: + msg15316
2012-03-14 17:57:24mndrixsetnosy: + mndrix
messages: + msg15318
2012-03-14 18:24:42ghsetmessages: + msg15319
2012-05-11 19:28:05ghsetmessages: + msg15669
2012-06-11 22:45:12ghsetmessages: + msg15807
2013-02-18 09:36:07ghsetstatus: followup-in-progress -> obsoleted
messages: + msg16692