diff options
author | Roman Smrž <roman.smrz@seznam.cz> | 2025-04-12 15:16:30 +0200 |
---|---|---|
committer | Roman Smrž <roman.smrz@seznam.cz> | 2025-04-12 21:04:14 +0200 |
commit | a8f1e216681a1f03e15b8b71d1f83f7aa3493617 (patch) | |
tree | d76481ca10a6d780d527bd16755dbcd7cf739190 /src/Eval.hs | |
parent | d6c4daa2fb0b7f8dd0afb3ef50b2b85106bfd2ac (diff) |
Track other used repos in job ID
Diffstat (limited to 'src/Eval.hs')
-rw-r--r-- | src/Eval.hs | 132 |
1 files changed, 86 insertions, 46 deletions
diff --git a/src/Eval.hs b/src/Eval.hs index 1278c6f..6413ecb 100644 --- a/src/Eval.hs +++ b/src/Eval.hs @@ -12,11 +12,14 @@ import Control.Monad import Control.Monad.Except import Control.Monad.Reader +import Data.Bifunctor import Data.List import Data.Maybe import Data.Text (Text) import Data.Text qualified as T +import System.FilePath + import Config import Job.Types import Repo @@ -42,15 +45,51 @@ runEval :: Eval a -> EvalInput -> IO (Either EvalError a) runEval action einput = runExceptT $ flip runReaderT einput action -evalJob :: DeclaredJob -> Eval Job -evalJob decl = do +commonPrefix :: Eq a => [ a ] -> [ a ] -> [ a ] +commonPrefix (x : xs) (y : ys) | x == y = x : commonPrefix xs ys +commonPrefix _ _ = [] + +isDefaultRepoMissingInId :: DeclaredJob -> Eval Bool +isDefaultRepoMissingInId djob + | [] <- jobContainingCheckout djob = return False + | otherwise = asks (not . any matches . eiCurrentIdRev) + where + matches (JobIdName _) = False + matches (JobIdCommit rname _) = isNothing rname + matches (JobIdTree rname _) = isNothing rname + +collectOtherRepos :: DeclaredJob -> Eval [ (( Maybe RepoName, Maybe Text ), FilePath ) ] +collectOtherRepos decl = do + missingDefault <- isDefaultRepoMissingInId decl + let checkouts = concat + [ if missingDefault then map (( Nothing, Nothing ), ) $ jobContainingCheckout decl else [] + , map (first (first Just)) $ jobOtherCheckout decl + ] + let commonSubdir reporev = joinPath $ foldr commonPrefix [] $ + map (maybe [] splitDirectories . jcSubtree . snd) . filter ((reporev ==) . fst) $ checkouts + return $ map (\r -> ( r, commonSubdir r )) . nub . map fst $ checkouts + + +evalJob :: [ ( Maybe RepoName, Tree ) ] -> DeclaredJob -> Eval Job +evalJob revisionOverrides decl = do EvalInput {..} <- ask - otherCheckout <- forM (jobOtherCheckout decl) $ \( name, revision, checkout ) -> do - repo <- maybe (throwError $ OtherEvalError $ "repo `" <> textRepoName name <> "' not defined") return $ - lookup name eiOtherRepos - return ( repo, revision, checkout ) + otherRepos <- collectOtherRepos decl + otherRepoIds <- forM otherRepos $ \(( mbname, mbrev ), _ ) -> do + tree <- case lookup mbname revisionOverrides of + Just tree -> return tree + Nothing -> case maybe eiContainingRepo (flip lookup eiOtherRepos) mbname of + Just repo -> getCommitTree =<< readCommit repo (fromMaybe "HEAD" mbrev) + Nothing -> throwError $ OtherEvalError $ "repo ‘" <> maybe "" textRepoName mbname <> "’ not defined" + return $ JobIdTree mbname $ treeId tree + otherCheckout <- forM (jobOtherCheckout decl) $ \(( name, revision ), checkout ) -> do + tree <- case lookup (Just name) revisionOverrides of + Just tree -> return tree + Nothing -> case lookup name eiOtherRepos of + Just repo -> getCommitTree =<< readCommit repo (fromMaybe "HEAD" revision) + Nothing -> throwError $ OtherEvalError $ "repo ‘" <> textRepoName name <> "’ not defined" + return ( tree, checkout ) return Job - { jobId = JobId $ reverse $ JobIdName (jobId decl) : eiCurrentIdRev + { jobId = JobId $ reverse $ reverse otherRepoIds ++ JobIdName (jobId decl) : eiCurrentIdRev , jobName = jobName decl , jobContainingCheckout = jobContainingCheckout decl , jobOtherCheckout = otherCheckout @@ -59,9 +98,9 @@ evalJob decl = do , jobUses = jobUses decl } -evalJobSet :: DeclaredJobSet -> Eval JobSet -evalJobSet decl = do - jobs <- either (return . Left) (handleToEither . mapM evalJob) $ jobsetJobsEither decl +evalJobSet :: [ ( Maybe RepoName, Tree ) ] -> DeclaredJobSet -> Eval JobSet +evalJobSet revisionOverrides decl = do + jobs <- either (return . Left) (handleToEither . mapM (evalJob revisionOverrides)) $ jobsetJobsEither decl return JobSet { jobsetCommit = jobsetCommit decl , jobsetJobsEither = jobs @@ -69,51 +108,52 @@ evalJobSet decl = do where handleToEither = handleError (return . Left . T.unpack . textEvalError) . fmap Right +evalRepo :: Maybe RepoName -> Eval Repo +evalRepo Nothing = asks eiContainingRepo >>= \case + Just repo -> return repo + Nothing -> throwError $ OtherEvalError $ "no default repo" +evalRepo (Just name) = asks (lookup name . eiOtherRepos) >>= \case + Just repo -> return repo + Nothing -> throwError $ OtherEvalError $ "repo ‘" <> textRepoName name <> "’ not defined" + -canonicalJobName :: [ Text ] -> Maybe Tree -> Config -> Eval [ JobIdPart ] -canonicalJobName (r : rs) mbTree config = do +canonicalJobName :: [ Text ] -> Config -> Eval JobId +canonicalJobName (r : rs) config = do let name = JobName r case find ((name ==) . jobName) (configJobs config) of Just djob -> do - job <- evalJob djob - repos <- concat <$> sequence - [ case mbTree of - Just _ -> return [] - Nothing -> maybeToList <$> asks eiContainingRepo - , return $ nub $ map (\( repo, _, _ ) -> repo) $ jobOtherCheckout job - ] - (JobIdName name :) <$> canonicalOtherCheckouts rs repos + otherRepos <- collectOtherRepos djob + ( overrides, rs' ) <- (\f -> foldM f ( [], rs ) otherRepos) $ + \( overrides, crs ) (( mbname, _ ), _ ) -> do + ( tree, crs' ) <- readTreeFromIdRef crs =<< evalRepo mbname + return ( ( mbname, tree ) : overrides, crs' ) + case rs' of + (r' : _) -> throwError $ OtherEvalError $ "unexpected job ref part ‘" <> r' <> "’" + _ -> return () + jobId <$> evalJob overrides djob Nothing -> throwError $ OtherEvalError $ "job ‘" <> r <> "’ not found" -canonicalJobName [] _ _ = throwError $ OtherEvalError "expected job name" +canonicalJobName [] _ = throwError $ OtherEvalError "expected job name" -canonicalOtherCheckouts :: [ Text ] -> [ Repo ] -> Eval [ JobIdPart ] -canonicalOtherCheckouts (r : rs) (repo : repos) = do - tree <- tryReadCommit repo r >>= \case - Just commit -> getCommitTree commit +readTreeFromIdRef :: [ Text ] -> Repo -> Eval ( Tree, [ Text ] ) +readTreeFromIdRef (r : rs) repo = do + tryReadCommit repo r >>= \case + Just commit -> (, rs) <$> getCommitTree commit Nothing -> tryReadTree repo r >>= \case - Just tree -> return tree - Nothing -> throwError $ OtherEvalError $ "failed to resolve ‘" <> r <> "’ to a commit or tree in " <> T.pack (show repo) - (JobIdTree (treeId tree) :) <$> canonicalOtherCheckouts rs repos -canonicalOtherCheckouts [] [] = return [] -canonicalOtherCheckouts [] (_ : _ ) = throwError $ OtherEvalError $ "expected commit or tree reference" -canonicalOtherCheckouts (r : _) [] = throwError $ OtherEvalError $ "unexpected job ref part ‘" <> r <> "’" - -canonicalCommitConfig :: [ Text ] -> Repo -> Eval [ JobIdPart ] -canonicalCommitConfig (r : rs) repo = do - tree <- tryReadCommit repo r >>= \case - Just commit -> getCommitTree commit - Nothing -> tryReadTree repo r >>= \case - Just tree -> return tree + Just tree -> return ( tree, rs ) 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 JobId +canonicalCommitConfig rs repo = do + ( tree, rs' ) <- readTreeFromIdRef rs repo config <- either fail return =<< loadConfigForCommit tree - (JobIdTree (treeId tree) :) <$> canonicalJobName rs (Just tree) config -canonicalCommitConfig [] _ = throwError $ OtherEvalError "expected commit or tree reference" + local (\ei -> ei { eiCurrentIdRev = JobIdTree Nothing (treeId tree) : eiCurrentIdRev ei }) $ + canonicalJobName rs' config evalJobReference :: JobRef -> Eval JobId evalJobReference (JobRef rs) = - JobId <$> do - asks eiJobRoot >>= \case - JobRootRepo defRepo -> do - canonicalCommitConfig rs defRepo - JobRootConfig config -> do - canonicalJobName rs Nothing config + asks eiJobRoot >>= \case + JobRootRepo defRepo -> do + canonicalCommitConfig rs defRepo + JobRootConfig config -> do + canonicalJobName rs config |