Skip to content

Commit

Permalink
Avoid 'shell' (insecure)
Browse files Browse the repository at this point in the history
  • Loading branch information
srid committed Jan 29, 2025
1 parent 357ffb5 commit 1006831
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 5 deletions.
7 changes: 7 additions & 0 deletions src/Vira/Lib/Git.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,13 @@ remoteBranches url = do
in Just (fromString . toString $ name, fromString . toString $ hash)
_unexpectedPartitions -> Nothing

-- | Return the `CreateProcess` to clone a repo at a specific commit
cloneAtCommit :: Text -> BranchName -> CommitID -> [CreateProcess]
cloneAtCommit url branch commit =
[ proc git ["clone", "--branch", toString branch, "--single-branch", "--depth", "1", toString url, "."]
, proc git ["checkout", toString commit]
]

spec :: Spec
spec = do
describe "Git" $ do
Expand Down
15 changes: 10 additions & 5 deletions src/Vira/Page/JobPage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Vira.Page.JobPage where

import Effectful (Eff)
import Effectful.Error.Static (throwError)
import Effectful.Process (CreateProcess (cwd), shell)
import Effectful.Process (CreateProcess (cwd), proc)
import Effectful.Reader.Dynamic (ask, asks)
import GHC.IO.Exception (ExitCode (..))
import Htmx.Servant.Response
Expand Down Expand Up @@ -93,7 +93,10 @@ triggerNewBuild repoName branchName = do
asks App.supervisor >>= \supervisor -> do
job <- App.update $ St.AddNewJobA repoName branchName branch.headCommit supervisor.baseWorkDir
log Info $ "Added job " <> show job
let stages = stageClone repo branch :| [stageBuild]
let stages =
stageCreateProjectDir
:| stagesClone repo branch
<> [stageBuild]
Supervisor.startTask supervisor job.jobId job.jobWorkingDir stages $ \exitCode -> do
let status = case exitCode of
ExitSuccess -> St.JobFinished St.JobSuccess
Expand All @@ -102,9 +105,11 @@ triggerNewBuild repoName branchName = do
App.update $ St.JobUpdateStatusA job.jobId St.JobRunning
log Info $ "Started task " <> show job.jobId
where
stageClone repo branch =
-- TODO: Avoid shell command for security
shell ("git clone " <> toString repo.cloneUrl <> " project && cd project && git checkout " <> toString branch.headCommit)
stageCreateProjectDir =
proc "mkdir" ["project"]
stagesClone repo branch =
Git.cloneAtCommit repo.cloneUrl branch.branchName branch.headCommit
<&> \p -> p {cwd = Just "project"}
stageBuild =
Omnix.omnixCiProcess
{ cwd = Just "project"
Expand Down

0 comments on commit 1006831

Please sign in to comment.