summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Command/Extract.hs5
-rw-r--r--src/Command/JobId.hs2
-rw-r--r--src/Command/Log.hs2
-rw-r--r--src/Command/Run.hs37
-rw-r--r--src/Config.hs3
-rw-r--r--src/Eval.hs124
-rw-r--r--src/Job.hs26
-rw-r--r--src/Job/Types.hs10
-rw-r--r--src/Repo.hs10
-rw-r--r--test/asset/artifact/minici.yaml14
-rw-r--r--test/asset/run/dependencies.yaml55
-rw-r--r--test/script/artifact.et24
-rw-r--r--test/script/run.et67
13 files changed, 337 insertions, 42 deletions
diff --git a/src/Command/Extract.hs b/src/Command/Extract.hs
index 8a0a035..b21c63c 100644
--- a/src/Command/Extract.hs
+++ b/src/Command/Extract.hs
@@ -14,6 +14,7 @@ import System.FilePath
import Command
import Eval
+import Job
import Job.Types
@@ -78,7 +79,7 @@ cmdExtract (ExtractCommand ExtractOptions {..} ExtractArguments {..}) = do
_ -> return False
forM_ extractArtifacts $ \( ref, ArtifactName aname ) -> do
- jid@(JobId ids) <- either (tfail . textEvalError) (return . jobId) =<<
+ jid@(JobId ids) <- either (tfail . textEvalError) (return . jobId . fst) =<<
liftIO (runEval (evalJobReference ref) einput)
let jdir = joinPath $ (storageDir :) $ ("jobs" :) $ map (T.unpack . textJobIdPart) ids
@@ -103,4 +104,4 @@ cmdExtract (ExtractCommand ExtractOptions {..} ExtractArguments {..}) = do
liftIO (doesPathExist tpath) >>= \case
True -> tfail $ "destination ‘" <> T.pack tpath <> "’ already exists"
False -> return ()
- liftIO $ copyFile (adir </> afile) tpath
+ liftIO $ copyRecursiveForce (adir </> afile) tpath
diff --git a/src/Command/JobId.hs b/src/Command/JobId.hs
index 173f543..096ed56 100644
--- a/src/Command/JobId.hs
+++ b/src/Command/JobId.hs
@@ -52,7 +52,7 @@ cmdJobId :: JobIdCommand -> CommandExec ()
cmdJobId (JobIdCommand JobIdOptions {..} ref) = do
einput <- getEvalInput
out <- getOutput
- JobId ids <- either (tfail . textEvalError) (return . jobId) =<<
+ JobId ids <- either (tfail . textEvalError) (return . jobId . fst) =<<
liftIO (runEval (evalJobReference ref) einput)
outputMessage out $ textJobId $ JobId ids
diff --git a/src/Command/Log.hs b/src/Command/Log.hs
index 25bfc06..e48ce8f 100644
--- a/src/Command/Log.hs
+++ b/src/Command/Log.hs
@@ -37,7 +37,7 @@ instance Command LogCommand where
cmdLog :: LogCommand -> CommandExec ()
cmdLog (LogCommand ref) = do
einput <- getEvalInput
- jid <- either (tfail . textEvalError) (return . jobId) =<<
+ jid <- either (tfail . textEvalError) (return . jobId . fst) =<<
liftIO (runEval (evalJobReference ref) einput)
output <- getOutput
storageDir <- getStorageDir
diff --git a/src/Command/Run.hs b/src/Command/Run.hs
index 9652529..a80e15d 100644
--- a/src/Command/Run.hs
+++ b/src/Command/Run.hs
@@ -126,7 +126,7 @@ mergeSources sources = do
argumentJobSource :: [ JobName ] -> CommandExec JobSource
argumentJobSource [] = emptyJobSource
argumentJobSource names = do
- ( config, jobsetCommit ) <- getJobRoot >>= \case
+ ( config, jcommit ) <- getJobRoot >>= \case
JobRootConfig config -> do
commit <- sequence . fmap createWipCommit =<< tryGetDefaultRepo
return ( config, commit )
@@ -135,29 +135,46 @@ argumentJobSource names = do
config <- either fail return =<< loadConfigForCommit =<< getCommitTree commit
return ( config, Just commit )
- jobtree <- case jobsetCommit of
+ jobtree <- case jcommit of
Just commit -> (: []) <$> getCommitTree commit
Nothing -> return []
let cidPart = map (JobIdTree Nothing "" . treeId) jobtree
- jobsetJobsEither <- fmap Right $ forM names $ \name ->
+ forM_ names $ \name ->
case find ((name ==) . jobName) (configJobs config) of
- Just job -> return job
+ Just _ -> return ()
Nothing -> tfail $ "job ‘" <> textJobName name <> "’ not found"
- oneshotJobSource . (: []) =<<
- cmdEvalWith (\ei -> ei { eiCurrentIdRev = cidPart ++ eiCurrentIdRev ei })
- (evalJobSet (map ( Nothing, ) jobtree) JobSet {..})
+
+ jset <- cmdEvalWith (\ei -> ei { eiCurrentIdRev = cidPart ++ eiCurrentIdRev ei }) $ do
+ fullSet <- evalJobSet (map ( Nothing, ) jobtree) JobSet
+ { jobsetId = ()
+ , jobsetCommit = jcommit
+ , jobsetJobsEither = Right (configJobs config)
+ }
+ let selectedSet = fullSet { jobsetJobsEither = fmap (filter ((`elem` names) . jobName)) (jobsetJobsEither fullSet) }
+ fillInDependencies selectedSet
+ oneshotJobSource [ jset ]
refJobSource :: [ JobRef ] -> CommandExec JobSource
refJobSource [] = emptyJobSource
refJobSource refs = do
- jobs <- cmdEvalWith id $ mapM evalJobReference refs
- oneshotJobSource . map (JobSet Nothing . Right . (: [])) $ jobs
+ jobs <- foldl' addJobToList [] <$> cmdEvalWith id (mapM evalJobReference refs)
+ sets <- cmdEvalWith id $ do
+ forM jobs $ \( sid, js ) -> do
+ fillInDependencies $ JobSet sid Nothing (Right $ reverse js)
+ oneshotJobSource sets
+ where
+ addJobToList :: [ ( JobSetId, [ Job ] ) ] -> ( Job, JobSetId ) -> [ ( JobSetId, [ Job ] ) ]
+ addJobToList (( sid, js ) : rest ) ( job, jsid )
+ | sid == jsid = ( sid, job : js ) : rest
+ | otherwise = ( sid, js ) : addJobToList rest ( job, jsid )
+ addJobToList [] ( job, jsid ) = [ ( jsid, [ job ] ) ]
loadJobSetFromRoot :: (MonadIO m, MonadFail m) => JobRoot -> Commit -> m DeclaredJobSet
loadJobSetFromRoot root commit = case root of
JobRootRepo _ -> loadJobSetForCommit commit
JobRootConfig config -> return JobSet
- { jobsetCommit = Just commit
+ { jobsetId = ()
+ , jobsetCommit = Just commit
, jobsetJobsEither = Right $ configJobs config
}
diff --git a/src/Config.hs b/src/Config.hs
index 4327193..ea2907c 100644
--- a/src/Config.hs
+++ b/src/Config.hs
@@ -173,6 +173,7 @@ loadJobSetForCommit :: (MonadIO m, MonadFail m) => Commit -> m DeclaredJobSet
loadJobSetForCommit commit = return . toJobSet =<< loadConfigForCommit =<< getCommitTree commit
where
toJobSet configEither = JobSet
- { jobsetCommit = Just commit
+ { jobsetId = ()
+ , jobsetCommit = Just commit
, jobsetJobsEither = fmap configJobs configEither
}
diff --git a/src/Eval.hs b/src/Eval.hs
index f064cb1..67fea8d 100644
--- a/src/Eval.hs
+++ b/src/Eval.hs
@@ -6,6 +6,9 @@ module Eval (
evalJob,
evalJobSet,
evalJobReference,
+
+ loadJobSetById,
+ fillInDependencies,
) where
import Control.Monad
@@ -14,6 +17,7 @@ import Control.Monad.Reader
import Data.List
import Data.Maybe
+import Data.Set qualified as S
import Data.Text (Text)
import Data.Text qualified as T
@@ -78,7 +82,7 @@ collectOtherRepos dset decl = do
return $ map (\r -> ( r, commonSubdir r )) . nub . map jcRepo $ checkouts
-evalJob :: [ ( Maybe RepoName, Tree ) ] -> DeclaredJobSet -> DeclaredJob -> Eval Job
+evalJob :: [ ( Maybe RepoName, Tree ) ] -> DeclaredJobSet -> DeclaredJob -> Eval ( Job, JobSetId )
evalJob revisionOverrides dset decl = do
EvalInput {..} <- ask
otherRepos <- collectOtherRepos dset decl
@@ -102,20 +106,27 @@ evalJob revisionOverrides dset decl = do
}
let otherRepoIds = map (\( repo, ( subtree, tree )) -> JobIdTree (fst <$> repo) subtree (treeId tree)) otherRepoTrees
- return Job
- { jobId = JobId $ reverse $ reverse otherRepoIds ++ JobIdName (jobId decl) : eiCurrentIdRev
- , jobName = jobName decl
- , jobCheckout = checkouts
- , jobRecipe = jobRecipe decl
- , jobArtifacts = jobArtifacts decl
- , jobUses = jobUses decl
- }
+ return
+ ( Job
+ { jobId = JobId $ reverse $ reverse otherRepoIds ++ JobIdName (jobId decl) : eiCurrentIdRev
+ , jobName = jobName decl
+ , jobCheckout = checkouts
+ , jobRecipe = jobRecipe decl
+ , jobArtifacts = jobArtifacts decl
+ , jobUses = jobUses decl
+ }
+ , JobSetId $ reverse $ reverse otherRepoIds ++ eiCurrentIdRev
+ )
evalJobSet :: [ ( Maybe RepoName, Tree ) ] -> DeclaredJobSet -> Eval JobSet
evalJobSet revisionOverrides decl = do
- jobs <- either (return . Left) (handleToEither . mapM (evalJob revisionOverrides decl)) $ jobsetJobsEither decl
+ EvalInput {..} <- ask
+ jobs <- fmap (fmap (map fst))
+ $ either (return . Left) (handleToEither . mapM (evalJob revisionOverrides decl))
+ $ jobsetJobsEither decl
return JobSet
- { jobsetCommit = jobsetCommit decl
+ { jobsetId = JobSetId $ reverse $ eiCurrentIdRev
+ , jobsetCommit = jobsetCommit decl
, jobsetJobsEither = jobs
}
where
@@ -130,10 +141,10 @@ evalRepo (Just name) = asks (lookup name . eiOtherRepos) >>= \case
Nothing -> throwError $ OtherEvalError $ "repo ‘" <> textRepoName name <> "’ not defined"
-canonicalJobName :: [ Text ] -> Config -> Maybe Tree -> Eval Job
+canonicalJobName :: [ Text ] -> Config -> Maybe Tree -> Eval ( Job, JobSetId )
canonicalJobName (r : rs) config mbDefaultRepo = do
let name = JobName r
- dset = JobSet Nothing $ Right $ configJobs config
+ dset = JobSet () Nothing $ Right $ configJobs config
case find ((name ==) . jobName) (configJobs config) of
Just djob -> do
otherRepos <- collectOtherRepos dset djob
@@ -157,17 +168,100 @@ readTreeFromIdRef (r : rs) subdir repo = do
Nothing -> throwError $ OtherEvalError $ "failed to resolve ‘" <> r <> "’ to a commit or tree in " <> T.pack (show repo)
readTreeFromIdRef [] _ _ = throwError $ OtherEvalError $ "expected commit or tree reference"
-canonicalCommitConfig :: [ Text ] -> Repo -> Eval Job
+canonicalCommitConfig :: [ Text ] -> Repo -> Eval ( Job, JobSetId )
canonicalCommitConfig rs repo = do
( tree, rs' ) <- readTreeFromIdRef rs "" repo
config <- either fail return =<< loadConfigForCommit tree
local (\ei -> ei { eiCurrentIdRev = JobIdTree Nothing "" (treeId tree) : eiCurrentIdRev ei }) $
canonicalJobName rs' config (Just tree)
-evalJobReference :: JobRef -> Eval Job
+evalJobReference :: JobRef -> Eval ( Job, JobSetId )
evalJobReference (JobRef rs) =
asks eiJobRoot >>= \case
JobRootRepo defRepo -> do
canonicalCommitConfig rs defRepo
JobRootConfig config -> do
canonicalJobName rs config Nothing
+
+
+jobsetFromConfig :: [ JobIdPart ] -> Config -> Maybe Tree -> Eval ( DeclaredJobSet, [ JobIdPart ], [ ( Maybe RepoName, Tree ) ] )
+jobsetFromConfig sid config _ = do
+ EvalInput {..} <- ask
+ let dset = JobSet () Nothing $ Right $ configJobs config
+ otherRepos <- forM sid $ \case
+ JobIdName name -> do
+ throwError $ OtherEvalError $ "expected tree id, not a job name ‘" <> textJobName name <> "’"
+ JobIdCommit name cid -> do
+ repo <- evalRepo name
+ tree <- getCommitTree =<< readCommitId repo cid
+ return ( name, tree )
+ JobIdTree name path tid -> do
+ repo <- evalRepo name
+ tree <- readTreeId repo path tid
+ return ( name, tree )
+ return ( dset, eiCurrentIdRev, otherRepos )
+
+jobsetFromCommitConfig :: [ JobIdPart ] -> Repo -> Eval ( DeclaredJobSet, [ JobIdPart ], [ ( Maybe RepoName, Tree ) ] )
+jobsetFromCommitConfig (JobIdTree name path tid : sid) repo = do
+ when (isJust name) $ do
+ throwError $ OtherEvalError $ "expected default repo commit or tree id"
+ when (not (null path)) $ do
+ throwError $ OtherEvalError $ "expected root commit or tree id"
+ tree <- readTreeId repo path tid
+ config <- either fail return =<< loadConfigForCommit tree
+ local (\ei -> ei { eiCurrentIdRev = JobIdTree Nothing "" (treeId tree) : eiCurrentIdRev ei }) $ do
+ ( dset, idRev, otherRepos ) <- jobsetFromConfig sid config (Just tree)
+ return ( dset, idRev, ( Nothing, tree ) : otherRepos )
+
+jobsetFromCommitConfig (JobIdCommit name cid : sid) repo = do
+ when (isJust name) $ do
+ throwError $ OtherEvalError $ "expected default repo commit or tree id"
+ tree <- getCommitTree =<< readCommitId repo cid
+ jobsetFromCommitConfig (JobIdTree name "" (treeId tree) : sid) repo
+
+jobsetFromCommitConfig (JobIdName name : _) _ = do
+ throwError $ OtherEvalError $ "expected commit or tree id, not a job name ‘" <> textJobName name <> "’"
+
+jobsetFromCommitConfig [] _ = do
+ throwError $ OtherEvalError $ "expected commit or tree id"
+
+loadJobSetById :: JobSetId -> Eval ( DeclaredJobSet, [ JobIdPart ], [ ( Maybe RepoName, Tree ) ] )
+loadJobSetById (JobSetId sid) = do
+ asks eiJobRoot >>= \case
+ JobRootRepo defRepo -> do
+ jobsetFromCommitConfig sid defRepo
+ JobRootConfig config -> do
+ jobsetFromConfig sid config Nothing
+
+fillInDependencies :: JobSet -> Eval JobSet
+fillInDependencies jset = do
+ ( dset, idRev, otherRepos ) <- local (\ei -> ei { eiCurrentIdRev = [] }) $ do
+ loadJobSetById (jobsetId jset)
+ origJobs <- either (throwError . OtherEvalError . T.pack) return $ jobsetJobsEither jset
+ declJobs <- either (throwError . OtherEvalError . T.pack) return $ jobsetJobsEither dset
+ deps <- gather declJobs S.empty (map jobName origJobs)
+
+ jobs <- local (\ei -> ei { eiCurrentIdRev = idRev }) $ do
+ fmap catMaybes $ forM declJobs $ \djob -> if
+ | Just job <- find ((jobName djob ==) . jobName) origJobs
+ -> return (Just job)
+
+ | jobName djob `S.member` deps
+ -> Just . fst <$> evalJob otherRepos dset djob
+
+ | otherwise
+ -> return Nothing
+
+ return $ jset { jobsetJobsEither = Right jobs }
+ where
+ gather djobs cur ( name : rest )
+ | name `S.member` cur
+ = gather djobs cur rest
+
+ | Just djob <- find ((name ==) . jobName) djobs
+ = gather djobs (S.insert name cur) $ map fst (jobUses djob) ++ rest
+
+ | otherwise
+ = throwError $ OtherEvalError $ "dependency ‘" <> textJobName name <> "’ not found"
+
+ gather _ cur [] = return cur
diff --git a/src/Job.hs b/src/Job.hs
index ee901ee..6782f6b 100644
--- a/src/Job.hs
+++ b/src/Job.hs
@@ -9,6 +9,9 @@ module Job (
JobManager(..), newJobManager, cancelAllJobs,
runJobs,
jobStorageSubdir,
+
+ copyRecursive,
+ copyRecursiveForce,
) where
import Control.Concurrent
@@ -309,7 +312,7 @@ runJob job uses checkoutPath jdir = do
liftIO $ forM_ uses $ \aout -> do
let target = checkoutPath </> aoutWorkPath aout
createDirectoryIfMissing True $ takeDirectory target
- copyFile (aoutStorePath aout) target
+ copyRecursive (aoutStorePath aout) target
bracket (liftIO $ openFile (jdir </> "log") WriteMode) (liftIO . hClose) $ \logs -> do
forM_ (jobRecipe job) $ \p -> do
@@ -338,7 +341,7 @@ runJob job uses checkoutPath jdir = do
let target = adir </> T.unpack tname </> takeFileName path
liftIO $ do
createDirectoryIfMissing True $ takeDirectory target
- copyFile path target
+ copyRecursiveForce path target
return $ ArtifactOutput
{ aoutName = name
, aoutWorkPath = makeRelative checkoutPath path
@@ -349,3 +352,22 @@ runJob job uses checkoutPath jdir = do
{ outName = jobName job
, outArtifacts = artifacts
}
+
+
+copyRecursive :: FilePath -> FilePath -> IO ()
+copyRecursive from to = do
+ doesDirectoryExist from >>= \case
+ False -> do
+ copyFile from to
+ True -> do
+ createDirectory to
+ content <- listDirectory from
+ forM_ content $ \name -> do
+ copyRecursive (from </> name) (to </> name)
+
+copyRecursiveForce :: FilePath -> FilePath -> IO ()
+copyRecursiveForce from to = do
+ doesDirectoryExist to >>= \case
+ False -> return ()
+ True -> removeDirectoryRecursive to
+ copyRecursive from to
diff --git a/src/Job/Types.hs b/src/Job/Types.hs
index 4024317..ad575a1 100644
--- a/src/Job/Types.hs
+++ b/src/Job/Types.hs
@@ -55,13 +55,18 @@ data ArtifactName = ArtifactName Text
data JobSet' d = JobSet
- { jobsetCommit :: Maybe Commit
+ { jobsetId :: JobSetId' d
+ , jobsetCommit :: Maybe Commit
, jobsetJobsEither :: Either String [ Job' d ]
}
type JobSet = JobSet' Evaluated
type DeclaredJobSet = JobSet' Declared
+type family JobSetId' d :: Type where
+ JobSetId' Declared = ()
+ JobSetId' Evaluated = JobSetId
+
jobsetJobs :: JobSet -> [ Job ]
jobsetJobs = either (const []) id . jobsetJobsEither
@@ -69,6 +74,9 @@ jobsetJobs = either (const []) id . jobsetJobsEither
newtype JobId = JobId [ JobIdPart ]
deriving (Eq, Ord)
+newtype JobSetId = JobSetId [ JobIdPart ]
+ deriving (Eq, Ord)
+
data JobIdPart
= JobIdName JobName
| JobIdCommit (Maybe RepoName) CommitId
diff --git a/src/Repo.hs b/src/Repo.hs
index b154209..09e577b 100644
--- a/src/Repo.hs
+++ b/src/Repo.hs
@@ -9,8 +9,8 @@ module Repo (
Tag(..),
openRepo,
- readCommit, tryReadCommit,
- readTree, tryReadTree,
+ readCommit, readCommitId, tryReadCommit,
+ readTree, readTreeId, tryReadTree,
readBranch,
readTag,
listCommits,
@@ -175,6 +175,9 @@ readCommit :: (MonadIO m, MonadFail m) => Repo -> Text -> m Commit
readCommit repo@GitRepo {..} ref = maybe (fail err) return =<< tryReadCommit repo ref
where err = "revision ‘" <> T.unpack ref <> "’ not found in ‘" <> gitDir <> "’"
+readCommitId :: (MonadIO m, MonadFail m) => Repo -> CommitId -> m Commit
+readCommitId repo cid = readCommit repo (textCommitId cid)
+
tryReadCommit :: (MonadIO m, MonadFail m) => Repo -> Text -> m (Maybe Commit)
tryReadCommit repo ref = sequence . fmap (mkCommit repo . CommitId) =<< tryReadObjectId repo "commit" ref
@@ -182,6 +185,9 @@ readTree :: (MonadIO m, MonadFail m) => Repo -> FilePath -> Text -> m Tree
readTree repo@GitRepo {..} subdir ref = maybe (fail err) return =<< tryReadTree repo subdir ref
where err = "tree ‘" <> T.unpack ref <> "’ not found in ‘" <> gitDir <> "’"
+readTreeId :: (MonadIO m, MonadFail m) => Repo -> FilePath -> TreeId -> m Tree
+readTreeId repo subdir tid = readTree repo subdir $ textTreeId tid
+
tryReadTree :: (MonadIO m, MonadFail m) => Repo -> FilePath -> Text -> m (Maybe Tree)
tryReadTree treeRepo treeSubdir ref = do
fmap (fmap TreeId) (tryReadObjectId treeRepo "tree" ref) >>= \case
diff --git a/test/asset/artifact/minici.yaml b/test/asset/artifact/minici.yaml
index 065ae84..7204bb3 100644
--- a/test/asset/artifact/minici.yaml
+++ b/test/asset/artifact/minici.yaml
@@ -3,15 +3,23 @@ job generate:
shell:
- echo "content 1" > f1
- - mkdir subdir
- - echo "content 2" > subdir/f2
+ - mkdir -p dir/subdir
+ - echo "content 2" > dir/f2
+ - echo "content a" > dir/fa
+ - echo "content b" > dir/subdir/fb
- echo "content 3" > f3
artifact first:
path: f1
artifact second:
- path: subdir/f2
+ path: dir/f2
artifact third:
path: f3
+
+ artifact dir:
+ path: dir
+
+ artifact sdir:
+ path: dir/subdir
diff --git a/test/asset/run/dependencies.yaml b/test/asset/run/dependencies.yaml
new file mode 100644
index 0000000..7452b5a
--- /dev/null
+++ b/test/asset/run/dependencies.yaml
@@ -0,0 +1,55 @@
+job first:
+ shell:
+ - touch x
+
+ artifact out:
+ path: x
+
+
+job second:
+ uses:
+ - first.out
+
+ shell:
+ - mv x y
+
+ artifact out:
+ path: y
+
+
+job third:
+ uses:
+ - first.out
+
+ shell:
+ - mv x z
+
+ artifact out:
+ path: z
+
+
+job fourth:
+ uses:
+ - second.out
+
+ shell:
+ - mv y w
+
+ artifact out:
+ path: w
+
+
+job fifth:
+ uses:
+ - third.out
+ - fourth.out
+
+ shell:
+ - mv z z2
+ - mv w w2
+
+ artifact out1:
+ path: z2
+
+ artifact out2:
+ path: w2
diff --git a/test/script/artifact.et b/test/script/artifact.et
index f1fc74e..c2bfc30 100644
--- a/test/script/artifact.et
+++ b/test/script/artifact.et
@@ -7,21 +7,39 @@ asset scripts:
test ExtractArtifact:
node n
local:
- spawn on n as p args [ "${scripts.path}/minici.yaml", "run", "generate" ]
+ spawn on n as p args [ "--storage=.minici", "${scripts.path}/minici.yaml", "run", "generate" ]
expect /job-finish generate done/ from p
local:
- spawn on n as p args [ "${scripts.path}/minici.yaml", "extract", "generate.first", "extracted" ]
+ spawn on n as p args [ "--storage=.minici", "${scripts.path}/minici.yaml", "extract", "generate.first", "extracted" ]
local:
shell on n as s:
cat ./extracted
expect /content 1/ from s
local:
- spawn on n as p args [ "${scripts.path}/minici.yaml", "extract", "generate.second", "generate.third", "." ]
+ spawn on n as p args [ "--storage=.minici", "${scripts.path}/minici.yaml", "extract", "generate.second", "generate.third", "." ]
local:
shell on n as s:
cat ./f2
cat ./f3
expect /content 2/ from s
expect /content 3/ from s
+
+ local:
+ spawn on n as p args [ "--storage=.minici", "${scripts.path}/minici.yaml", "extract", "generate.dir", "." ]
+ local:
+ shell on n as s:
+ cat ./dir/f2
+ cat ./dir/fa
+ cat ./dir/subdir/fb
+ expect /content 2/ from s
+ expect /content a/ from s
+ expect /content b/ from s
+
+ local:
+ spawn on n as p args [ "--storage=.minici", "${scripts.path}/minici.yaml", "extract", "generate.sdir", "extracted_subdir" ]
+ local:
+ shell on n as s:
+ cat ./extracted_subdir/fb
+ expect /content b/ from s
diff --git a/test/script/run.et b/test/script/run.et
index b6dc1b0..a05ddc4 100644
--- a/test/script/run.et
+++ b/test/script/run.et
@@ -14,7 +14,7 @@ def expect_success from p of job:
expect_result from p of job result "done"
-test RunWithouRepo:
+test RunWithoutRepo:
node n
spawn on n as p args [ "${scripts.path}/norepo-basic.yaml", "run", "success", "failure" ]
expect_result from p:
@@ -228,3 +228,68 @@ test RunExplicitJob:
cat list
rm list
expect /c d/ from s
+
+
+test RunExplicitDependentJob:
+ node n
+ shell on n as git_init:
+ mkdir -p main
+ git -C main -c init.defaultBranch=master init -q
+ cp "${scripts.path}/dependencies.yaml" main/minici.yaml
+ git -C main add minici.yaml
+ git -C main -c user.name=test -c user.email=test commit -q --allow-empty -m 'initial commit'
+
+ mkdir -p main/subdir
+
+ touch main/subdir/a
+ git -C main add subdir
+ git -C main -c user.name=test -c user.email=test commit -q -m 'commit'
+ git -C main rev-parse HEAD^{commit}
+ git -C main rev-parse HEAD^{tree}
+
+ touch main/subdir/b
+ git -C main add subdir
+ git -C main -c user.name=test -c user.email=test commit -q -m 'commit'
+ git -C main rev-parse HEAD^{tree}
+
+ rm main/subdir/a
+ rm main/subdir/b
+ touch main/subdir/c
+ git -C main add subdir
+ git -C main -c user.name=test -c user.email=test commit -q -m 'commit'
+ git -C main rev-parse HEAD^{tree}
+
+ touch main/subdir/d
+ git -C main add subdir
+ git -C main -c user.name=test -c user.email=test commit -q -m 'commit'
+ git -C main rev-parse HEAD^{tree}
+
+ expect /([0-9a-f]+)/ from git_init capture c1
+ expect /([0-9a-f]+)/ from git_init capture t1
+ expect /([0-9a-f]+)/ from git_init capture t2
+ expect /([0-9a-f]+)/ from git_init capture t3
+ expect /([0-9a-f]+)/ from git_init capture t4
+
+ local:
+ spawn on n as p args [ "./main", "run", "$c1.first", "$t2.first", "$t3.fourth", "$c1.fifth", "$c1.fourth", "$c1.third", "$c1.second", "$t4.fifth" ]
+ expect_success from p of "$t1.first"
+ expect_success from p of "$t1.second"
+ expect_success from p of "$t1.third"
+ expect_success from p of "$t1.fourth"
+ expect_success from p of "$t1.fifth"
+
+ expect_success from p of "$t2.first"
+
+ expect_success from p of "$t3.first"
+ expect_success from p of "$t3.second"
+ expect_success from p of "$t3.fourth"
+
+ expect_success from p of "$t4.first"
+ expect_success from p of "$t4.second"
+ expect_success from p of "$t4.third"
+ expect_success from p of "$t4.fourth"
+ expect_success from p of "$t4.fifth"
+
+ flush from p matching /note .*/
+ expect /(.*)/ from p capture done
+ guard (done == "run-finish")