-- -fno-warn-deprecations for use of Map.foldWithKey
{-# OPTIONS_GHC -fno-warn-deprecations #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.PackageDescription.Configuration
-- Copyright   :  Thomas Schilling, 2007
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is about the cabal configurations feature. It exports
-- 'finalizePD' and 'flattenPackageDescription' which are
-- functions for converting 'GenericPackageDescription's down to
-- 'PackageDescription's. It has code for working with the tree of conditions
-- and resolving or flattening conditions.

module Distribution.PackageDescription.Configuration (
    finalizePD,
    flattenPackageDescription,

    -- Utils
    parseCondition,
    freeVars,
    extractCondition,
    extractConditions,
    addBuildableCondition,
    mapCondTree,
    mapTreeData,
    mapTreeConds,
    mapTreeConstrs,
    transformAllBuildInfos,
    transformAllBuildDepends,
  ) where

import Prelude ()
import Distribution.Compat.Prelude

-- lens
import qualified Distribution.Types.BuildInfo.Lens as L
import qualified Distribution.Types.GenericPackageDescription.Lens as L
import qualified Distribution.Types.PackageDescription.Lens as L
import qualified Distribution.Types.SetupBuildInfo.Lens as L

import Distribution.PackageDescription
import Distribution.PackageDescription.Utils
import Distribution.Version
import Distribution.Compiler
import Distribution.System
import Distribution.Parsec
import Distribution.Pretty
import Distribution.Compat.CharParsing hiding (char)
import qualified Distribution.Compat.CharParsing as P
import Distribution.Simple.Utils
import Distribution.Compat.Lens
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.ForeignLib
import Distribution.Types.Component
import Distribution.Types.Dependency
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName
import Distribution.Types.CondTree
import Distribution.Types.Condition
import Distribution.Types.DependencyMap

import qualified Data.Map.Strict as Map.Strict
import qualified Data.Map.Lazy   as Map
import qualified Data.Set as Set
import Data.Tree ( Tree(Node) )

------------------------------------------------------------------------------

-- | Simplify a configuration condition using the OS and arch names.  Returns
--   the names of all the flags occurring in the condition.
simplifyWithSysParams :: OS -> Arch -> CompilerInfo -> Condition ConfVar
                      -> (Condition FlagName, [FlagName])
simplifyWithSysParams :: OS
-> Arch
-> CompilerInfo
-> Condition ConfVar
-> (Condition FlagName, [FlagName])
simplifyWithSysParams OS
os Arch
arch CompilerInfo
cinfo Condition ConfVar
cond = (Condition FlagName
cond', [FlagName]
flags)
  where
    (Condition FlagName
cond', [FlagName]
flags) = Condition ConfVar
-> (ConfVar -> Either FlagName Bool)
-> (Condition FlagName, [FlagName])
forall c d.
Condition c -> (c -> Either d Bool) -> (Condition d, [d])
simplifyCondition Condition ConfVar
cond ConfVar -> Either FlagName Bool
interp
    interp :: ConfVar -> Either FlagName Bool
interp (OS OS
os')    = Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right (Bool -> Either FlagName Bool) -> Bool -> Either FlagName Bool
forall a b. (a -> b) -> a -> b
$ OS
os' OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
os
    interp (Arch Arch
arch') = Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right (Bool -> Either FlagName Bool) -> Bool -> Either FlagName Bool
forall a b. (a -> b) -> a -> b
$ Arch
arch' Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
arch
    interp (Impl CompilerFlavor
comp VersionRange
vr)
      | CompilerId -> Bool
matchImpl (CompilerInfo -> CompilerId
compilerInfoId CompilerInfo
cinfo) = Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right Bool
True
      | Bool
otherwise = case CompilerInfo -> Maybe [CompilerId]
compilerInfoCompat CompilerInfo
cinfo of
          -- fixme: treat Nothing as unknown, rather than empty list once we
          --        support partial resolution of system parameters
          Maybe [CompilerId]
Nothing     -> Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right Bool
False
          Just [CompilerId]
compat -> Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right ((CompilerId -> Bool) -> [CompilerId] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any CompilerId -> Bool
matchImpl [CompilerId]
compat)
          where
            matchImpl :: CompilerId -> Bool
matchImpl (CompilerId CompilerFlavor
c Version
v) = CompilerFlavor
comp CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
== CompilerFlavor
c Bool -> Bool -> Bool
&& Version
v Version -> VersionRange -> Bool
`withinRange` VersionRange
vr
    interp (Flag FlagName
f) = FlagName -> Either FlagName Bool
forall a b. a -> Either a b
Left FlagName
f

-- TODO: Add instances and check
--
-- prop_sC_idempotent cond a o = cond' == cond''
--   where
--     cond'  = simplifyCondition cond a o
--     cond'' = simplifyCondition cond' a o
--
-- prop_sC_noLits cond a o = isLit res || not (hasLits res)
--   where
--     res = simplifyCondition cond a o
--     hasLits (Lit _) = True
--     hasLits (CNot c) = hasLits c
--     hasLits (COr l r) = hasLits l || hasLits r
--     hasLits (CAnd l r) = hasLits l || hasLits r
--     hasLits _ = False
--

-- | Parse a configuration condition from a string.
parseCondition :: CabalParsing m => m (Condition ConfVar)
parseCondition :: m (Condition ConfVar)
parseCondition = m (Condition ConfVar)
condOr
  where
    condOr :: m (Condition ConfVar)
condOr   = m (Condition ConfVar) -> m () -> m (NonEmpty (Condition ConfVar))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
sepByNonEmpty m (Condition ConfVar)
condAnd (String -> m ()
oper String
"||") m (NonEmpty (Condition ConfVar))
-> (NonEmpty (Condition ConfVar) -> m (Condition ConfVar))
-> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (NonEmpty (Condition ConfVar) -> Condition ConfVar)
-> NonEmpty (Condition ConfVar)
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Condition ConfVar -> Condition ConfVar -> Condition ConfVar)
-> NonEmpty (Condition ConfVar) -> Condition ConfVar
forall a. (a -> a -> a) -> NonEmpty a -> a
foldl1 Condition ConfVar -> Condition ConfVar -> Condition ConfVar
forall c. Condition c -> Condition c -> Condition c
COr
    condAnd :: m (Condition ConfVar)
condAnd  = m (Condition ConfVar) -> m () -> m (NonEmpty (Condition ConfVar))
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
sepByNonEmpty m (Condition ConfVar)
cond (String -> m ()
oper String
"&&")m (NonEmpty (Condition ConfVar))
-> (NonEmpty (Condition ConfVar) -> m (Condition ConfVar))
-> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (NonEmpty (Condition ConfVar) -> Condition ConfVar)
-> NonEmpty (Condition ConfVar)
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Condition ConfVar -> Condition ConfVar -> Condition ConfVar)
-> NonEmpty (Condition ConfVar) -> Condition ConfVar
forall a. (a -> a -> a) -> NonEmpty a -> a
foldl1 Condition ConfVar -> Condition ConfVar -> Condition ConfVar
forall c. Condition c -> Condition c -> Condition c
CAnd
    -- TODO: try?
    cond :: m (Condition ConfVar)
cond     = m ()
sp m () -> m (Condition ConfVar) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (m (Condition ConfVar)
forall c. m (Condition c)
boolLiteral m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar) -> m (Condition ConfVar)
forall a. m a -> m a
inparens m (Condition ConfVar)
condOr m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar)
notCond m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar)
osCond
                      m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar)
archCond m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar)
flagCond m (Condition ConfVar)
-> m (Condition ConfVar) -> m (Condition ConfVar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m (Condition ConfVar)
implCond )
    inparens :: m a -> m a
inparens   = m () -> m () -> m a -> m a
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
between (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'(' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp) (m ()
sp m () -> m Char -> m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
')' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp)
    notCond :: m (Condition ConfVar)
notCond  = Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'!' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp m () -> m (Condition ConfVar) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m (Condition ConfVar)
cond m (Condition ConfVar)
-> (Condition ConfVar -> m (Condition ConfVar))
-> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (Condition ConfVar -> Condition ConfVar)
-> Condition ConfVar
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Condition ConfVar -> Condition ConfVar
forall c. Condition c -> Condition c
CNot
    osCond :: m (Condition ConfVar)
osCond   = String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
string String
"os" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp m () -> m ConfVar -> m ConfVar
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ConfVar -> m ConfVar
forall a. m a -> m a
inparens m ConfVar
osIdent m ConfVar
-> (ConfVar -> m (Condition ConfVar)) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (ConfVar -> Condition ConfVar)
-> ConfVar
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfVar -> Condition ConfVar
forall c. c -> Condition c
Var
    archCond :: m (Condition ConfVar)
archCond = String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
string String
"arch" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp m () -> m ConfVar -> m ConfVar
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ConfVar -> m ConfVar
forall a. m a -> m a
inparens m ConfVar
archIdent m ConfVar
-> (ConfVar -> m (Condition ConfVar)) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (ConfVar -> Condition ConfVar)
-> ConfVar
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfVar -> Condition ConfVar
forall c. c -> Condition c
Var
    flagCond :: m (Condition ConfVar)
flagCond = String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
string String
"flag" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp m () -> m ConfVar -> m ConfVar
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ConfVar -> m ConfVar
forall a. m a -> m a
inparens m ConfVar
flagIdent m ConfVar
-> (ConfVar -> m (Condition ConfVar)) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (ConfVar -> Condition ConfVar)
-> ConfVar
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfVar -> Condition ConfVar
forall c. c -> Condition c
Var
    implCond :: m (Condition ConfVar)
