Skip to content

Commit bf9de80

Browse files
committed
Try each pkg-config query separatedly if returned list doesn't match query length
MinGW's pkg-config returns only one version even if queried for multiple libraries.
1 parent 2564b54 commit bf9de80

File tree

1 file changed

+86
-72
lines changed

1 file changed

+86
-72
lines changed
Lines changed: 86 additions & 72 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,10 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
2-
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE DeriveGeneric #-}
3+
4+
-----------------------------------------------------------------------------
5+
36
-----------------------------------------------------------------------------
7+
48
-- |
59
-- Module : Distribution.Solver.Types.PkgConfigDb
610
-- Copyright : (c) Iñaki García Etxebarria 2016
@@ -10,46 +14,51 @@
1014
-- Portability : portable
1115
--
1216
-- Read the list of packages available to pkg-config.
13-
-----------------------------------------------------------------------------
1417
module Distribution.Solver.Types.PkgConfigDb
15-
( PkgConfigDb (..)
16-
, readPkgConfigDb
17-
, pkgConfigDbFromList
18-
, pkgConfigPkgIsPresent
19-
, pkgConfigDbPkgVersion
20-
, getPkgConfigDbDirs
21-
) where
18+
( PkgConfigDb (..)
19+
, readPkgConfigDb
20+
, pkgConfigDbFromList
21+
, pkgConfigPkgIsPresent
22+
, pkgConfigDbPkgVersion
23+
, getPkgConfigDbDirs
24+
) where
2225

2326
import Distribution.Solver.Compat.Prelude
2427
import Prelude ()
2528

26-
import Control.Exception (handle)
27-
import Control.Monad (mapM)
28-
import qualified Data.Map as M
29-
import System.FilePath (splitSearchPath)
29+
import Control.Exception (handle)
30+
import Control.Monad (mapM)
31+
import qualified Data.Map as M
32+
import System.FilePath (splitSearchPath)
3033

31-
import Distribution.Compat.Environment (lookupEnv)
32-
import Distribution.Package (PkgconfigName, mkPkgconfigName)
34+
import Distribution.Compat.Environment (lookupEnv)
35+
import Distribution.Package (PkgconfigName, mkPkgconfigName)
3336
import Distribution.Parsec
3437
import Distribution.Simple.Program
35-
(ProgramDb, getProgramOutput, pkgConfigProgram, needProgram, ConfiguredProgram)
36-
import Distribution.Simple.Program.Run (getProgramInvocationOutputAndErrors, programInvocation)
37-
import Distribution.Simple.Utils (info)
38+
( ConfiguredProgram
39+
, ProgramDb
40+
, getProgramOutput
41+
, needProgram
42+
, pkgConfigProgram
43+
)
44+
import Distribution.Simple.Program.Run (getProgramInvocationOutputAndErrors, programInvocation)
45+
import Distribution.Simple.Utils (info)
3846
import Distribution.Types.PkgconfigVersion
3947
import Distribution.Types.PkgconfigVersionRange
40-
import Distribution.Verbosity (Verbosity)
48+
import Distribution.Verbosity (Verbosity)
4149

4250
-- | The list of packages installed in the system visible to
4351
-- @pkg-config@. This is an opaque datatype, to be constructed with
4452
-- `readPkgConfigDb` and queried with `pkgConfigPkgPresent`.
45-
data PkgConfigDb = PkgConfigDb (M.Map PkgconfigName (Maybe PkgconfigVersion))
46-
-- ^ If an entry is `Nothing`, this means that the
47-
-- package seems to be present, but we don't know the
48-
-- exact version (because parsing of the version
49-
-- number failed).
50-
| NoPkgConfigDb
51-
-- ^ For when we could not run pkg-config successfully.
52-
deriving (Show, Generic, Typeable)
53+
data PkgConfigDb
54+
= -- | If an entry is `Nothing`, this means that the
55+
-- package seems to be present, but we don't know the
56+
-- exact version (because parsing of the version
57+
-- number failed).
58+
PkgConfigDb (M.Map PkgconfigName (Maybe PkgconfigVersion))
59+
| -- | For when we could not run pkg-config successfully.
60+
NoPkgConfigDb
61+
deriving (Show, Generic, Typeable)
5362

