[darcs-devel] [patch2021] replace shelly with turtle

Ben Franksen bugs at darcs.net
Wed May 20 09:43:50 UTC 2020


Ben Franksen <ben.franksen at online.de> added the comment:

> Unfortunately all the shell tests fail without any output at all (just
> '[failed]').

This probably means that the call to createProcess_ (that runs "bash
test" inside the test directory) fails.

I have attached a patch that replaces the low-level call to
createProcess_ with a high-level one from turtle. On my system this will
report a number of failed tests because stderr and stdout have not been
set to binary mode.

Can you check that with this patch you can run at least
tests/harness.sh? If that succeeds it confirms that I have made a
mistake with the low-level call to createProcess_. If it fails, we
should at least get some output, unless systemStrictWithErr from turtle
is broken, too, in which case I can file a bug report with turtle.

__________________________________
Darcs bug tracker <bugs at darcs.net>
<http://bugs.darcs.net/patch2021>
__________________________________
-------------- next part --------------
7 patches for repository http://darcs.net/screened:

patch 5b5dc69a13fde05309a5b57cd01b2e9b04f2df29
Author: Ben Franksen <ben.franksen at online.de>
Date:   Fri May  1 18:52:27 CEST 2020
  * harnes,tests: import lib in all test scripts, no longer set env in Haskell
  
  This slightly simplifies the environment handling logic in the harness.

patch 02e55fa4bfb0f785f7c24efe7a4257d70c3cea97
Author: Ben Franksen <ben.franksen at online.de>
Date:   Fri May  1 14:26:45 CEST 2020
  * harness: use PatchFormat and DiffAlgorithm from Darcs.Repository.Flags

patch b2d0d11007ec22e816bbe14641076091aa2e9474
Author: Ben Franksen <ben.franksen at online.de>
Date:   Fri May  1 16:48:03 CEST 2020
  * harness: use RecordWildCards in test.hs

patch a0528921a72d3130c70f791bd1d0b1414a77bbf0
Author: Ben Franksen <ben.franksen at online.de>
Date:   Fri May  1 21:10:30 CEST 2020
  * harness: further simplify environment logic for PATH
  
  Instead of splitting and reconstructing the PATH variable, just prepend the
  directory of the darcs under test directly in the env file.

patch 9265001d8f5c159b4bab4f0b1ec574754bfe01a0
Author: Ben Franksen <ben.franksen at online.de>
Date:   Fri May  1 14:15:11 CEST 2020
  * harness: use turtle to find the darcs executable to test
  
  This is a first step toward refactoring harness/test.hs to get rid of the
  shelly dependency.

patch d101ae051e27711bb7747c225c1a1cdedd7baecd
Author: Ben Franksen <ben.franksen at online.de>
Date:   Sat May  2 01:06:10 CEST 2020
  * replace dependency on shelly with turtle
  
  This has been more difficult than I expected. There are two points where
  turtle is weaker than shelly: first, the 'cd' and 'setenv' commands are not
  thread-safe, whereas in shelly they are; second, in turtle (as in the
  standard System.Process) there is no way to intercept the handles that are
  created when we specify that they should be captured using pipes. Again,
  shelly offers this as a feature.
  
  The solution for the first problem is to not set the environment and to not
  use 'cd'. Instead we pass the working directory directly to the process that
  runs the shell script. The second problem is solved using some low-level
  primitives from System.Process.

patch c2d14c7244167c74df50693b6f1e40585fb3e7f7
Author: Ben Franksen <ben.franksen at online.de>
Date:   Wed May 20 11:40:06 CEST 2020
  * TEST PATCH
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA256


New patches:

[harnes,tests: import lib in all test scripts, no longer set env in Haskell
Ben Franksen <ben.franksen at online.de>**20200501165227
 Ignore-this: 8dab5a2e308fb17a40b21d353ec07295cc9e07bab262006420e6227e914ea05b895df89ddacf3a4f
 
 This slightly simplifies the environment handling logic in the harness.
] hunk ./harness/test.hs 27
- -import qualified System.FilePath as Native ( searchPathSeparator, splitSearchPath )
+import qualified System.FilePath as Native ( splitSearchPath )
hunk ./harness/test.hs 115
- -     -- just in case the test script doesn't source ./lib:
- -     mapM_ (\(k,v) -> setenv k (envItemForEnv v)) env
hunk ./harness/test.hs 140
- -        -- convert an 'EnvItem' to a string you can put in the environment directly
- -        envItemForEnv :: EnvItem -> Text
- -        envItemForEnv (EnvString v) = pack v
- -        envItemForEnv (EnvFilePath v) = toTextIgnore v
- -        envItemForEnv (EnvSearchPath vs) =
- -          T.intercalate (T.singleton Native.searchPathSeparator) $ map toTextIgnore vs
- -
hunk ./tests/issue1609-conflict-markup-depends-on-patch-order.sh 1
- -#!/bin/sh
+#!/bin/bash
+
+. lib
+
hunk ./tests/issue2378-moving-directory-to-file.sh 1
+#!/usr/bin/env bash
+
+. lib
+
hunk ./tests/issue494-pending-sort.sh 26
+. lib
+
hunk ./tests/mark-conflicts.sh 3
- -# Automated tests for "darcs mark-conflicts".
+# tests for "darcs mark-conflicts".
hunk ./tests/mark-conflicts.sh 5
- -# The builtin ! has the wrong semantics for not.
- -not () { "$@" && exit 1 || :; }
+. lib

[harness: use PatchFormat and DiffAlgorithm from Darcs.Repository.Flags
Ben Franksen <ben.franksen at online.de>**20200501122645
 Ignore-this: cf77ca8b56ff201aeabca7d81f6b283f2b050d5f422e62624c36c25e7d92a53c1ad9e816ffafd181
] hunk ./harness/test.hs 8
+import Darcs.Repository.Flags ( PatchFormat(..), DiffAlgorithm(..) )
hunk ./harness/test.hs 44
- --- | This is the big list of tests that will be run using testrunner.
+-- | List of all unit tests.
hunk ./harness/test.hs 50
- -  ] ++ (Darcs.Test.Patch.RepoPatchV1.testSuite : Darcs.Test.Patch.testSuite)
+  ]
+  ++
+  [ Darcs.Test.Patch.RepoPatchV1.testSuite
+  ]
+  ++ Darcs.Test.Patch.testSuite
hunk ./harness/test.hs 60
- -data Format = Darcs1 | Darcs2 | Darcs3 deriving (Show, Eq, Typeable, Data)
- -data DiffAlgorithm = MyersDiff | PatienceDiff deriving (Show, Eq, Typeable, Data)
hunk ./harness/test.hs 73
- -data ShellTest = ShellTest { format :: Format
+data ShellTest = ShellTest { format :: PatchFormat
hunk ./harness/test.hs 136
- -                  Darcs3 -> "darcs-3"
- -                  Darcs2 -> "darcs-2"
- -                  Darcs1 -> "darcs-1"
+                  PatchFormat3 -> "darcs-3"
+                  PatchFormat2 -> "darcs-2"
+                  PatchFormat1 -> "darcs-1"
hunk ./harness/test.hs 195
- -shellTest :: FilePath -> Format -> Maybe FilePath -> String -> DiffAlgorithm -> Test
+shellTest :: FilePath -> PatchFormat -> Maybe FilePath -> String -> DiffAlgorithm -> Test
hunk ./harness/test.hs 203
- -findShell :: FilePath -> Text -> Maybe FilePath -> Bool -> [DiffAlgorithm] -> [Format] -> Sh [Test]
+findShell :: FilePath -> Text -> Maybe FilePath -> Bool -> [DiffAlgorithm] -> [PatchFormat] -> Sh [Test]
hunk ./harness/test.hs 320
- -    let repoFormat    = (if darcs1 conf then (Darcs1:) else id)
- -                      . (if darcs2 conf then (Darcs2:) else id)
- -                      . (if darcs3 conf then (Darcs3:) else id)
+    let repoFormat    = (if darcs1 conf then (PatchFormat1:) else id)
+                      . (if darcs2 conf then (PatchFormat2:) else id)
+                      . (if darcs3 conf then (PatchFormat3:) else id)

[harness: use RecordWildCards in test.hs
Ben Franksen <ben.franksen at online.de>**20200501144803
 Ignore-this: 69362b539b97050b54d7ccddb9ca31598a26d2040c35da9525241e2264f0d94d03ead868fd0cea4c
] hunk ./harness/test.hs 1
- -{-# LANGUAGE CPP, MultiParamTypeClasses, DeriveDataTypeable, ViewPatterns, OverloadedStrings, ExtendedDefaultRules #-}
+{-# LANGUAGE CPP, MultiParamTypeClasses, DeriveDataTypeable,
+  ViewPatterns, OverloadedStrings, ExtendedDefaultRules, RecordWildCards #-}
hunk ./harness/test.hs 74
- -data ShellTest = ShellTest { format :: PatchFormat
- -                           , testfile :: FilePath
- -                           , testdir  :: Maybe FilePath -- ^ only if you want to set it explicitly
- -                           , _darcspath :: FilePath
- -                           , diffalgorithm :: DiffAlgorithm
- -                           }
- -                 deriving Typeable
+data ShellTest = ShellTest
+  { format :: PatchFormat
+  , testfile :: FilePath
+  , testdir :: Maybe FilePath -- ^ only if set explicitly
+  , darcspath :: FilePath
+  , diffalgorithm :: DiffAlgorithm
+  } deriving (Typeable)
hunk ./harness/test.hs 92
- -runtest' (ShellTest fmt _ _ dp da) srcdir =
+runtest' (ShellTest {..}) srcdir =
hunk ./harness/test.hs 95
- -     let pathToUse = map (fromText . pack) $ takeDirectory dp:Native.splitSearchPath p
+     let pathToUse = map (fromText . pack) $ takeDirectory darcspath:Native.splitSearchPath p
hunk ./harness/test.hs 112
- -          , ("DARCS", EnvString dp)
+          , ("DARCS", EnvString darcspath)
hunk ./harness/test.hs 136
- -        fmtstr = case fmt of
+        fmtstr = case format of
hunk ./harness/test.hs 140
- -        daf = case da of
+        daf = case diffalgorithm of

[harness: further simplify environment logic for PATH
Ben Franksen <ben.franksen at online.de>**20200501191030
 Ignore-this: 25e71a6ab95bb12982a14ee71d1fa69fd7eafb0c2e7eff7ead8ac653b727eba96b9523d45628fcfa
 
 Instead of splitting and reconstructing the PATH variable, just prepend the
 directory of the darcs under test directly in the env file.
] hunk ./harness/test.hs 29
- -import qualified System.FilePath as Native ( splitSearchPath )
- -import qualified System.FilePath.Posix as Posix ( searchPathSeparator )
hunk ./harness/test.hs 87
- -  | EnvSearchPath [Shelly.FilePath] -- ^ A list of paths on disk, for the PATH variable
hunk ./harness/test.hs 91
- -     p <- unpack <$> get_env_text "PATH"
- -     let pathToUse = map (fromText . pack) $ takeDirectory darcspath:Native.splitSearchPath p
hunk ./harness/test.hs 103
- -          , ("PATH", EnvSearchPath pathToUse)
+          , ("PATH", EnvString (takeDirectory darcspath <> ":$PATH"))
hunk ./harness/test.hs 144
- -        envItemForScript (EnvSearchPath vs) =
- -           -- note the use of the Posix search path separator (':') regardless of platform
- -           T.intercalate (T.singleton Posix.searchPathSeparator) $ map filePathForScript vs

[harness: use turtle to find the darcs executable to test
Ben Franksen <ben.franksen at online.de>**20200501121511
 Ignore-this: 13b5e032d821d9cc779ca7a6ee82107dfeaffe209e674068bcf4730cbc4749734aacda9d677694f
 
 This is a first step toward refactoring harness/test.hs to get rid of the
 shelly dependency.
] hunk ./darcs.cabal 536
+                    foldl        >= 1.4 && < 1.5,
hunk ./darcs.cabal 540
+                    turtle       >= 1.5 && < 1.5.17,
hunk ./darcs.cabal 610
+                    Darcs.Test.Shell
addfile ./harness/Darcs/Test/Shell.hs
hunk ./harness/Darcs/Test/Shell.hs 1
+{-# LANGUAGE CPP, OverloadedStrings #-}
+module Darcs.Test.Shell ( findDarcs ) where
+
+import Darcs.Prelude hiding ( FilePath, (<>) )
+-- import Control.Exception
+import qualified Control.Foldl as F
+-- import Data.Maybe ( fromMaybe )
+import System.Environment.FindBin ( getProgPath )
+-- import qualified Data.Text as T
+import Turtle
+
+-- | Find the most relevant darcs binary to test.
+findDarcs :: IO String
+findDarcs = do
+  path <- decodeString <$> getProgPath
+  found <- fmap encodeString $ findNearest darcsExe path
+  putStrLn $ "Testing darcs executable found at: " <> found
+  return found
+  where
+    darcsExe = suffix $ "darcs"
+#ifdef WIN32
+      >> ".exe"
+#endif
+    findNearest :: Pattern a -> FilePath -> IO FilePath
+    findNearest pat path = do
+      mres <-
+        flip foldIO (F.prefilterM isExeFile (F.generalize F.head)) $
+        find pat path <|>
+        if parent path == path
+          then empty
+          else find pat (parent path)
+      case mres of
+        Nothing -> die "darcs not found"
+        Just r -> return r
+    isExeFile :: FilePath -> IO Bool
+    isExeFile path = do
+      status <- stat path
+      perms <- getmod path
+      return $ _executable perms && not (isDirectory status)
hunk ./harness/test.hs 16
+import Darcs.Test.Shell
hunk ./harness/test.hs 19
- -import Control.Monad ( filterM )
hunk ./harness/test.hs 26
- -import System.Directory ( doesFileExist )
- -import System.Environment.FindBin ( getProgPath )
hunk ./harness/test.hs 277
- -            "" -> do
- -                path <- getProgPath
- -                let candidates =
- -                      -- if darcs-test lives in foo/something, look for foo/darcs[.exe]
- -                      -- for example if we've done cabal install -ftest, there'll be a darcs-test and darcs in the cabal
- -                      -- installation folder
- -                      [path </> ("darcs" ++ exeSuffix)] ++
- -                      -- if darcs-test lives in foo/darcs-test/something, look for foo/darcs/darcs[.exe]
- -                      -- for example after cabal build we can run dist/build/darcs-test/darcs-test and it'll find
- -                      -- the darcs in dist/build/darcs/darcs
- -                      [takeDirectory path </> "darcs" </> ("darcs" ++ exeSuffix) | takeBaseName path == "darcs-test" ] ++
- -                      -- nowadays cabal v2-build produces more complicated structures:
- -                      -- t/darcs-test/build/darcs-test/darcs-test and x/darcs/build/darcs/darcs
- -                      [takeDirectory path </> ".." </> ".." </> ".." </> "x"
- -                                          </> "darcs" </> "build" </> "darcs" </> ("darcs" ++ exeSuffix)
- -                            | takeBaseName path == "darcs-test" ] ++
- -                      [takeDirectory path </> ".." </> ".." </> ".." </> ".." </> "x"
- -                                          </> "darcs" </> "noopt" </> "build" </> "darcs" </> ("darcs" ++ exeSuffix)
- -                            | takeBaseName path == "darcs-test" ]
- -                availableCandidates <- filterM doesFileExist (map toString candidates)
- -                case availableCandidates of
- -                     (darcsBin:_) -> do
- -                         putStrLn $ "Using darcs executable in " ++ darcsBin
- -                         return darcsBin
- -                     [] -> die ("No darcs specified or found nearby. Tried:\n" ++ unlines (map toString candidates))
+            "" -> findDarcs

[replace dependency on shelly with turtle
Ben Franksen <ben.franksen at online.de>**20200501230610
 Ignore-this: 80849637be8715b67a9b253bf6e8da4f529eb8a337d786a83da154bd1812cd5fc09bee59759d63f
 
 This has been more difficult than I expected. There are two points where
 turtle is weaker than shelly: first, the 'cd' and 'setenv' commands are not
 thread-safe, whereas in shelly they are; second, in turtle (as in the
 standard System.Process) there is no way to intercept the handles that are
 created when we specify that they should be captured using pipes. Again,
 shelly offers this as a feature.
 
 The solution for the first problem is to not set the environment and to not
 use 'cd'. Instead we pass the working directory directly to the process that
 runs the shell script. The second problem is solved using some low-level
 primitives from System.Process.
] hunk ./darcs.cabal 531
+                    async,
hunk ./darcs.cabal 539
+                    process,
hunk ./darcs.cabal 541
- -                    shelly       >= 1.6.8 && < 1.10,
hunk ./harness/Darcs/Test/Shell.hs 2
- -module Darcs.Test.Shell ( findDarcs ) where
+module Darcs.Test.Shell
+    ( findDarcs
+    , ShellTestConfig(..)
+    , shellTests
+    , filePathToText
+    ) where
hunk ./harness/Darcs/Test/Shell.hs 10
- --- import Control.Exception
+import Darcs.Repository.Flags ( PatchFormat(..), DiffAlgorithm(..) )
+
+import Control.Concurrent.Async ( Concurrently(..), runConcurrently )
hunk ./harness/Darcs/Test/Shell.hs 14
- --- import Data.Maybe ( fromMaybe )
+import Control.Exception ( bracket )
+import qualified System.Directory as D
hunk ./harness/Darcs/Test/Shell.hs 17
- --- import qualified Data.Text as T
- -import Turtle
+import System.Process
+    ( CreateProcess(..)
+    , StdStream(..)
+    , createProcess_
+    , proc
+    , waitForProcess
+    )
+import System.IO ( hClose, hSetBinaryMode )
+import Test.Framework.Providers.API
+    ( Test
+    , Test(..)
+    , TestResultlike(..)
+    , Testlike(..)
+    , liftIO
+    , runImprovingIO
+    , yieldImprovement
+    )
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
+-- note we must not use 'cd' and 'export' because they are not thread safe
+import Turtle hiding ( err, liftIO, cd, proc, export )
hunk ./harness/Darcs/Test/Shell.hs 43
- -  found <- fmap encodeString $ findNearest darcsExe path
+  found <- encodeString <$> findNearest darcsExe path
hunk ./harness/Darcs/Test/Shell.hs 67
+
+data ShellTestConfig = ShellTestConfig
+  { darcspath :: FilePath     -- ^ path to the darcs executable we test
+  , sourcedir :: FilePath     -- ^ directory that contains the tests
+  , basedir :: FilePath       -- ^ directory to run tests in
+  , scriptdirs :: [FilePath]  -- ^ directories with test scripts to scan
+  , formats :: [PatchFormat]
+  , diffalgs :: [DiffAlgorithm]
+  , runfailing :: Bool
+  }
+
+shellTests :: ShellTestConfig -> IO [Test]
+shellTests cfg =
+  shellToList $ do
+    dir <- select (scriptdirs cfg)
+    tf <- includeFailing (runfailing cfg) $ findTests dir
+    pf <- select (formats cfg)
+    da <- select (diffalgs cfg)
+    let test = 
+          ShellTest{patchformat=pf,diffalgorithm=da,testscript=tf,testconfig=cfg}
+        name = T.unpack $
+          filePathToText (testName tf) <>
+          " (" <> patchformatName test <> "," <> diffalgorithmName test <> ")"
+    return (Test name test)
+
+findTests :: FilePath -> Shell FilePath
+findTests = select <=< sort . findtree (suffix (".sh")) . ls
+
+includeFailing :: Bool -> Shell FilePath -> Shell FilePath
+includeFailing True = id
+includeFailing False =
+  mfilter (not . matches (prefix "failing-") . filePathToText . filename)
+
+data ShellTest = ShellTest
+  { testscript :: FilePath
+  , patchformat :: PatchFormat
+  , diffalgorithm :: DiffAlgorithm
+  , testconfig :: ShellTestConfig
+  }
+
+data Result = Success | Skipped | Failed Text
+
+instance Show Result where
+  show Success = "Success"
+  show Skipped = "Skipped"
+  show (Failed msg) = T.unpack $ T.unlines $ map ("| " <>) $ T.lines msg
+
+instance TestResultlike Running Result where
+  testSucceeded Success = True
+  testSucceeded Skipped = True
+  testSucceeded _ = False
+
+instance Testlike Running Result ShellTest where
+  testTypeName _ = "Shell"
+  runTest _ test =
+    runImprovingIO $ do
+      yieldImprovement Running
+      liftIO (runtest test)
+
+data Running = Running deriving Show
+
+runtest :: ShellTest -> IO Result
+runtest t = do
+  let cfg = testconfig t
+      tmpdir = basedir cfg
+  dir <- makeAbsolute (tmpdir </> specificTestDir t)
+  mktree dir
+  srcdir <- pwd
+  cp ("tests" </> "lib") (dir </> "lib")
+  cp ("tests" </> "network" </> "sshlib") (dir </> "sshlib")
+  cp (testscript t) (dir </> "test")
+  writeEnvFile (dir </> "env") (testEnv srcdir dir (darcspath cfg))
+  mkdir (dir </> ".darcs")
+  writeTextFile (dir </> ".darcs" </> "defaults") (defaults t)
+  -- We cannot use systemStructWithErr from turtle nor
+  -- readCreateProcessWithExitCode from process as they
+  -- don't allow us to set the handles to binary mode.
+  let process =
+        (proc "bash" ["test"])
+          { cwd=Just (encodeString dir)
+          , std_in=CreatePipe
+          , std_out=CreatePipe
+          , std_err=CreatePipe
+          }
+  (_out,err,exc) <- bracket
+    (do (Just hIn, Just hOut, Just hErr, ph) <- createProcess_ "bash test" process
+        hClose hIn
+        hSetBinaryMode hOut True
+        hSetBinaryMode hErr True
+        return (hOut, hErr, ph))
+    (\(hOut, hErr, _) -> do
+      hClose hOut
+      hClose hErr)
+    (\(hOut, hErr, ph) ->
+      runConcurrently $ (,,)
+        <$> Concurrently (T.hGetContents hOut)
+        <*> Concurrently (T.hGetContents hErr)
+        <*> Concurrently (waitForProcess ph))
+  r <-
+    case exc of
+      ExitSuccess -> return Success
+      ExitFailure n
+        | n == 200 -> return Skipped
+        | otherwise -> return (Failed err)
+  return r
+
+-- the specific subdirectory in which to run a test, depending on options
+specificTestDir :: ShellTest -> FilePath
+specificTestDir t =
+  fromText (patchformatName t) </> fromText (diffalgorithmName t) </> testName (testscript t)
+
+testName :: FilePath -> FilePath
+testName path =
+  case stripPrefix "tests/" path of
+    Just path' -> dropExtension path'
+    Nothing -> error $ "precondition: " ++ show path
+
+defaults :: ShellTest -> Text
+defaults t =
+  T.unlines
+    [ "ALL " <> patchformatName t
+    , "send no-edit-description"
+    , "ALL ignore-times"
+    , "ALL " <> diffalgorithmName t
+    ]
+
+patchformatName :: ShellTest -> Text
+patchformatName t =
+  case patchformat t of
+    PatchFormat3 -> "darcs-3"
+    PatchFormat2 -> "darcs-2"
+    PatchFormat1 -> "darcs-1"
+
+diffalgorithmName :: ShellTest -> Text
+diffalgorithmName t =
+  case diffalgorithm t of
+    PatienceDiff -> "patience"
+    MyersDiff -> "myers"
+
+writeEnvFile :: FilePath -> [(Text, Text)] -> IO ()
+writeEnvFile path =
+  writeTextFile path .
+    T.unlines .
+    map (\(k, v) -> T.concat ["export ", k, "=", v])
+
+testEnv :: FilePath -> FilePath -> FilePath -> [(Text, Text)]
+testEnv srcdir wd dd =
+  [ ("HOME", filePathForScript wd)
+  , ("TESTDATA", filePathForScript (srcdir </> "tests" </> "data"))
+  , ("TESTBIN", filePathForScript (srcdir </> "tests" </> "bin"))
+  , ("DARCS_TESTING_PREFS_DIR", filePathForScript $ wd </> ".darcs")
+  , ("EMAIL", "tester")
+  , ("GIT_AUTHOR_NAME", "tester")
+  , ("GIT_AUTHOR_EMAIL", "tester")
+  , ("GIT_COMMITTER_NAME", "tester")
+  , ("GIT_COMMITTER_EMAIL", "tester")
+  , ("DARCS_DONT_COLOR", "1")
+  , ("DARCS_DONT_ESCAPE_ANYTHING", "1")
+  , ("PATH", (filePathForScript (parent dd) <> ":$PATH"))
+  -- the DARCS variable is passed to the tests purely so they can
+  -- double-check that the darcs on the path is the expected one,
+  -- so is passed as Text directly without any translation
+  , ("DARCS", filePathToText dd)
+  , ("GHC_VERSION", T.pack $ show (__GLASGOW_HASKELL__ :: Int))
+  ]
+
+-- | Convert a 'FilePath' to a 'String' that will evaluate to the right
+-- value when put in a bash script.
+filePathForScript :: FilePath -> Text
+filePathForScript v =
+#ifdef WIN32
+  -- We have a native Windows path, but we are going to put it in an bash
+  -- script run in an environment like msys2 which works with an illusion of a
+  -- Unix style filesystem. Calling cygpath at runtime does the necessary
+  -- translation.
+  T.concat ["$(cygpath ", quotedFilePath v, ")"]
+#else
+  quotedFilePath v
+#endif
+  where
+    -- quote a 'FilePath' for shell use
+    quotedFilePath :: FilePath -> Text
+    quotedFilePath = T.pack . show . filePathToText
+
+-- utilities missing from Turtle
+
+shellToList :: Shell a -> IO [a]
+shellToList = reduce F.list
+
+matches :: Pattern a -> Text -> Bool
+matches pattern = not . null . match pattern
+
+-- this is only necessary because they insist on using 'T.Text' which is
+-- completely inappropriate for file paths and even input and output of
+-- programs
+filePathToText :: FilePath -> Text
+filePathToText path =
+  case toText path of
+    Right r -> r
+    Left r -> r -- this r is only an approximation, may fail
+
+makeAbsolute :: FilePath -> IO FilePath
+makeAbsolute path = decodeString <$> D.makeAbsolute (encodeString path)
hunk ./harness/test.hs 7
- -import Darcs.Prelude
+import Darcs.Prelude hiding ( FilePath, (<>) )
hunk ./harness/test.hs 17
- -import Darcs.Util.Exception ( die )
hunk ./harness/test.hs 18
- -import Control.Exception ( SomeException )
- -import Data.Text ( Text, pack, unpack )
- -import qualified Data.Text as T
- -import Data.List ( isPrefixOf, isSuffixOf, sort )
+import Data.List ( isSuffixOf )
hunk ./harness/test.hs 22
- -import System.FilePath( takeDirectory, takeBaseName, isAbsolute, makeRelative )
+import System.FilePath( isAbsolute )
hunk ./harness/test.hs 24
- -import Test.Framework.Providers.API
- -  ( TestResultlike(..), Testlike(..), Test, runImprovingIO, yieldImprovement, Test(..), liftIO )
+import Test.Framework.Providers.API ( Test )
hunk ./harness/test.hs 26
- -import Shelly hiding ( liftIO, run, FilePath, path )
- -import qualified Shelly
+import Turtle hiding ( shell, stderr, stdin, stdout )
hunk ./harness/test.hs 47
- --- ----------------------------------------------------------------------
- --- shell tests
- --- ----------------------------------------------------------------------
- -
- -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 :: PatchFormat
- -  , testfile :: FilePath
- -  , testdir :: Maybe FilePath -- ^ only if set explicitly
- -  , darcspath :: FilePath
- -  , diffalgorithm :: DiffAlgorithm
- -  } deriving (Typeable)
- -
- --- |Environment variable values may need translating depending
- --- on whether we are setting them directly or writing out a shell script
- --- to set them, and depending on the kind of value and the platform.
- --- This type captures the different kinds of values.
- -data EnvItem
- -  = EnvString String  -- ^ A normal string that won't need conversion
- -  | EnvFilePath Shelly.FilePath -- ^ A path on disk that may need conversion for the platform
- -
- -runtest' :: ShellTest -> Text -> Sh Result
- -runtest' (ShellTest {..}) srcdir =
- -  do wd <- pwd
- -     let env =
- -          [ ("HOME", EnvFilePath wd)
- -          , ("TESTDATA", EnvFilePath (srcdir </> "tests" </> "data"))
- -          , ("TESTBIN", EnvFilePath (srcdir </> "tests" </> "bin"))
- -          , ("DARCS_TESTING_PREFS_DIR", EnvFilePath $ wd </> ".darcs")
- -          , ("EMAIL", EnvString "tester")
- -          , ("GIT_AUTHOR_NAME", EnvString "tester")
- -          , ("GIT_AUTHOR_EMAIL", EnvString "tester")
- -          , ("GIT_COMMITTER_NAME", EnvString "tester")
- -          , ("GIT_COMMITTER_EMAIL", EnvString "tester")
- -          , ("DARCS_DONT_COLOR", EnvString "1")
- -          , ("DARCS_DONT_ESCAPE_ANYTHING", EnvString "1")
- -          , ("PATH", EnvString (takeDirectory darcspath <> ":$PATH"))
- -          -- the DARCS variable is passed to the tests purely so they can
- -          -- double-check that the darcs on the path is the expected one,
- -          -- so is passed as a string directly without any translation
- -          , ("DARCS", EnvString darcspath)
- -          , ("GHC_VERSION", EnvString $ show (__GLASGOW_HASKELL__ :: Int))
- -          ]
- -     -- we write the variables to a shell script and source them from there in ./lib,
- -     -- so that it's easy to reproduce a test failure after running the harness with -d.
- -     writefile "env" $ T.unlines $
- -        map (\(k,v) -> T.concat ["export ", k, "=", envItemForScript v]) env
- -
- -     mkdir ".darcs"
- -     writefile ".darcs/defaults" defaults
- -     _ <- onCommandHandles (initOutputHandles (\h -> hSetBinaryMode h True)) $
- -          Shelly.run "bash" [ "test" ]
- -     return Success
- -   `catch_sh` \(_::SomeException)
- -                 -> do code <- lastExitCode
- -                       case code of
- -                        200 -> return Skipped
- -                        _   -> Failed <$> unpack <$> lastStderr
- -  where defaults = pack $ unlines
- -          [ "ALL " ++ fmtstr
- -          , "send no-edit-description"
- -          , "ALL ignore-times"
- -          , "ALL " ++ daf
- -          ]
- -        fmtstr = case format of
- -                  PatchFormat3 -> "darcs-3"
- -                  PatchFormat2 -> "darcs-2"
- -                  PatchFormat1 -> "darcs-1"
- -        daf = case diffalgorithm of
- -                PatienceDiff -> "patience"
- -                MyersDiff -> "myers"
- -
- -        -- convert an 'EnvItem' to a string that will evaluate to the right value
- -        -- when embedded in a bash script
- -        envItemForScript :: EnvItem -> Text
- -        envItemForScript (EnvString v) = pack (show v)
- -        envItemForScript (EnvFilePath v) = filePathForScript v
- -
- -        -- add quotes around a 'Shelly.FilePath'
- -        quotedFilePath :: Shelly.FilePath -> Text
- -        quotedFilePath = pack . show . toTextIgnore
- -
- -        -- convert a 'Shelly.FilePath' into a string that will evaluate to the right
- -        -- value when put in a bash script
- -        filePathForScript :: Shelly.FilePath -> Text
- -#ifdef WIN32
- -        -- we have a native Windows path, but we are going to put it in an bash script
- -        -- run in an environment like msys2 which works with an illusion of a Unix style
- -        -- filesystem. Calling cygpath at runtime does the necessary translation.
- -        filePathForScript v = T.concat ["$(cygpath ", quotedFilePath v, ")"]
- -#else
- -        filePathForScript v = quotedFilePath v
- -#endif
- -
- -takeTestName :: FilePath -> Shelly.FilePath
- -takeTestName n =
- -  let n' = makeRelative "tests" n in
- -    takeBaseName (takeDirectory n') </> takeBaseName n'
- -
- -runtest :: ShellTest -> Sh Result
- -runtest t =
- - withTmp $ \dir -> do
- -  cp "tests/lib" dir
- -  cp "tests/network/sshlib" dir
- -  cp (fromText $ pack $ testfile t) (dir </> "test")
- -  srcdir <- pwd
- -  silently $ sub $ cd dir >> runtest' t (toTextIgnore srcdir)
- - where
- -  withTmp =
- -   case testdir t of
- -     Just dir -> \job -> do
- -       let d = (dir </> show (format t) </> show (diffalgorithm t) </> takeTestName (testfile t))
- -       mkdir_p d
- -       job d
- -     Nothing  -> withTmpDir
- -
- -instance Testlike Running Result ShellTest where
- -  testTypeName _ = "Shell"
- -  runTest _ test = runImprovingIO $ do yieldImprovement Running
- -                                       liftIO (shelly $ runtest test)
- -
- -shellTest :: FilePath -> PatchFormat -> Maybe FilePath -> String -> DiffAlgorithm -> Test
- -shellTest dp fmt tdir file da =
- -  Test (toString (takeTestName file) ++ " (" ++ show fmt ++ ")" ++ " (" ++ show da ++ ")") $
- -  ShellTest fmt file tdir dp da
- -
- -toString :: Shelly.FilePath -> String
- -toString = unpack . toTextIgnore
- -
- -findShell :: FilePath -> Text -> Maybe FilePath -> Bool -> [DiffAlgorithm] -> [PatchFormat] -> Sh [Test]
- -findShell dp sdir tdir isFailing diffAlgorithms repoFormats =
- -  do files <- ls (fromText sdir)
- -     let test_files = sort $ filter relevant $ filter (hasExt "sh") files
- -     return [ shellTest dp fmt tdir file da
- -            | file <- map toString test_files
- -            , fmt <- repoFormats
- -            , da <- diffAlgorithms ]
- -  where relevant = (if isFailing then id else not) . ("failing-" `isPrefixOf`) . takeBaseName . toString
- -
hunk ./harness/test.hs 64
- -                     , testDir :: Maybe FilePath
+                     , testDir :: Maybe String
hunk ./harness/test.hs 106
- -             ++ concat [ ["-t", x ] | x <- tests conf ]
+             ++ concat [ ["-t", t ] | t <- tests conf ]
hunk ./harness/test.hs 115
- -       Nothing -> return ()
- -       Just d  -> do e <- shelly (test_e (fromText $ pack d))
- -                     when e $ die ("Directory " ++ d ++ " already exists. Cowardly exiting")
+        Nothing -> return ()
+        Just td -> do
+          exists <- testdir (fromString td)
+          when exists $
+            die ("Directory " <> fromString td <> " already exists. Cowardly exiting")
hunk ./harness/test.hs 124
- -    when (shell conf || network conf || failing conf) $ do
+
+    let exeSuffix :: String
+#ifdef WIN32
+        exeSuffix = ".exe"
+#else
+        exeSuffix = ""
+#endif
+
+    when (shell conf || network conf) $ do
hunk ./harness/test.hs 140
- -    let repoFormat    = (if darcs1 conf then (PatchFormat1:) else id)
- -                      . (if darcs2 conf then (PatchFormat2:) else id)
- -                      . (if darcs3 conf then (PatchFormat3:) else id)
- -                      $ []
- -    let diffAlgorithm = (if myers conf then (MyersDiff:) else id)
- -                      . (if patience conf then (PatienceDiff:) else id)
- -                      $ []
+    let repoFormats    = (if darcs1 conf then (PatchFormat1:) else id)
+                       . (if darcs2 conf then (PatchFormat2:) else id)
+                       . (if darcs3 conf then (PatchFormat3:) else id)
+                       $ []
+    let diffAlgorithms = (if myers conf then (MyersDiff:) else id)
+                       . (if patience conf then (PatienceDiff:) else id)
+                       $ []
+    let scriptDirs     = (if shell conf then ("tests":) else id)
+                       . (if network conf then ("tests"</>"network":) else id)
+                       $ []
+
+    wd <- pwd
hunk ./harness/test.hs 153
- -    stests <- shelly $
- -      if shell conf
- -        then findShell darcsBin "tests" (testDir conf) (failing conf) diffAlgorithm repoFormat
- -        else return []
- -    utests <- if unit conf then doUnit else return []
- -    ntests <- shelly $ if network conf then findShell darcsBin "tests/network" (testDir conf) (failing conf) diffAlgorithm repoFormat else return []
- -    hstests <- if hashed conf then doHashed else return []
- -    defaultMainWithArgs (stests ++ utests ++ ntests ++ hstests) args
- -       where
- -          exeSuffix :: String
- -#ifdef WIN32
- -          exeSuffix = ".exe"
- -#else
- -          exeSuffix = ""
- -#endif
+    let runTests td = do
+          stests <-
+            shellTests ShellTestConfig
+              { darcspath = fromString darcsBin
+              , sourcedir  = wd
+              , basedir = td
+              , scriptdirs = scriptDirs
+              , formats = repoFormats
+              , diffalgs = diffAlgorithms
+              , runfailing = failing conf
+              }
+          utests <- if unit conf then doUnit else return []
+          hstests <- if hashed conf then doHashed else return []
+          defaultMainWithArgs (stests ++ utests ++ hstests) args
+
+    case fromString <$> testDir conf of
+      Just td -> do
+        mktree td
+        runTests td
+      Nothing ->
+        with (mktempdir "." "darcs-test") runTests
hunk ./harness/test.hs 191
+              , darcs3   = True

[TEST PATCH
Ben Franksen <ben.franksen at online.de>**20200520094006
 Ignore-this: 22c56935a21976fc4d269a60c138e4f8590f85dabd3c4233c4037fe69e486b743012c4073cfc298e
] hunk ./harness/Darcs/Test/Shell.hs 144
+  (exc,_out,err) <-
+    systemStrictWithErr (proc "bash" ["test"]) {cwd = Just (encodeString dir)} empty
+{-
hunk ./harness/Darcs/Test/Shell.hs 168
+-}

Context:

[harness: properly translate env script on Windows
Ganesh Sittampalam <ganesh at earth.li>**20190826201843
 Ignore-this: 8aeec4ecdcfce78075c5be4debfe286f
 
 We have Windows paths in Haskell but we need
 Unix style paths in the env script
 
] 
[harness: windows fixes for env file
Ganesh Sittampalam <ganesh at earth.li>**20190825133243
 Ignore-this: 90f2ef59c1f45c5c46d180b3ceeb75d1
 
 This corrects issues on Windows introduced by
 "harness: create an environment file and source it
 from tests/lib"
 
] 
[massive boilerplate reduction in test harness
Ben Franksen <ben.franksen at online.de>**20200216085332
 Ignore-this: 2ffc7cabc51171648141e20e5832ffaf23eb3bfb8d90e6a8c6e7f0769bfefaf11622701a86927adc
 
 This patch makes a number of invasive refactors in the test harness that
 dramatically reduce the boilerplate of repeated instance Arbitrary
 definitions. Here are the main ideas:
 
 First, remove all instances for Sealed patches and keep only the ones for
 Sealed2 patches. The generators and infrastructure have been refactored to
 always take and generate Sealed2 patches. This has the beneficial
 side-effect of cleaning up a lot of the types in the testing infrastructure.
 
 For most of the remaining Arbitrary instances we can provide a single
 generic instance. To make this possible we need to use the generic model
 generator (aSmallRepo from the RepoModel class), which we always do except
 for the RepoPatchV1 tests. My solution for this was to move all the
 RepoPatchV1 tests into a separate module and throw out the tests that are
 disabled for RepoPatchV1 anyway. Even with this out of the way, I needed to
 refactor WithState and the class ArbitraryState to no longer take the
 model/state as parameter, but rather use the type function ModelOf. This,
 too, make the types simpler and signatures less verbose.
 
 Additional minor cleanups:
 - The TestGenerator/TestCondition/TestCheck machinery now lives in the
   D.T.Patch.Utils module.
 - Generalize qc_prim32/3 to qc_named_prim.
 - Removed some redundant constraints.
 - Renamed Darcs.Test.Util.TestResult.fromMaybe to avoid collision with the
   well known Data.Maybe.fromMaybe
 - Allow all darcs-lib extensions for darcs-test, too; cleanup module-local
   extension pragmas.
] 
[simplify ArbitraryState instances
Ganesh Sittampalam <ganesh at earth.li>**20200126123527
 Ignore-this: ce0845ca944d12f9f4736fde08b5b854
] 
[update darcs-test => darcs discovery for recent cabal behaviour
Ganesh Sittampalam <ganesh at earth.li>**20200126131607
 Ignore-this: 71130489b95b1805d3debf87c4434002
] 
[add combineTestResults utility
Ganesh Sittampalam <ganesh at earth.li>**20200129072310
 Ignore-this: f408c4017523a27cf65441256d47a4a6
] 
[remove obsolete comment
Ganesh Sittampalam <ganesh at earth.li>**20200131171836
 Ignore-this: 88fadb6e21899e49f586973f36a8cd94
] 
[shrinking names and file content
Ganesh Sittampalam <ganesh at earth.li>**20200209002238
 Ignore-this: 61be1064b90b1d3ae906e6aba3a08601
] 
[tests: add some more comments about ShrinkModel/PropagateShrink
Ganesh Sittampalam <ganesh at earth.li>**20200212130152
 Ignore-this: 4268562c02d9b5409c1c0dbf1bfa9ce1
] 
[tests: list MultiParamTypeClasses in the cabal file
Ganesh Sittampalam <ganesh at earth.li>**20200215145635
 Ignore-this: d8b663f4afce28f361693cbb74f3e01
 
 It's very widely used in the tests and generally we wouldn't
 think twice about using it in test code/infrastructure.
] 
[tests: remove some redundant LANGUAGE pragmas
Ganesh Sittampalam <ganesh at earth.li>**20200215145542
 Ignore-this: d52d2fac5ff315db7ae7299826ab8e2b
] 
[tests: add DefaultSignatures to .cabal file
Ganesh Sittampalam <ganesh at earth.li>**20200215144040
 Ignore-this: dec50e31599f57cc287b58602832fe13
] 
[tests: sort default-extensions
Ganesh Sittampalam <ganesh at earth.li>**20200215143632
 Ignore-this: 5799beffc4b5909536a0bdbd12e9e631
] 
[use the shrinking for MergeableSequence on existing tests
Ganesh Sittampalam <ganesh at earth.li>**20200215092921
 Ignore-this: e98eb2288d356604409adcf005701f40
] 
[remove Invert from RepoPatch constraint synonym
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: 41d2353fb0edd53d99a540d97fdc5b5b95ed37dbc044887afea0faec1697e1a153195cf93e1155
 
 This also disables tests for inverses of RepoPatches and fixes the
 permutivity test to no longer require it.
] 
[annotate: push inversion down to the prim level
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: cd2c6896b17d531e2c52e817aac241471a19e005372181d4b9061a7b2bfa8f986f123ba9382432d8
 
 We must take care that we call the annotate method only on inverted prims
 and that we traverse the history (of prims) in reverse order. To avoid
 mistakes when defining instances (outside of Darcs.Patch.Annotate), we now
 use a default method with a default signature.
] 
[get rid of the last Invert constraints for RepoPatch in rebase
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: 6abd9b5c4e7f13998f83ad7b427f2a9d8b297850b8f051c0c4932181ef79551b918b70f134890120
 
 This is done by changing the forceCommute implementation to do inversion on
 the underlying prims.
] 
[unify RebaseChange and RebaseSelect
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: 1a68ed05992b8a9e72f6ebdc99fcf1268541a0fc1755aa0516252d9cf3575ac0296560d471a345dc
] 
[use StandaloneDeriving for some Show instances
Ganesh Sittampalam <ganesh at earth.li>**20190902221900
 Ignore-this: 8ab9c2769f4f3b5610c0ab1413347605
 
 This is possible in cases where all the directly included
 patches are concrete types rather than type variables.
 
 For example it works for
 
  data Foo p wX wY where
   Foo :: Named p wX wY -> Foo p wX wY
 
 but not for
 
  data Foo p wX wY where
   Foo :: p wX wY -> Foo p wX wY
] 
[re-write Darcs.Patch.Bundle using Darcs.Util.Parser
Ben Franksen <ben.franksen at online.de>**20190902202035
 Ignore-this: 1c60e07d0a1752ff6ef1db0a27a975683b9f9f5241eef933e7b486a176fce4108c8a9c4ab3c53238
 
 This does not delete any of the old code yet. It merely renames the old
 parseBundle to parseBundleOld. The old code will be deleted in a later
 patch. It also doesn't re-implement scanContextFile yet.
] 
[rename D.P.Rebase.Container to D.P.Rebase.Suspended
Ganesh Sittampalam <ganesh at earth.li>**20190914153826
 Ignore-this: 6d8e0781683f4d6b6f242a1aca3cdd0f
 
 The module primarily contains the Suspended type and code
 to manipulate it.
 
] 
[remove bogus ReadPatch instances for RebaseSelect and RebaseChange
Ben Franksen <ben.franksen at online.de>**20190910081742
 Ignore-this: 27d4e8c0d4886e4b4b1d4a031acf4c9b0f3cb395b33aaf1daea81a8d52bb35816f4cd3557663cbba
] 
[cleanups in log command
Ben Franksen <ben.franksen at online.de>**20190912085841
 Ignore-this: beb145f355e35b98ecfcc839d9ea393cf83142098ae47fb647d5df1ac43b7aa847031601e9cc0204
] 
[RebaseFixup take a prim as type argument, not a RepoPatch
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: 67c29ae73d63aa6c0347bb01cb3fb548d9509d6128757da3d5e55d6263d6c202f48822dd3586a036
] 
[remove patch type parameter to RebaseName
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: 630b06b6ccb86f21992daf8f6371e89636a18fef9832b607ba084d971491b97a36e3c7fa0cca671f
 
 Also remove its Apply and PrimPatchBase instances.
] 
[reduce the Show1/Show2 boilerplate with DefaultSignatures
Ganesh Sittampalam <ganesh at earth.li>**20190902130857
 Ignore-this: ef867619eda2321368d1a6b2d5763aab
] 
[eliminate Invert instances for Named, WrappedNamed, and PatchInfoAnd
Ben Franksen <ben.franksen at online.de>**20190919164037
 Ignore-this: 4e554c70104c989f300cb36a846c406caf384856c96d1012e3170b066c161f13c2bb6860c8265457
] 
[remove CommuteNoConflicts from RepoPatch
Ben Franksen <ben.franksen at online.de>**20190919164038
 Ignore-this: b10430ecf5311cf6f9afe67281adf63c6370b2011c9d0e6eb94d807f72e47eed178c101f78570c60
] 
[use cleanMerge to implement partitionConflictingFL
Ben Franksen <ben.franksen at online.de>**20190919164037
 Ignore-this: f96859e6e37f5045f95a66700d65ae01e1ec4fedea4eb40df58842d75f35e6be508a92822919dba4
 
 In order to simplify this change, it no longer takes a commuter as argument
 but only works with plain FLs. This necessitates an upstream change to
 filterOutConflicts, which while (we're at it) now gets the repositoiry
 argument first, like all similar functions.
] 
[fix lazy reading of inventories for apply command
Ben Franksen <ben.franksen at online.de>**20190914180221
 Ignore-this: cfae5beaaf8687f3184852a7cb681521c39183daeb1941f85462bfd1b325220103d9b159f74dafc7
 
 This was broken by checking availability of patches to be applied in a
 complicated and inefficient way, which as a side-effect reads all local
 inventories in our history.
] 
[fix interpretation of bundles as patchsets
Ben Franksen <ben.franksen at online.de>**20190901131900
 Ignore-this: 58d5603379eb21531c461e8838782a6bc9a8fcca9a7904a0d6a8bec33c420b67be6ded7f12b27847
 
 We previously created invalid patchsets when a tag was present in the
 context of a bundle. This worked (sort of) due to laziness but only if we
 actually have that tag in our repo. If we don't then this rather dirty hack
 interprets the bundle in a wrong context, i.e. Origin. Depending on how
 findCommonAndUncommon is implemented we either get immediate errors ("cannot
 commute common patches") or it hangs indefinitely trying to perform huge
 amounts of bugus commutes of patches that aren't in their rightful context.
 
 The same bug is still present in scanContextFile.
] 
[replace CommuteNoConflicts with CleanMerge for prim patch types
Ben Franksen <ben.franksen at online.de>**20190919164037
 Ignore-this: 797a05625580c7c277159ad6032779a61e7e3c80816b747ab4008d757d74d2b369656f19b9420aa0
 
 As a logical consequence this moves the definition of mergeList from
 D.P.CommuteNoConflicts to D.P.Merge. We also explicitly call error in
 definitions of cleanMerge and merge if the patch type has an Ident instance
 and we try to merge two identical patches, since this is an undefined
 operation.
] 
[turn PrimPatch into a constraint synonym
Ben Franksen <ben.franksen at online.de>**20190829163003
 Ignore-this: 47127bef77c142a41cf44ca6718902285224f089e8c325fd3873e10d9e5514942b3b4a30852ff04
] 
[add class CleanMerge & make it super class of Merge
Ben Franksen <ben.franksen at online.de>**20190919164037
 Ignore-this: 57e6cec77040c30342bfa0958009b7324dba5ffef0b7233d322d95ba303611777761da455ac8187d
 
 This does not yet replace CommuteNoConflicts. Instead, instances for
 CleanMerge are, for now, defined in terms of mergeNoConflicts.
] 
[use showPatch ForStorage in V3 error messages
Ben Franksen <ben.franksen at online.de>**20190901200334
 Ignore-this: bfe50cc9dddf0f58bd2256f84220419c7da06685d5e23e24b513e704ba1bb763e6c8ea92afdc52d2
] 
[tests: introduce concept of shrinking models
Ganesh Sittampalam <ganesh at earth.li>**20200208172542
 Ignore-this: 1ab8bd721379b43de6bb4787e344cd2b
] 
[remove lots of redundant constraints
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: e28236636e10b3110e59361106bdbeeba9c6f24d69af6e0ffdeec0f0afa2f23fa74fc335fc11245a
] 
[remove superclass Commute from class Merge
Ben Franksen <ben.franksen at online.de>**20190910100155
 Ignore-this: 7e6a752b226cbe930df0519e7a8ab63e80a02dc539e44e04ccb54e426ff3ee4a85c4b27b19220019
] 
[Invertible: allow showPatch etc of Rev patches
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: 392d0f4a4e5222b76dc0c22d1ddcbb0d4ff4dad2de874164879a26532e2c3a77515554ab39dc9261
 
 Instead of calling error for Rev patches, requiring that the calling code
 first re-inverts the patch, we now do that ourselves. This means a Rev patch
 is shown in exactly the same way as a Fwd patch. This removes the need for
 reInvert in Darcs.UI.SelectPatches.
] 
[possible fix for D.UI.SelectChanges.selected
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: 9fc482a1070d243f41ab1d2bb5b764f71de9258e27d99bb40b85fff7b428a0a82fdcc33c8c19798e
 
 This makes it actually do what the docs claim it does. I am not sure this is
 the correct behavior, though. It also renames it to getSelected to make its
 easier to see where it is used, since the word 'selected' appears in lots of
 places in this module, but getSelected is used only in printSelected.
] 
[rename repr to reInvert and fix its haddocks
Ben Franksen <ben.franksen at online.de>**20190830081513
 Ignore-this: 60877d2cf753e7bce24bb1cccbbe92ffabd5483c532104bc1642366516c0b5df28844d87f582ab56
] 
[remove reverse constructors from RebaseSelect and RebaseChange
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: c789b18be7b8e30590578aa59909f34f64afdb9a1bc967108609940d0f680fa2d76363c90da1e9e0
] 
[rewrite Summary RebaseChange to avoid force-commute
Ganesh Sittampalam <ganesh at earth.li>**20190911134024
 Ignore-this: 65e0c112000c4d3a1025ef3d211ed0e6
] 
[simplify instance Summary RebaseChange
Ganesh Sittampalam <ganesh at earth.li>**20190903140534
 Ignore-this: a5f0306c4213dcd701fb993f54e92e84
 
 I'm not sure why it was so complicated before. Perhaps
 changeAsMerge was used elsewhere at some point.
 
 Also removed the comment about resolveConflicts which
 doesn't make much sense now.
 
] 
[use Invertible when calling lookTouch in log command
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: 617804a94451acd6261c3a0ed6edc977d2d36c73c634547316909c6a5129480ea4a06e88d00fb717
 
 We call lookTouch with the patches inverted. To get rid of the Invert
 constraint, we wrap the patch as an Invertible patch.
] 
[use Invertible to generalize runSelection
Ben Franksen <ben.franksen at online.de>**20190919164036
 Ignore-this: bfcc3d4ab562293cf8c7bc66a0d11e6f006920d1d2fd920377c97784686249928227adc7fbb77d45
 
 The new runSelection no longer requires an Invert instance for the patches.
 This is done by wrapping them internally with Invertible. We keep the old
 function under the new name runInvertibleSelection so we can use it for
 selecting prims, since these are naturally invertible and we cannot and will
 not use Splitters with wrapped Invertible patches.
] 
[matching a patch should be invariant under inversion
Ben Franksen <ben.franksen at online.de>**20190830080459
 Ignore-this: a7321c90ead98c2d1dea84b7c2752a66c159531c2d4e2034406fdca5c2be9448b3285b846b3de41b
 
 This adds a property (only in the haddocks) to D.P.Match.matchAPatch and
 removes re-inversion of patches when we apply a match criterion from
 D.UI.SelectChanges.
] 
[add Darcs.Patch.Invertible
Ben Franksen <ben.franksen at online.de>**20190919164026
 Ignore-this: 40fd44bd46e5630779a3ecebc028a33c1147785ab56dff6d0b48bc2de34cfb75bfd817a7fdcb6b3b
 
 This is a wrapper type to make an arbitrary patch type formally invertible.
 We define only instances that will be needed to statisfy Invert constraints
 that are currently required in the Repository and UI subsystem. Some of the
 class methods defined for Invertible assume the patch is actually positive.
] 
[re-export all imported classes (with members) from Darcs.Patch.RepoPatch
Ben Franksen <ben.franksen at online.de>**20190829163918
 Ignore-this: 25f54fe286b4efb9ae5bfb5d74bf47d94c263d06f762a26bda820efb7f44b1374cc8796efadbaebc
] 
[turn RepoPatch into a constraint synonym
Ben Franksen <ben.franksen at online.de>**20190829162443
 Ignore-this: 3925585e444f26e1b238e5a0df41e6aad5e9983bcce38194d0f8eb5c4bd6398ebed934ce6e95ffec
 
 This has a lot of advantages wrt maintenance and gets us rid of a few orphan
 instances. Also included a few minor cleanups in Darcs.Patch.RepoPatch.
] 
[add unapply method to class Apply
Ben Franksen <ben.franksen at online.de>**20190919164009
 Ignore-this: 831f51055ca373b7d41be78e6c582dd68cf09d6c221a63a901417e8f8c4df7bdc5bda832dce6eea1
 
 The idea here is to allow to "inverse apply" a patch without that patch
 necessarily having an Invert instance.
] 
[introduce PrimWithName and make NamedPrim a type synonym
Ganesh Sittampalam <ganesh at earth.li>**20190827114448
 Ignore-this: 934632425eaa3bc82e5769dbee7549a9
] 
[use Darcs.Util.Graph.components for RepoPatchV3
Ben Franksen <ben.franksen at online.de>**20190825211920
 Ignore-this: a6991e94f26b09f302c3a51ea09171f8fa09c9c73caa3f701f752f00c76c8274761a2dd0bdbe3d86
 
 This required a few refactors and the introduction of a new data type for
 components. In particular, the ltmis algorithm needs to be adapted to
 working with just a subset of the vertices of a graph.
] 
[simplify and improve Darcs.Util.Graph.components
Ben Franksen <ben.franksen at online.de>**20190825162606
 Ignore-this: ed2245de76947994d2a937643fb3d6c406968d7c31f779733504ed605eb15302c6dc1a3703427567
 
 It wasn't incorrect (according to the spec) but it did not always return
 vertices ordered and also did a bit too much work.
] 
[move functions to generate graphs from harness to library
Ben Franksen <ben.franksen at online.de>**20190825162321
 Ignore-this: b31586463112c753be6a0112b555f7b7f848cc5c39470ede7701a94f2268d021c1000a45e0b093a5
] 
[add Darcs.Util.Graph.components with properties and tests
Ben Franksen <ben.franksen at online.de>**20190825123434
 Ignore-this: 3d7e63f134e3528d7d1d64973bc32fb8bbd6d5ba174423d72cd2bc34e02251119394633179e0fa59
] 
[remove Darcs.Util.Graph.bk and some minor refactors
Ben Franksen <ben.franksen at online.de>**20190825123225
 Ignore-this: b3e8e66874b3692e2f417ba3c877d9573b6fc8b39507b1d28aacd80a087cd35705c524039ac64731
] 
[Darcs.Util.Graph: add hadocks
Ben Franksen <ben.franksen at online.de>**20190821084048
 Ignore-this: 7b7931bdd919da44e34ae60340f446783e1b5343dfe3aeca2b241d4b1ee25c7e514c35907bdc60ca
] 
[Darcs.Util.Graph: make helper functions local to ltmis
Ben Franksen <ben.franksen at online.de>**20190821083917
 Ignore-this: 7869236b4f6e283050b2195f54c2465091194278a9b32f210de5c6cb24b2a2f11b1f8b2a402084c6
] 
[Refactor the commute implementation for NamedPrims
Ganesh Sittampalam <ganesh at earth.li>**20190827113620
 Ignore-this: b1aabe8d5b3340a8a65a636460710dd8
 
 It now just relies on the Ident class instead of the internals.
 This also distinguishes a case that ought to be an internal error,
 but the unit tests seem to rely on it, so this is left as a
 TODO for now.
] 
[remove Invert constraint from Matchable and MatchableRP
Ben Franksen <ben.franksen at online.de>**20190830221922
 Ignore-this: e87f1de33bae746920f91cd1fa065215918ea9ee74916ff4c4b7775e93d486ff7eed15c0464a8a1e
 
 This means we need to add it to a a few function that actually require it.
 We do this as a preparation for eventually removing Invert instances from
 all the higher level patch types.
] 
[tests: add Shrinkable class
Ganesh Sittampalam <ganesh at earth.li>**20200207224817
 Ignore-this: e874b19b45a593966e1a4704a26c1c41
] 
[add ArbitraryState instance for Named
Ganesh Sittampalam <ganesh at earth.li>**20200127225640
 Ignore-this: 362778cb63746d15d1fb97334f4d6c29
] 
[tests: introduce an explicit MergeableSequence type
Ganesh Sittampalam <ganesh at earth.li>**20200209193131
 Ignore-this: e66e93547c9fb1afa63680b745289f52
] 
[use NoImplicitPrelude for test harness
Ganesh Sittampalam <ganesh at earth.li>**20200126082637
 Ignore-this: 379a4025d6db9de6c02c1c2c0f23ba62
] 
[generalize sequence generation
Ganesh Sittampalam <ganesh at earth.li>**20200127225949
 Ignore-this: 990b349ed7d9501121761f109d4a2594
] 
[specialise the types of withSingle etc
Ganesh Sittampalam <ganesh at earth.li>**20200214065131
 Ignore-this: 3fda114ae11a17b6d24fd8e86b4a00ee
 
 The new types reflect their actual usage and will make it
 easier to move logic around.
] 
[darcs.cabal: remove redundant version constraints
Ben Franksen <ben.franksen at online.de>**20200427140342
 Ignore-this: 13501612338c6df2258acfaf2f9d71c5840e14f25849f66cc874e1fd20b18e6e4c34d34789e51e31
] 
[replace quickcheck with leancheck for testing Graph properties
Ben Franksen <ben.franksen at online.de>**20190825133104
 Ignore-this: 6ef50b2fd5c131b28df5584f650b525b1e8ed1c5af17dc0a6c0ff4ecfb11022c3286e182fc8fffcd
 
 Calculating graph properties scales very badly because the specifications
 aren't optimised (naturally). Exhaustive testing with leancheck is a lot
 more effective here because we avoid testing with (too) large graphs.
 Unfortunately test-framework is a bit limited in that it doesn't allow to
 scale the number of tests, just to set them to a fixed value. We opt to
 set it to 0x8000 which covers all graphs up to size 6.
] 
[Darcs.Util.Graph: add properties and test them
Ben Franksen <ben.franksen at online.de>**20190821104132
 Ignore-this: 51c2f7127ec6bf9366b0afc8a5aee83e602505c16a12d9d69623369cff58365cccef73d31b3bd3b5
] 
[resolve conflicts after 347aeb4b5c1eccfe00956ac318a2123bca9ef9ca
Ben Franksen <ben.franksen at online.de>**20200427135437
 Ignore-this: 9217132f46b0b7fb62c71b6202f744dcc480fbc1698f602ae2537b0566051c1b676f7790d32e5fec
] 
[resolve conflicts after 5d63e665634c964d7b23dcf9c28efc72d6a6f947
Ben Franksen <ben.franksen at online.de>**20200427125216
 Ignore-this: 47121a51606f226d64d22f3a2cde9a1661672e91d4eb7c1e0e0e292c76a9883ea42377a4ea1ef2a4
] 
[add the darcs executable as a build-tool-depend of darcs-test
Ganesh Sittampalam <ganesh at earth.li>**20190826144023
 Ignore-this: d6e797d692e92855074e77520dc052cb
 
 This means we can use cabal to run the tests and be sure that the
 darcs executable they test will be up to date.
 
 Without this change, 'cabal v2-run test:darcs-test'
 (needed to run the harness with custom options) doesn't build the
 executable.
 
] 
[remove unused dependency of darcs-test on split package
Ben Franksen <ben.franksen at online.de>**20190827194508
 Ignore-this: ac442d26dba35d0d83763736d96eb9cbef783a7a081d4c765ce29f19e9a44f474c1aa10bdde7a255
] 
[loosen upper bound for shelly to <1.10
Ben Franksen <ben.franksen at online.de>**20200421081429
 Ignore-this: f2a47bfd51083a65d445bf8c0e6d85a497d3462270d55ff1d6c4c54ce31d4cb72e281bddf733739e
 
 This is required to find a build plan with ghc >= 8.8.
 
 A comment in the cabal file claims we cannot use shelly-1.9 because of two
 open issues. However, these issues only concern windows; but for windows we
 use an even stricter bound in a separate build-depend stanza, where we
 require < 1.7.2. I have moved the comment to this other stanza. The upshot
 is that building against ghc versions >= 8.8 is currently not supported on
 windows.
] 
[document why we can't bump the shelly dependency
Ganesh Sittampalam <ganesh at earth.li>**20190920184131
 Ignore-this: 3cd9ac649ec4acc2dc92027e47d10c60
] 
[clean up Darcs.Test.Patch.Check
Ben Franksen <ben.franksen at online.de>**20200426182607
 Ignore-this: fb38c25c164f284cc6b9ab7db57a5af6a0c848cc89ab6fe1add562917512c3b132c269931b0cb388
 
 There was a comment in the code about the strangeness of how in this test
 module returning a Boolean was used to communicate a failure, and how this
 should be replaced with a more conventional way of error handling. This is
 now done, using the MaybeT monad transformer.
] 
[TAG 2.15.1
Ben Franksen <ben.franksen at online.de>**20190821065908
 Ignore-this: 4e9190f24c0c02b97865896d38e42743f7276dc9a3b28e0fa2a90086da5d6734cae6224e1a3141b5
] 
Patch bundle hash:
73c1159df11449f0f71e06c56ae5b9abc84ccc0f
-----BEGIN PGP SIGNATURE-----

iHUEAREIAB0WIQS1sLTEOCbYp4iyltnTbkUxbljMlwUCXsT7KgAKCRDTbkUxbljM
lyBEAQCYBSNfyc+7yWPUd79e3h9eQnKMhoHldKO62XfjtB/ESAEAz2J4kd5iqmmT
pCDXBXYT/1vcx50pJx3C71VB4LjxejU=
=mBL8
-----END PGP SIGNATURE-----


More information about the darcs-devel mailing list