implCond = String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
string String
"impl" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp m () -> m ConfVar -> m ConfVar
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ConfVar -> m ConfVar
forall a. m a -> m a
inparens m ConfVar
implIdent m ConfVar
-> (ConfVar -> m (Condition ConfVar)) -> m (Condition ConfVar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Condition ConfVar -> m (Condition ConfVar)
forall (m :: * -> *) a. Monad m => a -> m a
return (Condition ConfVar -> m (Condition ConfVar))
-> (ConfVar -> Condition ConfVar)
-> ConfVar
-> m (Condition ConfVar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfVar -> Condition ConfVar
forall c. c -> Condition c
Var
    boolLiteral :: m (Condition c)
boolLiteral   = (Bool -> Condition c) -> m Bool -> m (Condition c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Condition c
forall c. Bool -> Condition c
Lit  m Bool
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    archIdent :: m ConfVar
archIdent     = (Arch -> ConfVar) -> m Arch -> m ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Arch -> ConfVar
Arch m Arch
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    osIdent :: m ConfVar
osIdent       = (OS -> ConfVar) -> m OS -> m ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OS -> ConfVar
OS   m OS
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    flagIdent :: m ConfVar
flagIdent     = (String -> ConfVar) -> m String -> m ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FlagName -> ConfVar
Flag (FlagName -> ConfVar) -> (String -> FlagName) -> String -> ConfVar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FlagName
mkFlagName (String -> FlagName) -> (String -> String) -> String -> FlagName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
lowercase) ((Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
munch1 Char -> Bool
isIdentChar)
    isIdentChar :: Char -> Bool
isIdentChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'
    oper :: String -> m ()
oper String
s        = m ()
sp m () -> m String -> m String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
string String
s m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m ()
sp
    sp :: m ()
sp            = m ()
forall (m :: * -> *). CharParsing m => m ()
spaces 
    implIdent :: m ConfVar
implIdent     = do CompilerFlavor
i <- m CompilerFlavor
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
                       VersionRange
vr <- m ()
sp m () -> m VersionRange -> m VersionRange
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> VersionRange -> m VersionRange -> m VersionRange
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option VersionRange
anyVersion m VersionRange
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
                       ConfVar -> m ConfVar
forall (m :: * -> *) a. Monad m => a -> m a
return (ConfVar -> m ConfVar) -> ConfVar -> m ConfVar
forall a b. (a -> b) -> a -> b
$ CompilerFlavor -> VersionRange -> ConfVar
Impl CompilerFlavor
i VersionRange
vr

------------------------------------------------------------------------------

-- | Result of dependency test. Isomorphic to @Maybe d@ but renamed for
--   clarity.
data DepTestRslt d = DepOk | MissingDeps d

instance Semigroup d => Monoid (DepTestRslt d) where
    mempty :: DepTestRslt d
mempty = DepTestRslt d
forall d. DepTestRslt d
DepOk
    mappend :: DepTestRslt d -> DepTestRslt d -> DepTestRslt d
mappend = DepTestRslt d -> DepTestRslt d -> DepTestRslt d
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup d => Semigroup (DepTestRslt d) where
    DepTestRslt d
DepOk <> :: DepTestRslt d -> DepTestRslt d -> DepTestRslt d
<> DepTestRslt d
x     = DepTestRslt d
x
    DepTestRslt d
x     <> DepTestRslt d
DepOk = DepTestRslt d
x
    (MissingDeps d
d) <> (MissingDeps d
d') = d -> DepTestRslt d
forall d. d -> DepTestRslt d
MissingDeps (d
d d -> d -> d
forall a. Semigroup a => a -> a -> a
<> d
d')


-- | Try to find a flag assignment that satisfies the constraints of all trees.
--
-- Returns either the missing dependencies, or a tuple containing the
-- resulting data, the associated dependencies, and the chosen flag
-- assignments.
--
-- In case of failure, the union of the dependencies that led to backtracking
-- on all branches is returned.
-- [TODO: Could also be specified with a function argument.]
--
-- TODO: The current algorithm is rather naive.  A better approach would be to:
--
-- * Rule out possible paths, by taking a look at the associated dependencies.
--
-- * Infer the required values for the conditions of these paths, and
--   calculate the required domains for the variables used in these
--   conditions.  Then picking a flag assignment would be linear (I guess).
--
-- This would require some sort of SAT solving, though, thus it's not
-- implemented unless we really need it.
--
resolveWithFlags ::
     [(FlagName,[Bool])]
        -- ^ Domain for each flag name, will be tested in order.
  -> ComponentRequestedSpec
  -> OS      -- ^ OS as returned by Distribution.System.buildOS
  -> Arch    -- ^ Arch as returned by Distribution.System.buildArch
  -> CompilerInfo  -- ^ Compiler information
  -> [Dependency]  -- ^ Additional constraints
  -> [CondTree ConfVar [Dependency] PDTagged]
  -> ([Dependency] -> DepTestRslt [Dependency])  -- ^ Dependency test function.
  -> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
       -- ^ Either the missing dependencies (error case), or a pair of
       -- (set of build targets with dependencies, chosen flag assignments)
resolveWithFlags :: [(FlagName, [Bool])]
-> ComponentRequestedSpec
-> OS
-> Arch
-> CompilerInfo
-> [Dependency]
-> [CondTree ConfVar [Dependency] PDTagged]
-> ([Dependency] -> DepTestRslt [Dependency])
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
resolveWithFlags [(FlagName, [Bool])]
dom ComponentRequestedSpec
enabled OS
os Arch
arch CompilerInfo
impl [Dependency]
constrs [CondTree ConfVar [Dependency] PDTagged]
trees [Dependency] -> DepTestRslt [Dependency]
checkDeps =
    (DepMapUnion
 -> Either [Dependency] (TargetSet PDTagged, FlagAssignment))
-> ((TargetSet PDTagged, FlagAssignment)
    -> Either [Dependency] (TargetSet PDTagged, FlagAssignment))
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Dependency]
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
forall a b. a -> Either a b
Left ([Dependency]
 -> Either [Dependency] (TargetSet PDTagged, FlagAssignment))
-> (DepMapUnion -> [Dependency])
-> DepMapUnion
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DepMapUnion -> [Dependency]
fromDepMapUnion) (TargetSet PDTagged, FlagAssignment)
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
forall a b. b -> Either a b
Right (Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
 -> Either [Dependency] (TargetSet PDTagged, FlagAssignment))
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
forall a b. (a -> b) -> a -> b
$ Tree FlagAssignment
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
explore (FlagAssignment -> [(FlagName, [Bool])] -> Tree FlagAssignment
build FlagAssignment
forall a. Monoid a => a
mempty [(FlagName, [Bool])]
dom)
  where
    extraConstrs :: DependencyMap
extraConstrs = [Dependency] -> DependencyMap
toDepMap [Dependency]
constrs

    -- simplify trees by (partially) evaluating all conditions and converting
    -- dependencies to dependency maps.
    simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged]
    simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged]
simplifiedTrees = (CondTree ConfVar [Dependency] PDTagged
 -> CondTree FlagName DependencyMap PDTagged)
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree FlagName DependencyMap PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map ( ([Dependency] -> DependencyMap)
-> CondTree FlagName [Dependency] PDTagged
-> CondTree FlagName DependencyMap PDTagged
forall c d v a. (c -> d) -> CondTree v c a -> CondTree v d a
mapTreeConstrs [Dependency] -> DependencyMap
toDepMap  -- convert to maps
                          (CondTree FlagName [Dependency] PDTagged
 -> CondTree FlagName DependencyMap PDTagged)
-> (CondTree ConfVar [Dependency] PDTagged
    -> CondTree FlagName [Dependency] PDTagged)
-> CondTree ConfVar [Dependency] PDTagged
-> CondTree FlagName DependencyMap PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree FlagName [Dependency] PDTagged
-> CondTree FlagName [Dependency] PDTagged
forall v c.
(Eq v, Monoid c) =>
CondTree v c PDTagged -> CondTree v c PDTagged
addBuildableConditionPDTagged
                          (CondTree FlagName [Dependency] PDTagged
 -> CondTree FlagName [Dependency] PDTagged)
-> (CondTree ConfVar [Dependency] PDTagged
    -> CondTree FlagName [Dependency] PDTagged)
-> CondTree ConfVar [Dependency] PDTagged
-> CondTree FlagName [Dependency] PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Condition ConfVar -> Condition FlagName)
-> CondTree ConfVar [Dependency] PDTagged
-> CondTree FlagName [Dependency] PDTagged
forall v w c a.
(Condition v -> Condition w) -> CondTree v c a -> CondTree w c a
mapTreeConds ((Condition FlagName, [FlagName]) -> Condition FlagName
forall a b. (a, b) -> a
fst ((Condition FlagName, [FlagName]) -> Condition FlagName)
-> (Condition ConfVar -> (Condition FlagName, [FlagName]))
-> Condition ConfVar
-> Condition FlagName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OS
-> Arch
-> CompilerInfo
-> Condition ConfVar
-> (Condition FlagName, [FlagName])
simplifyWithSysParams OS
os Arch
arch CompilerInfo
impl))
                          [CondTree ConfVar [Dependency] PDTagged]
trees

    -- @explore@ searches a tree of assignments, backtracking whenever a flag
    -- introduces a dependency that cannot be satisfied.  If there is no
    -- solution, @explore@ returns the union of all dependencies that caused
    -- it to backtrack.  Since the tree is constructed lazily, we avoid some
    -- computation overhead in the successful case.
    explore :: Tree FlagAssignment
            -> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
    explore :: Tree FlagAssignment
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
explore (Node FlagAssignment
flags Forest FlagAssignment
ts) =
        let targetSet :: TargetSet PDTagged
targetSet = [(DependencyMap, PDTagged)] -> TargetSet PDTagged
forall a. [(DependencyMap, a)] -> TargetSet a
TargetSet ([(DependencyMap, PDTagged)] -> TargetSet PDTagged)
-> [(DependencyMap, PDTagged)] -> TargetSet PDTagged
forall a b. (a -> b) -> a -> b
$ ((CondTree FlagName DependencyMap PDTagged
  -> (DependencyMap, PDTagged))
 -> [CondTree FlagName DependencyMap PDTagged]
 -> [(DependencyMap, PDTagged)])
-> [CondTree FlagName DependencyMap PDTagged]
-> (CondTree FlagName DependencyMap PDTagged
    -> (DependencyMap, PDTagged))
-> [(DependencyMap, PDTagged)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CondTree FlagName DependencyMap PDTagged
 -> (DependencyMap, PDTagged))
-> [CondTree FlagName DependencyMap PDTagged]
-> [(DependencyMap, PDTagged)]
forall a b. (a -> b) -> [a] -> [b]
map [CondTree FlagName DependencyMap PDTagged]
simplifiedTrees ((CondTree FlagName DependencyMap PDTagged
  -> (DependencyMap, PDTagged))
 -> [(DependencyMap, PDTagged)])
-> (CondTree FlagName DependencyMap PDTagged
    -> (DependencyMap, PDTagged))
