Skip to content

Commit

Permalink
merge from git-annex
Browse files Browse the repository at this point in the history
and simplify configure
  • Loading branch information
joeyh committed Aug 14, 2023
1 parent edf8398 commit 0b16009
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 86 deletions.
28 changes: 15 additions & 13 deletions Build/Configure.hs
Original file line number Diff line number Diff line change
@@ -1,31 +1,33 @@
{- Checks system configuration and generates SysConfig. -}
{- Checks system configuration and generates Build/SysConfig. -}

{-# OPTIONS_GHC -fno-warn-tabs #-}

module Build.Configure where

import Control.Monad.IfElse
import Control.Applicative
import Prelude

import Build.TestConfig
import Build.Version
import Git.Version
import Utility.Env.Basic
import qualified Git.Version

import Control.Monad

tests :: [TestCase]
tests =
[ TestCase "version" (Config "packageversion" . StringConfig <$> getVersion)
, TestCase "git" $ testCmd "git" "git --version >/dev/null"
[ TestCase "git" $ testCmd "git" "git --version >/dev/null"
, TestCase "git version" getGitVersion
]

getGitVersion :: Test
getGitVersion = Config "gitversion" . StringConfig . show
<$> Git.Version.installed
getGitVersion = go =<< getEnv "FORCE_GIT_VERSION"
where
go (Just s) = return $ Config "gitversion" $ StringConfig s
go Nothing = do
v <- Git.Version.installed
let oldestallowed = Git.Version.normalize "2.1"
when (v < oldestallowed) $
error $ "installed git version " ++ show v ++ " is too old! (Need " ++ show oldestallowed ++ " or newer)"
return $ Config "gitversion" $ StringConfig $ show v

run :: [TestCase] -> IO ()
run ts = do
config <- runTests ts
writeSysConfig config
whenM (isReleaseBuild) $
cabalSetup "git-repair.cabal"
2 changes: 1 addition & 1 deletion Build/TestConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Build.TestConfig where
import Utility.Path
import Utility.Monad
import Utility.SafeCommand
import Utility.Directory
import Utility.SystemDirectory

import System.IO
import System.FilePath
Expand Down
71 changes: 0 additions & 71 deletions Build/Version.hs

This file was deleted.

1 change: 0 additions & 1 deletion git-repair.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,6 @@ Executable git-repair
BuildInfo
Build.Configure
Build.TestConfig
Build.Version
Common
Git
Git.Branch
Expand Down

0 comments on commit 0b16009

Please sign in to comment.