{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}

-- | Copyright: (c) 2020-2021 berberman
-- SPDX-License-Identifier: MIT
-- Maintainer: berberman <berberman@yandex.com>
-- Stability: experimental
-- Portability: portable
-- Miscellaneous functions used crossing modules.
module Distribution.ArchHs.Utils
  ( findCabalFile,
    getPkgName,
    getPkgName',
    getPkgVersion,
    dependencyTypeToKind,
    unExe,
    unExeV,
    unLegacyExeV,
    unBuildTools,
    unSystemDependency,
    unDepV,
    getUrl,
    getTwo,
    buildDependsIfBuild,
    buildToolsAndbuildToolDependsIfBuild,
    pkgconfigDependsAndExtraLibsIfBuild,
    traceCallStack,
    trace',
    depNotInGHCLib,
    depNotMyself,
    depIsKind,
    extractFromEVR,
    isProvided,
    filterFirstDiff,
    filterFirstAndBothDiff,
    filterSecondDiff,
    filterSecondAndBothDiff,
    noDiff,
    mapDiff,
    unDiff,
    archHsVersion,
    defaultFlags,
    getFlagAssignment,
  )
where

import Control.Monad ((<=<))
import Data.Algorithm.Diff
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Distribution.ArchHs.Internal.Prelude
import Distribution.ArchHs.Local (ghcLibList)
import Distribution.ArchHs.Types
import Distribution.PackageDescription (repoLocation)
import Distribution.Types.BuildInfo (BuildInfo (..))
import Distribution.Types.Dependency (Dependency, depPkgName, depVerRange)
import Distribution.Types.ExeDependency (ExeDependency (..))
import Distribution.Types.LegacyExeDependency
import qualified Distribution.Types.PackageId as I
import Distribution.Types.PkgconfigDependency
import Distribution.Types.PkgconfigName
import Distribution.Utils.ShortText (fromShortText)
import GHC.Stack (callStack, prettyCallStack)
import Options.Applicative.Simple (simpleVersion)
import qualified Paths_arch_hs as Path
import System.Directory (listDirectory)
import System.FilePath (takeExtension)

-- | Find a cabal file in @dir@,
-- throws error if nothing or more than one files are found
findCabalFile :: FilePath -> IO FilePath
findCabalFile :: FilePath -> IO FilePath
findCabalFile FilePath
dir =
  FilePath -> IO [FilePath]
listDirectory FilePath
dir
    IO [FilePath] -> ([FilePath] -> IO FilePath) -> IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ( \case
            [FilePath
x] -> FilePath -> IO FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
x
            [] -> FilePath -> IO FilePath
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"Unable to find any cabal file in directory " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
dir
            [FilePath]
xs -> FilePath -> IO FilePath
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"Found more than one cabal files" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> [FilePath] -> FilePath
forall a. Show a => a -> FilePath
show [FilePath]
xs FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"in directory " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
dir
        )
      ([FilePath] -> IO FilePath)
-> ([FilePath] -> [FilePath]) -> [FilePath] -> IO FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FilePath
x -> FilePath -> FilePath
takeExtension FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".cabal")

-- | Extract the package name from a 'ExeDependency'.
unExe :: ExeDependency -> PackageName
unExe :: ExeDependency -> PackageName
unExe (ExeDependency PackageName
name UnqualComponentName
_ VersionRange
_) = PackageName
name

-- | Extract the package name and the version range from a 'ExeDependency'.
unExeV :: ExeDependency -> (PackageName, VersionRange)
unExeV :: ExeDependency -> (PackageName, VersionRange)
unExeV (ExeDependency PackageName
name UnqualComponentName
_ VersionRange
v) = (PackageName
name, VersionRange
v)

-- | Extract the package name and the version range from a 'LegacyExeDependency'.
unLegacyExeV :: LegacyExeDependency -> (PackageName, VersionRange)
unLegacyExeV :: LegacyExeDependency -> (PackageName, VersionRange)
unLegacyExeV (LegacyExeDependency FilePath
name VersionRange
v) = (FilePath -> PackageName
mkPackageName FilePath
name, VersionRange
v)

-- | Extract and join package names and version ranges of '[LegacyExeDependency]' and '[ExeDependency]'.
unBuildTools :: ([LegacyExeDependency], [ExeDependency]) -> [(PackageName, VersionRange)]
unBuildTools :: ([LegacyExeDependency], [ExeDependency])
-> [(PackageName, VersionRange)]
unBuildTools ([LegacyExeDependency]
l, [ExeDependency]
e) = (LegacyExeDependency -> (PackageName, VersionRange)
unLegacyExeV (LegacyExeDependency -> (PackageName, VersionRange))
-> [LegacyExeDependency] -> [(PackageName, VersionRange)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [LegacyExeDependency]
l) [(PackageName, VersionRange)]
-> [(PackageName, VersionRange)] -> [(PackageName, VersionRange)]
forall a. Semigroup a => a -> a -> a
<> (ExeDependency -> (PackageName, VersionRange)
unExeV (ExeDependency -> (PackageName, VersionRange))
-> [ExeDependency] -> [(PackageName, VersionRange)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ExeDependency]
e)

-- | Extract dependency names from '[PkgconfigDependency]' and '[SystemDependency]'.
-- >>> (PkgconfigDependency "foo" _ver) --> (SystemDependency "foo.pc")
-- >>> "foo" --> (SystemDependency "libfoo.so")
unSystemDependency :: ([PkgconfigDependency], [String]) -> [SystemDependency]
unSystemDependency :: ([PkgconfigDependency], [FilePath]) -> [SystemDependency]
unSystemDependency ([PkgconfigDependency]
p, [FilePath]
s) = [FilePath -> SystemDependency
SystemDependency (FilePath -> SystemDependency) -> FilePath -> SystemDependency
forall a b. (a -> b) -> a -> b
$ FilePath
name FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
".pc" | (PkgconfigDependency (PkgconfigName -> FilePath
unPkgconfigName -> FilePath
name) PkgconfigVersionRange
_) <- [PkgconfigDependency]
p] [SystemDependency] -> [SystemDependency] -> [SystemDependency]
forall a. Semigroup a => a -> a -> a
<> [FilePath -> SystemDependency
SystemDependency (FilePath -> SystemDependency) -> FilePath -> SystemDependency
forall a b. (a -> b) -> a -> b
$ FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
name FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
".so" | FilePath
name <- [FilePath]
s]

-- | Extract the 'PackageName' and 'VersionRange' of a 'Dependency'.
unDepV :: Dependency -> (PackageName, VersionRange)
unDepV :: Dependency -> (PackageName, VersionRange)
unDepV Dependency
dep = (Dependency -> PackageName
depPkgName Dependency
dep, Dependency -> VersionRange
depVerRange Dependency
dep)

-- | Extract the package name from 'PackageDescription'.
getPkgName :: PackageDescription -> PackageName
getPkgName :: PackageDescription -> PackageName
getPkgName = PackageIdentifier -> PackageName
I.pkgName (PackageIdentifier -> PackageName)
-> (PackageDescription -> PackageIdentifier)
-> PackageDescription
-> PackageName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
package

-- | Extract the package name from 'GenericPackageDescription'.
getPkgName' :: GenericPackageDescription -> PackageName
getPkgName' :: GenericPackageDescription -> PackageName
getPkgName' = PackageIdentifier -> PackageName
I.pkgName (PackageIdentifier -> PackageName)
-> (GenericPackageDescription -> PackageIdentifier)
-> GenericPackageDescription
-> PackageName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
package (PackageDescription -> PackageIdentifier)
-> (GenericPackageDescription -> PackageDescription)
-> GenericPackageDescription
-> PackageIdentifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericPackageDescription -> PackageDescription
packageDescription

-- | Extract the package version from 'PackageDescription'.
getPkgVersion :: PackageDescription -> Version
getPkgVersion :: PackageDescription -> Version
getPkgVersion = PackageIdentifier -> Version
I.pkgVersion (PackageIdentifier -> Version)
-> (PackageDescription -> PackageIdentifier)
-> PackageDescription
-> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
package

-- | Extract the url from 'PackageDescription'.
-- It tries 'homepage', the head of 'sourceRepos', and finally fallback into hackage website.
getUrl :: PackageDescription -> String
getUrl :: PackageDescription -> FilePath
getUrl PackageDescription
cabal = Maybe FilePath -> FilePath
forall (m :: * -> *) a. MonadFail m => Maybe (m a) -> m a
fromJust (Maybe FilePath -> FilePath) -> Maybe FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Maybe FilePath
home Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FilePath
vcs Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FilePath
fallback
  where
    f :: FilePath -> Maybe FilePath
f FilePath
"" = Maybe FilePath
forall a. Maybe a
Nothing
    f FilePath
x = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
x
    fromJust :: Maybe (m a) -> m a
fromJust (Just m a
x) = m a
x
    fromJust Maybe (m a)
_ = FilePath -> m a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Impossible."
    home :: Maybe FilePath
home = FilePath -> Maybe FilePath
f (FilePath -> Maybe FilePath)
-> (PackageDescription -> FilePath)
-> PackageDescription
-> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> FilePath
fromShortText (ShortText -> FilePath)
-> (PackageDescription -> ShortText)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> ShortText
homepage (PackageDescription -> Maybe FilePath)
-> PackageDescription -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ PackageDescription
cabal
    vcs :: Maybe FilePath
vcs = SourceRepo -> Maybe FilePath
repoLocation (SourceRepo -> Maybe FilePath)
-> (PackageDescription -> Maybe SourceRepo)
-> PackageDescription
-> Maybe FilePath
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ([SourceRepo]
-> Getting (First SourceRepo) [SourceRepo] SourceRepo
-> Maybe SourceRepo
forall s a. s -> Getting (First a) s a -> Maybe a
^? Index [SourceRepo]
-> Traversal' [SourceRepo] (IxValue [SourceRepo])
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index [SourceRepo]
0) ([SourceRepo] -> Maybe SourceRepo)
-> (PackageDescription -> [SourceRepo])
-> PackageDescription
-> Maybe SourceRepo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> [SourceRepo]
sourceRepos (PackageDescription -> Maybe FilePath)
-> PackageDescription -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ PackageDescription
cabal
    fallback :: Maybe FilePath
fallback = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"https://hackage.haskell.org/package/" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> PackageName -> FilePath
unPackageName (PackageDescription -> PackageName
getPkgName PackageDescription
cabal)

-- | Map 'DependencyType' with its data constructor tag 'DependencyKind'.
dependencyTypeToKind :: DependencyType -> DependencyKind
dependencyTypeToKind :: DependencyType -> DependencyKind
dependencyTypeToKind (CExe UnqualComponentName
_) = DependencyKind
Exe
dependencyTypeToKind (CExeBuildTools UnqualComponentName
_) = DependencyKind
ExeBuildTools
dependencyTypeToKind DependencyType
CLib = DependencyKind
Lib
dependencyTypeToKind (CTest UnqualComponentName
_) = DependencyKind
Test
dependencyTypeToKind (CBenchmark UnqualComponentName
_) = DependencyKind
Benchmark
dependencyTypeToKind DependencyType
CLibBuildTools = DependencyKind
LibBuildTools
dependencyTypeToKind (CTestBuildTools UnqualComponentName
_) = DependencyKind
TestBuildTools
dependencyTypeToKind (CBenchmarkBuildTools UnqualComponentName
_) = DependencyKind
BenchmarkBuildTools
dependencyTypeToKind (CSubLibs UnqualComponentName
_) = DependencyKind
SubLibs
dependencyTypeToKind (CSubLibsBuildTools UnqualComponentName
_) = DependencyKind
SubLibsBuildTools
dependencyTypeToKind DependencyType
CSetup = DependencyKind
Setup

-- | Apply a 'Getting' to two values respectively, and get the result as a pair.
getTwo :: Getting b s b -> s -> s -> (b, b)
getTwo :: Getting b s b -> s -> s -> (b, b)
getTwo Getting b s b
l s
a s
b = (s
a, s
b) (s, s) -> ((s, s) -> (b, b)) -> (b, b)
forall a b. a -> (a -> b) -> b
& (s -> Identity b) -> (s, s) -> Identity (b, b)
forall a b. Traversal (a, a) (b, b) a b
both ((s -> Identity b) -> (s, s) -> Identity (b, b))
-> (s -> b) -> (s, s) -> (b, b)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (s -> Getting b s b -> b
forall s a. s -> Getting a s a -> a
^. Getting b s b
l)

-- | Same as 'targetBuildDepends', but check if this is 'buildable'.
buildDependsIfBuild :: BuildInfo -> [Dependency]
buildDependsIfBuild :: BuildInfo -> [Dependency]
buildDependsIfBuild BuildInfo
info = [Dependency]
-> BuildInfo -> (BuildInfo -> [Dependency]) -> [Dependency]
forall a. a -> BuildInfo -> (BuildInfo -> a) -> a
whenBuildable [] BuildInfo
info BuildInfo -> [Dependency]
targetBuildDepends

-- | 'buildToolDepends' combined with 'buildTools', and check if this is 'buildable'.
-- Actually, we should avoid accessing these two fields directly, in in favor of 'Distribution.Simple.BuildToolDepends.getAllToolDependencies'
buildToolsAndbuildToolDependsIfBuild :: BuildInfo -> ([LegacyExeDependency], [ExeDependency])
buildToolsAndbuildToolDependsIfBuild :: BuildInfo -> ([LegacyExeDependency], [ExeDependency])
buildToolsAndbuildToolDependsIfBuild BuildInfo
info = ([LegacyExeDependency], [ExeDependency])
-> BuildInfo
-> (BuildInfo -> ([LegacyExeDependency], [ExeDependency]))
-> ([LegacyExeDependency], [ExeDependency])
forall a. a -> BuildInfo -> (BuildInfo -> a) -> a
whenBuildable ([], []) BuildInfo
info ((BuildInfo -> ([LegacyExeDependency], [ExeDependency]))
 -> ([LegacyExeDependency], [ExeDependency]))
-> (BuildInfo -> ([LegacyExeDependency], [ExeDependency]))
-> ([LegacyExeDependency], [ExeDependency])
forall a b. (a -> b) -> a -> b
$ \BuildInfo
i -> (BuildInfo -> [LegacyExeDependency]
buildTools BuildInfo
i, BuildInfo -> [ExeDependency]
buildToolDepends BuildInfo
i)

-- | 'pkgconfigDepends' combined with 'extraLibs', and check if this is 'buildable'.
pkgconfigDependsAndExtraLibsIfBuild :: BuildInfo -> ([PkgconfigDependency], [String])
pkgconfigDependsAndExtraLibsIfBuild :: BuildInfo -> ([PkgconfigDependency], [FilePath])
pkgconfigDependsAndExtraLibsIfBuild BuildInfo
info = ([PkgconfigDependency], [FilePath])
-> BuildInfo
-> (BuildInfo -> ([PkgconfigDependency], [FilePath]))
-> ([PkgconfigDependency], [FilePath])
forall a. a -> BuildInfo -> (BuildInfo -> a) -> a
whenBuildable ([], []) BuildInfo
info ((BuildInfo -> ([PkgconfigDependency], [FilePath]))
 -> ([PkgconfigDependency], [FilePath]))
-> (BuildInfo -> ([PkgconfigDependency], [FilePath]))
-> ([PkgconfigDependency], [FilePath])
forall a b. (a -> b) -> a -> b
$ \BuildInfo
i -> (BuildInfo -> [PkgconfigDependency]
pkgconfigDepends BuildInfo
i, BuildInfo -> [FilePath]
extraLibs BuildInfo
i)

whenBuildable :: a -> BuildInfo -> (BuildInfo -> a) -> a
whenBuildable :: a -> BuildInfo -> (BuildInfo -> a) -> a
whenBuildable a
def BuildInfo
info BuildInfo -> a
f
  | BuildInfo -> Bool
buildable BuildInfo
info = BuildInfo -> a
f BuildInfo
info
  | Bool
otherwise = a
def

-- | Trace with prefix @[TRACE]@.
trace' :: Member Trace r => String -> Sem r ()
trace' :: FilePath -> Sem r ()
trace' FilePath
s = FilePath -> Sem r ()
forall (r :: EffectRow). Member Trace r => FilePath -> Sem r ()
trace (FilePath -> Sem r ()) -> FilePath -> Sem r ()
forall a b. (a -> b) -> a -> b
$ FilePath
"[TRACE]  " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
s

-- | Trace 'GHC.Stack.CallStack'.
traceCallStack :: (HasCallStack, Member Trace r) => Sem r ()
traceCallStack :: Sem r ()
traceCallStack = do
  FilePath -> Sem r ()
forall (r :: EffectRow). Member Trace r => FilePath -> Sem r ()
trace (FilePath -> Sem r ())
-> (FilePath -> FilePath) -> FilePath -> Sem r ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
prefix (FilePath -> Sem r ()) -> FilePath -> Sem r ()
forall a b. (a -> b) -> a -> b
$ CallStack -> FilePath
prettyCallStack CallStack
HasCallStack => CallStack
callStack
  where
    prefix :: FilePath -> FilePath
prefix = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath)
-> (FilePath -> [FilePath]) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath
"[TRACE]  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
lines

-- | 'SolvedDependency' @x@' is not provided by ghc.
depNotInGHCLib :: SolvedDependency -> Bool
depNotInGHCLib :: SolvedDependency -> Bool
depNotInGHCLib SolvedDependency
x = (SolvedDependency
x SolvedDependency
-> Getting PackageName SolvedDependency PackageName -> PackageName
forall s a. s -> Getting a s a -> a
^. Getting PackageName SolvedDependency PackageName
Lens' SolvedDependency PackageName
depName) PackageName -> [PackageName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [PackageName]
ghcLibList

-- | 'SolvedDependency' @x@'s name is not equal to @name@.
depNotMyself :: PackageName -> SolvedDependency -> Bool
depNotMyself :: PackageName -> SolvedDependency -> Bool
depNotMyself PackageName
name SolvedDependency
x = SolvedDependency
x SolvedDependency
-> Getting PackageName SolvedDependency PackageName -> PackageName
forall s a. s -> Getting a s a -> a
^. Getting PackageName SolvedDependency PackageName
Lens' SolvedDependency PackageName
depName PackageName -> PackageName -> Bool
forall a. Eq a => a -> a -> Bool
/= PackageName
name

-- | 'SolvedDependency' @x@' has 'DependencyKind' @k@.
depIsKind :: DependencyKind -> SolvedDependency -> Bool
depIsKind :: DependencyKind -> SolvedDependency -> Bool
depIsKind DependencyKind
k SolvedDependency
x = DependencyKind
k DependencyKind -> [DependencyKind] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (SolvedDependency
x SolvedDependency
-> Getting [DependencyType] SolvedDependency [DependencyType]
-> [DependencyType]
forall s a. s -> Getting a s a -> a
^. Getting [DependencyType] SolvedDependency [DependencyType]
Lens' SolvedDependency [DependencyType]
depType [DependencyType]
-> (DependencyType -> DependencyKind) -> [DependencyKind]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> DependencyType -> DependencyKind
dependencyTypeToKind)

-- | Extract package version from epoch-version-release.
--
-- >>> extractFromEVR "8.10.2-1"
-- "8.10.2"
-- >>> extractFromEVR "3:2.4.11-19"
-- "2.4.11"
extractFromEVR :: String -> ArchLinuxVersion
extractFromEVR :: FilePath -> FilePath
extractFromEVR FilePath
evr =
  let ev :: FilePath
ev = [FilePath] -> FilePath
forall a. [a] -> a
head ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> [FilePath]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn FilePath
"-" FilePath
evr
   in if Char
':' Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
ev then FilePath -> FilePath
forall a. [a] -> [a]
tail (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':') FilePath
ev else FilePath
ev

-- | Whether a 'SolvedPackage' is provided
isProvided :: SolvedPackage -> Bool
isProvided :: SolvedPackage -> Bool
isProvided (ProvidedPackage PackageName
_ DependencyProvider
_) = Bool
True
isProvided SolvedPackage
_ = Bool
False

-- | Filter values from only 'First' list
filterFirstDiff :: [Diff a] -> [Diff a]
filterFirstDiff :: [Diff a] -> [Diff a]
filterFirstDiff = (Diff a -> Bool) -> [Diff a] -> [Diff a]
forall a. (a -> Bool) -> [a] -> [a]
filter (\case First a
_ -> Bool
True; Diff a
_ -> Bool
False)

-- | Filter values from only 'Second' list
filterSecondDiff :: [Diff a] -> [Diff a]
filterSecondDiff :: [Diff a] -> [Diff a]
filterSecondDiff = (Diff a -> Bool) -> [Diff a] -> [Diff a]
forall a. (a -> Bool) -> [a] -> [a]
filter (\case Second a
_ -> Bool
True; Diff a
_ -> Bool
False)

-- | Filter values from 'First' and 'Both' list
filterFirstAndBothDiff :: [Diff a] -> [Diff a]
filterFirstAndBothDiff :: [Diff a] -> [Diff a]
filterFirstAndBothDiff = (Diff a -> Bool) -> [Diff a] -> [Diff a]
forall a. (a -> Bool) -> [a] -> [a]
filter (\case Second a
_ -> Bool
False; Diff a
_ -> Bool
True)

-- | Filter values from 'Second' and 'Both' list
filterSecondAndBothDiff :: [Diff a] -> [Diff a]
filterSecondAndBothDiff :: [Diff a] -> [Diff a]
filterSecondAndBothDiff = (Diff a -> Bool) -> [Diff a] -> [Diff a]
forall a. (a -> Bool) -> [a] -> [a]
filter (\case First a
_ -> Bool
False; Diff a
_ -> Bool
True)

-- | Whether it only has 'Both'
noDiff :: [Diff a] -> Bool
noDiff :: [Diff a] -> Bool
noDiff = (Diff a -> Bool) -> [Diff a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\case Both a
_ a
_ -> Bool
True; Diff a
_ -> Bool
False)

-- | Map value of diff
mapDiff :: (a -> b) -> Diff a -> Diff b
mapDiff :: (a -> b) -> Diff a -> Diff b
mapDiff a -> b
f (First a
x) = b -> Diff b
forall a b. a -> PolyDiff a b
First (b -> Diff b) -> b -> Diff b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
x
mapDiff a -> b
f (Second a
x) = b -> Diff b
forall a b. b -> PolyDiff a b
Second (b -> Diff b) -> b -> Diff b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
x
mapDiff a -> b
f (Both a
x a
y) = b -> b -> Diff b
forall a b. a -> b -> PolyDiff a b
Both (a -> b
f a
x) (a -> b
f a
y)

-- | Extract value from diff
unDiff :: Diff a -> a
unDiff :: Diff a -> a
unDiff (First a
x) = a
x
unDiff (Second a
x) = a
x
unDiff (Both a
x a
_) = a
x

-- | The version of arch-hs
archHsVersion :: String
archHsVersion :: FilePath
archHsVersion = $(simpleVersion Path.version)

-- | Take default flag values of @pkgFlag@ overriden by @assignment@
defaultFlags :: [PkgFlag] -> FlagAssignment -> FlagAssignment
defaultFlags :: [PkgFlag] -> FlagAssignment -> FlagAssignment
defaultFlags [PkgFlag]
pkgFlags FlagAssignment
assignment = FlagAssignment
result
  where
    defaultFlagAssignments :: FlagAssignment
defaultFlagAssignments =
      (PkgFlag -> FlagAssignment -> FlagAssignment)
-> FlagAssignment -> [PkgFlag] -> FlagAssignment
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\PkgFlag
f FlagAssignment
acc -> FlagName -> Bool -> FlagAssignment -> FlagAssignment
insertFlagAssignment (PkgFlag -> FlagName
flagName PkgFlag
f) (PkgFlag -> Bool
flagDefault PkgFlag
f) FlagAssignment
acc) ([(FlagName, Bool)] -> FlagAssignment
mkFlagAssignment []) [PkgFlag]
pkgFlags
    flagAssignment :: [(FlagName, Bool)]
flagAssignment = FlagAssignment -> [(FlagName, Bool)]
unFlagAssignment FlagAssignment
assignment
    flagNames :: [FlagName]
flagNames = ((FlagName, Bool) -> FlagName) -> [(FlagName, Bool)] -> [FlagName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FlagName, Bool) -> FlagName
forall a b. (a, b) -> a
fst [(FlagName, Bool)]
flagAssignment
    result :: FlagAssignment
result =
      [(FlagName, Bool)] -> FlagAssignment
mkFlagAssignment
        ([(FlagName, Bool)] -> FlagAssignment)
-> ([(FlagName, Bool)] -> [(FlagName, Bool)])
-> [(FlagName, Bool)]
-> FlagAssignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(FlagName, Bool)] -> [(FlagName, Bool)] -> [(FlagName, Bool)]
forall a. Semigroup a => a -> a -> a
<> [(FlagName, Bool)]
flagAssignment)
        ([(FlagName, Bool)] -> [(FlagName, Bool)])
-> ([(FlagName, Bool)] -> [(FlagName, Bool)])
-> [(FlagName, Bool)]
-> [(FlagName, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FlagName, Bool) -> Bool)
-> [(FlagName, Bool)] -> [(FlagName, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(FlagName
fName, Bool
_) -> FlagName
fName FlagName -> [FlagName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FlagName]
flagNames)
        ([(FlagName, Bool)] -> FlagAssignment)
-> [(FlagName, Bool)] -> FlagAssignment
forall a b. (a -> b) -> a -> b
$ FlagAssignment -> [(FlagName, Bool)]
unFlagAssignment FlagAssignment
defaultFlagAssignments

-- | Get 'FlagAssignment' from 'FlagAssignments'
--
-- Returns an empty FlagAssignment if no corresponding package in 'FlagAssignments'
getFlagAssignment :: PackageName -> FlagAssignments -> FlagAssignment
getFlagAssignment :: PackageName -> FlagAssignments -> FlagAssignment
getFlagAssignment PackageName
k FlagAssignments
v = FlagAssignment -> Maybe FlagAssignment -> FlagAssignment
forall a. a -> Maybe a -> a
fromMaybe ([(FlagName, Bool)] -> FlagAssignment
mkFlagAssignment []) (Maybe FlagAssignment -> FlagAssignment)
-> Maybe FlagAssignment -> FlagAssignment
forall a b. (a -> b) -> a -> b
$ PackageName
k PackageName -> FlagAssignments -> Maybe FlagAssignment
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` FlagAssignments
v