-> [(DependencyMap, PDTagged)]
forall a b. (a -> b) -> a -> b
$
                -- apply additional constraints to all dependencies
                (DependencyMap -> DependencyMap)
-> (DependencyMap, PDTagged) -> (DependencyMap, PDTagged)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (DependencyMap -> DependencyMap -> DependencyMap
`constrainBy` DependencyMap
extraConstrs) ((DependencyMap, PDTagged) -> (DependencyMap, PDTagged))
-> (CondTree FlagName DependencyMap PDTagged
    -> (DependencyMap, PDTagged))
-> CondTree FlagName DependencyMap PDTagged
-> (DependencyMap, PDTagged)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                (FlagName -> Either FlagName Bool)
-> CondTree FlagName DependencyMap PDTagged
-> (DependencyMap, PDTagged)
forall a d v.
(Semigroup a, Semigroup d) =>
(v -> Either v Bool) -> CondTree v d a -> (d, a)
simplifyCondTree (FlagAssignment -> FlagName -> Either FlagName Bool
env FlagAssignment
flags)
            deps :: DependencyMap
deps = ComponentRequestedSpec -> TargetSet PDTagged -> DependencyMap
overallDependencies ComponentRequestedSpec
enabled TargetSet PDTagged
targetSet
        in case [Dependency] -> DepTestRslt [Dependency]
checkDeps (DependencyMap -> [Dependency]
fromDepMap DependencyMap
deps) of
             DepTestRslt [Dependency]
DepOk | Forest FlagAssignment -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Forest FlagAssignment
ts   -> (TargetSet PDTagged, FlagAssignment)
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
forall a b. b -> Either a b
Right (TargetSet PDTagged
targetSet, FlagAssignment
flags)
                   | Bool
otherwise -> [Either DepMapUnion (TargetSet PDTagged, FlagAssignment)]
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
forall a. [Either DepMapUnion a] -> Either DepMapUnion a
tryAll ([Either DepMapUnion (TargetSet PDTagged, FlagAssignment)]
 -> Either DepMapUnion (TargetSet PDTagged, FlagAssignment))
-> [Either DepMapUnion (TargetSet PDTagged, FlagAssignment)]
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
forall a b. (a -> b) -> a -> b
$ (Tree FlagAssignment
 -> Either DepMapUnion (TargetSet PDTagged, FlagAssignment))
-> Forest FlagAssignment
-> [Either DepMapUnion (TargetSet PDTagged, FlagAssignment)]
forall a b. (a -> b) -> [a] -> [b]
map Tree FlagAssignment
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
explore Forest FlagAssignment
ts
             MissingDeps [Dependency]
mds   -> DepMapUnion
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
forall a b. a -> Either a b
Left ([Dependency] -> DepMapUnion
toDepMapUnion [Dependency]
mds)

    -- Builds a tree of all possible flag assignments.  Internal nodes
    -- have only partial assignments.
    build :: FlagAssignment -> [(FlagName, [Bool])] -> Tree FlagAssignment
    build :: FlagAssignment -> [(FlagName, [Bool])] -> Tree FlagAssignment
build FlagAssignment
assigned [] = FlagAssignment -> Forest FlagAssignment -> Tree FlagAssignment
forall a. a -> Forest a -> Tree a
Node FlagAssignment
assigned []
    build FlagAssignment
assigned ((FlagName
fn, [Bool]
vals) : [(FlagName, [Bool])]
unassigned) =
        FlagAssignment -> Forest FlagAssignment -> Tree FlagAssignment
forall a. a -> Forest a -> Tree a
Node FlagAssignment
assigned (Forest FlagAssignment -> Tree FlagAssignment)
-> Forest FlagAssignment -> Tree FlagAssignment
forall a b. (a -> b) -> a -> b
$ (Bool -> Tree FlagAssignment) -> [Bool] -> Forest FlagAssignment
forall a b. (a -> b) -> [a] -> [b]
map (\Bool
v -> FlagAssignment -> [(FlagName, [Bool])] -> Tree FlagAssignment
build (FlagName -> Bool -> FlagAssignment -> FlagAssignment
insertFlagAssignment FlagName
fn Bool
v FlagAssignment
assigned) [(FlagName, [Bool])]
unassigned) [Bool]
vals

    tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a
    tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a
tryAll = (Either DepMapUnion a
 -> Either DepMapUnion a -> Either DepMapUnion a)
-> Either DepMapUnion a
-> [Either DepMapUnion a]
-> Either DepMapUnion a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Either DepMapUnion a
-> Either DepMapUnion a -> Either DepMapUnion a
forall a.
Either DepMapUnion a
-> Either DepMapUnion a -> Either DepMapUnion a
mp Either DepMapUnion a
forall a. Either DepMapUnion a
mz

    -- special version of `mplus' for our local purposes
    mp :: Either DepMapUnion a -> Either DepMapUnion a -> Either DepMapUnion a
    mp :: Either DepMapUnion a
-> Either DepMapUnion a -> Either DepMapUnion a
mp m :: Either DepMapUnion a
m@(Right a
_) Either DepMapUnion a
_           = Either DepMapUnion a
m
    mp Either DepMapUnion a
_           m :: Either DepMapUnion a
m@(Right a
_) = Either DepMapUnion a
m
    mp (Left DepMapUnion
xs)   (Left DepMapUnion
ys)   =
        let union :: Map PackageName (VersionRange, Set LibraryName)
union = (PackageName
 -> (VersionRange, Set LibraryName)
 -> Map PackageName (VersionRange, Set LibraryName)
 -> Map PackageName (VersionRange, Set LibraryName))
-> Map PackageName (VersionRange, Set LibraryName)
-> Map PackageName (VersionRange, Set LibraryName)
-> Map PackageName (VersionRange, Set LibraryName)
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey (((VersionRange, Set LibraryName)
 -> (VersionRange, Set LibraryName)
 -> (VersionRange, Set LibraryName))
-> PackageName
-> (VersionRange, Set LibraryName)
-> Map PackageName (VersionRange, Set LibraryName)
-> Map PackageName (VersionRange, Set LibraryName)
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.Strict.insertWith (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
combine)
                    (DepMapUnion -> Map PackageName (VersionRange, Set LibraryName)
unDepMapUnion DepMapUnion
xs) (DepMapUnion -> Map PackageName (VersionRange, Set LibraryName)
unDepMapUnion DepMapUnion
ys)
            combine :: (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
combine (VersionRange, Set LibraryName)
x (VersionRange, Set LibraryName)
y = (\(VersionRange
vr, Set LibraryName
cs) -> (VersionRange -> VersionRange
simplifyVersionRange VersionRange
vr,Set LibraryName
cs)) ((VersionRange, Set LibraryName)
 -> (VersionRange, Set LibraryName))
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
forall a b. (a -> b) -> a -> b
$ (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
unionVersionRanges' (VersionRange, Set LibraryName)
x (VersionRange, Set LibraryName)
y
        in Map PackageName (VersionRange, Set LibraryName)
union Map PackageName (VersionRange, Set LibraryName)
-> Either DepMapUnion a -> Either DepMapUnion a
`seq` DepMapUnion -> Either DepMapUnion a
forall a b. a -> Either a b
Left (Map PackageName (VersionRange, Set LibraryName) -> DepMapUnion
DepMapUnion Map PackageName (VersionRange, Set LibraryName)
union)

    -- `mzero'
    mz :: Either DepMapUnion a
    mz :: Either DepMapUnion a
mz = DepMapUnion -> Either DepMapUnion a
forall a b. a -> Either a b
Left (Map PackageName (VersionRange, Set LibraryName) -> DepMapUnion
DepMapUnion Map PackageName (VersionRange, Set LibraryName)
forall k a. Map k a
Map.empty)

    env :: FlagAssignment -> FlagName -> Either FlagName Bool
    env :: FlagAssignment -> FlagName -> Either FlagName Bool
env FlagAssignment
flags FlagName
flag = (Either FlagName Bool
-> (Bool -> Either FlagName Bool)
-> Maybe Bool
-> Either FlagName Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FlagName -> Either FlagName Bool
forall a b. a -> Either a b
Left FlagName
flag) Bool -> Either FlagName Bool
forall a b. b -> Either a b
Right (Maybe Bool -> Either FlagName Bool)
-> (FlagAssignment -> Maybe Bool)
-> FlagAssignment
-> Either FlagName Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagName -> FlagAssignment -> Maybe Bool
lookupFlagAssignment FlagName
flag) FlagAssignment
flags

-- | Transforms a 'CondTree' by putting the input under the "then" branch of a
-- conditional that is True when Buildable is True. If 'addBuildableCondition'
-- can determine that Buildable is always True, it returns the input unchanged.
-- If Buildable is always False, it returns the empty 'CondTree'.
addBuildableCondition :: (Eq v, Monoid a, Monoid c) => (a -> BuildInfo)
                      -> CondTree v c a
                      -> CondTree v c a
addBuildableCondition :: (a -> BuildInfo) -> CondTree v c a -> CondTree v c a
addBuildableCondition a -> BuildInfo
getInfo CondTree v c a
t =
  case (a -> Bool) -> CondTree v c a -> Condition v
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
buildable (BuildInfo -> Bool) -> (a -> BuildInfo) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> BuildInfo
getInfo) CondTree v c a
t of
    Lit Bool
True  -> CondTree v c a
t
    Lit Bool
False -> a -> c -> [CondBranch v c a] -> CondTree v c a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
forall a. Monoid a => a
mempty c
forall a. Monoid a => a
mempty []
    Condition v
c         -> a -> c -> [CondBranch v c a] -> CondTree v c a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
forall a. Monoid a => a
mempty c
forall a. Monoid a => a
mempty [Condition v -> CondTree v c a -> CondBranch v c a
forall v c a. Condition v -> CondTree v c a -> CondBranch v c a
condIfThen Condition v
c CondTree v c a
t]

-- | This is a special version of 'addBuildableCondition' for the 'PDTagged'
-- type.
--
-- It is not simply a specialisation. It is more complicated than it
-- ought to be because of the way the 'PDTagged' monoid instance works. The
-- @mempty = 'PDNull'@ forgets the component type, which has the effect of
-- completely deleting components that are not buildable.
--
-- See <https://github.com/haskell/cabal/pull/4094> for more details.
--
addBuildableConditionPDTagged :: (Eq v, Monoid c) =>
                                 CondTree v c PDTagged
                              -> CondTree v c PDTagged