5463
instance Binary PkgConfigDb
5564
instance Structured PkgConfigDb
@@ -59,67 +68,72 @@ instance Structured PkgConfigDb
5968
-- information.
6069
readPkgConfigDb :: Verbosity -> ProgramDb -> IO PkgConfigDb
6170
readPkgConfigDb verbosity progdb = handle ioErrorHandler $ do
62-
mpkgConfig <- needProgram verbosity pkgConfigProgram progdb
63-
case mpkgConfig of
64-
Nothing -> noPkgConfig "Cannot find pkg-config program"
65-
Just (pkgConfig, _) -> do
66-
pkgList <- lines <$> getProgramOutput verbosity pkgConfig ["--list-all"]
67-
-- The output of @pkg-config --list-all@ also includes a description
68-
-- for each package, which we do not need.
69-
let pkgNames = map (takeWhile (not . isSpace)) pkgList
70-
(pkgVersions, _errs, exitCode) <-
71-
getProgramInvocationOutputAndErrors verbosity
72-
(programInvocation pkgConfig ("--modversion" : pkgNames))
73-
case exitCode of
74-
ExitSuccess -> (return . pkgConfigDbFromList . zip pkgNames) (lines pkgVersions)
75-
-- if there's a single broken pc file the above fails, so we fall back into calling it individually
76-
_ -> do
77-
info verbosity ("call to pkg-config --modversion on all packages failed. Falling back to querying pkg-config individually on each package")
78-
pkgConfigDbFromList . catMaybes <$> mapM (getIndividualVersion pkgConfig) pkgNames
71+
mpkgConfig <- needProgram verbosity pkgConfigProgram progdb
72+
case mpkgConfig of
73+
Nothing -> noPkgConfig "Cannot find pkg-config program"
74+
Just (pkgConfig, _) -> do
75+
pkgList <- lines <$> getProgramOutput verbosity pkgConfig ["--list-all"]
76+
-- The output of @pkg-config --list-all@ also includes a description
77+
-- for each package, which we do not need.
78+
let pkgNames = map (takeWhile (not . isSpace)) pkgList
79+
(pkgVersions, _errs, exitCode) <-
80+
getProgramInvocationOutputAndErrors
81+
verbosity
82+
(programInvocation pkgConfig ("--modversion" : pkgNames))
83+
if exitCode == ExitSuccess && length pkgNames == length pkgList
84+
then (return . pkgConfigDbFromList . zip pkgNames) (lines pkgVersions)
85+
else -- if there's a single broken pc file the above fails, so we fall back into calling it individually
86+
do
87+
info verbosity ("call to pkg-config --modversion on all packages failed. Falling back to querying pkg-config individually on each package")
88+
pkgConfigDbFromList . catMaybes <$> mapM (getIndividualVersion pkgConfig) pkgNames
89+
where
90+
7991
where
8092
-- For when pkg-config invocation fails (possibly because of a
8193
-- too long command line).
8294
noPkgConfig extra = do
83-
info verbosity ("Failed to query pkg-config, Cabal will continue"
84-
++ " without solving for pkg-config constraints: "
85-
++ extra)
86-
return NoPkgConfigDb
95+
info
96+
verbosity
97+
( "Failed to query pkg-config, Cabal will continue"
98+
++ " without solving for pkg-config constraints: "
99+
++ extra
100+
)
101+
return NoPkgConfigDb
87102

88103
ioErrorHandler :: IOException -> IO PkgConfigDb
89104
ioErrorHandler e = noPkgConfig (show e)
90105

91106
getIndividualVersion :: ConfiguredProgram -> String -> IO (Maybe (String, String))
92107
getIndividualVersion pkgConfig pkg = do
93-
(pkgVersion, _errs, exitCode) <-
94-
getProgramInvocationOutputAndErrors verbosity
95-
(programInvocation pkgConfig ["--modversion",pkg])
96-
return $ case exitCode of
97-
ExitSuccess -> Just (pkg, pkgVersion)
98-
_ -> Nothing
108+
(pkgVersion, _errs, exitCode) <-
109+
getProgramInvocationOutputAndErrors
110+
verbosity
111+
(programInvocation pkgConfig ["--modversion", pkg])
112+
return $ case exitCode of
113+
ExitSuccess -> Just (pkg, pkgVersion)
114+
_ -> Nothing
99115

