module CabalLenses.CondVars
( CondVars(..)
, fromDefaults
, enableFlag
, disableFlag
, eval
) where
import qualified Distribution.PackageDescription as PD
import Distribution.PackageDescription (Condition(..))
import qualified Distribution.System as S
import Distribution.System (OS(..), Arch(..))
import Distribution.Compiler (CompilerFlavor(..), buildCompilerFlavor)
import Distribution.Version (Version, withinRange)
import qualified Data.HashMap.Strict as HM
import Control.Lens
type FlagName = String
type FlagMap = HM.HashMap FlagName Bool
data CondVars = CondVars
{ flags :: FlagMap
, os :: OS
, arch :: Arch
, compilerFlavor :: CompilerFlavor
, compilerVersion :: Maybe Version
} deriving (Show)
makeLensesFor [ ("flags", "flagsL")
] ''CondVars
fromDefaults :: PD.GenericPackageDescription -> CondVars
fromDefaults pkgDescrp = CondVars { flags = flags
, os = S.buildOS
, arch = S.buildArch
, compilerFlavor = buildCompilerFlavor
, compilerVersion = Nothing
}
where
flags = HM.fromList $ map nameWithDflt (PD.genPackageFlags pkgDescrp)
nameWithDflt PD.MkFlag { PD.flagName = name, PD.flagDefault = dflt } =
(PD.unFlagName name, dflt)
enableFlag :: FlagName -> CondVars -> CondVars
enableFlag flag condVars =
condVars & flagsL %~ HM.insert flag True
disableFlag :: FlagName -> CondVars -> CondVars
disableFlag flag condVars =
condVars & flagsL %~ HM.insert flag False
eval :: CondVars -> Condition PD.ConfVar -> Bool
eval condVars = eval'
where
eval' (Var var) = hasVar var
eval' (Lit val) = val
eval' (CNot c) = not $ eval' c
eval' (COr c1 c2) = eval' c1 || eval' c2
eval' (CAnd c1 c2) = eval' c1 && eval' c2
hasVar (PD.OS osVar) = osVar == os condVars
hasVar (PD.Arch archVar) = archVar == arch condVars
hasVar (PD.Impl cflavor vrange)
| Just version <- compilerVersion condVars
= cflavor == compilerFlavor condVars && version `withinRange` vrange
| otherwise
= cflavor == compilerFlavor condVars
hasVar (PD.Flag name)
| Just v <- HM.lookup (PD.unFlagName name) (flags condVars)
= v
| otherwise
= False