addBuildableConditionPDTagged :: CondTree v c PDTagged -> CondTree v c PDTagged
addBuildableConditionPDTagged CondTree v c PDTagged
t =
    case (PDTagged -> Bool) -> CondTree v c PDTagged -> Condition v
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
buildable (BuildInfo -> Bool) -> (PDTagged -> BuildInfo) -> PDTagged -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PDTagged -> BuildInfo
getInfo) CondTree v c PDTagged
t of
      Lit Bool
True  -> CondTree v c PDTagged
t
      Lit Bool
False -> CondTree v c PDTagged -> CondTree v c PDTagged
forall v b a. CondTree v b a -> CondTree v c a
deleteConstraints CondTree v c PDTagged
t
      Condition v
c         -> PDTagged -> c -> [CondBranch v c PDTagged] -> CondTree v c PDTagged
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode PDTagged
forall a. Monoid a => a
mempty c
forall a. Monoid a => a
mempty [Condition v
-> CondTree v c PDTagged
-> CondTree v c PDTagged
-> CondBranch v c PDTagged
forall v c a.
Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a
condIfThenElse Condition v
c CondTree v c PDTagged
t (CondTree v c PDTagged -> CondTree v c PDTagged
forall v b a. CondTree v b a -> CondTree v c a
deleteConstraints CondTree v c PDTagged
t)]
  where
    deleteConstraints :: CondTree v b a -> CondTree v c a
deleteConstraints = (b -> c) -> CondTree v b a -> CondTree v c a
forall c d v a. (c -> d) -> CondTree v c a -> CondTree v d a
mapTreeConstrs (c -> b -> c
forall a b. a -> b -> a
const c
forall a. Monoid a => a
mempty)

    getInfo :: PDTagged -> BuildInfo
    getInfo :: PDTagged -> BuildInfo
getInfo (Lib Library
l) = Library -> BuildInfo
libBuildInfo Library
l
    getInfo (SubComp UnqualComponentName
_ Component
c) = Component -> BuildInfo
componentBuildInfo Component
c
    getInfo PDTagged
PDNull = BuildInfo
forall a. Monoid a => a
mempty


-- Note: extracting buildable conditions.
-- --------------------------------------
--
-- If the conditions in a cond tree lead to Buildable being set to False, then
-- none of the dependencies for this cond tree should actually be taken into
-- account. On the other hand, some of the flags may only be decided in the
-- solver, so we cannot necessarily make the decision whether a component is
-- Buildable or not prior to solving.
--
-- What we are doing here is to partially evaluate a condition tree in order to
-- extract the condition under which Buildable is True. The predicate determines
-- whether data under a 'CondTree' is buildable.

-- | Extract conditions matched by the given predicate from all cond trees in a
-- 'GenericPackageDescription'.
extractConditions :: (BuildInfo -> Bool) -> GenericPackageDescription
                     -> [Condition ConfVar]
extractConditions :: (BuildInfo -> Bool)
-> GenericPackageDescription -> [Condition ConfVar]
extractConditions BuildInfo -> Bool
f GenericPackageDescription
gpkg =
  [[Condition ConfVar]] -> [Condition ConfVar]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
      (Library -> Bool)
-> CondTree ConfVar [Dependency] Library -> Condition ConfVar
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
f (BuildInfo -> Bool) -> (Library -> BuildInfo) -> Library -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
libBuildInfo)             (CondTree ConfVar [Dependency] Library -> Condition ConfVar)
-> [CondTree ConfVar [Dependency] Library] -> [Condition ConfVar]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (CondTree ConfVar [Dependency] Library)
-> [CondTree ConfVar [Dependency] Library]
forall a. Maybe a -> [a]
maybeToList (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condLibrary GenericPackageDescription
gpkg)
    , (Library -> Bool)
-> CondTree ConfVar [Dependency] Library -> Condition ConfVar
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
f (BuildInfo -> Bool) -> (Library -> BuildInfo) -> Library -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
libBuildInfo)       (CondTree ConfVar [Dependency] Library -> Condition ConfVar)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
    -> CondTree ConfVar [Dependency] Library)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> Condition ConfVar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> CondTree ConfVar [Dependency] Library
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
 -> Condition ConfVar)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [Condition ConfVar]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries   GenericPackageDescription
gpkg
    , (Executable -> Bool)
-> CondTree ConfVar [Dependency] Executable -> Condition ConfVar
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
f (BuildInfo -> Bool)
-> (Executable -> BuildInfo) -> Executable -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> BuildInfo
buildInfo)          (CondTree ConfVar [Dependency] Executable -> Condition ConfVar)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
    -> CondTree ConfVar [Dependency] Executable)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Condition ConfVar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> CondTree ConfVar [Dependency] Executable
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
 -> Condition ConfVar)
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [Condition ConfVar]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
condExecutables GenericPackageDescription
gpkg
    , (TestSuite -> Bool)
-> CondTree ConfVar [Dependency] TestSuite -> Condition ConfVar
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
f (BuildInfo -> Bool)
-> (TestSuite -> BuildInfo) -> TestSuite -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> BuildInfo
testBuildInfo)      (CondTree ConfVar [Dependency] TestSuite -> Condition ConfVar)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
    -> CondTree ConfVar [Dependency] TestSuite)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> Condition ConfVar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
 -> Condition ConfVar)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [Condition ConfVar]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites  GenericPackageDescription
gpkg
    , (Benchmark -> Bool)
-> CondTree ConfVar [Dependency] Benchmark -> Condition ConfVar
forall v a c. Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition (BuildInfo -> Bool
f (BuildInfo -> Bool)
-> (Benchmark -> BuildInfo) -> Benchmark -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Benchmark -> BuildInfo
benchmarkBuildInfo) (CondTree ConfVar [Dependency] Benchmark -> Condition ConfVar)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
    -> CondTree ConfVar [Dependency] Benchmark)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Condition ConfVar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
 -> Condition ConfVar)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [Condition ConfVar]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks  GenericPackageDescription
gpkg
    ]


-- | A map of dependencies that combines version ranges using 'unionVersionRanges'.
newtype DepMapUnion = DepMapUnion { DepMapUnion -> Map PackageName (VersionRange, Set LibraryName)
unDepMapUnion :: Map PackageName (VersionRange, Set LibraryName) }

-- An union of versions should correspond to an intersection of the components.
-- The intersection may not be necessary.
unionVersionRanges' :: (VersionRange, Set LibraryName)
                    -> (VersionRange, Set LibraryName)
                    -> (VersionRange, Set LibraryName)
unionVersionRanges' :: (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
unionVersionRanges' (VersionRange
vra, Set LibraryName
csa) (VersionRange
vrb, Set LibraryName
csb) =
  (VersionRange -> VersionRange -> VersionRange
unionVersionRanges VersionRange
vra VersionRange
vrb, Set LibraryName -> Set LibraryName -> Set LibraryName
forall a. Ord a => Set a -> Set a -> Set a
Set.intersection Set LibraryName
csa Set LibraryName
csb)

toDepMapUnion :: [Dependency] -> DepMapUnion
toDepMapUnion :: [Dependency] -> DepMapUnion
toDepMapUnion [Dependency]
ds =
  Map PackageName (VersionRange, Set LibraryName) -> DepMapUnion
DepMapUnion (Map PackageName (VersionRange, Set LibraryName) -> DepMapUnion)
-> Map PackageName (VersionRange, Set LibraryName) -> DepMapUnion
forall a b. (a -> b) -> a -> b
$ ((VersionRange, Set LibraryName)
 -> (VersionRange, Set LibraryName)
 -> (VersionRange, Set LibraryName))
-> [(PackageName, (VersionRange, Set LibraryName))]
-> Map PackageName (VersionRange, Set LibraryName)
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
-> (VersionRange, Set LibraryName)
unionVersionRanges' [ (PackageName
p,(VersionRange
vr,Set LibraryName
cs)) | Dependency PackageName
p VersionRange
vr Set LibraryName
cs <- [Dependency]
ds ]

fromDepMapUnion :: DepMapUnion -> [Dependency]
fromDepMapUnion :: DepMapUnion -> [Dependency]
fromDepMapUnion DepMapUnion
m = [ PackageName -> VersionRange -> Set LibraryName -> Dependency
Dependency PackageName
p VersionRange
vr Set LibraryName
cs | (PackageName
p,(VersionRange
vr,Set LibraryName
cs)) <- Map PackageName (VersionRange, Set LibraryName)
-> [(PackageName, (VersionRange, Set LibraryName))]
forall k a. Map k a -> [(k, a)]
Map.toList (DepMapUnion -> Map PackageName (VersionRange, Set LibraryName)
unDepMapUnion DepMapUnion
m) ]

freeVars :: CondTree ConfVar c a  -> [FlagName]
freeVars :: CondTree ConfVar c a -> [FlagName]
freeVars CondTree ConfVar c a
t = [ FlagName
f | Flag FlagName
f <- CondTree ConfVar c a -> [ConfVar]
forall a c a. CondTree a c a -> [a]
freeVars' CondTree ConfVar c a
t ]
  where
    freeVars' :: CondTree a c a -> [a]
freeVars' (CondNode a
_ c
_ [CondBranch a c a]
ifs) = (CondBranch a c a -> [a]) -> [CondBranch a c a] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CondBranch a c a -> [a]
compfv [CondBranch a c a]
ifs
    compfv :: CondBranch a c a -> [a]
compfv (CondBranch Condition a
c CondTree a c a
ct Maybe (CondTree a c a)
mct) = Condition a -> [a]
forall a. Condition a -> [a]
condfv Condition a
c [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ CondTree a c a -> [a]
freeVars' CondTree a c a
ct [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a] -> (CondTree a c a -> [a]) -> Maybe (CondTree a c a) -> [a]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] CondTree a c a -> [a]
freeVars' Maybe (CondTree a c a)
mct
    condfv :: Condition a -> [a]
condfv Condition a
c = case Condition a
c of
      Var a
v      -> [a
v]
      Lit Bool
_      -> []
      CNot Condition a
c'    -> Condition a -> [a]
condfv Condition a
c'
      COr Condition a