100116
-- | Create a `PkgConfigDb` from a list of @(packageName, version)@ pairs.
101117
pkgConfigDbFromList :: [(String, String)] -> PkgConfigDb
102118
pkgConfigDbFromList pairs = (PkgConfigDb . M.fromList . map convert) pairs
103-
where
104-
convert :: (String, String) -> (PkgconfigName, Maybe PkgconfigVersion)
105-
convert (n,vs) = (mkPkgconfigName n, simpleParsec vs)
119+
where
120+
convert :: (String, String) -> (PkgconfigName, Maybe PkgconfigVersion)
121+
convert (n, vs) = (mkPkgconfigName n, simpleParsec vs)
106122

107123
-- | Check whether a given package range is satisfiable in the given
108124
-- @pkg-config@ database.
109125
pkgConfigPkgIsPresent :: PkgConfigDb -> PkgconfigName -> PkgconfigVersionRange -> Bool
110126
pkgConfigPkgIsPresent (PkgConfigDb db) pn vr =
111-
case M.lookup pn db of
112-
Nothing -> False -- Package not present in the DB.
113-
Just Nothing -> True -- Package present, but version unknown.
114-
Just (Just v) -> withinPkgconfigVersionRange v vr
127+
case M.lookup pn db of
128+
Nothing -> False -- Package not present in the DB.
129+
Just Nothing -> True -- Package present, but version unknown.
130+
Just (Just v) -> withinPkgconfigVersionRange v vr
115131
-- If we could not read the pkg-config database successfully we fail.
116132
-- The plan found by the solver can't be executed later, because pkg-config itself
117133
-- is going to be called in the build phase to get the library location for linking
118134
-- so even if there is a library, it would need to be passed manual flags anyway.
119135
pkgConfigPkgIsPresent NoPkgConfigDb _ _ = False
120136

121-
122-
123137
-- | Query the version of a package in the @pkg-config@ database.
124138
-- @Nothing@ indicates the package is not in the database, while
125139
-- @Just Nothing@ indicates that the package is in the database,
@@ -132,23 +146,22 @@ pkgConfigDbPkgVersion (PkgConfigDb db) pn = M.lookup pn db
132146
-- don't know about it.
133147
pkgConfigDbPkgVersion NoPkgConfigDb _ = Just Nothing
134148

135-
136149
-- | Query pkg-config for the locations of pkg-config's package files. Use this
137150
-- to monitor for changes in the pkg-config DB.
138-
--
139151
getPkgConfigDbDirs :: Verbosity -> ProgramDb -> IO [FilePath]
140152
getPkgConfigDbDirs verbosity progdb =
141-
(++) <$> getEnvPath <*> getDefPath
142-
where
153+
(++) <$> getEnvPath <*> getDefPath
154+
where
143155
-- According to @man pkg-config@:
144156
--
145157
-- PKG_CONFIG_PATH
146158
-- A colon-separated (on Windows, semicolon-separated) list of directories
147159
-- to search for .pc files. The default directory will always be searched
148160
-- after searching the path
149161
--
150-
getEnvPath = maybe [] parseSearchPath
151-
<$> lookupEnv "PKG_CONFIG_PATH"
162+
getEnvPath =
163+
maybe [] parseSearchPath
164+
<$> lookupEnv "PKG_CONFIG_PATH"
152165

153166
-- Again according to @man pkg-config@:
154167
--
@@ -161,13 +174,14 @@ getPkgConfigDbDirs verbosity progdb =
161174
mpkgConfig <- needProgram verbosity pkgConfigProgram progdb
162175
case mpkgConfig of
163176
Nothing -> return []
164-
Just (pkgConfig, _) -> parseSearchPath <$>
165-
getProgramOutput verbosity pkgConfig ["--variable", "pc_path", "pkg-config"]
177+
Just (pkgConfig, _) ->
178+
parseSearchPath
179+
<$> getProgramOutput verbosity pkgConfig ["--variable", "pc_path", "pkg-config"]
166180

167181
parseSearchPath str =
168182
case lines str of
169183
[p] | not (null p) -> splitSearchPath p
170-
_ -> []
184+
_ -> []
171185

172186
ioErrorHandler :: IOException -> IO [FilePath]
173187
ioErrorHandler _e = return []

0 commit comments

Comments
 (0)