Skip to content

Commit

Permalink
tools: refactor: extract repo checks to utility method
Browse files Browse the repository at this point in the history
  • Loading branch information
frasertweedale authored and blackheaven committed Aug 2, 2024
1 parent 2105eb1 commit 37a07b3
Show file tree
Hide file tree
Showing 4 changed files with 31 additions and 31 deletions.
24 changes: 5 additions & 19 deletions code/hsec-tools/app/Command/NextID.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,10 @@
{-# LANGUAGE LambdaCase #-}

module Command.NextID where

import Control.Monad (unless)
import Data.Maybe (fromMaybe)
import System.Exit (die)

import Security.Advisories.Git (getRepoRoot)
import Security.Advisories.Core.HsecId (printHsecId, getNextHsecId)
import Security.Advisories.Filesystem (isSecurityAdvisoriesRepo, getGreatestId)
import Security.Advisories.Filesystem (getGreatestId)

runNextIDCommand :: Maybe FilePath -> IO ()
runNextIDCommand mPath = do
let
path = fromMaybe "." mPath
repoPath <- getRepoRoot path >>= \case
Left _ -> die "Not a git repo"
Right a -> pure a
isRepo <- isSecurityAdvisoriesRepo repoPath
unless isRepo $
die "Not a security-advisories repo"
import Util (ensureRepo)

getGreatestId repoPath >>= getNextHsecId >>= putStrLn . printHsecId
runNextIDCommand :: Maybe FilePath -> IO ()
runNextIDCommand mPath =
ensureRepo mPath >>= getGreatestId >>= getNextHsecId >>= putStrLn . printHsecId
16 changes: 4 additions & 12 deletions code/hsec-tools/app/Command/Reserve.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,14 @@

module Command.Reserve where

import Control.Monad (unless, when)
import Data.Maybe (fromMaybe)
import Control.Monad (when)
import System.Exit (die)
import System.FilePath ((</>), (<.>))

import Security.Advisories.Git
( add
, commit
, explainGitError
, getRepoRoot
)
import Security.Advisories.Core.HsecId
( placeholder
Expand All @@ -21,10 +19,11 @@ import Security.Advisories.Core.HsecId
import Security.Advisories.Filesystem
( dirNameAdvisories
, dirNameReserved
, isSecurityAdvisoriesRepo
, getGreatestId
)

import Util (ensureRepo)

-- | How to choose IDs when creating advisories or
-- reservations.
data IdMode
Expand All @@ -40,14 +39,7 @@ data CommitFlag = Commit | DoNotCommit

runReserveCommand :: Maybe FilePath -> IdMode -> CommitFlag -> IO ()
runReserveCommand mPath idMode commitFlag = do
let
path = fromMaybe "." mPath
repoPath <- getRepoRoot path >>= \case
Left _ -> die "Not a git repo"
Right a -> pure a
isRepo <- isSecurityAdvisoriesRepo repoPath
unless isRepo $
die "Not a security-advisories repo"
repoPath <- ensureRepo mPath

hsid <- case idMode of
IdModePlaceholder -> pure placeholder
Expand Down
21 changes: 21 additions & 0 deletions code/hsec-tools/app/Util.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
{-# LANGUAGE LambdaCase #-}

module Util where

import Data.Maybe (fromMaybe)
import System.Exit (die)

import Security.Advisories.Filesystem (isSecurityAdvisoriesRepo)
import Security.Advisories.Git (getRepoRoot)

-- | Ensure the given path (or current directory "." if @Nothing@)
-- is an advisory Git repo. Return the (valid) repo root, or die
-- with an error message.
--
ensureRepo :: Maybe FilePath -> IO FilePath
ensureRepo mPath =
getRepoRoot (fromMaybe "." mPath) >>= \case
Left _ -> die "Not a git repo"
Right repoPath -> isSecurityAdvisoriesRepo repoPath >>= \case
False -> die "Not a security-advisories repo"
True -> pure repoPath
1 change: 1 addition & 0 deletions code/hsec-tools/hsec-tools.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,7 @@ executable hsec-tools
main-is: Main.hs
other-modules: Command.Reserve
, Command.NextID
, Util

-- Modules included in this executable, other than Main.
-- other-modules:
Expand Down

0 comments on commit 37a07b3

Please sign in to comment.