c1 Condition a
c2  -> Condition a -> [a]
condfv Condition a
c1 [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ Condition a -> [a]
condfv Condition a
c2
      CAnd Condition a
c1 Condition a
c2 -> Condition a -> [a]
condfv Condition a
c1 [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ Condition a -> [a]
condfv Condition a
c2


------------------------------------------------------------------------------

-- | A set of targets with their package dependencies
newtype TargetSet a = TargetSet [(DependencyMap, a)]

-- | Combine the target-specific dependencies in a TargetSet to give the
-- dependencies for the package as a whole.
overallDependencies :: ComponentRequestedSpec -> TargetSet PDTagged -> DependencyMap
overallDependencies :: ComponentRequestedSpec -> TargetSet PDTagged -> DependencyMap
overallDependencies ComponentRequestedSpec
enabled (TargetSet [(DependencyMap, PDTagged)]
targets) = [DependencyMap] -> DependencyMap
forall a. Monoid a => [a] -> a
mconcat [DependencyMap]
depss
  where
    ([DependencyMap]
depss, [PDTagged]
_) = [(DependencyMap, PDTagged)] -> ([DependencyMap], [PDTagged])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(DependencyMap, PDTagged)] -> ([DependencyMap], [PDTagged]))
-> [(DependencyMap, PDTagged)] -> ([DependencyMap], [PDTagged])
forall a b. (a -> b) -> a -> b
$ ((DependencyMap, PDTagged) -> Bool)
-> [(DependencyMap, PDTagged)] -> [(DependencyMap, PDTagged)]
forall a. (a -> Bool) -> [a] -> [a]
filter (PDTagged -> Bool
removeDisabledSections (PDTagged -> Bool)
-> ((DependencyMap, PDTagged) -> PDTagged)
-> (DependencyMap, PDTagged)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DependencyMap, PDTagged) -> PDTagged
forall a b. (a, b) -> b
snd) [(DependencyMap, PDTagged)]
targets
    removeDisabledSections :: PDTagged -> Bool
    -- UGH. The embedded componentName in the 'Component's here is
    -- BLANK.  I don't know whose fault this is but I'll use the tag
    -- instead. -- ezyang
    removeDisabledSections :: PDTagged -> Bool
removeDisabledSections (Lib Library
_)     = ComponentRequestedSpec -> ComponentName -> Bool
componentNameRequested
                                           ComponentRequestedSpec
enabled
                                           (LibraryName -> ComponentName
CLibName LibraryName
LMainLibName)
    removeDisabledSections (SubComp UnqualComponentName
t Component
c)
        -- Do NOT use componentName
        = ComponentRequestedSpec -> ComponentName -> Bool
componentNameRequested ComponentRequestedSpec
enabled
        (ComponentName -> Bool) -> ComponentName -> Bool
forall a b. (a -> b) -> a -> b
$ case Component
c of
            CLib  Library
_ -> LibraryName -> ComponentName
CLibName (UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
t)
            CFLib ForeignLib
_ -> UnqualComponentName -> ComponentName
CFLibName   UnqualComponentName
t
            CExe  Executable
_ -> UnqualComponentName -> ComponentName
CExeName    UnqualComponentName
t
            CTest TestSuite
_ -> UnqualComponentName -> ComponentName
CTestName   UnqualComponentName
t
            CBench Benchmark
_ -> UnqualComponentName -> ComponentName
CBenchName UnqualComponentName
t
    removeDisabledSections PDTagged
PDNull      = Bool
True

-- | Collect up the targets in a TargetSet of tagged targets, storing the
-- dependencies as we go.
flattenTaggedTargets :: TargetSet PDTagged -> (Maybe Library, [(UnqualComponentName, Component)])
flattenTaggedTargets :: TargetSet PDTagged
-> (Maybe Library, [(UnqualComponentName, Component)])
flattenTaggedTargets (TargetSet [(DependencyMap, PDTagged)]
targets) = ((DependencyMap, PDTagged)
 -> (Maybe Library, [(UnqualComponentName, Component)])
 -> (Maybe Library, [(UnqualComponentName, Component)]))
-> (Maybe Library, [(UnqualComponentName, Component)])
-> [(DependencyMap, PDTagged)]
-> (Maybe Library, [(UnqualComponentName, Component)])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (DependencyMap, PDTagged)
-> (Maybe Library, [(UnqualComponentName, Component)])
-> (Maybe Library, [(UnqualComponentName, Component)])
untag (Maybe Library
forall a. Maybe a
Nothing, []) [(DependencyMap, PDTagged)]
targets where
  untag :: (DependencyMap, PDTagged)
-> (Maybe Library, [(UnqualComponentName, Component)])
-> (Maybe Library, [(UnqualComponentName, Component)])
untag (DependencyMap
depMap, PDTagged
pdTagged) (Maybe Library, [(UnqualComponentName, Component)])
accum = case (PDTagged
pdTagged, (Maybe Library, [(UnqualComponentName, Component)])
accum) of
    (Lib Library
_, (Just Library
_, [(UnqualComponentName, Component)]
_)) -> String -> (Maybe Library, [(UnqualComponentName, Component)])
forall a. String -> a
userBug String
"Only one library expected"
    (Lib Library
l, (Maybe Library
Nothing, [(UnqualComponentName, Component)]
comps)) -> (Library -> Maybe Library
forall a. a -> Maybe a
Just (Library -> Maybe Library) -> Library -> Maybe Library
forall a b. (a -> b) -> a -> b
$ Library -> Library
forall a. HasBuildInfo a => a -> a
redoBD Library
l, [(UnqualComponentName, Component)]
comps)
    (SubComp UnqualComponentName
n Component
c, (Maybe Library
mb_lib, [(UnqualComponentName, Component)]
comps))
      | ((UnqualComponentName, Component) -> Bool)
-> [(UnqualComponentName, Component)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((UnqualComponentName -> UnqualComponentName -> Bool
forall a. Eq a => a -> a -> Bool
== UnqualComponentName
n) (UnqualComponentName -> Bool)
-> ((UnqualComponentName, Component) -> UnqualComponentName)
-> (UnqualComponentName, Component)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, Component) -> UnqualComponentName
forall a b. (a, b) -> a
fst) [(UnqualComponentName, Component)]
comps ->
        String -> (Maybe Library, [(UnqualComponentName, Component)])
forall a. String -> a
userBug (String -> (Maybe Library, [(UnqualComponentName, Component)]))
-> String -> (Maybe Library, [(UnqualComponentName, Component)])
forall a b. (a -> b) -> a -> b
$ String
"There exist several components with the same name: '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"
      | Bool
otherwise -> (Maybe Library
mb_lib, (UnqualComponentName
n, Component -> Component
forall a. HasBuildInfo a => a -> a
redoBD Component
c) (UnqualComponentName, Component)
-> [(UnqualComponentName, Component)]
-> [(UnqualComponentName, Component)]
forall a. a -> [a] -> [a]
: [(UnqualComponentName, Component)]
comps)
    (PDTagged
PDNull, (Maybe Library, [(UnqualComponentName, Component)])
x) -> (Maybe Library, [(UnqualComponentName, Component)])
x  -- actually this should not happen, but let's be liberal
    where
      redoBD :: L.HasBuildInfo a => a -> a
      redoBD :: a -> a
redoBD = ASetter a a [Dependency] [Dependency] -> [Dependency] -> a -> a
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter a a [Dependency] [Dependency]
forall a. HasBuildInfo a => Lens' a [Dependency]
L.targetBuildDepends ([Dependency] -> a -> a) -> [Dependency] -> a -> a
forall a b. (a -> b) -> a -> b
$ DependencyMap -> [Dependency]
fromDepMap DependencyMap
depMap

------------------------------------------------------------------------------
-- Convert GenericPackageDescription to PackageDescription
--

data PDTagged = Lib Library
              | SubComp UnqualComponentName Component
              | PDNull
              deriving Int -> PDTagged -> String -> String
[PDTagged] -> String -> String
PDTagged -> String
(Int -> PDTagged -> String -> String)
-> (PDTagged -> String)
-> ([PDTagged] -> String -> String)
-> Show PDTagged
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PDTagged] -> String -> String
$cshowList :: [PDTagged] -> String -> String
show :: PDTagged -> String
$cshow :: PDTagged -> String
showsPrec :: Int -> PDTagged -> String -> String
$cshowsPrec :: Int -> PDTagged -> String -> String
Show

instance Monoid PDTagged where
    mempty :: PDTagged
mempty = PDTagged
PDNull
    mappend :: PDTagged -> PDTagged -> PDTagged
mappend = PDTagged -> PDTagged -> PDTagged
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup PDTagged where
    PDTagged
PDNull    <> :: PDTagged -> PDTagged -> PDTagged
<> PDTagged
x      = PDTagged
x
    PDTagged
x         <> PDTagged
PDNull = PDTagged
x
    Lib Library
