Skip to content
Snippets Groups Projects
Commit bec0c699 authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Add needProgram

And use it to make readPkgConfigDb not fail if there aren't pkg-config
executable.
parent 713367d5
No related branches found
No related tags found
No related merge requests found
......@@ -90,6 +90,7 @@ module Distribution.Simple.Program (
, reconfigurePrograms
, requireProgram
, requireProgramVersion
, needProgram
, runDbProgram
, getDbProgramOutput
......
......@@ -57,6 +57,7 @@ module Distribution.Simple.Program.Db (
reconfigurePrograms,
requireProgram,
requireProgramVersion,
needProgram,
) where
......@@ -413,6 +414,22 @@ reconfigurePrograms verbosity paths argss progdb = do
requireProgram :: Verbosity -> Program -> ProgramDb
-> IO (ConfiguredProgram, ProgramDb)
requireProgram verbosity prog progdb = do
mres <- needProgram verbosity prog progdb
case mres of
Nothing -> die' verbosity notFound
Just res -> return res
where
notFound = "The program '" ++ programName prog ++ "' is required but it could not be found."
-- | Check that a program is configured and available to be run.
--
-- It returns 'Nothing' if the program couldn't be configured,
-- or is not found.
--
-- @since 3.2.0.0
needProgram :: Verbosity -> Program -> ProgramDb
-> IO (Maybe (ConfiguredProgram, ProgramDb))
needProgram verbosity prog progdb = do
-- If it's not already been configured, try to configure it now
progdb' <- case lookupProgram prog progdb of
......@@ -420,12 +437,8 @@ requireProgram verbosity prog progdb = do
Just _ -> return progdb
case lookupProgram prog progdb' of
Nothing -> die' verbosity notFound
Just configuredProg -> return (configuredProg, progdb')
where notFound = "The program '" ++ programName prog
++ "' is required but it could not be found."
Nothing -> return Nothing
Just configuredProg -> return (Just (configuredProg, progdb'))
-- | Check that a program is configured and available to be run.
--
......
......@@ -31,7 +31,7 @@ import Distribution.Compat.Environment (lookupEnv)
import Distribution.Package (PkgconfigName, mkPkgconfigName)
import Distribution.Parsec
import Distribution.Simple.Program
(ProgramDb, getProgramOutput, pkgConfigProgram, requireProgram)
(ProgramDb, getProgramOutput, pkgConfigProgram, needProgram)
import Distribution.Simple.Utils (info)
import Distribution.Types.PkgconfigVersion
import Distribution.Types.PkgconfigVersionRange
......@@ -56,23 +56,28 @@ instance Binary PkgConfigDb
-- information.
readPkgConfigDb :: Verbosity -> ProgramDb -> IO PkgConfigDb
readPkgConfigDb verbosity progdb = handle ioErrorHandler $ do
(pkgConfig, _) <- requireProgram verbosity pkgConfigProgram progdb
pkgList <- lines <$> getProgramOutput verbosity pkgConfig ["--list-all"]
-- The output of @pkg-config --list-all@ also includes a description
-- for each package, which we do not need.
let pkgNames = map (takeWhile (not . isSpace)) pkgList
pkgVersions <- lines <$> getProgramOutput verbosity pkgConfig
("--modversion" : pkgNames)
(return . pkgConfigDbFromList . zip pkgNames) pkgVersions
where
-- For when pkg-config invocation fails (possibly because of a
-- too long command line).
ioErrorHandler :: IOException -> IO PkgConfigDb
ioErrorHandler e = do
info verbosity ("Failed to query pkg-config, Cabal will continue"
++ " without solving for pkg-config constraints: "
++ show e)
return NoPkgConfigDb
mpkgConfig <- needProgram verbosity pkgConfigProgram progdb
case mpkgConfig of
Nothing -> noPkgConfig "Cannot find pkg-config program"
Just (pkgConfig, _) -> do
pkgList <- lines <$> getProgramOutput verbosity pkgConfig ["--list-all"]
-- The output of @pkg-config --list-all@ also includes a description
-- for each package, which we do not need.
let pkgNames = map (takeWhile (not . isSpace)) pkgList
pkgVersions <- lines <$> getProgramOutput verbosity pkgConfig
("--modversion" : pkgNames)
(return . pkgConfigDbFromList . zip pkgNames) pkgVersions
where
-- For when pkg-config invocation fails (possibly because of a
-- too long command line).
noPkgConfig extra = do
info verbosity ("Failed to query pkg-config, Cabal will continue"
++ " without solving for pkg-config constraints: "
++ extra)
return NoPkgConfigDb
ioErrorHandler :: IOException -> IO PkgConfigDb
ioErrorHandler e = noPkgConfig (show e)
-- | Create a `PkgConfigDb` from a list of @(packageName, version)@ pairs.
pkgConfigDbFromList :: [(String, String)] -> PkgConfigDb
......@@ -134,10 +139,11 @@ getPkgConfigDbDirs verbosity progdb =
-- > pkg-config --variable pc_path pkg-config
--
getDefPath = handle ioErrorHandler $ do
(pkgConfig, _) <- requireProgram verbosity pkgConfigProgram progdb
parseSearchPath <$>
getProgramOutput verbosity pkgConfig
["--variable", "pc_path", "pkg-config"]
mpkgConfig <- needProgram verbosity pkgConfigProgram progdb
case mpkgConfig of
Nothing -> return []
Just (pkgConfig, _) -> parseSearchPath <$>
getProgramOutput verbosity pkgConfig ["--variable", "pc_path", "pkg-config"]
parseSearchPath str =
case lines str of
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment