2018-02-18 15:48:48 +00:00
|
|
|
{- git-annex test suite framework
|
|
|
|
-
|
2022-03-14 19:24:37 +00:00
|
|
|
- Copyright 2010-2022 Joey Hess <id@joeyh.name>
|
2018-02-18 15:48:48 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2018-02-18 15:48:48 +00:00
|
|
|
-}
|
|
|
|
|
2019-09-24 20:59:37 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
module Test.Framework where
|
|
|
|
|
|
|
|
import Test.Tasty
|
|
|
|
import Test.Tasty.Runners
|
|
|
|
import Test.Tasty.HUnit
|
2022-03-14 19:24:37 +00:00
|
|
|
import Test.Tasty.QuickCheck
|
|
|
|
import Test.Tasty.Options
|
|
|
|
import Test.Tasty.Ingredients.Rerun
|
|
|
|
import Options.Applicative.Types
|
add small delay to avoid problems on systems with low-resolution mtime
I've seen intermittent failures of the test suite with v6 for a long time,
it seems to have possibly gotten worse with the changes around v7. Or just
being unlucky; all tests failed today.
Seen on amd64 and i386 builders, repeatedly but intermittently:
unused: FAIL (4.86s)
Test.hs:928:
git diff did not show changes to unlocked file
And I think other such failures, all involving v7/v6 mode tests.
I managed to reproduce the unused failure with --keep-failures,
and inside the repo, git diff was indeed not showing any changes for
the modified unlocked file.
The two stats will be the same other than mtime; the old and new files have
the same size and inode, since the test case writes to the file and then
overwrites it.
Indeed, notice the identical timestamps:
builder@orca:~/gitbuilder/build/.t/tmprepo335$ echo 1 > foo; stat foo; echo 2 > foo; stat foo
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.894942036 +0000
Change: 2018-10-29 22:14:10.894942036 +0000
Birth: -
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.898942036 +0000
Change: 2018-10-29 22:14:10.898942036 +0000
Birth: -
I'm seeing this in Linux VMs; it doesn't happen on my laptop. I've also
not experienced the intermittent test suite failures on my laptop.
So, I hope that this small delay will avoid the problem.
Update: I didn't, indeed I then reproduced the same failure on my
laptop, so it must be due to something else. But keeping this change anyway
since not needing to worry about lowish-resolution mtime in the test suite seems
worthwhile.
2018-10-29 22:42:20 +00:00
|
|
|
import Control.Concurrent
|
2022-03-14 19:24:37 +00:00
|
|
|
import Control.Concurrent.Async
|
|
|
|
import System.Environment (getArgs)
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
import Common
|
|
|
|
import Types.Test
|
|
|
|
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Annex.UUID
|
2018-10-25 21:23:53 +00:00
|
|
|
import qualified Types.RepoVersion
|
2018-02-18 15:48:48 +00:00
|
|
|
import qualified Backend
|
|
|
|
import qualified Git.CurrentRepo
|
|
|
|
import qualified Git.Construct
|
2019-12-02 14:57:09 +00:00
|
|
|
import qualified Git.Types
|
2020-06-23 21:41:50 +00:00
|
|
|
import qualified Git.Branch
|
|
|
|
import qualified Git.Ref
|
2018-02-18 15:48:48 +00:00
|
|
|
import qualified Types.KeySource
|
|
|
|
import qualified Types.Backend
|
|
|
|
import qualified Types
|
|
|
|
import qualified Remote
|
|
|
|
import qualified Key
|
|
|
|
import qualified Types.Key
|
|
|
|
import qualified Types.Messages
|
|
|
|
import qualified Config
|
|
|
|
import qualified Annex.WorkTree
|
|
|
|
import qualified Annex.Link
|
|
|
|
import qualified Annex.Path
|
|
|
|
import qualified Annex.Action
|
2018-11-05 17:27:16 +00:00
|
|
|
import qualified Annex.AdjustedBranch
|
2022-03-14 19:24:37 +00:00
|
|
|
import qualified Annex.Init
|
2018-02-18 15:48:48 +00:00
|
|
|
import qualified Utility.Process
|
2020-11-24 18:07:46 +00:00
|
|
|
import qualified Utility.Process.Transcript
|
2018-02-18 15:48:48 +00:00
|
|
|
import qualified Utility.Env
|
|
|
|
import qualified Utility.Env.Set
|
|
|
|
import qualified Utility.Exception
|
|
|
|
import qualified Utility.ThreadScheduler
|
|
|
|
import qualified Utility.Tmp.Dir
|
2019-06-25 15:37:52 +00:00
|
|
|
import qualified Utility.Metered
|
2018-02-18 15:48:48 +00:00
|
|
|
import qualified Command.Uninit
|
|
|
|
|
2020-11-24 18:07:46 +00:00
|
|
|
-- Run a process. The output and stderr is captured, and is only
|
|
|
|
-- displayed if the process does not return the expected value.
|
2020-11-24 21:17:09 +00:00
|
|
|
testProcess :: String -> [String] -> (Bool -> Bool) -> String -> Assertion
|
|
|
|
testProcess command params expectedret faildesc = do
|
2020-11-24 18:07:46 +00:00
|
|
|
(transcript, ret) <- Utility.Process.Transcript.processTranscript command params Nothing
|
2020-11-24 21:17:09 +00:00
|
|
|
(expectedret ret) @? (faildesc ++ " failed (transcript follows)\n" ++ transcript)
|
2020-11-24 18:07:46 +00:00
|
|
|
|
|
|
|
-- Run git. (Do not use to run git-annex as the one being tested
|
|
|
|
-- may not be in path.)
|
2020-11-24 21:17:09 +00:00
|
|
|
git :: String -> [String] -> String -> Assertion
|
|
|
|
git command params = testProcess "git" (command:params) (== True)
|
2020-11-24 18:07:46 +00:00
|
|
|
|
|
|
|
-- For when git is expected to fail.
|
2020-11-24 21:17:09 +00:00
|
|
|
git_shouldfail :: String -> [String] -> String -> Assertion
|
|
|
|
git_shouldfail command params = testProcess "git" (command:params) (== False)
|
2020-11-24 18:07:46 +00:00
|
|
|
|
2019-08-16 15:11:55 +00:00
|
|
|
-- Run git-annex.
|
2020-11-24 21:17:09 +00:00
|
|
|
git_annex :: String -> [String] -> String -> Assertion
|
|
|
|
git_annex = git_annex' (== True)
|
2018-10-30 14:49:39 +00:00
|
|
|
|
|
|
|
-- For when git-annex is expected to fail.
|
2020-11-24 21:17:09 +00:00
|
|
|
git_annex_shouldfail :: String -> [String] -> String -> Assertion
|
|
|
|
git_annex_shouldfail = git_annex' (== False)
|
|
|
|
|
|
|
|
git_annex' :: (Bool -> Bool) -> String -> [String] -> String -> Assertion
|
|
|
|
git_annex' expectedret command params faildesc = do
|
2020-11-24 18:07:46 +00:00
|
|
|
pp <- Annex.Path.programPath
|
2020-11-24 21:17:09 +00:00
|
|
|
testProcess pp (command:params) expectedret faildesc
|
2018-02-18 15:48:48 +00:00
|
|
|
|
2020-11-24 21:17:09 +00:00
|
|
|
{- Runs git-annex and returns its standard output. -}
|
2018-02-18 15:48:48 +00:00
|
|
|
git_annex_output :: String -> [String] -> IO String
|
|
|
|
git_annex_output command params = do
|
|
|
|
pp <- Annex.Path.programPath
|
2019-08-16 15:11:55 +00:00
|
|
|
Utility.Process.readProcess pp (command:params)
|
2018-02-18 15:48:48 +00:00
|
|
|
|
2020-11-24 21:17:09 +00:00
|
|
|
git_annex_expectoutput :: String -> [String] -> [String] -> Assertion
|
2018-02-18 15:48:48 +00:00
|
|
|
git_annex_expectoutput command params expected = do
|
|
|
|
got <- lines <$> git_annex_output command params
|
|
|
|
got == expected @? ("unexpected value running " ++ command ++ " " ++ show params ++ " -- got: " ++ show got ++ " expected: " ++ show expected)
|
|
|
|
|
|
|
|
-- Runs an action in the current annex. Note that shutdown actions
|
|
|
|
-- are not run; this should only be used for actions that query state.
|
|
|
|
annexeval :: Types.Annex a -> IO a
|
|
|
|
annexeval a = do
|
|
|
|
s <- Annex.new =<< Git.CurrentRepo.get
|
|
|
|
Annex.eval s $ do
|
|
|
|
Annex.setOutput Types.Messages.QuietOutput
|
|
|
|
a `finally` Annex.Action.stopCoProcesses
|
|
|
|
|
2020-04-29 19:48:09 +00:00
|
|
|
innewrepo :: IO () -> IO ()
|
2018-02-18 15:48:48 +00:00
|
|
|
innewrepo a = withgitrepo $ \r -> indir r a
|
|
|
|
|
2020-04-29 19:48:09 +00:00
|
|
|
inmainrepo :: IO a -> IO a
|
2019-08-08 18:29:28 +00:00
|
|
|
inmainrepo a = do
|
|
|
|
d <- mainrepodir
|
|
|
|
indir d a
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
with_ssh_origin :: (Assertion -> Assertion) -> (Assertion -> Assertion)
|
|
|
|
with_ssh_origin cloner a = cloner $ do
|
2021-08-11 00:45:02 +00:00
|
|
|
let k = Git.Types.ConfigKey (encodeBS config)
|
2019-12-05 18:36:43 +00:00
|
|
|
let v = Git.Types.ConfigValue (toRawFilePath "/dev/null")
|
2020-11-02 20:31:28 +00:00
|
|
|
origindir <- absPath . Git.Types.fromConfigValue
|
|
|
|
=<< annexeval (Config.getConfig k v)
|
|
|
|
let originurl = "localhost:" ++ fromRawFilePath origindir
|
2020-11-24 21:17:09 +00:00
|
|
|
git "config" [config, originurl] "git config failed"
|
2018-02-18 15:48:48 +00:00
|
|
|
a
|
|
|
|
where
|
|
|
|
config = "remote.origin.url"
|
|
|
|
|
|
|
|
intmpclonerepo :: Assertion -> Assertion
|
|
|
|
intmpclonerepo a = withtmpclonerepo $ \r -> indir r a
|
|
|
|
|
|
|
|
checkRepo :: Types.Annex a -> FilePath -> IO a
|
|
|
|
checkRepo getval d = do
|
2020-11-02 20:31:28 +00:00
|
|
|
s <- Annex.new =<< Git.Construct.fromPath (toRawFilePath d)
|
2018-02-18 15:48:48 +00:00
|
|
|
Annex.eval s $
|
|
|
|
getval `finally` Annex.Action.stopCoProcesses
|
|
|
|
|
|
|
|
intmpbareclonerepo :: Assertion -> Assertion
|
|
|
|
intmpbareclonerepo a = withtmpclonerepo' (newCloneRepoConfig { bareClone = True } ) $
|
|
|
|
\r -> indir r a
|
|
|
|
|
|
|
|
intmpsharedclonerepo :: Assertion -> Assertion
|
|
|
|
intmpsharedclonerepo a = withtmpclonerepo' (newCloneRepoConfig { sharedClone = True } ) $
|
|
|
|
\r -> indir r a
|
|
|
|
|
|
|
|
withtmpclonerepo :: (FilePath -> Assertion) -> Assertion
|
|
|
|
withtmpclonerepo = withtmpclonerepo' newCloneRepoConfig
|
|
|
|
|
|
|
|
withtmpclonerepo' :: CloneRepoConfig -> (FilePath -> Assertion) -> Assertion
|
|
|
|
withtmpclonerepo' cfg a = do
|
|
|
|
dir <- tmprepodir
|
2019-08-08 18:29:28 +00:00
|
|
|
maindir <- mainrepodir
|
|
|
|
clone <- clonerepo maindir dir cfg
|
2018-02-18 15:48:48 +00:00
|
|
|
r <- tryNonAsync (a clone)
|
|
|
|
case r of
|
|
|
|
Right () -> return ()
|
|
|
|
Left e -> do
|
|
|
|
whenM (keepFailures <$> getTestMode) $
|
|
|
|
putStrLn $ "** Preserving repo for failure analysis in " ++ clone
|
|
|
|
throwM e
|
|
|
|
|
|
|
|
disconnectOrigin :: Assertion
|
2020-11-24 21:17:09 +00:00
|
|
|
disconnectOrigin = git "remote" ["rm", "origin"] "remote rm"
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
withgitrepo :: (FilePath -> Assertion) -> Assertion
|
2019-08-08 18:29:28 +00:00
|
|
|
withgitrepo a = do
|
|
|
|
maindir <- mainrepodir
|
|
|
|
bracket (setuprepo maindir) return a
|
2018-02-18 15:48:48 +00:00
|
|
|
|
2018-11-05 17:27:16 +00:00
|
|
|
indir :: FilePath -> IO a -> IO a
|
2018-02-18 15:48:48 +00:00
|
|
|
indir dir a = do
|
|
|
|
currdir <- getCurrentDirectory
|
|
|
|
-- Assertion failures throw non-IO errors; catch
|
|
|
|
-- any type of error and change back to currdir before
|
|
|
|
-- rethrowing.
|
2018-11-05 17:27:16 +00:00
|
|
|
r <- bracket_
|
2022-03-14 19:24:37 +00:00
|
|
|
(changeToTopDir dir)
|
2018-11-05 17:27:16 +00:00
|
|
|
(setCurrentDirectory currdir)
|
|
|
|
(tryNonAsync a)
|
2018-02-18 15:48:48 +00:00
|
|
|
case r of
|
2018-11-05 17:27:16 +00:00
|
|
|
Right v -> return v
|
2018-02-18 15:48:48 +00:00
|
|
|
Left e -> throwM e
|
|
|
|
|
2018-11-05 17:27:16 +00:00
|
|
|
adjustedbranchsupported :: FilePath -> IO Bool
|
2019-08-30 17:54:57 +00:00
|
|
|
adjustedbranchsupported repo = indir repo $ Annex.AdjustedBranch.isGitVersionSupported
|
2018-11-05 17:27:16 +00:00
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
setuprepo :: FilePath -> IO FilePath
|
|
|
|
setuprepo dir = do
|
|
|
|
cleanup dir
|
2020-11-24 21:17:09 +00:00
|
|
|
git "init" ["-q", dir] "git init"
|
2018-02-18 15:48:48 +00:00
|
|
|
configrepo dir
|
|
|
|
return dir
|
|
|
|
|
|
|
|
data CloneRepoConfig = CloneRepoConfig
|
|
|
|
{ bareClone :: Bool
|
|
|
|
, sharedClone :: Bool
|
|
|
|
}
|
|
|
|
|
|
|
|
newCloneRepoConfig :: CloneRepoConfig
|
|
|
|
newCloneRepoConfig = CloneRepoConfig
|
|
|
|
{ bareClone = False
|
|
|
|
, sharedClone = False
|
|
|
|
}
|
|
|
|
|
|
|
|
-- clones are always done as local clones; we cannot test ssh clones
|
|
|
|
clonerepo :: FilePath -> FilePath -> CloneRepoConfig -> IO FilePath
|
|
|
|
clonerepo old new cfg = do
|
|
|
|
cleanup new
|
|
|
|
let cloneparams = catMaybes
|
2020-11-24 18:07:46 +00:00
|
|
|
[ Just "-q"
|
|
|
|
, if bareClone cfg then Just "--bare" else Nothing
|
|
|
|
, if sharedClone cfg then Just "--shared" else Nothing
|
|
|
|
, Just old
|
|
|
|
, Just new
|
2018-02-18 15:48:48 +00:00
|
|
|
]
|
2020-11-24 21:17:09 +00:00
|
|
|
git "clone" cloneparams "git clone"
|
2018-02-18 15:48:48 +00:00
|
|
|
configrepo new
|
|
|
|
indir new $ do
|
|
|
|
ver <- annexVersion <$> getTestMode
|
2020-11-24 21:17:09 +00:00
|
|
|
git_annex "init"
|
|
|
|
[ "-q"
|
|
|
|
, new, "--version"
|
|
|
|
, show (Types.RepoVersion.fromRepoVersion ver)
|
|
|
|
]
|
|
|
|
"git annex init"
|
2018-02-18 15:48:48 +00:00
|
|
|
unless (bareClone cfg) $
|
|
|
|
indir new $
|
|
|
|
setupTestMode
|
|
|
|
return new
|
|
|
|
|
|
|
|
configrepo :: FilePath -> IO ()
|
|
|
|
configrepo dir = indir dir $ do
|
|
|
|
-- ensure git is set up to let commits happen
|
2020-11-24 18:07:46 +00:00
|
|
|
git "config" ["user.name", "Test User"]
|
2020-11-24 21:17:09 +00:00
|
|
|
"git config"
|
2020-11-24 18:07:46 +00:00
|
|
|
git "config" ["user.email", "test@example.com"]
|
2020-11-24 21:17:09 +00:00
|
|
|
"git config"
|
2018-02-18 15:48:48 +00:00
|
|
|
-- avoid signed commits by test suite
|
2020-11-24 18:07:46 +00:00
|
|
|
git "config" ["commit.gpgsign", "false"]
|
2020-11-24 21:17:09 +00:00
|
|
|
"git config"
|
2018-02-18 15:48:48 +00:00
|
|
|
-- tell git-annex to not annex the ingitfile
|
2020-11-24 18:07:46 +00:00
|
|
|
git "config" ["annex.largefiles", "exclude=" ++ ingitfile]
|
2020-11-24 21:17:09 +00:00
|
|
|
"git config annex.largefiles"
|
2018-02-18 15:48:48 +00:00
|
|
|
|
2022-03-14 19:24:37 +00:00
|
|
|
ensuredir :: FilePath -> IO ()
|
|
|
|
ensuredir d = do
|
|
|
|
e <- doesDirectoryExist d
|
2018-02-18 15:48:48 +00:00
|
|
|
unless e $
|
2022-03-14 19:24:37 +00:00
|
|
|
createDirectory d
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
{- Prevent global git configs from affecting the test suite. -}
|
|
|
|
isolateGitConfig :: IO a -> IO a
|
|
|
|
isolateGitConfig a = Utility.Tmp.Dir.withTmpDir "testhome" $ \tmphome -> do
|
2020-11-02 20:31:28 +00:00
|
|
|
tmphomeabs <- fromRawFilePath <$> absPath (toRawFilePath tmphome)
|
2018-02-18 15:48:48 +00:00
|
|
|
Utility.Env.Set.setEnv "HOME" tmphomeabs True
|
|
|
|
Utility.Env.Set.setEnv "XDG_CONFIG_HOME" tmphomeabs True
|
|
|
|
Utility.Env.Set.setEnv "GIT_CONFIG_NOSYSTEM" "1" True
|
|
|
|
a
|
|
|
|
|
2019-09-24 20:59:37 +00:00
|
|
|
removeDirectoryForCleanup :: FilePath -> IO ()
|
2019-09-24 21:32:33 +00:00
|
|
|
#if MIN_VERSION_directory(1,2,7)
|
2019-09-24 20:59:37 +00:00
|
|
|
removeDirectoryForCleanup = removePathForcibly
|
|
|
|
#else
|
|
|
|
removeDirectoryForCleanup = removeDirectoryRecursive
|
|
|
|
#endif
|
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
cleanup :: FilePath -> IO ()
|
|
|
|
cleanup dir = whenM (doesDirectoryExist dir) $ do
|
|
|
|
Command.Uninit.prepareRemoveAnnexDir' dir
|
|
|
|
-- This can fail if files in the directory are still open by a
|
|
|
|
-- subprocess.
|
2019-09-24 20:59:37 +00:00
|
|
|
void $ tryIO $ removeDirectoryForCleanup dir
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
finalCleanup :: IO ()
|
|
|
|
finalCleanup = whenM (doesDirectoryExist tmpdir) $ do
|
|
|
|
Command.Uninit.prepareRemoveAnnexDir' tmpdir
|
2019-09-24 20:59:37 +00:00
|
|
|
catchIO (removeDirectoryForCleanup tmpdir) $ \e -> do
|
2018-02-18 15:48:48 +00:00
|
|
|
print e
|
|
|
|
putStrLn "sleeping 10 seconds and will retry directory cleanup"
|
|
|
|
Utility.ThreadScheduler.threadDelaySeconds $
|
|
|
|
Utility.ThreadScheduler.Seconds 10
|
2020-09-25 15:47:34 +00:00
|
|
|
whenM (doesDirectoryExist tmpdir) $
|
2019-09-24 20:59:37 +00:00
|
|
|
removeDirectoryForCleanup tmpdir
|
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
checklink :: FilePath -> Assertion
|
2019-08-26 19:07:10 +00:00
|
|
|
checklink f = ifM (annexeval Config.crippledFileSystem)
|
2019-11-26 19:27:22 +00:00
|
|
|
( (isJust <$> annexeval (Annex.Link.getAnnexLinkTarget (toRawFilePath f)))
|
2019-08-26 19:07:10 +00:00
|
|
|
@? f ++ " is not a (crippled) symlink"
|
|
|
|
, do
|
|
|
|
s <- getSymbolicLinkStatus f
|
|
|
|
isSymbolicLink s @? f ++ " is not a symlink"
|
|
|
|
)
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
checkregularfile :: FilePath -> Assertion
|
|
|
|
checkregularfile f = do
|
|
|
|
s <- getSymbolicLinkStatus f
|
|
|
|
isRegularFile s @? f ++ " is not a normal file"
|
|
|
|
return ()
|
|
|
|
|
|
|
|
checkdoesnotexist :: FilePath -> Assertion
|
|
|
|
checkdoesnotexist f =
|
|
|
|
(either (const True) (const False) <$> Utility.Exception.tryIO (getSymbolicLinkStatus f))
|
|
|
|
@? f ++ " exists unexpectedly"
|
|
|
|
|
|
|
|
checkexists :: FilePath -> Assertion
|
|
|
|
checkexists f =
|
|
|
|
(either (const False) (const True) <$> Utility.Exception.tryIO (getSymbolicLinkStatus f))
|
|
|
|
@? f ++ " does not exist"
|
|
|
|
|
|
|
|
checkcontent :: FilePath -> Assertion
|
|
|
|
checkcontent f = do
|
|
|
|
c <- Utility.Exception.catchDefaultIO "could not read file" $ readFile f
|
|
|
|
assertEqual ("checkcontent " ++ f) (content f) c
|
|
|
|
|
|
|
|
checkunwritable :: FilePath -> Assertion
|
2019-08-26 19:07:10 +00:00
|
|
|
checkunwritable f = do
|
2018-02-18 15:48:48 +00:00
|
|
|
-- Look at permissions bits rather than trying to write or
|
|
|
|
-- using fileAccess because if run as root, any file can be
|
|
|
|
-- modified despite permissions.
|
|
|
|
s <- getFileStatus f
|
|
|
|
let mode = fileMode s
|
|
|
|
when (mode == mode `unionFileModes` ownerWriteMode) $
|
|
|
|
assertFailure $ "able to modify annexed file's " ++ f ++ " content"
|
|
|
|
|
|
|
|
checkwritable :: FilePath -> Assertion
|
|
|
|
checkwritable f = do
|
|
|
|
s <- getFileStatus f
|
|
|
|
let mode = fileMode s
|
|
|
|
unless (mode == mode `unionFileModes` ownerWriteMode) $
|
|
|
|
assertFailure $ "unable to modify " ++ f
|
|
|
|
|
|
|
|
checkdangling :: FilePath -> Assertion
|
|
|
|
checkdangling f = ifM (annexeval Config.crippledFileSystem)
|
|
|
|
( return () -- probably no real symlinks to test
|
|
|
|
, do
|
|
|
|
r <- tryIO $ readFile f
|
|
|
|
case r of
|
|
|
|
Left _ -> return () -- expected; dangling link
|
|
|
|
Right _ -> assertFailure $ f ++ " was not a dangling link as expected"
|
|
|
|
)
|
|
|
|
|
|
|
|
checklocationlog :: FilePath -> Bool -> Assertion
|
|
|
|
checklocationlog f expected = do
|
|
|
|
thisuuid <- annexeval Annex.UUID.getUUID
|
2020-07-10 18:17:35 +00:00
|
|
|
r <- annexeval $ Annex.WorkTree.lookupKey (toRawFilePath f)
|
2018-02-18 15:48:48 +00:00
|
|
|
case r of
|
|
|
|
Just k -> do
|
|
|
|
uuids <- annexeval $ Remote.keyLocations k
|
2019-01-14 17:03:35 +00:00
|
|
|
assertEqual ("bad content in location log for " ++ f ++ " key " ++ Key.serializeKey k ++ " uuid " ++ show thisuuid)
|
2018-02-18 15:48:48 +00:00
|
|
|
expected (thisuuid `elem` uuids)
|
|
|
|
_ -> assertFailure $ f ++ " failed to look up key"
|
|
|
|
|
|
|
|
checkbackend :: FilePath -> Types.Backend -> Assertion
|
|
|
|
checkbackend file expected = do
|
|
|
|
b <- annexeval $ maybe (return Nothing) (Backend.getBackend file)
|
2020-07-10 18:17:35 +00:00
|
|
|
=<< Annex.WorkTree.lookupKey (toRawFilePath file)
|
2018-02-18 15:48:48 +00:00
|
|
|
assertEqual ("backend for " ++ file) (Just expected) b
|
|
|
|
|
|
|
|
checkispointerfile :: FilePath -> Assertion
|
2019-11-26 19:27:22 +00:00
|
|
|
checkispointerfile f = unlessM (isJust <$> Annex.Link.isPointerFile (toRawFilePath f)) $
|
2018-02-18 15:48:48 +00:00
|
|
|
assertFailure $ f ++ " is not a pointer file"
|
|
|
|
|
|
|
|
inlocationlog :: FilePath -> Assertion
|
|
|
|
inlocationlog f = checklocationlog f True
|
|
|
|
|
|
|
|
notinlocationlog :: FilePath -> Assertion
|
|
|
|
notinlocationlog f = checklocationlog f False
|
|
|
|
|
|
|
|
runchecks :: [FilePath -> Assertion] -> FilePath -> Assertion
|
|
|
|
runchecks [] _ = return ()
|
|
|
|
runchecks (a:as) f = do
|
|
|
|
a f
|
|
|
|
runchecks as f
|
|
|
|
|
|
|
|
annexed_notpresent :: FilePath -> Assertion
|
2019-08-09 15:06:54 +00:00
|
|
|
annexed_notpresent f = ifM (hasUnlockedFiles <$> getTestMode)
|
2018-02-18 15:48:48 +00:00
|
|
|
( annexed_notpresent_unlocked f
|
|
|
|
, annexed_notpresent_locked f
|
|
|
|
)
|
|
|
|
|
|
|
|
annexed_notpresent_locked :: FilePath -> Assertion
|
|
|
|
annexed_notpresent_locked = runchecks [checklink, checkdangling, notinlocationlog]
|
|
|
|
|
|
|
|
annexed_notpresent_unlocked :: FilePath -> Assertion
|
|
|
|
annexed_notpresent_unlocked = runchecks [checkregularfile, checkispointerfile, notinlocationlog]
|
|
|
|
|
|
|
|
annexed_present :: FilePath -> Assertion
|
2019-08-09 15:06:54 +00:00
|
|
|
annexed_present f = ifM (hasUnlockedFiles <$> getTestMode)
|
2018-02-18 15:48:48 +00:00
|
|
|
( annexed_present_unlocked f
|
|
|
|
, annexed_present_locked f
|
|
|
|
)
|
|
|
|
|
|
|
|
annexed_present_locked :: FilePath -> Assertion
|
|
|
|
annexed_present_locked f = ifM (annexeval Config.crippledFileSystem)
|
|
|
|
( runchecks [checklink, inlocationlog] f
|
|
|
|
, runchecks [checklink, checkcontent, checkunwritable, inlocationlog] f
|
|
|
|
)
|
|
|
|
|
|
|
|
annexed_present_unlocked :: FilePath -> Assertion
|
|
|
|
annexed_present_unlocked = runchecks
|
|
|
|
[checkregularfile, checkcontent, checkwritable, inlocationlog]
|
2019-08-09 17:33:29 +00:00
|
|
|
|
|
|
|
annexed_present_imported :: FilePath -> Assertion
|
|
|
|
annexed_present_imported f = ifM (annexeval Config.crippledFileSystem)
|
|
|
|
( annexed_present_unlocked f
|
|
|
|
, ifM (adjustedUnlockedBranch <$> getTestMode)
|
|
|
|
( annexed_present_unlocked f
|
|
|
|
, annexed_present_locked f
|
|
|
|
)
|
|
|
|
)
|
|
|
|
|
|
|
|
annexed_notpresent_imported :: FilePath -> Assertion
|
|
|
|
annexed_notpresent_imported f = ifM (annexeval Config.crippledFileSystem)
|
|
|
|
( annexed_notpresent_unlocked f
|
|
|
|
, ifM (adjustedUnlockedBranch <$> getTestMode)
|
|
|
|
( annexed_notpresent_unlocked f
|
|
|
|
, annexed_notpresent_locked f
|
|
|
|
)
|
|
|
|
)
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
unannexed :: FilePath -> Assertion
|
|
|
|
unannexed = runchecks [checkregularfile, checkcontent, checkwritable]
|
|
|
|
|
2021-05-10 18:19:24 +00:00
|
|
|
-- Check that a file is unannexed, but also that what's recorded in git
|
|
|
|
-- is not an annexed file.
|
|
|
|
unannexed_in_git :: FilePath -> Assertion
|
|
|
|
unannexed_in_git f = do
|
|
|
|
unannexed f
|
|
|
|
r <- annexeval $ Annex.WorkTree.lookupKey (toRawFilePath f)
|
|
|
|
case r of
|
|
|
|
Just _k -> assertFailure $ f ++ " is annexed in git"
|
|
|
|
Nothing -> return ()
|
|
|
|
|
2020-11-24 21:17:09 +00:00
|
|
|
add_annex :: FilePath -> String -> Assertion
|
|
|
|
add_annex f faildesc = ifM (unlockedFiles <$> getTestMode)
|
|
|
|
( git "add" [f] faildesc
|
|
|
|
, git_annex "add" [f] faildesc
|
2018-02-18 15:48:48 +00:00
|
|
|
)
|
|
|
|
|
|
|
|
data TestMode = TestMode
|
2019-08-26 19:07:10 +00:00
|
|
|
{ unlockedFiles :: Bool
|
2019-08-09 15:06:54 +00:00
|
|
|
, adjustedUnlockedBranch :: Bool
|
2018-10-25 21:23:53 +00:00
|
|
|
, annexVersion :: Types.RepoVersion.RepoVersion
|
2018-02-18 15:48:48 +00:00
|
|
|
, keepFailures :: Bool
|
|
|
|
} deriving (Read, Show)
|
|
|
|
|
2018-10-25 21:23:53 +00:00
|
|
|
testMode :: TestOptions -> Types.RepoVersion.RepoVersion -> TestMode
|
2018-02-18 15:48:48 +00:00
|
|
|
testMode opts v = TestMode
|
2019-08-26 19:07:10 +00:00
|
|
|
{ unlockedFiles = False
|
2019-08-09 15:06:54 +00:00
|
|
|
, adjustedUnlockedBranch = False
|
2018-02-18 15:48:48 +00:00
|
|
|
, annexVersion = v
|
|
|
|
, keepFailures = keepFailuresOption opts
|
|
|
|
}
|
|
|
|
|
2019-08-09 15:06:54 +00:00
|
|
|
hasUnlockedFiles :: TestMode -> Bool
|
|
|
|
hasUnlockedFiles m = unlockedFiles m || adjustedUnlockedBranch m
|
|
|
|
|
2020-04-30 16:59:20 +00:00
|
|
|
withTestMode :: TestMode -> Maybe TestTree -> TestTree -> TestTree
|
|
|
|
withTestMode testmode minittests = withResource prepare release . const
|
2018-02-18 15:48:48 +00:00
|
|
|
where
|
|
|
|
prepare = do
|
|
|
|
setTestMode testmode
|
2019-08-08 18:29:28 +00:00
|
|
|
setmainrepodir =<< newmainrepodir
|
2020-04-30 16:59:20 +00:00
|
|
|
case minittests of
|
|
|
|
Just inittests ->
|
|
|
|
case tryIngredients [consoleTestReporter] mempty inittests of
|
|
|
|
Nothing -> error "No tests found!?"
|
|
|
|
Just act -> unlessM act $
|
|
|
|
error "init tests failed! cannot continue"
|
|
|
|
Nothing -> return ()
|
2019-08-08 18:29:28 +00:00
|
|
|
release _ = noop
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
setTestMode :: TestMode -> IO ()
|
|
|
|
setTestMode testmode = do
|
|
|
|
currdir <- getCurrentDirectory
|
|
|
|
p <- Utility.Env.getEnvDefault "PATH" ""
|
2022-03-01 20:08:55 +00:00
|
|
|
pp <- Annex.Path.programPath
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
mapM_ (\(var, val) -> Utility.Env.Set.setEnv var val True)
|
2022-03-01 20:08:55 +00:00
|
|
|
-- Ensure that the same git-annex binary that is running
|
|
|
|
-- git-annex test is at the front of the PATH.
|
|
|
|
[ ("PATH", takeDirectory pp ++ [searchPathSeparator] ++ p)
|
2018-02-18 15:48:48 +00:00
|
|
|
, ("TOPDIR", currdir)
|
|
|
|
-- Avoid git complaining if it cannot determine the user's
|
|
|
|
-- email address, or exploding if it doesn't know the user's
|
|
|
|
-- name.
|
|
|
|
, ("GIT_AUTHOR_EMAIL", "test@example.com")
|
|
|
|
, ("GIT_AUTHOR_NAME", "git-annex test")
|
|
|
|
, ("GIT_COMMITTER_EMAIL", "test@example.com")
|
|
|
|
, ("GIT_COMMITTER_NAME", "git-annex test")
|
|
|
|
-- force gpg into batch mode for the tests
|
|
|
|
, ("GPG_BATCH", "1")
|
|
|
|
-- Make git and git-annex access ssh remotes on the local
|
|
|
|
-- filesystem, without using ssh at all.
|
|
|
|
, ("GIT_SSH_COMMAND", "git-annex test --fakessh --")
|
|
|
|
, ("GIT_ANNEX_USE_GIT_SSH", "1")
|
|
|
|
, ("TESTMODE", show testmode)
|
|
|
|
]
|
2021-08-03 16:18:10 +00:00
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
runFakeSsh :: [String] -> IO ()
|
|
|
|
runFakeSsh ("-n":ps) = runFakeSsh ps
|
2020-06-03 19:48:09 +00:00
|
|
|
runFakeSsh (_host:cmd:[]) =
|
|
|
|
withCreateProcess (shell cmd) $
|
|
|
|
\_ _ _ pid -> exitWith =<< waitForProcess pid
|
2018-02-18 15:48:48 +00:00
|
|
|
runFakeSsh ps = error $ "fake ssh option parse error: " ++ show ps
|
|
|
|
|
|
|
|
getTestMode :: IO TestMode
|
|
|
|
getTestMode = Prelude.read <$> Utility.Env.getEnvDefault "TESTMODE" ""
|
|
|
|
|
|
|
|
setupTestMode :: IO ()
|
|
|
|
setupTestMode = do
|
|
|
|
testmode <- getTestMode
|
2019-08-09 15:06:54 +00:00
|
|
|
when (adjustedUnlockedBranch testmode) $ do
|
2020-11-24 21:17:09 +00:00
|
|
|
git "commit" ["--allow-empty", "-m", "empty"] "git commit failed"
|
|
|
|
git_annex "adjust" ["--unlock"] "git annex adjust failed"
|
2018-02-18 15:48:48 +00:00
|
|
|
|
2022-03-14 19:24:37 +00:00
|
|
|
changeToTopDir :: FilePath -> IO ()
|
|
|
|
changeToTopDir t = do
|
2018-02-18 15:48:48 +00:00
|
|
|
topdir <- Utility.Env.getEnvDefault "TOPDIR" (error "TOPDIR not set")
|
|
|
|
setCurrentDirectory $ topdir ++ "/" ++ t
|
|
|
|
|
|
|
|
tmpdir :: String
|
|
|
|
tmpdir = ".t"
|
|
|
|
|
2019-08-08 18:29:28 +00:00
|
|
|
mainrepodir :: IO FilePath
|
|
|
|
mainrepodir = Utility.Env.getEnvDefault "MAINREPODIR"
|
|
|
|
(giveup "MAINREPODIR not set")
|
|
|
|
|
|
|
|
setmainrepodir :: FilePath -> IO ()
|
|
|
|
setmainrepodir d = Utility.Env.Set.setEnv "MAINREPODIR" d True
|
|
|
|
|
|
|
|
newmainrepodir :: IO FilePath
|
|
|
|
newmainrepodir = go (0 :: Int)
|
|
|
|
where
|
|
|
|
go n = do
|
2022-03-14 19:24:37 +00:00
|
|
|
let d = "main" ++ show n
|
2019-08-08 18:29:28 +00:00
|
|
|
ifM (doesDirectoryExist d)
|
|
|
|
( go $ n + 1
|
|
|
|
, do
|
|
|
|
createDirectory d
|
|
|
|
return d
|
|
|
|
)
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
tmprepodir :: IO FilePath
|
|
|
|
tmprepodir = go (0 :: Int)
|
|
|
|
where
|
|
|
|
go n = do
|
2022-03-14 19:24:37 +00:00
|
|
|
let d = "tmprepo" ++ show n
|
2018-02-18 15:48:48 +00:00
|
|
|
ifM (doesDirectoryExist d)
|
|
|
|
( go $ n + 1
|
|
|
|
, return d
|
|
|
|
)
|
|
|
|
|
|
|
|
annexedfile :: String
|
|
|
|
annexedfile = "foo"
|
|
|
|
|
|
|
|
annexedfiledup :: String
|
|
|
|
annexedfiledup = "foodup"
|
|
|
|
|
|
|
|
wormannexedfile :: String
|
|
|
|
wormannexedfile = "apple"
|
|
|
|
|
|
|
|
sha1annexedfile :: String
|
|
|
|
sha1annexedfile = "sha1foo"
|
|
|
|
|
|
|
|
sha1annexedfiledup :: String
|
|
|
|
sha1annexedfiledup = "sha1foodup"
|
|
|
|
|
|
|
|
ingitfile :: String
|
|
|
|
ingitfile = "bar.c"
|
|
|
|
|
|
|
|
content :: FilePath -> String
|
|
|
|
content f
|
|
|
|
| f == annexedfile = "annexed file content"
|
|
|
|
| f == ingitfile = "normal file content"
|
|
|
|
| f == sha1annexedfile ="sha1 annexed file content"
|
|
|
|
| f == annexedfiledup = content annexedfile
|
|
|
|
| f == sha1annexedfiledup = content sha1annexedfile
|
|
|
|
| f == wormannexedfile = "worm annexed file content"
|
|
|
|
| "import" `isPrefixOf` f = "imported content"
|
|
|
|
| otherwise = "unknown file " ++ f
|
|
|
|
|
2018-10-30 05:08:29 +00:00
|
|
|
-- Writes new content to a file, and makes sure that it has a different
|
|
|
|
-- mtime than it did before
|
add small delay to avoid problems on systems with low-resolution mtime
I've seen intermittent failures of the test suite with v6 for a long time,
it seems to have possibly gotten worse with the changes around v7. Or just
being unlucky; all tests failed today.
Seen on amd64 and i386 builders, repeatedly but intermittently:
unused: FAIL (4.86s)
Test.hs:928:
git diff did not show changes to unlocked file
And I think other such failures, all involving v7/v6 mode tests.
I managed to reproduce the unused failure with --keep-failures,
and inside the repo, git diff was indeed not showing any changes for
the modified unlocked file.
The two stats will be the same other than mtime; the old and new files have
the same size and inode, since the test case writes to the file and then
overwrites it.
Indeed, notice the identical timestamps:
builder@orca:~/gitbuilder/build/.t/tmprepo335$ echo 1 > foo; stat foo; echo 2 > foo; stat foo
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.894942036 +0000
Change: 2018-10-29 22:14:10.894942036 +0000
Birth: -
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.898942036 +0000
Change: 2018-10-29 22:14:10.898942036 +0000
Birth: -
I'm seeing this in Linux VMs; it doesn't happen on my laptop. I've also
not experienced the intermittent test suite failures on my laptop.
So, I hope that this small delay will avoid the problem.
Update: I didn't, indeed I then reproduced the same failure on my
laptop, so it must be due to something else. But keeping this change anyway
since not needing to worry about lowish-resolution mtime in the test suite seems
worthwhile.
2018-10-29 22:42:20 +00:00
|
|
|
writecontent :: FilePath -> String -> IO ()
|
2018-10-30 05:08:29 +00:00
|
|
|
writecontent f c = go (10000000 :: Integer)
|
|
|
|
where
|
|
|
|
go ticsleft = do
|
|
|
|
oldmtime <- catchMaybeIO $ getModificationTime f
|
|
|
|
writeFile f c
|
|
|
|
newmtime <- getModificationTime f
|
|
|
|
if Just newmtime == oldmtime
|
|
|
|
then do
|
|
|
|
threadDelay 100000
|
|
|
|
let ticsleft' = ticsleft - 100000
|
|
|
|
if ticsleft' > 0
|
|
|
|
then go ticsleft'
|
|
|
|
else do
|
|
|
|
hPutStrLn stderr "file mtimes do not seem to be changing (tried for 10 seconds)"
|
|
|
|
hFlush stderr
|
|
|
|
return ()
|
|
|
|
else return ()
|
add small delay to avoid problems on systems with low-resolution mtime
I've seen intermittent failures of the test suite with v6 for a long time,
it seems to have possibly gotten worse with the changes around v7. Or just
being unlucky; all tests failed today.
Seen on amd64 and i386 builders, repeatedly but intermittently:
unused: FAIL (4.86s)
Test.hs:928:
git diff did not show changes to unlocked file
And I think other such failures, all involving v7/v6 mode tests.
I managed to reproduce the unused failure with --keep-failures,
and inside the repo, git diff was indeed not showing any changes for
the modified unlocked file.
The two stats will be the same other than mtime; the old and new files have
the same size and inode, since the test case writes to the file and then
overwrites it.
Indeed, notice the identical timestamps:
builder@orca:~/gitbuilder/build/.t/tmprepo335$ echo 1 > foo; stat foo; echo 2 > foo; stat foo
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.894942036 +0000
Change: 2018-10-29 22:14:10.894942036 +0000
Birth: -
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.898942036 +0000
Change: 2018-10-29 22:14:10.898942036 +0000
Birth: -
I'm seeing this in Linux VMs; it doesn't happen on my laptop. I've also
not experienced the intermittent test suite failures on my laptop.
So, I hope that this small delay will avoid the problem.
Update: I didn't, indeed I then reproduced the same failure on my
laptop, so it must be due to something else. But keeping this change anyway
since not needing to worry about lowish-resolution mtime in the test suite seems
worthwhile.
2018-10-29 22:42:20 +00:00
|
|
|
|
2018-02-18 15:48:48 +00:00
|
|
|
changecontent :: FilePath -> IO ()
|
add small delay to avoid problems on systems with low-resolution mtime
I've seen intermittent failures of the test suite with v6 for a long time,
it seems to have possibly gotten worse with the changes around v7. Or just
being unlucky; all tests failed today.
Seen on amd64 and i386 builders, repeatedly but intermittently:
unused: FAIL (4.86s)
Test.hs:928:
git diff did not show changes to unlocked file
And I think other such failures, all involving v7/v6 mode tests.
I managed to reproduce the unused failure with --keep-failures,
and inside the repo, git diff was indeed not showing any changes for
the modified unlocked file.
The two stats will be the same other than mtime; the old and new files have
the same size and inode, since the test case writes to the file and then
overwrites it.
Indeed, notice the identical timestamps:
builder@orca:~/gitbuilder/build/.t/tmprepo335$ echo 1 > foo; stat foo; echo 2 > foo; stat foo
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.894942036 +0000
Change: 2018-10-29 22:14:10.894942036 +0000
Birth: -
File: foo
Size: 2 Blocks: 8 IO Block: 4096 regular file
Device: 801h/2049d Inode: 3546179 Links: 1
Access: (0644/-rw-r--r--) Uid: ( 1000/ builder) Gid: ( 1000/ builder)
Access: 2018-10-29 22:14:10.894942036 +0000
Modify: 2018-10-29 22:14:10.898942036 +0000
Change: 2018-10-29 22:14:10.898942036 +0000
Birth: -
I'm seeing this in Linux VMs; it doesn't happen on my laptop. I've also
not experienced the intermittent test suite failures on my laptop.
So, I hope that this small delay will avoid the problem.
Update: I didn't, indeed I then reproduced the same failure on my
laptop, so it must be due to something else. But keeping this change anyway
since not needing to worry about lowish-resolution mtime in the test suite seems
worthwhile.
2018-10-29 22:42:20 +00:00
|
|
|
changecontent f = writecontent f $ changedcontent f
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
changedcontent :: FilePath -> String
|
|
|
|
changedcontent f = content f ++ " (modified)"
|
|
|
|
|
|
|
|
backendSHA1 :: Types.Backend
|
|
|
|
backendSHA1 = backend_ "SHA1"
|
|
|
|
|
|
|
|
backendSHA256 :: Types.Backend
|
|
|
|
backendSHA256 = backend_ "SHA256"
|
|
|
|
|
|
|
|
backendSHA256E :: Types.Backend
|
|
|
|
backendSHA256E = backend_ "SHA256E"
|
|
|
|
|
|
|
|
backendWORM :: Types.Backend
|
|
|
|
backendWORM = backend_ "WORM"
|
|
|
|
|
|
|
|
backend_ :: String -> Types.Backend
|
2020-07-29 19:23:18 +00:00
|
|
|
backend_ = Backend.lookupBuiltinBackendVariety . Types.Key.parseKeyVariety . encodeBS
|
2018-02-18 15:48:48 +00:00
|
|
|
|
|
|
|
getKey :: Types.Backend -> FilePath -> IO Types.Key
|
2020-07-20 18:06:05 +00:00
|
|
|
getKey b f = case Types.Backend.genKey b of
|
2020-05-15 16:51:09 +00:00
|
|
|
Just a -> annexeval $ a ks Utility.Metered.nullMeterUpdate
|
|
|
|
Nothing -> error "internal"
|
2018-02-18 15:48:48 +00:00
|
|
|
where
|
2019-06-25 15:37:52 +00:00
|
|
|
ks = Types.KeySource.KeySource
|
2020-02-21 13:34:59 +00:00
|
|
|
{ Types.KeySource.keyFilename = toRawFilePath f
|
|
|
|
, Types.KeySource.contentLocation = toRawFilePath f
|
2019-06-25 15:37:52 +00:00
|
|
|
, Types.KeySource.inodeCache = Nothing
|
|
|
|
}
|
2020-06-23 21:41:50 +00:00
|
|
|
|
|
|
|
{- Get the name of the original branch, eg the current branch, or
|
|
|
|
- if in an adjusted branch, the parent branch. -}
|
|
|
|
origBranch :: Types.Annex String
|
|
|
|
origBranch = maybe "foo"
|
|
|
|
(Git.Types.fromRef . Git.Ref.base . Annex.AdjustedBranch.fromAdjustedBranch)
|
|
|
|
<$> Annex.inRepo Git.Branch.current
|
2021-08-30 20:39:02 +00:00
|
|
|
|
|
|
|
{- Set up repos as remotes of each other. -}
|
|
|
|
pair :: FilePath -> FilePath -> Assertion
|
|
|
|
pair r1 r2 = forM_ [r1, r2] $ \r -> indir r $ do
|
|
|
|
when (r /= r1) $
|
2022-03-14 19:24:37 +00:00
|
|
|
git "remote" ["add", "r1", "../" ++ r1] "remote add"
|
2021-08-30 20:39:02 +00:00
|
|
|
when (r /= r2) $
|
2022-03-14 19:24:37 +00:00
|
|
|
git "remote" ["add", "r2", "../" ++ r2] "remote add"
|
2021-08-30 20:39:02 +00:00
|
|
|
|
2021-12-30 17:16:57 +00:00
|
|
|
|
|
|
|
{- Runs a query in the current repository, but first makes the repository
|
|
|
|
- read-only. The write bit is added back at the end, so when possible,
|
|
|
|
- include multiple tests within a single call for efficiency. -}
|
|
|
|
readonly_query :: Assertion -> Assertion
|
|
|
|
readonly_query = bracket_ (make_readonly ".") (make_writeable ".")
|
|
|
|
|
|
|
|
{- Not guaranteed to do anything:
|
|
|
|
- chmod may fail, or not be available, or the filesystem not support
|
|
|
|
- permissions. -}
|
|
|
|
make_readonly :: FilePath -> IO ()
|
|
|
|
make_readonly d = void $
|
|
|
|
Utility.Process.Transcript.processTranscript
|
|
|
|
"chmod" ["-R", "-w", d] Nothing
|
|
|
|
|
|
|
|
{- The write bit is added back for the current user, but not for other
|
|
|
|
- users, even though make_readonly removes any other user's write bits. -}
|
|
|
|
make_writeable :: FilePath -> IO ()
|
|
|
|
make_writeable d = void $
|
|
|
|
Utility.Process.Transcript.processTranscript
|
|
|
|
"chmod" ["-R", "u+w", d] Nothing
|
2022-03-14 19:24:37 +00:00
|
|
|
|
|
|
|
{- Tests each TestTree in parallel, and exits with succcess/failure.
|
|
|
|
-
|
|
|
|
- Tasty supports parallel tests, but this does not use it, because
|
|
|
|
- many tests need to be run in test repos, and chdir would not be
|
|
|
|
- thread safe. Instead, this starts one child process for each TestTree.
|
|
|
|
-
|
|
|
|
- An added benefit of using child processes is that any files they may
|
|
|
|
- leave open are closed before finalCleanup is run at the end. This
|
|
|
|
- prevents some failures to clean up after the test suite.
|
|
|
|
-}
|
allow tests to be split for more granularity
Unit tests are the main bulk of runtime, so splitting them into 2 or 3
parts should help.
For now, the number of parts is still 1, because on my 4 core laptop,
2 was a little bit slower, and 3 slower yet. However, this probably does
vary based on the number of cores, so needs to be revisited, and perhaps
made dynamic.
Since each test mode gets split into the specified number of parts,
plus property and remote tests, 2 gives 8 parts, and 3 gives 11 parts.
Load went to maybe 18, so there was probably contention slowing things
down.
So probably it needs to start N workers with some parts, and when a
worker finishes, run it with the next part, until all parts are
processed.
Sponsored-by: Dartmouth College's Datalad project
2022-03-14 21:23:52 +00:00
|
|
|
parallelTestRunner :: TestOptions -> (Int -> Bool -> Bool -> TestOptions -> [TestTree]) -> IO ()
|
2022-03-14 19:24:37 +00:00
|
|
|
parallelTestRunner opts mkts
|
|
|
|
| fakeSsh opts = runFakeSsh (internalData opts)
|
|
|
|
| otherwise = go =<< Utility.Env.getEnv subenv
|
|
|
|
where
|
allow tests to be split for more granularity
Unit tests are the main bulk of runtime, so splitting them into 2 or 3
parts should help.
For now, the number of parts is still 1, because on my 4 core laptop,
2 was a little bit slower, and 3 slower yet. However, this probably does
vary based on the number of cores, so needs to be revisited, and perhaps
made dynamic.
Since each test mode gets split into the specified number of parts,
plus property and remote tests, 2 gives 8 parts, and 3 gives 11 parts.
Load went to maybe 18, so there was probably contention slowing things
down.
So probably it needs to start N workers with some parts, and when a
worker finishes, run it with the next part, until all parts are
processed.
Sponsored-by: Dartmouth College's Datalad project
2022-03-14 21:23:52 +00:00
|
|
|
numparts = 1
|
2022-03-14 19:24:37 +00:00
|
|
|
subenv = "GIT_ANNEX_TEST_SUBPROCESS"
|
|
|
|
go Nothing = do
|
|
|
|
ensuredir tmpdir
|
|
|
|
crippledfilesystem <- fst <$> Annex.Init.probeCrippledFileSystem'
|
|
|
|
(toRawFilePath tmpdir)
|
|
|
|
Nothing Nothing False
|
|
|
|
adjustedbranchok <- Annex.AdjustedBranch.isGitVersionSupported
|
allow tests to be split for more granularity
Unit tests are the main bulk of runtime, so splitting them into 2 or 3
parts should help.
For now, the number of parts is still 1, because on my 4 core laptop,
2 was a little bit slower, and 3 slower yet. However, this probably does
vary based on the number of cores, so needs to be revisited, and perhaps
made dynamic.
Since each test mode gets split into the specified number of parts,
plus property and remote tests, 2 gives 8 parts, and 3 gives 11 parts.
Load went to maybe 18, so there was probably contention slowing things
down.
So probably it needs to start N workers with some parts, and when a
worker finishes, run it with the next part, until all parts are
processed.
Sponsored-by: Dartmouth College's Datalad project
2022-03-14 21:23:52 +00:00
|
|
|
let ts = mkts numparts crippledfilesystem adjustedbranchok opts
|
2022-03-14 19:24:37 +00:00
|
|
|
let warnings = fst (tastyParser ts)
|
|
|
|
unless (null warnings) $ do
|
|
|
|
hPutStrLn stderr "warnings from tasty:"
|
|
|
|
mapM_ (hPutStrLn stderr) warnings
|
|
|
|
environ <- Utility.Env.getEnvironment
|
|
|
|
ps <- getArgs
|
|
|
|
pp <- Annex.Path.programPath
|
|
|
|
exitcodes <- forConcurrently [1..length ts] $ \n -> do
|
|
|
|
let subdir = tmpdir </> show n
|
|
|
|
ensuredir subdir
|
|
|
|
let p = (proc pp ps)
|
|
|
|
{ env = Just ((subenv, show (n, crippledfilesystem, adjustedbranchok)):environ)
|
|
|
|
, cwd = Just subdir
|
|
|
|
}
|
|
|
|
withCreateProcess p $
|
|
|
|
\_ _ _ pid -> waitForProcess pid
|
|
|
|
unless (keepFailuresOption opts) finalCleanup
|
|
|
|
if all (== ExitSuccess) exitcodes
|
|
|
|
then exitSuccess
|
|
|
|
else case (filter (/= ExitFailure 1) exitcodes) of
|
|
|
|
[] -> do
|
|
|
|
putStrLn " (Failures above could be due to a bug in git-annex, or an incompatibility"
|
|
|
|
putStrLn " with utilities, such as git, installed on this system.)"
|
|
|
|
exitFailure
|
|
|
|
v -> do
|
|
|
|
putStrLn $ " Test subprocesses exited with unexpected exit codes: " ++ show v
|
|
|
|
exitFailure
|
|
|
|
go (Just subenvval) = case readish subenvval of
|
|
|
|
Nothing -> error ("Bad " ++ subenv)
|
|
|
|
Just (n, crippledfilesystem, adjustedbranchok) -> isolateGitConfig $ do
|
allow tests to be split for more granularity
Unit tests are the main bulk of runtime, so splitting them into 2 or 3
parts should help.
For now, the number of parts is still 1, because on my 4 core laptop,
2 was a little bit slower, and 3 slower yet. However, this probably does
vary based on the number of cores, so needs to be revisited, and perhaps
made dynamic.
Since each test mode gets split into the specified number of parts,
plus property and remote tests, 2 gives 8 parts, and 3 gives 11 parts.
Load went to maybe 18, so there was probably contention slowing things
down.
So probably it needs to start N workers with some parts, and when a
worker finishes, run it with the next part, until all parts are
processed.
Sponsored-by: Dartmouth College's Datalad project
2022-03-14 21:23:52 +00:00
|
|
|
let ts = mkts numparts crippledfilesystem adjustedbranchok opts
|
2022-03-14 19:24:37 +00:00
|
|
|
let t = topLevelTestGroup
|
|
|
|
-- This group is needed to avoid what
|
|
|
|
-- seems to be a tasty bug which causes a
|
|
|
|
-- segfault.
|
|
|
|
[ testGroup "Tasty"
|
|
|
|
[ testProperty "tasty self-check" True
|
|
|
|
]
|
|
|
|
, ts !! (n - 1)
|
|
|
|
]
|
|
|
|
case tryIngredients ingredients (tastyOptionSet opts) t of
|
|
|
|
Nothing -> error "No tests found!?"
|
|
|
|
Just act -> ifM act
|
|
|
|
( exitSuccess
|
|
|
|
, exitFailure
|
|
|
|
)
|
|
|
|
|
|
|
|
topLevelTestGroup :: [TestTree] -> TestTree
|
|
|
|
topLevelTestGroup = testGroup "Tests"
|
|
|
|
|
|
|
|
tastyParser :: [TestTree] -> ([String], Parser Test.Tasty.Options.OptionSet)
|
|
|
|
#if MIN_VERSION_tasty(1,3,0)
|
|
|
|
tastyParser ts = go
|
|
|
|
#else
|
|
|
|
tastyParser ts = ([], go)
|
|
|
|
#endif
|
|
|
|
where
|
|
|
|
go = suiteOptionParser ingredients (topLevelTestGroup ts)
|
|
|
|
|
|
|
|
ingredients :: [Ingredient]
|
|
|
|
ingredients =
|
|
|
|
[ listingTests
|
|
|
|
, rerunningTests [consoleTestReporter]
|
|
|
|
]
|
|
|
|
|