l     <> Lib Library
l' = Library -> PDTagged
Lib (Library
l Library -> Library -> Library
forall a. Semigroup a => a -> a -> a
<> Library
l')
    SubComp UnqualComponentName
n Component
x <> SubComp UnqualComponentName
n' Component
x' | UnqualComponentName
n UnqualComponentName -> UnqualComponentName -> Bool
forall a. Eq a => a -> a -> Bool
== UnqualComponentName
n' = UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
n (Component
x Component -> Component -> Component
forall a. Semigroup a => a -> a -> a
<> Component
x')
    PDTagged
_         <> PDTagged
_  = String -> PDTagged
forall a. String -> a
cabalBug String
"Cannot combine incompatible tags"

-- | Create a package description with all configurations resolved.
--
-- This function takes a `GenericPackageDescription` and several environment
-- parameters and tries to generate `PackageDescription` by finding a flag
-- assignment that result in satisfiable dependencies.
--
-- It takes as inputs a not necessarily complete specifications of flags
-- assignments, an optional package index as well as platform parameters.  If
-- some flags are not assigned explicitly, this function will try to pick an
-- assignment that causes this function to succeed.  The package index is
-- optional since on some platforms we cannot determine which packages have
-- been installed before.  When no package index is supplied, every dependency
-- is assumed to be satisfiable, therefore all not explicitly assigned flags
-- will get their default values.
--
-- This function will fail if it cannot find a flag assignment that leads to
-- satisfiable dependencies.  (It will not try alternative assignments for
-- explicitly specified flags.)  In case of failure it will return the missing
-- dependencies that it encountered when trying different flag assignments.
-- On success, it will return the package description and the full flag
-- assignment chosen.
--
-- Note that this drops any stanzas which have @buildable: False@.  While
-- this is arguably the right thing to do, it means we give bad error
-- messages in some situations, see #3858.
--
finalizePD ::
     FlagAssignment  -- ^ Explicitly specified flag assignments
  -> ComponentRequestedSpec
  -> (Dependency -> Bool) -- ^ Is a given dependency satisfiable from the set of
                          -- available packages?  If this is unknown then use
                          -- True.
  -> Platform      -- ^ The 'Arch' and 'OS'
  -> CompilerInfo  -- ^ Compiler information
  -> [Dependency]  -- ^ Additional constraints
  -> GenericPackageDescription
  -> Either [Dependency]
            (PackageDescription, FlagAssignment)
             -- ^ Either missing dependencies or the resolved package
             -- description along with the flag assignments chosen.
finalizePD :: FlagAssignment
-> ComponentRequestedSpec
-> (Dependency -> Bool)
-> Platform
-> CompilerInfo
-> [Dependency]
-> GenericPackageDescription
-> Either [Dependency] (PackageDescription, FlagAssignment)
finalizePD FlagAssignment
userflags ComponentRequestedSpec
enabled Dependency -> Bool
satisfyDep
        (Platform Arch
arch OS
os) CompilerInfo
impl [Dependency]
constraints
        (GenericPackageDescription PackageDescription
pkg [Flag]
flags Maybe (CondTree ConfVar [Dependency] Library)
mb_lib0 [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
sub_libs0 [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs0 [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes0 [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests0 [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
bms0) = do
  (TargetSet PDTagged
targetSet, FlagAssignment
flagVals) <-
    [(FlagName, [Bool])]
-> ComponentRequestedSpec
-> OS
-> Arch
-> CompilerInfo
-> [Dependency]
-> [CondTree ConfVar [Dependency] PDTagged]
-> ([Dependency] -> DepTestRslt [Dependency])
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
resolveWithFlags [(FlagName, [Bool])]
flagChoices ComponentRequestedSpec
enabled OS
os Arch
arch CompilerInfo
impl [Dependency]
constraints [CondTree ConfVar [Dependency] PDTagged]
condTrees [Dependency] -> DepTestRslt [Dependency]
check
  let
    (Maybe Library
mb_lib, [(UnqualComponentName, Component)]
comps) = TargetSet PDTagged
-> (Maybe Library, [(UnqualComponentName, Component)])
flattenTaggedTargets TargetSet PDTagged
targetSet
    mb_lib' :: Maybe Library
mb_lib' = (Library -> Library) -> Maybe Library -> Maybe Library
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Library
libFillInDefaults Maybe Library
mb_lib
    comps' :: [Component]
comps' = (((UnqualComponentName, Component) -> Component)
 -> [(UnqualComponentName, Component)] -> [Component])
-> [(UnqualComponentName, Component)]
-> ((UnqualComponentName, Component) -> Component)
-> [Component]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((UnqualComponentName, Component) -> Component)
-> [(UnqualComponentName, Component)] -> [Component]
forall a b. (a -> b) -> [a] -> [b]
map [(UnqualComponentName, Component)]
comps (((UnqualComponentName, Component) -> Component) -> [Component])
-> ((UnqualComponentName, Component) -> Component) -> [Component]
forall a b. (a -> b) -> a -> b
$ \(UnqualComponentName
n,Component
c) -> (Library -> Component)
-> (ForeignLib -> Component)
-> (Executable -> Component)
-> (TestSuite -> Component)
-> (Benchmark -> Component)
-> Component
-> Component
forall a.
(Library -> a)
-> (ForeignLib -> a)
-> (Executable -> a)
-> (TestSuite -> a)
-> (Benchmark -> a)
-> Component
-> a
foldComponent
      (\Library
l -> Library -> Component
CLib   (Library -> Library
libFillInDefaults Library
l)   { libName :: LibraryName
libName = UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
n
                                            , libExposed :: Bool
libExposed = Bool
False })
      (\ForeignLib
l -> ForeignLib -> Component
CFLib  (ForeignLib -> ForeignLib
flibFillInDefaults ForeignLib
l)  { foreignLibName :: UnqualComponentName
foreignLibName = UnqualComponentName
n })
      (\Executable
e -> Executable -> Component
CExe   (Executable -> Executable
exeFillInDefaults Executable
e)   { exeName :: UnqualComponentName
exeName = UnqualComponentName
n })
      (\TestSuite
t -> TestSuite -> Component
CTest  (TestSuite -> TestSuite
testFillInDefaults TestSuite
t)  { testName :: UnqualComponentName
testName = UnqualComponentName
n })
      (\Benchmark
b -> Benchmark -> Component
CBench (Benchmark -> Benchmark
benchFillInDefaults Benchmark
b) { benchmarkName :: UnqualComponentName
benchmarkName = UnqualComponentName
n })
      Component
c
    ([Library]
sub_libs', [ForeignLib]
flibs', [Executable]
exes', [TestSuite]
tests', [Benchmark]
bms') = [Component]
-> ([Library], [ForeignLib], [Executable], [TestSuite],
    [Benchmark])
partitionComponents [Component]
comps'
  (PackageDescription, FlagAssignment)
-> Either [Dependency] (PackageDescription, FlagAssignment)
forall (m :: * -> *) a. Monad m => a -> m a
return ( PackageDescription
pkg { library :: Maybe Library
library = Maybe Library
mb_lib'
               , subLibraries :: [Library]
subLibraries = [Library]
sub_libs'
               , foreignLibs :: [ForeignLib]
foreignLibs = [ForeignLib]
flibs'
               , executables :: [Executable]
executables = [Executable]
exes'
               , testSuites :: [TestSuite]
testSuites = [TestSuite]
tests'
               , benchmarks :: [Benchmark]
benchmarks = [Benchmark]
bms'
               }
         , FlagAssignment
flagVals )
  where
    -- Combine lib, exes, and tests into one list of @CondTree@s with tagged data
    condTrees :: [CondTree ConfVar [Dependency] PDTagged]
condTrees =    Maybe (CondTree ConfVar [Dependency] PDTagged)
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. Maybe a -> [a]
maybeToList ((CondTree ConfVar [Dependency] Library
 -> CondTree ConfVar [Dependency] PDTagged)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> Maybe (CondTree ConfVar [Dependency] PDTagged)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Library -> PDTagged)
-> CondTree ConfVar [Dependency] Library
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData Library -> PDTagged
Lib) Maybe (CondTree ConfVar [Dependency] Library)
mb_lib0)
                [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. [a] -> [a] -> [a]
++ ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
 -> CondTree ConfVar [Dependency] PDTagged)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map (\(UnqualComponentName
name,CondTree ConfVar [Dependency] Library
tree) -> (Library -> PDTagged)
-> CondTree ConfVar [Dependency] Library
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData (UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
name (Component -> PDTagged)
-> (Library -> Component) -> Library -> PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> Component
CLib) CondTree ConfVar [Dependency] Library
tree) [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
sub_libs0
                [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. [a] -> [a] -> [a]
++ ((UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
 -> CondTree ConfVar [Dependency] PDTagged)
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map (\(UnqualComponentName
name,CondTree ConfVar [Dependency] ForeignLib
tree) -> (ForeignLib -> PDTagged)
-> CondTree ConfVar [Dependency] ForeignLib
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData (UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
name (Component -> PDTagged)
-> (ForeignLib -> Component) -> ForeignLib -> PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> Component
CFLib) CondTree ConfVar [Dependency] ForeignLib
tree) [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs0
                [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. [a] -> [a] -> [a]
++ ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
 -> CondTree ConfVar [Dependency] PDTagged)
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map (\(UnqualComponentName
name,CondTree ConfVar [Dependency] Executable
tree) -> (Executable -> PDTagged)
-> CondTree ConfVar [Dependency] Executable
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData (UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
name (Component -> PDTagged)
-> (Executable -> Component) -> Executable -> PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> Component
CExe) CondTree ConfVar [Dependency] Executable
tree) [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes0
                [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. [a] -> [a] -> [a]
++ ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
 -> CondTree ConfVar [Dependency] PDTagged)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map (\(UnqualComponentName
name,CondTree ConfVar [Dependency] TestSuite
tree) -> (TestSuite -> PDTagged)
-> CondTree ConfVar [Dependency] TestSuite
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData (UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
name (Component -> PDTagged)
-> (TestSuite -> Component) -> TestSuite -> PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> Component
CTest) CondTree ConfVar [Dependency] TestSuite
tree) [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests0
                [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a. [a] -> [a] -> [a]
++ ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
 -> CondTree ConfVar [Dependency] PDTagged)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [CondTree ConfVar [Dependency] PDTagged]
forall a b. (a -> b) -> [a] -> [b]
map (\(UnqualComponentName
name,CondTree ConfVar [Dependency] Benchmark
tree) -> (Benchmark -> PDTagged)
-> CondTree ConfVar [Dependency] Benchmark
-> CondTree ConfVar [Dependency] PDTagged
forall a b v c. (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData (UnqualComponentName -> Component -> PDTagged
SubComp UnqualComponentName
name (Component -> PDTagged)
-> (Benchmark -> Component) -> Benchmark -> PDTagged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Benchmark -> Component
CBench) CondTree ConfVar [Dependency] Benchmark
tree) [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
bms0

    flagChoices :: [(FlagName, [Bool])]
flagChoices    = (Flag -> (FlagName, [Bool])) -> [Flag] -> [(FlagName, [Bool])]
forall a b. (a -> b) -> [a] -> [b]
map (\(MkFlag FlagName
n String
_ Bool
d Bool
manual) -> (FlagName
n, Bool -> FlagName -> Bool -> [Bool]
d2c Bool
manual FlagName
n Bool
d)) [Flag]
flags
    d2c :: Bool -> FlagName -> Bool -> [Bool]
d2c Bool
manual FlagName
n Bool
b = case FlagName -> FlagAssignment -> Maybe Bool
lookupFlagAssignment FlagName
n FlagAssignment
userflags of
                     Just Bool
val -> [Bool
val]
                     Maybe Bool
Nothing
                      | Bool
manual -> [Bool
b]
                      | Bool
otherwise -> [Bool
b, Bool -> Bool
not Bool
b]
    --flagDefaults = map (\(n,x:_) -> (n,x)) flagChoices
    check :: [Dependency] -> DepTestRslt [Dependency]
check [Dependency]
ds     = let missingDeps :: [Dependency]
missingDeps = (Dependency -> Bool) -> [Dependency] -> [Dependency]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Dependency -> Bool) -> Dependency -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Bool
satisfyDep) [Dependency]
ds
                   in if [Dependency] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Dependency]
missingDeps
                      then DepTestRslt [Dependency]
forall d. DepTestRslt d
DepOk
                      else [Dependency] -> DepTestRslt [Dependency]
forall d. d -> DepTestRslt d
MissingDeps [Dependency]
missingDeps

{-
let tst_p = (CondNode [1::Int] [Distribution.Package.Dependency "a" AnyVersion] [])
let tst_p2 = (CondNode [1::Int] [Distribution.Package.Dependency "a" (EarlierVersion (Version [1,0] [])), Distribution.Package.Dependency "a" (LaterVersion (Version [2,0] []))] [])

let p_index = Distribution.Simple.PackageIndex.fromList [Distribution.Package.PackageIdentifier "a" (Version [0,5] []), Distribution.Package.PackageIdentifier "a" (Version [2,5] [])]
let look = not . null . Distribution.Simple.PackageIndex.lookupDependency p_index
let looks ds = mconcat $ map (\d -> if look d then DepOk else MissingDeps [d]) ds
resolveWithFlags [] Distribution.System.Linux Distribution.System.I386 (Distribution.Compiler.GHC,Version [6,8,2] []) [tst_p] looks   ===>  Right ...
resolveWithFlags [] Distribution.System.Linux Distribution.System.I386 (Distribution.Compiler.GHC,Version [6,8,2] []) [tst_p2] looks  ===>  Left ...
-}

-- | Flatten a generic package description by ignoring all conditions and just
-- join the field descriptors into on package description.  Note, however,
-- that this may lead to inconsistent field values, since all values are
-- joined into one field, which may not be possible in the original package
-- description, due to the use of exclusive choices (if ... else ...).
--
-- TODO: One particularly tricky case is defaulting.  In the original package
-- description, e.g., the source directory might either be the default or a
-- certain, explicitly set path.  Since defaults are filled in only after the
-- package has been resolved and when no explicit value has been set, the
-- default path will be missing from the package description returned by this
-- function.
flattenPackageDescription :: GenericPackageDescription -> PackageDescription
flattenPackageDescription :: GenericPackageDescription -> PackageDescription
flattenPackageDescription
  (GenericPackageDescription PackageDescription
pkg [Flag]
_ Maybe (CondTree ConfVar [Dependency] Library)
mlib0 [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
sub_libs0 [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs0 [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes0 [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests0 [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
bms0) =
    PackageDescription
pkg { library :: Maybe Library
library      = Maybe Library
mlib
        , subLibraries :: [Library]
subLibraries = [Library] -> [Library]
forall a. [a] -> [a]
reverse [Library]
sub_libs
        , foreignLibs :: [ForeignLib]
foreignLibs  = [ForeignLib] -> [ForeignLib]
forall a. [a] -> [a]
reverse [ForeignLib]
flibs
        , executables :: [Executable]
executables  = [Executable] -> [Executable]
forall a. [a] -> [a]
reverse [Executable]
exes
        , testSuites :: [TestSuite]
testSuites   = [TestSuite] -> [TestSuite]
forall a. [a] -> [a]
reverse [TestSuite]
tests
        , benchmarks :: [Benchmark]
benchmarks   = [Benchmark] -> [Benchmark]
forall a. [a] -> [a]
reverse [Benchmark]
bms
        }
  where
    mlib :: Maybe Library
mlib = CondTree ConfVar [Dependency] Library -> Library
forall b v. Semigroup b => CondTree v b Library -> Library
f (CondTree ConfVar [Dependency] Library -> Library)
-> Maybe (CondTree ConfVar [Dependency] Library) -> Maybe Library
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (CondTree ConfVar [Dependency] Library)
mlib0
      where f :: CondTree v b Library -> Library
f CondTree v b Library
lib = (Library -> Library
libFillInDefaults (Library -> Library)
-> (CondTree v b Library -> Library)
-> CondTree v b Library
-> Library
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Library, b) -> Library
forall a b. (a, b) -> a
fst ((Library, b) -> Library)
-> (CondTree v b Library -> (Library, b))
-> CondTree v b Library
-> Library
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree v b Library -> (Library, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions (CondTree v b Library -> Library)
-> CondTree v b Library -> Library
forall a b. (a -> b) -> a -> b
$ CondTree v b Library
lib) { libName :: LibraryName
libName = LibraryName
LMainLibName }
    sub_libs :: [Library]
sub_libs = (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> Library
forall b v.
Semigroup b =>
(UnqualComponentName, CondTree v b Library) -> Library
flattenLib  ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
 -> Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [Library]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
sub_libs0
    flibs :: [ForeignLib]
flibs    = (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> ForeignLib
forall b v.
Semigroup b =>
(UnqualComponentName, CondTree v b ForeignLib) -> ForeignLib
flattenFLib ((UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
 -> ForeignLib)
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> [ForeignLib]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
flibs0
    exes :: [Executable]
exes     = (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Executable
forall b v.
Semigroup b =>
(UnqualComponentName, CondTree v b Executable) -> Executable
flattenExe  ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
 -> Executable)
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
-> [Executable]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes0
    tests :: [TestSuite]
tests    = (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> TestSuite
forall b v.
Semigroup b =>
(UnqualComponentName, CondTree v b TestSuite) -> TestSuite
flattenTst  ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
 -> TestSuite)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [TestSuite]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests0
    bms :: [Benchmark]
bms      = (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Benchmark
forall b v.
Semigroup b =>
(UnqualComponentName, CondTree v b Benchmark) -> Benchmark
flattenBm   ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
 -> Benchmark)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [Benchmark]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
bms0
    flattenLib :: (UnqualComponentName, CondTree v b Library) -> Library
flattenLib (UnqualComponentName
n, CondTree v b Library
t) = Library -> Library
libFillInDefaults (Library -> Library) -> Library -> Library
forall a b. (a -> b) -> a -> b
$ ((Library, b) -> Library
forall a b. (a, b) -> a
fst ((Library, b) -> Library) -> (Library, b) -> Library
forall a b. (a -> b) -> a -> b
$ CondTree v b Library -> (Library, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v b Library
t)
      { libName :: LibraryName
libName = UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
n, libExposed :: Bool
libExposed = Bool
False }
    flattenFLib :: (UnqualComponentName, CondTree v b ForeignLib) -> ForeignLib
flattenFLib (UnqualComponentName
n, CondTree v b ForeignLib
t) = ForeignLib -> ForeignLib
flibFillInDefaults (ForeignLib -> ForeignLib) -> ForeignLib -> ForeignLib
forall a b. (a -> b) -> a -> b
$ ((ForeignLib, b) -> ForeignLib
forall a b. (a, b) -> a
fst ((ForeignLib, b) -> ForeignLib) -> (ForeignLib, b) -> ForeignLib
forall a b. (a -> b) -> a -> b
$ CondTree v b ForeignLib -> (ForeignLib, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v b ForeignLib
t)
      { foreignLibName :: UnqualComponentName
foreignLibName = UnqualComponentName
n }
    flattenExe :: (UnqualComponentName, CondTree v b Executable) -> Executable
flattenExe (UnqualComponentName
n, CondTree v b Executable
t) = Executable -> Executable
exeFillInDefaults (Executable -> Executable) -> Executable -> Executable
forall a b. (a -> b) -> a -> b
$ ((Executable, b) -> Executable
forall a b. (a, b) -> a
fst ((Executable, b) -> Executable) -> (Executable, b) -> Executable
forall a b. (a -> b) -> a -> b
$ CondTree v b Executable -> (Executable, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v b Executable
t)
      { exeName :: UnqualComponentName
exeName = UnqualComponentName
n }
    flattenTst :: (UnqualComponentName, CondTree v b TestSuite) -> TestSuite
flattenTst (UnqualComponentName
n, CondTree v b TestSuite
t) = TestSuite -> TestSuite
testFillInDefaults (TestSuite -> TestSuite) -> TestSuite -> TestSuite
forall a b. (a -> b) -> a -> b
$ ((TestSuite, b) -> TestSuite
forall a b. (a, b) -> a
fst ((TestSuite, b) -> TestSuite) -> (TestSuite, b) -> TestSuite
forall a b. (a -> b) -> a -> b
$ CondTree v b TestSuite -> (TestSuite, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v b TestSuite
t)
      { testName :: UnqualComponentName
testName = UnqualComponentName
n }
    flattenBm :: (UnqualComponentName, CondTree v b Benchmark) -> Benchmark
flattenBm (UnqualComponentName
n, CondTree v b Benchmark
t) = Benchmark -> Benchmark
benchFillInDefaults (Benchmark -> Benchmark) -> Benchmark -> Benchmark
forall a b. (a -> b) -> a -> b
$ ((Benchmark, b) -> Benchmark
forall a b. (a, b) -> a
fst ((Benchmark, b) -> Benchmark) -> (Benchmark, b) -> Benchmark
forall a b. (a -> b) -> a -> b
$ CondTree v b Benchmark -> (Benchmark, b)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v b Benchmark
t)
      { benchmarkName :: UnqualComponentName
benchmarkName = UnqualComponentName
n }

-- This is in fact rather a hack.  The original version just overrode the
-- default values, however, when adding conditions we had to switch to a
-- modifier-based approach.  There, nothing is ever overwritten, but only
-- joined together.
--
-- This is the cleanest way i could think of, that doesn't require
-- changing all field parsing functions to return modifiers instead.
libFillInDefaults :: Library -> Library
libFillInDefaults :: Library -> Library
libFillInDefaults lib :: Library
lib@(Library { libBuildInfo :: Library -> BuildInfo
libBuildInfo = BuildInfo
bi }) =
    Library
lib { libBuildInfo :: BuildInfo
libBuildInfo = BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi }

flibFillInDefaults :: ForeignLib -> ForeignLib
flibFillInDefaults :: ForeignLib -> ForeignLib
flibFillInDefaults flib :: ForeignLib
flib@(ForeignLib { foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
bi }) =
    ForeignLib
flib { foreignLibBuildInfo :: BuildInfo
foreignLibBuildInfo = BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi }

exeFillInDefaults :: Executable -> Executable
exeFillInDefaults :: Executable -> Executable
exeFillInDefaults exe :: Executable
exe@(Executable { buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bi }) =
    Executable
exe { buildInfo :: BuildInfo
buildInfo = BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi }

testFillInDefaults :: TestSuite -> TestSuite
testFillInDefaults :: TestSuite -> TestSuite
testFillInDefaults tst :: TestSuite
tst@(TestSuite { testBuildInfo :: TestSuite -> BuildInfo
testBuildInfo = BuildInfo
bi }) =
    TestSuite
tst { testBuildInfo :: BuildInfo
testBuildInfo = BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi }

benchFillInDefaults :: Benchmark -> Benchmark
benchFillInDefaults :: Benchmark -> Benchmark
benchFillInDefaults bm :: Benchmark
bm@(Benchmark { benchmarkBuildInfo :: Benchmark -> BuildInfo
benchmarkBuildInfo = BuildInfo
bi }) =
    Benchmark
bm { benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo = BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi }

biFillInDefaults :: BuildInfo -> BuildInfo
biFillInDefaults :: BuildInfo -> BuildInfo
biFillInDefaults BuildInfo
bi =
    if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [String]
hsSourceDirs BuildInfo
bi)
    then BuildInfo
bi { hsSourceDirs :: [String]
hsSourceDirs = [String
currentDir] }
    else BuildInfo
bi

-- Walk a 'GenericPackageDescription' and apply @onBuildInfo@/@onSetupBuildInfo@
-- to all nested 'BuildInfo'/'SetupBuildInfo' values.
transformAllBuildInfos :: (BuildInfo -> BuildInfo)
                       -> (SetupBuildInfo -> SetupBuildInfo)
                       -> GenericPackageDescription
                       -> GenericPackageDescription
transformAllBuildInfos :: (BuildInfo -> BuildInfo)
-> (SetupBuildInfo -> SetupBuildInfo)
-> GenericPackageDescription
-> GenericPackageDescription
transformAllBuildInfos BuildInfo -> BuildInfo
onBuildInfo SetupBuildInfo -> SetupBuildInfo
onSetupBuildInfo =
  ASetter
  GenericPackageDescription
  GenericPackageDescription
  BuildInfo
  BuildInfo
-> (BuildInfo -> BuildInfo)
-> GenericPackageDescription
-> GenericPackageDescription
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
  GenericPackageDescription
  GenericPackageDescription
  BuildInfo
  BuildInfo
forall a. HasBuildInfos a => Traversal' a BuildInfo
L.traverseBuildInfos BuildInfo -> BuildInfo
onBuildInfo
  (GenericPackageDescription -> GenericPackageDescription)
-> (GenericPackageDescription -> GenericPackageDescription)
-> GenericPackageDescription
-> GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter
  GenericPackageDescription
  GenericPackageDescription
  SetupBuildInfo
  SetupBuildInfo
-> (SetupBuildInfo -> SetupBuildInfo)
-> GenericPackageDescription
-> GenericPackageDescription
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (LensLike
  Identity
  GenericPackageDescription
  GenericPackageDescription
  PackageDescription
  PackageDescription
Lens' GenericPackageDescription PackageDescription
L.packageDescription LensLike
  Identity
  GenericPackageDescription
  GenericPackageDescription
  PackageDescription
  PackageDescription
-> ((SetupBuildInfo -> Identity SetupBuildInfo)
    -> PackageDescription -> Identity PackageDescription)
-> ASetter
     GenericPackageDescription
     GenericPackageDescription
     SetupBuildInfo
     SetupBuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike
  Identity
  PackageDescription
  PackageDescription
  (Maybe SetupBuildInfo)
  (Maybe SetupBuildInfo)
Lens' PackageDescription (Maybe SetupBuildInfo)
L.setupBuildInfo LensLike
  Identity
  PackageDescription
  PackageDescription
  (Maybe SetupBuildInfo)
  (Maybe SetupBuildInfo)
-> ((SetupBuildInfo -> Identity SetupBuildInfo)
    -> Maybe SetupBuildInfo -> Identity (Maybe SetupBuildInfo))
-> (SetupBuildInfo -> Identity SetupBuildInfo)
-> PackageDescription
-> Identity PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SetupBuildInfo -> Identity SetupBuildInfo)
-> Maybe SetupBuildInfo -> Identity (Maybe SetupBuildInfo)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) SetupBuildInfo -> SetupBuildInfo
onSetupBuildInfo

-- | Walk a 'GenericPackageDescription' and apply @f@ to all nested
-- @build-depends@ fields.
transformAllBuildDepends :: (Dependency -> Dependency)
                         -> GenericPackageDescription
                         -> GenericPackageDescription
transformAllBuildDepends :: (Dependency -> Dependency)
-> GenericPackageDescription -> GenericPackageDescription
transformAllBuildDepends Dependency -> Dependency
f =
  ASetter
  GenericPackageDescription
  GenericPackageDescription
  Dependency
  Dependency
-> (Dependency -> Dependency)
-> GenericPackageDescription
-> GenericPackageDescription
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (ASetter
  GenericPackageDescription
  GenericPackageDescription
  BuildInfo
  BuildInfo
forall a. HasBuildInfos a => Traversal' a BuildInfo
L.traverseBuildInfos ASetter
  GenericPackageDescription
  GenericPackageDescription
  BuildInfo
  BuildInfo
-> ((Dependency -> Identity Dependency)
    -> BuildInfo -> Identity BuildInfo)
-> ASetter
     GenericPackageDescription
     GenericPackageDescription
     Dependency
     Dependency
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike Identity BuildInfo BuildInfo [Dependency] [Dependency]
forall a. HasBuildInfo a => Lens' a [Dependency]
L.targetBuildDepends LensLike Identity BuildInfo BuildInfo [Dependency] [Dependency]
-> ((Dependency -> Identity Dependency)
    -> [Dependency] -> Identity [Dependency])
-> (Dependency -> Identity Dependency)
-> BuildInfo
-> Identity BuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dependency -> Identity Dependency)
-> [Dependency] -> Identity [Dependency]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) Dependency -> Dependency
f
  (GenericPackageDescription -> GenericPackageDescription)
-> (GenericPackageDescription -> GenericPackageDescription)
-> GenericPackageDescription
-> GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter
  GenericPackageDescription
  GenericPackageDescription
  Dependency
  Dependency
-> (Dependency -> Dependency)
-> GenericPackageDescription
-> GenericPackageDescription
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (LensLike
  Identity
  GenericPackageDescription
  GenericPackageDescription
  PackageDescription
  PackageDescription
Lens' GenericPackageDescription PackageDescription
L.packageDescription LensLike
  Identity
  GenericPackageDescription
  GenericPackageDescription
  PackageDescription
  PackageDescription
-> ((Dependency -> Identity Dependency)
    -> PackageDescription -> Identity PackageDescription)
-> ASetter
     GenericPackageDescription
     GenericPackageDescription
     Dependency
     Dependency
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike
  Identity
  PackageDescription
  PackageDescription
  (Maybe SetupBuildInfo)
  (Maybe SetupBuildInfo)
Lens' PackageDescription (Maybe SetupBuildInfo)
L.setupBuildInfo LensLike
  Identity
  PackageDescription
  PackageDescription
  (Maybe SetupBuildInfo)
  (Maybe SetupBuildInfo)
-> ((Dependency -> Identity Dependency)
    -> Maybe SetupBuildInfo -> Identity (Maybe SetupBuildInfo))
-> (Dependency -> Identity Dependency)
-> PackageDescription
-> Identity PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SetupBuildInfo -> Identity SetupBuildInfo)
-> Maybe SetupBuildInfo -> Identity (Maybe SetupBuildInfo)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((SetupBuildInfo -> Identity SetupBuildInfo)
 -> Maybe SetupBuildInfo -> Identity (Maybe SetupBuildInfo))
-> ((Dependency -> Identity Dependency)
    -> SetupBuildInfo -> Identity SetupBuildInfo)
-> (Dependency -> Identity Dependency)
-> Maybe SetupBuildInfo
-> Identity (Maybe SetupBuildInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike
  Identity SetupBuildInfo SetupBuildInfo [Dependency] [Dependency]
Lens' SetupBuildInfo [Dependency]
L.setupDepends LensLike
  Identity SetupBuildInfo SetupBuildInfo [Dependency] [Dependency]
-> ((Dependency -> Identity Dependency)
    -> [Dependency] -> Identity [Dependency])
-> (Dependency -> Identity Dependency)
-> SetupBuildInfo
-> Identity SetupBuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dependency -> Identity Dependency)
-> [Dependency] -> Identity [Dependency]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse) Dependency -> Dependency
f
  -- cannot be point-free as normal because of higher rank
  (GenericPackageDescription -> GenericPackageDescription)
-> (GenericPackageDescription -> GenericPackageDescription)
-> GenericPackageDescription
-> GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter
  GenericPackageDescription
  GenericPackageDescription
  [Dependency]
  [Dependency]
-> ([Dependency] -> [Dependency])
-> GenericPackageDescription
-> GenericPackageDescription
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (\[Dependency] -> Identity [Dependency]
f' -> (forall a.
 CondTree ConfVar [Dependency] a
 -> Identity (CondTree ConfVar [Dependency] a))
-> GenericPackageDescription -> Identity GenericPackageDescription
forall (f :: * -> *).
Applicative f =>
(forall a.
 CondTree ConfVar [Dependency] a
 -> f (CondTree ConfVar [Dependency] a))
-> GenericPackageDescription -> f GenericPackageDescription
L.allCondTrees ((forall a.
  CondTree ConfVar [Dependency] a
  -> Identity (CondTree ConfVar [Dependency] a))
 -> GenericPackageDescription -> Identity GenericPackageDescription)
-> (forall a.
    CondTree ConfVar [Dependency] a
    -> Identity (CondTree ConfVar [Dependency] a))
-> GenericPackageDescription
-> Identity GenericPackageDescription
forall a b. (a -> b) -> a -> b
$ LensLike
  Identity
  (CondTree ConfVar [Dependency] a)
  (CondTree ConfVar [Dependency] a)
  [Dependency]
  [Dependency]
forall v c a d. Traversal (CondTree v c a) (CondTree v d a) c d
traverseCondTreeC [Dependency] -> Identity [Dependency]
f') ((Dependency -> Dependency) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> Dependency
f)