{-# LANGUAGE CPP #-}
module Merge.Dependencies
( EDep(..)
, RetroPackageDescription(..)
, exeAndLibDeps
, mkRetroPD
, resolveDependencies
) where
import Control.DeepSeq (NFData(..))
import Control.Parallel.Strategies
import Data.Maybe ( isJust, isNothing )
import qualified Data.List as L
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup (Semigroup(..))
#endif
import qualified Data.Set as S
import qualified Distribution.CabalSpecVersion as Cabal
import qualified Distribution.Compat.NonEmptySet as NES
import qualified Distribution.Package as Cabal
import qualified Distribution.PackageDescription as Cabal
import qualified Distribution.Version as Cabal
import qualified Distribution.Pretty as Cabal
import qualified Distribution.Compiler as Cabal
import qualified Portage.Cabal as Portage
import qualified Portage.Dependency as Portage
import qualified Portage.Dependency.Normalize as PN
import qualified Portage.Overlay as Portage
import qualified Portage.PackageId as Portage
import qualified Portage.Use as Portage
import qualified Portage.Tables as Portage
import qualified Cabal2Ebuild as C2E
import qualified Portage.GHCCore as GHCCore
import Debug.Trace ( trace )
data EDep = EDep
{
EDep -> Dependency
rdep :: Portage.Dependency,
EDep -> Set String
rdep_e :: S.Set String,
EDep -> Dependency
dep :: Portage.Dependency,
EDep -> Set String
dep_e :: S.Set String
}
deriving (Int -> EDep -> ShowS
[EDep] -> ShowS
EDep -> String
(Int -> EDep -> ShowS)
-> (EDep -> String) -> ([EDep] -> ShowS) -> Show EDep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EDep] -> ShowS
$cshowList :: [EDep] -> ShowS
show :: EDep -> String
$cshow :: EDep -> String
showsPrec :: Int -> EDep -> ShowS
$cshowsPrec :: Int -> EDep -> ShowS
Show, EDep -> EDep -> Bool
(EDep -> EDep -> Bool) -> (EDep -> EDep -> Bool) -> Eq EDep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EDep -> EDep -> Bool
$c/= :: EDep -> EDep -> Bool
== :: EDep -> EDep -> Bool
$c== :: EDep -> EDep -> Bool
Eq, Eq EDep
Eq EDep
-> (EDep -> EDep -> Ordering)
-> (EDep -> EDep -> Bool)
-> (EDep -> EDep -> Bool)
-> (EDep -> EDep -> Bool)
-> (EDep -> EDep -> Bool)
-> (EDep -> EDep -> EDep)
-> (EDep -> EDep -> EDep)
-> Ord EDep
EDep -> EDep -> Bool
EDep -> EDep -> Ordering
EDep -> EDep -> EDep
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EDep -> EDep -> EDep
$cmin :: EDep -> EDep -> EDep
max :: EDep -> EDep -> EDep
$cmax :: EDep -> EDep -> EDep
>= :: EDep -> EDep -> Bool
$c>= :: EDep -> EDep -> Bool
> :: EDep -> EDep -> Bool
$c> :: EDep -> EDep -> Bool
<= :: EDep -> EDep -> Bool
$c<= :: EDep -> EDep -> Bool
< :: EDep -> EDep -> Bool
$c< :: EDep -> EDep -> Bool
compare :: EDep -> EDep -> Ordering
$ccompare :: EDep -> EDep -> Ordering
$cp1Ord :: Eq EDep
Ord)
instance NFData EDep where
rnf :: EDep -> ()
rnf (EDep Dependency
rd Set String
rde Dependency
d Set String
de) = Dependency -> ()
forall a. NFData a => a -> ()
rnf Dependency
rd () -> () -> ()
`seq` Set String -> ()
forall a. NFData a => a -> ()
rnf Set String
rde () -> () -> ()
`seq` Dependency -> ()
forall a. NFData a => a -> ()
rnf Dependency
d () -> () -> ()
`seq` Set String -> ()
forall a. NFData a => a -> ()
rnf Set String
de
data RetroPackageDescription = RetroPackageDescription {
RetroPackageDescription -> PackageDescription
packageDescription :: Cabal.PackageDescription,
RetroPackageDescription -> [Dependency]
buildDepends :: [Cabal.Dependency]
} deriving (Int -> RetroPackageDescription -> ShowS
[RetroPackageDescription] -> ShowS
RetroPackageDescription -> String
(Int -> RetroPackageDescription -> ShowS)
-> (RetroPackageDescription -> String)
-> ([RetroPackageDescription] -> ShowS)
-> Show RetroPackageDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetroPackageDescription] -> ShowS
$cshowList :: [RetroPackageDescription] -> ShowS
show :: RetroPackageDescription -> String
$cshow :: RetroPackageDescription -> String
showsPrec :: Int -> RetroPackageDescription -> ShowS
$cshowsPrec :: Int -> RetroPackageDescription -> ShowS
Show)
mkRetroPD :: Cabal.PackageDescription -> RetroPackageDescription
mkRetroPD :: PackageDescription -> RetroPackageDescription
mkRetroPD PackageDescription
pd = RetroPackageDescription :: PackageDescription -> [Dependency] -> RetroPackageDescription
RetroPackageDescription { packageDescription :: PackageDescription
packageDescription = PackageDescription
pd, buildDepends :: [Dependency]
buildDepends = PackageDescription -> [Dependency]
exeAndLibDeps PackageDescription
pd }
exeAndLibDeps :: Cabal.PackageDescription -> [Cabal.Dependency]
exeAndLibDeps :: PackageDescription -> [Dependency]
exeAndLibDeps PackageDescription
pkg = (Executable -> [Dependency]) -> [Executable] -> [Dependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [Dependency]
Cabal.targetBuildDepends (BuildInfo -> [Dependency])
-> (Executable -> BuildInfo) -> Executable -> [Dependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> BuildInfo
Cabal.buildInfo)
(PackageDescription -> [Executable]
Cabal.executables PackageDescription
pkg)
[Dependency] -> [Dependency] -> [Dependency]
forall a. Eq a => [a] -> [a] -> [a]
`L.union`
(Library -> [Dependency]) -> [Library] -> [Dependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [Dependency]
Cabal.targetBuildDepends (BuildInfo -> [Dependency])
-> (Library -> BuildInfo) -> Library -> [Dependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
Cabal.libBuildInfo)
(PackageDescription -> [Library]
Cabal.allLibraries PackageDescription
pkg)
instance Semigroup EDep where
(EDep Dependency
rdepA Set String
rdep_eA Dependency
depA Set String
dep_eA) <> :: EDep -> EDep -> EDep
<> (EDep Dependency
rdepB Set String
rdep_eB Dependency
depB Set String
dep_eB) = EDep :: Dependency -> Set String -> Dependency -> Set String -> EDep
EDep
{ rdep :: Dependency
rdep = [Dependency] -> Dependency
Portage.DependAllOf [Dependency
rdepA, Dependency
rdepB]
, rdep_e :: Set String
rdep_e = Set String
rdep_eA Set String -> Set String -> Set String
forall a. Ord a => Set a -> Set a -> Set a
`S.union` Set String
rdep_eB
, dep :: Dependency
dep = [Dependency] -> Dependency
Portage.DependAllOf [Dependency
depA, Dependency
depB]
, dep_e :: Set String
dep_e = Set String
dep_eA Set String -> Set String -> Set String
forall a. Ord a => Set a -> Set a -> Set a
`S.union` Set String
dep_eB
}
instance Monoid EDep where
mempty :: EDep
mempty = EDep :: Dependency -> Set String -> Dependency -> Set String -> EDep
EDep
{
rdep :: Dependency
rdep = Dependency
Portage.empty_dependency,
rdep_e :: Set String
rdep_e = Set String
forall a. Set a
S.empty,
dep :: Dependency
dep = Dependency
Portage.empty_dependency,
dep_e :: Set String
dep_e = Set String
forall a. Set a
S.empty
}
#if !(MIN_VERSION_base(4,11,0))
(EDep rdepA rdep_eA depA dep_eA) `mappend` (EDep rdepB rdep_eB depB dep_eB) = EDep
{ rdep = Portage.DependAllOf [rdepA, rdepB]
, rdep_e = rdep_eA `S.union` rdep_eB
, dep = Portage.DependAllOf [depA, depB]
, dep_e = dep_eA `S.union` dep_eB
}
#endif
resolveDependencies :: Portage.Overlay -> RetroPackageDescription -> Cabal.CompilerInfo
-> [Cabal.PackageName] -> Cabal.PackageName
-> EDep
resolveDependencies :: Overlay
-> RetroPackageDescription
-> CompilerInfo
-> [PackageName]
-> PackageName
-> EDep
resolveDependencies Overlay
overlay RetroPackageDescription
pkg CompilerInfo
compiler_info [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name = EDep
edeps
where
treatAsLibrary :: Bool
treatAsLibrary :: Bool
treatAsLibrary = Maybe Library -> Bool
forall a. Maybe a -> Bool
isJust (PackageDescription -> Maybe Library
Cabal.library (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg))
raw_haskell_deps :: Portage.Dependency
raw_haskell_deps :: Dependency
raw_haskell_deps = Dependency -> Dependency
PN.normalize_depend (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$ [Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$ Overlay -> [Dependency] -> [Dependency]
haskellDependencies Overlay
overlay (RetroPackageDescription -> [Dependency]
buildDepends RetroPackageDescription
pkg)
test_deps :: Portage.Dependency
test_deps :: Dependency
test_deps = (Bool, Use) -> Dependency -> Dependency
Portage.mkUseDependency (Bool
True, String -> Use
Portage.Use String
"test") (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$
[Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$
[Dependency] -> [Dependency]
remove_raw_common ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$
Overlay
-> PackageDescription
-> [PackageName]
-> PackageName
-> [Dependency]
testDependencies Overlay
overlay (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg) [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name
cabal_dep :: Portage.Dependency
cabal_dep :: Dependency
cabal_dep = Overlay -> PackageDescription -> CompilerInfo -> Dependency
cabalDependency Overlay
overlay (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg) CompilerInfo
compiler_info
ghc_dep :: Portage.Dependency
ghc_dep :: Dependency
ghc_dep = CompilerInfo -> Dependency
compilerInfoToDependency CompilerInfo
compiler_info
extra_libs :: Portage.Dependency
extra_libs :: Dependency
extra_libs = [Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$ PackageDescription -> [Dependency]
findCLibs (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg)
pkg_config_libs :: [Portage.Dependency]
pkg_config_libs :: [Dependency]
pkg_config_libs = Overlay -> PackageDescription -> [Dependency]
pkgConfigDependencies Overlay
overlay (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg)
pkg_config_tools :: Portage.Dependency
pkg_config_tools :: Dependency
pkg_config_tools = [Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$ if [Dependency] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null [Dependency]
pkg_config_libs
then []
else [String -> String -> Dependency
any_c_p String
"virtual" String
"pkgconfig"]
build_tools :: Portage.Dependency
build_tools :: Dependency
build_tools = [Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$ Dependency
pkg_config_tools Dependency -> [Dependency] -> [Dependency]
forall a. a -> [a] -> [a]
: PackageDescription -> [Dependency]
legacyBuildToolsDependencies (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg)
[Dependency] -> [Dependency] -> [Dependency]
forall a. [a] -> [a] -> [a]
++ Overlay -> PackageDescription -> [Dependency]
hackageBuildToolsDependencies Overlay
overlay (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg)
setup_deps :: Portage.Dependency
setup_deps :: Dependency
setup_deps = Dependency -> Dependency
PN.normalize_depend (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$ [Dependency] -> Dependency
Portage.DependAllOf ([Dependency] -> Dependency) -> [Dependency] -> Dependency
forall a b. (a -> b) -> a -> b
$
[Dependency] -> [Dependency]
remove_raw_common ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$
Overlay
-> PackageDescription
-> [PackageName]
-> PackageName
-> [Dependency]
setupDependencies Overlay
overlay (RetroPackageDescription -> PackageDescription
packageDescription RetroPackageDescription
pkg) [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name
edeps :: EDep
edeps :: EDep
edeps
| Bool
treatAsLibrary = EDep
forall a. Monoid a => a
mempty
{
dep :: Dependency
dep = [Dependency] -> Dependency
Portage.DependAllOf
[ Dependency
cabal_dep
, Dependency
setup_deps
, Dependency
build_tools
, Dependency
test_deps
],
dep_e :: Set String
dep_e = String -> Set String
forall a. a -> Set a
S.singleton String
"${RDEPEND}",
rdep :: Dependency
rdep = [Dependency] -> Dependency
Portage.DependAllOf
[ Dependency -> Dependency
Portage.set_build_slot Dependency
ghc_dep
, Dependency -> Dependency
Portage.set_build_slot (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$ Dependency -> Dependency
add_profile (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$ Dependency
raw_haskell_deps
, Dependency
extra_libs
, [Dependency] -> Dependency
Portage.DependAllOf [Dependency]
pkg_config_libs
]
}
| Bool
otherwise = EDep
forall a. Monoid a => a
mempty
{
dep :: Dependency
dep = [Dependency] -> Dependency
Portage.DependAllOf
[ Dependency
cabal_dep
, Dependency
setup_deps
, Dependency
build_tools
, Dependency
test_deps
],
dep_e :: Set String
dep_e = String -> Set String
forall a. a -> Set a
S.singleton String
"${RDEPEND}",
rdep :: Dependency
rdep = [Dependency] -> Dependency
Portage.DependAllOf
[ Dependency -> Dependency
Portage.set_build_slot Dependency
ghc_dep
, Dependency -> Dependency
Portage.set_build_slot (Dependency -> Dependency) -> Dependency -> Dependency
forall a b. (a -> b) -> a -> b
$ Dependency
raw_haskell_deps
, Dependency
extra_libs
, [Dependency] -> Dependency
Portage.DependAllOf [Dependency]
pkg_config_libs
]
}
add_profile :: Dependency -> Dependency
add_profile = UseFlag -> Dependency -> Dependency
Portage.addDepUseFlag (Use -> UseFlag
Portage.mkQUse (String -> Use
Portage.Use String
"profile"))
remove_raw_common :: [Dependency] -> [Dependency]
remove_raw_common = (Dependency -> Bool) -> [Dependency] -> [Dependency]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Dependency
d -> Bool -> Bool
not (Dependency -> Dependency -> Bool
Portage.dep_as_broad_as Dependency
d Dependency
raw_haskell_deps))
([Dependency] -> [Dependency])
-> ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dependency -> Dependency) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> Dependency
PN.normalize_depend
setupDependencies :: Portage.Overlay -> Cabal.PackageDescription -> [Cabal.PackageName] -> Cabal.PackageName -> [Portage.Dependency]
setupDependencies :: Overlay
-> PackageDescription
-> [PackageName]
-> PackageName
-> [Dependency]
setupDependencies Overlay
overlay PackageDescription
pkg [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name = [Dependency]
deps
where cabalDeps :: [Dependency]
cabalDeps = [Dependency]
-> ([Dependency] -> [Dependency])
-> Maybe [Dependency]
-> [Dependency]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] [Dependency] -> [Dependency]
forall a. a -> a
id (Maybe [Dependency] -> [Dependency])
-> Maybe [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$ SetupBuildInfo -> [Dependency]
Cabal.setupDepends (SetupBuildInfo -> [Dependency])
-> Maybe SetupBuildInfo -> Maybe [Dependency]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` PackageDescription -> Maybe SetupBuildInfo
Cabal.setupBuildInfo PackageDescription
pkg
cabalDeps' :: [Dependency]
cabalDeps' = ([Dependency], [Dependency]) -> [Dependency]
forall a b. (a, b) -> a
fst (([Dependency], [Dependency]) -> [Dependency])
-> ([Dependency], [Dependency]) -> [Dependency]
forall a b. (a -> b) -> a -> b
$ [PackageName]
-> PackageName -> [Dependency] -> ([Dependency], [Dependency])
Portage.partition_depends [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name [Dependency]
cabalDeps
deps :: [Dependency]
deps = Overlay -> Category -> [Dependency] -> [Dependency]
C2E.convertDependencies Overlay
overlay (String -> Category
Portage.Category String
"dev-haskell") [Dependency]
cabalDeps'
testDependencies :: Portage.Overlay -> Cabal.PackageDescription -> [Cabal.PackageName] -> Cabal.PackageName -> [Portage.Dependency]
testDependencies :: Overlay
-> PackageDescription
-> [PackageName]
-> PackageName
-> [Dependency]
testDependencies Overlay
overlay PackageDescription
pkg [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name = [Dependency]
deps
where cabalDeps :: [Dependency]
cabalDeps = (TestSuite -> [Dependency]) -> [TestSuite] -> [Dependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [Dependency]
Cabal.targetBuildDepends (BuildInfo -> [Dependency])
-> (TestSuite -> BuildInfo) -> TestSuite -> [Dependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> BuildInfo
Cabal.testBuildInfo) (PackageDescription -> [TestSuite]
Cabal.testSuites PackageDescription
pkg)
cabalDeps' :: [Dependency]
cabalDeps' = ([Dependency], [Dependency]) -> [Dependency]
forall a b. (a, b) -> a
fst (([Dependency], [Dependency]) -> [Dependency])
-> ([Dependency], [Dependency]) -> [Dependency]
forall a b. (a -> b) -> a -> b
$ [PackageName]
-> PackageName -> [Dependency] -> ([Dependency], [Dependency])
Portage.partition_depends [PackageName]
ghc_package_names PackageName
merged_cabal_pkg_name [Dependency]
cabalDeps
deps :: [Dependency]
deps = Overlay -> Category -> [Dependency] -> [Dependency]
C2E.convertDependencies Overlay
overlay (String -> Category
Portage.Category String
"dev-haskell") [Dependency]
cabalDeps'
haskellDependencies :: Portage.Overlay -> [Cabal.Dependency] -> [Portage.Dependency]
haskellDependencies :: Overlay -> [Dependency] -> [Dependency]
haskellDependencies Overlay
overlay [Dependency]
deps =
Overlay -> Category -> [Dependency] -> [Dependency]
C2E.convertDependencies Overlay
overlay (String -> Category
Portage.Category String
"dev-haskell") [Dependency]
deps
cabalDependency :: Portage.Overlay -> Cabal.PackageDescription -> Cabal.CompilerInfo -> Portage.Dependency
cabalDependency :: Overlay -> PackageDescription -> CompilerInfo -> Dependency
cabalDependency Overlay
overlay PackageDescription
pkg ~(Cabal.CompilerInfo {
compilerInfoId :: CompilerInfo -> CompilerId
Cabal.compilerInfoId =
Cabal.CompilerId CompilerFlavor
Cabal.GHC Version
cabal_version
}) =
Overlay -> Category -> Dependency -> Dependency
C2E.convertDependency Overlay
overlay
(String -> Category
Portage.Category String
"dev-haskell")
(PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Cabal.Dependency (String -> PackageName
Cabal.mkPackageName String
"Cabal")
VersionRange
finalCabalDep (LibraryName -> NonEmptySet LibraryName
forall a. a -> NonEmptySet a
NES.singleton LibraryName
Cabal.defaultLibName))
where
versionNumbers :: [Int]
versionNumbers = Version -> [Int]
Cabal.versionNumbers Version
cabal_version
userCabalVersion :: VersionRange
userCabalVersion = Version -> VersionRange
Cabal.orLaterVersion (Version -> VersionRange) -> Version -> VersionRange
forall a b. (a -> b) -> a -> b
$ [Int] -> Version
Cabal.mkVersion
([Int] -> Version) -> [Int] -> Version
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion -> [Int]
Cabal.cabalSpecToVersionDigits (CabalSpecVersion -> [Int]) -> CabalSpecVersion -> [Int]
forall a b. (a -> b) -> a -> b
$ PackageDescription -> CabalSpecVersion
Cabal.specVersion PackageDescription
pkg
shippedCabalVersion :: Maybe Version
shippedCabalVersion = [Int] -> Maybe Version
GHCCore.cabalFromGHC [Int]
versionNumbers
shippedCabalDep :: VersionRange
shippedCabalDep = VersionRange
-> (Version -> VersionRange) -> Maybe Version -> VersionRange
forall b a. b -> (a -> b) -> Maybe a -> b
maybe VersionRange
Cabal.anyVersion Version -> VersionRange
Cabal.orLaterVersion Maybe Version
shippedCabalVersion
finalCabalDep :: VersionRange
finalCabalDep = VersionRange -> VersionRange
Cabal.simplifyVersionRange
(VersionRange -> VersionRange -> VersionRange
Cabal.intersectVersionRanges
VersionRange
userCabalVersion
VersionRange
shippedCabalDep)
compilerInfoToDependency :: Cabal.CompilerInfo -> Portage.Dependency
compilerInfoToDependency :: CompilerInfo -> Dependency
compilerInfoToDependency ~(Cabal.CompilerInfo {
compilerInfoId :: CompilerInfo -> CompilerId
Cabal.compilerInfoId =
Cabal.CompilerId CompilerFlavor
Cabal.GHC Version
cabal_version}) =
String -> String -> [Int] -> Dependency
at_least_c_p_v String
"dev-lang" String
"ghc" (Version -> [Int]
Cabal.versionNumbers Version
cabal_version)
findCLibs :: Cabal.PackageDescription -> [Portage.Dependency]
findCLibs :: PackageDescription -> [Dependency]
findCLibs (Cabal.PackageDescription { library :: PackageDescription -> Maybe Library
Cabal.library = Maybe Library
lib, executables :: PackageDescription -> [Executable]
Cabal.executables = [Executable]
exes }) =
[ String -> Dependency -> Dependency
forall a. String -> a -> a
trace (String
"WARNING: This package depends on a C library we don't know the portage name for: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
p String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
". Check the generated ebuild.")
(String -> String -> Dependency
any_c_p String
"unknown-c-lib" String
p)
| String
p <- [String]
notFound
] [Dependency] -> [Dependency] -> [Dependency]
forall a. [a] -> [a] -> [a]
++
[Dependency]
found
where
libE :: [String]
libE = (Library -> [String]) -> [Library] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [String]
Cabal.extraLibs (BuildInfo -> [String])
-> (Library -> BuildInfo) -> Library -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
Cabal.libBuildInfo) ([Library] -> [String]) -> [Library] -> [String]
forall a b. (a -> b) -> a -> b
$ [Library] -> (Library -> [Library]) -> Maybe Library -> [Library]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Library -> [Library]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Library
lib
exeE :: [String]
exeE = (BuildInfo -> [String]) -> [BuildInfo] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap BuildInfo -> [String]
Cabal.extraLibs ((BuildInfo -> Bool) -> [BuildInfo] -> [BuildInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter BuildInfo -> Bool
Cabal.buildable ((Executable -> BuildInfo) -> [Executable] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> BuildInfo
Cabal.buildInfo [Executable]
exes))
allE :: [String]
allE = [String]
libE [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
exeE
notFound :: [String]
notFound = [ String
p | String
p <- [String]
allE, Maybe Dependency -> Bool
forall a. Maybe a -> Bool
isNothing (String -> Maybe Dependency
staticTranslateExtraLib String
p) ]
found :: [Dependency]
found = [ Dependency
p | Just Dependency
p <- (String -> Maybe Dependency) -> [String] -> [Maybe Dependency]
forall a b. (a -> b) -> [a] -> [b]
map String -> Maybe Dependency
staticTranslateExtraLib [String]
allE ]
any_c_p_s_u :: String -> String -> Portage.SlotDepend -> [Portage.UseFlag] -> Portage.Dependency
any_c_p_s_u :: String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
cat String
pn SlotDepend
slot [UseFlag]
uses = Atom -> Dependency
Portage.DependAtom (Atom -> Dependency) -> Atom -> Dependency
forall a b. (a -> b) -> a -> b
$
PackageName -> DRange -> DAttr -> Atom
Portage.Atom (String -> String -> PackageName
Portage.mkPackageName String
cat String
pn)
(LBound -> UBound -> DRange
Portage.DRange LBound
Portage.ZeroB UBound
Portage.InfinityB)
(SlotDepend -> [UseFlag] -> DAttr
Portage.DAttr SlotDepend
slot [UseFlag]
uses)
any_c_p :: String -> String -> Portage.Dependency
any_c_p :: String -> String -> Dependency
any_c_p String
cat String
pn = String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
cat String
pn SlotDepend
Portage.AnySlot []
at_least_c_p_v :: String -> String -> [Int] -> Portage.Dependency
at_least_c_p_v :: String -> String -> [Int] -> Dependency
at_least_c_p_v String
cat String
pn [Int]
v = Atom -> Dependency
Portage.DependAtom (Atom -> Dependency) -> Atom -> Dependency
forall a b. (a -> b) -> a -> b
$
PackageName -> DRange -> DAttr -> Atom
Portage.Atom (String -> String -> PackageName
Portage.mkPackageName String
cat String
pn)
(LBound -> UBound -> DRange
Portage.DRange (Version -> LBound
Portage.NonstrictLB ([Int] -> Maybe Char -> [Suffix] -> Int -> Version
Portage.Version [Int]
v Maybe Char
forall a. Maybe a
Nothing [] Int
0)) UBound
Portage.InfinityB)
(SlotDepend -> [UseFlag] -> DAttr
Portage.DAttr SlotDepend
Portage.AnySlot [])
staticTranslateExtraLib :: String -> Maybe Portage.Dependency
String
lib = String -> [(String, Dependency)] -> Maybe Dependency
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
lib [(String, Dependency)]
m
where
m :: [(String, Dependency)]
m = [ (String
"z", String -> String -> Dependency
any_c_p String
"sys-libs" String
"zlib")
, (String
"bz2", String -> String -> Dependency
any_c_p String
"app-arch" String
"bzip2")
, (String
"mysqlclient", String -> String -> [Int] -> Dependency
at_least_c_p_v String
"virtual" String
"mysql" [Int
4,Int
0])
, (String
"pq", String -> String -> [Int] -> Dependency
at_least_c_p_v String
"dev-db" String
"postgresql" [Int
7])
, (String
"ev", String -> String -> Dependency
any_c_p String
"dev-libs" String
"libev")
, (String
"expat", String -> String -> Dependency
any_c_p String
"dev-libs" String
"expat")
, (String
"curl", String -> String -> Dependency
any_c_p String
"net-misc" String
"curl")
, (String
"xml2", String -> String -> Dependency
any_c_p String
"dev-libs" String
"libxml2")
, (String
"mecab", String -> String -> Dependency
any_c_p String
"app-text" String
"mecab")
, (String
"zmq", String -> String -> Dependency
any_c_p String
"net-libs" String
"zeromq")
, (String
"SDL", String -> String -> Dependency
any_c_p String
"media-libs" String
"libsdl")
, (String
"adns", String -> String -> Dependency
any_c_p String
"net-libs" String
"adns")
, (String
"pcre", String -> String -> Dependency
any_c_p String
"dev-libs" String
"libpcre")
, (String
"GL", String -> String -> Dependency
any_c_p String
"virtual" String
"opengl")
, (String
"GLU", String -> String -> Dependency
any_c_p String
"virtual" String
"glu")
, (String
"glut", String -> String -> Dependency
any_c_p String
"media-libs" String
"freeglut")
, (String
"X11", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libX11")
, (String
"libzip", String -> String -> Dependency
any_c_p String
"dev-libs" String
"libzip")
, (String
"ssl", String -> String -> Dependency
any_c_p String
"dev-libs" String
"openssl")
, (String
"Judy", String -> String -> Dependency
any_c_p String
"dev-libs" String
"judy")
, (String
"fcgi", String -> String -> Dependency
any_c_p String
"dev-libs" String
"fcgi")
, (String
"gnutls", String -> String -> Dependency
any_c_p String
"net-libs" String
"gnutls")
, (String
"idn", String -> String -> Dependency
any_c_p String
"net-dns" String
"libidn")
, (String
"tre", String -> String -> Dependency
any_c_p String
"dev-libs" String
"tre")
, (String
"m", String -> String -> Dependency
any_c_p String
"virtual" String
"libc")
, (String
"asound", String -> String -> Dependency
any_c_p String
"media-libs" String
"alsa-lib")
, (String
"sqlite3", String -> String -> [Int] -> Dependency
at_least_c_p_v String
"dev-db" String
"sqlite" [Int
3,Int
0])
, (String
"stdc++", String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
"sys-devel" String
"gcc" SlotDepend
Portage.AnySlot [Use -> UseFlag
Portage.mkUse (String -> Use
Portage.Use String
"cxx")])
, (String
"crack", String -> String -> Dependency
any_c_p String
"sys-libs" String
"cracklib")
, (String
"exif", String -> String -> Dependency
any_c_p String
"media-libs" String
"libexif")
, (String
"IL", String -> String -> Dependency
any_c_p String
"media-libs" String
"devil")
, (String
"Imlib2", String -> String -> Dependency
any_c_p String
"media-libs" String
"imlib2")
, (String
"pcap", String -> String -> Dependency
any_c_p String
"net-libs" String
"libpcap")
, (String
"lber", String -> String -> Dependency
any_c_p String
"net-nds" String
"openldap")
, (String
"ldap", String -> String -> Dependency
any_c_p String
"net-nds" String
"openldap")
, (String
"expect", String -> String -> Dependency
any_c_p String
"dev-tcltk" String
"expect")
, (String
"tcl", String -> String -> Dependency
any_c_p String
"dev-lang" String
"tcl")
, (String
"Xext", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXext")
, (String
"Xrandr", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXrandr")
, (String
"crypto", String -> String -> Dependency
any_c_p String
"dev-libs" String
"openssl")
, (String
"gmp", String -> String -> Dependency
any_c_p String
"dev-libs" String
"gmp")
, (String
"fuse", String -> String -> Dependency
any_c_p String
"sys-fs" String
"fuse")
, (String
"zip", String -> String -> Dependency
any_c_p String
"dev-libs" String
"libzip")
, (String
"QtCore", String -> String -> Dependency
any_c_p String
"dev-qt" String
"qtcore")
, (String
"QtDeclarative", String -> String -> Dependency
any_c_p String
"dev-qt" String
"qtdeclarative")
, (String
"QtGui", String -> String -> Dependency
any_c_p String
"dev-qt" String
"qtgui")
, (String
"QtOpenGL", String -> String -> Dependency
any_c_p String
"dev-qt" String
"qtopengl")
, (String
"QtScript", String -> String -> Dependency
any_c_p String
"dev-qt" String
"qtscript")
, (String
"gsl", String -> String -> Dependency
any_c_p String
"sci-libs" String
"gsl")
, (String
"gslcblas", String -> String -> Dependency
any_c_p String
"sci-libs" String
"gsl")
, (String
"mkl_core", String -> String -> Dependency
any_c_p String
"sci-libs" String
"mkl")
, (String
"mkl_intel_lp64", String -> String -> Dependency
any_c_p String
"sci-libs" String
"mkl")
, (String
"mkl_lapack", String -> String -> Dependency
any_c_p String
"sci-libs" String
"mkl")
, (String
"mkl_sequential", String -> String -> Dependency
any_c_p String
"sci-libs" String
"mkl")
, (String
"Xi", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXi")
, (String
"Xxf86vm", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXxf86vm")
, (String
"pthread", String -> String -> Dependency
any_c_p String
"virtual" String
"libc")
, (String
"panelw", String -> String -> Dependency
any_c_p String
"sys-libs" String
"ncurses")
, (String
"ncursesw", String -> String -> Dependency
any_c_p String
"sys-libs" String
"ncurses")
, (String
"ftgl", String -> String -> Dependency
any_c_p String
"media-libs" String
"ftgl")
, (String
"glpk", String -> String -> Dependency
any_c_p String
"sci-mathematics" String
"glpk")
, (String
"sndfile", String -> String -> Dependency
any_c_p String
"media-libs" String
"libsndfile")
, (String
"portaudio", String -> String -> Dependency
any_c_p String
"media-libs" String
"portaudio")
, (String
"icudata", String -> String -> Dependency
any_c_p String
"dev-libs" String
"icu")
, (String
"icui18n", String -> String -> Dependency
any_c_p String
"dev-libs" String
"icu")
, (String
"icuuc", String -> String -> Dependency
any_c_p String
"dev-libs" String
"icu")
, (String
"chipmunk", String -> String -> Dependency
any_c_p String
"sci-physics" String
"chipmunk")
, (String
"alut", String -> String -> Dependency
any_c_p String
"media-libs" String
"freealut")
, (String
"openal", String -> String -> Dependency
any_c_p String
"media-libs" String
"openal")
, (String
"iw", String -> String -> Dependency
any_c_p String
"net-wireless" String
"wireless-tools")
, (String
"attr", String -> String -> Dependency
any_c_p String
"sys-apps" String
"attr")
, (String
"ncurses", String -> String -> Dependency
any_c_p String
"sys-libs" String
"ncurses")
, (String
"panel", String -> String -> Dependency
any_c_p String
"sys-libs" String
"ncurses")
, (String
"nanomsg", String -> String -> Dependency
any_c_p String
"dev-libs" String
"nanomsg")
, (String
"pgf", String -> String -> Dependency
any_c_p String
"media-libs" String
"libpgf")
, (String
"ssh2", String -> String -> Dependency
any_c_p String
"net-libs" String
"libssh2")
, (String
"dl", String -> String -> Dependency
any_c_p String
"virtual" String
"libc")
, (String
"glfw", String -> String -> Dependency
any_c_p String
"media-libs" String
"glfw")
, (String
"nettle", String -> String -> Dependency
any_c_p String
"dev-libs" String
"nettle")
, (String
"Xpm", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXpm")
, (String
"Xss", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXScrnSaver")
, (String
"tag_c", String -> String -> Dependency
any_c_p String
"media-libs" String
"taglib")
, (String
"magic", String -> String -> Dependency
any_c_p String
"sys-apps" String
"file")
, (String
"crypt", String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
"virtual" String
"libcrypt" SlotDepend
Portage.AnyBuildTimeSlot [])
, (String
"Xrender", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXrender")
, (String
"Xcursor", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXcursor")
, (String
"Xinerama", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libXinerama")
, (String
"wayland-client", String -> String -> Dependency
any_c_p String
"dev-libs" String
"wayland")
, (String
"wayland-cursor", String -> String -> Dependency
any_c_p String
"dev-libs" String
"wayland")
, (String
"wayland-server", String -> String -> Dependency
any_c_p String
"dev-libs" String
"wayland")
, (String
"wayland-egl", String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
"media-libs" String
"mesa" SlotDepend
Portage.AnySlot [Use -> UseFlag
Portage.mkUse (String -> Use
Portage.Use String
"wayland")])
, (String
"xkbcommon", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libxkbcommon")
, (String
"SDL_gfx", String -> String -> Dependency
any_c_p String
"media-libs" String
"sdl-gfx")
, (String
"SDL_image", String -> String -> Dependency
any_c_p String
"media-libs" String
"sdl-image")
, (String
"SDL_ttf", String -> String -> Dependency
any_c_p String
"media-libs" String
"sdl-ttf")
, (String
"odbc", String -> String -> Dependency
any_c_p String
"dev-db" String
"unixODBC")
, (String
"uuid", String -> String -> Dependency
any_c_p String
"sys-apps" String
"util-linux")
, (String
"notify", String -> String -> Dependency
any_c_p String
"x11-libs" String
"libnotify")
, (String
"SDL2", String -> String -> Dependency
any_c_p String
" media-libs" String
"libsdl2")
, (String
"SDL2_mixer", String -> String -> Dependency
any_c_p String
"media-libs" String
"sdl2-mixer")
, (String
"blas", String -> String -> Dependency
any_c_p String
"virtual" String
"blas")
, (String
"lapack", String -> String -> Dependency
any_c_p String
"virtual" String
"lapack")
]
legacyBuildToolsDependencies :: Cabal.PackageDescription -> [Portage.Dependency]
legacyBuildToolsDependencies :: PackageDescription -> [Dependency]
legacyBuildToolsDependencies (Cabal.PackageDescription { library :: PackageDescription -> Maybe Library
Cabal.library = Maybe Library
lib, executables :: PackageDescription -> [Executable]
Cabal.executables = [Executable]
exes }) = [Dependency] -> [Dependency]
forall a. Eq a => [a] -> [a]
L.nub ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$
[ case Maybe Dependency
pkg of
Just Dependency
p -> Dependency
p
Maybe Dependency
Nothing -> String -> Dependency -> Dependency
forall a. String -> a -> a
trace (String
"WARNING: Unknown build tool '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ LegacyExeDependency -> String
forall a. Pretty a => a -> String
Cabal.prettyShow LegacyExeDependency
exe String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'. Check the generated ebuild.")
(String -> String -> Dependency
any_c_p String
"unknown-build-tool" String
pn)
| exe :: LegacyExeDependency
exe@(Cabal.LegacyExeDependency String
pn VersionRange
_range) <- [LegacyExeDependency]
cabalDeps
, Maybe Dependency
pkg <- Maybe Dependency -> [Maybe Dependency]
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> [(String, Dependency)] -> Maybe Dependency
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
pn [(String, Dependency)]
buildToolsTable)
]
where
cabalDeps :: [LegacyExeDependency]
cabalDeps = (LegacyExeDependency -> Bool)
-> [LegacyExeDependency] -> [LegacyExeDependency]
forall a. (a -> Bool) -> [a] -> [a]
filter LegacyExeDependency -> Bool
notProvided ([LegacyExeDependency] -> [LegacyExeDependency])
-> [LegacyExeDependency] -> [LegacyExeDependency]
forall a b. (a -> b) -> a -> b
$ [LegacyExeDependency]
depL [LegacyExeDependency]
-> [LegacyExeDependency] -> [LegacyExeDependency]
forall a. [a] -> [a] -> [a]
++ [LegacyExeDependency]
depE
depL :: [LegacyExeDependency]
depL = (Library -> [LegacyExeDependency])
-> [Library] -> [LegacyExeDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [LegacyExeDependency]
Cabal.buildTools (BuildInfo -> [LegacyExeDependency])
-> (Library -> BuildInfo) -> Library -> [LegacyExeDependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
Cabal.libBuildInfo) ([Library] -> [LegacyExeDependency])
-> [Library] -> [LegacyExeDependency]
forall a b. (a -> b) -> a -> b
$ [Library] -> (Library -> [Library]) -> Maybe Library -> [Library]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Library -> [Library]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Library
lib
depE :: [LegacyExeDependency]
depE = (BuildInfo -> [LegacyExeDependency])
-> [BuildInfo] -> [LegacyExeDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap BuildInfo -> [LegacyExeDependency]
Cabal.buildTools ((BuildInfo -> Bool) -> [BuildInfo] -> [BuildInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter BuildInfo -> Bool
Cabal.buildable ((Executable -> BuildInfo) -> [Executable] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> BuildInfo
Cabal.buildInfo [Executable]
exes))
notProvided :: LegacyExeDependency -> Bool
notProvided (Cabal.LegacyExeDependency String
pn VersionRange
_range) = String
pn String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String]
buildToolsProvided
buildToolsTable :: [(String, Portage.Dependency)]
buildToolsTable :: [(String, Dependency)]
buildToolsTable =
[ (String
"happy", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"happy")
, (String
"alex", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"alex")
, (String
"c2hs", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"c2hs")
, (String
"cabal", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"cabal-install")
, (String
"cabal-install", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"cabal-install")
, (String
"cpphs", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"cpphs")
, (String
"ghc", String -> String -> Dependency
any_c_p String
"dev-lang" String
"ghc")
, (String
"gtk2hsTypeGen", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"gtk2hs-buildtools")
, (String
"gtk2hsHookGenerator", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"gtk2hs-buildtools")
, (String
"gtk2hsC2hs", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"gtk2hs-buildtools")
, (String
"hsb2hs", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"hsb2hs")
, (String
"hsx2hs", String -> String -> Dependency
any_c_p String
"dev-haskell" String
"hsx2hs")
, (String
"llvm-config", String -> String -> Dependency
any_c_p String
"sys-devel" String
"llvm")
]
buildToolsProvided :: [String]
buildToolsProvided :: [String]
buildToolsProvided = [String
"hsc2hs"]
hackageBuildToolsDependencies :: Portage.Overlay -> Cabal.PackageDescription -> [Portage.Dependency]
hackageBuildToolsDependencies :: Overlay -> PackageDescription -> [Dependency]
hackageBuildToolsDependencies Overlay
overlay (Cabal.PackageDescription { library :: PackageDescription -> Maybe Library
Cabal.library = Maybe Library
lib, executables :: PackageDescription -> [Executable]
Cabal.executables = [Executable]
exes }) =
Overlay -> [Dependency] -> [Dependency]
haskellDependencies Overlay
overlay ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$ [Dependency] -> [Dependency]
forall a. Eq a => [a] -> [a]
L.nub ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$
[ PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Cabal.Dependency PackageName
pn VersionRange
versionRange (NonEmptySet LibraryName -> Dependency)
-> NonEmptySet LibraryName -> Dependency
forall a b. (a -> b) -> a -> b
$ LibraryName -> NonEmptySet LibraryName
forall a. a -> NonEmptySet a
NES.singleton LibraryName
Cabal.defaultLibName
| Cabal.ExeDependency PackageName
pn UnqualComponentName
_component VersionRange
versionRange <- [ExeDependency]
cabalDeps
]
where
cabalDeps :: [ExeDependency]
cabalDeps = [ExeDependency]
depL [ExeDependency] -> [ExeDependency] -> [ExeDependency]
forall a. [a] -> [a] -> [a]
++ [ExeDependency]
depE
depL :: [ExeDependency]
depL = (Library -> [ExeDependency]) -> [Library] -> [ExeDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [ExeDependency]
Cabal.buildToolDepends (BuildInfo -> [ExeDependency])
-> (Library -> BuildInfo) -> Library -> [ExeDependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
Cabal.libBuildInfo) ([Library] -> [ExeDependency]) -> [Library] -> [ExeDependency]
forall a b. (a -> b) -> a -> b
$ [Library] -> (Library -> [Library]) -> Maybe Library -> [Library]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Library -> [Library]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Library
lib
depE :: [ExeDependency]
depE = (BuildInfo -> [ExeDependency]) -> [BuildInfo] -> [ExeDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap BuildInfo -> [ExeDependency]
Cabal.buildToolDepends ((BuildInfo -> Bool) -> [BuildInfo] -> [BuildInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter BuildInfo -> Bool
Cabal.buildable ((Executable -> BuildInfo) -> [Executable] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> BuildInfo
Cabal.buildInfo [Executable]
exes))
pkgConfigDependencies :: Portage.Overlay -> Cabal.PackageDescription -> [Portage.Dependency]
pkgConfigDependencies :: Overlay -> PackageDescription -> [Dependency]
pkgConfigDependencies Overlay
overlay (Cabal.PackageDescription { library :: PackageDescription -> Maybe Library
Cabal.library = Maybe Library
lib, executables :: PackageDescription -> [Executable]
Cabal.executables = [Executable]
exes }) = [Dependency] -> [Dependency]
forall a. Eq a => [a] -> [a]
L.nub ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$ Overlay -> [PkgconfigDependency] -> [Dependency]
resolvePkgConfigs Overlay
overlay [PkgconfigDependency]
cabalDeps
where
cabalDeps :: [PkgconfigDependency]
cabalDeps = [PkgconfigDependency]
depL [PkgconfigDependency]
-> [PkgconfigDependency] -> [PkgconfigDependency]
forall a. [a] -> [a] -> [a]
++ [PkgconfigDependency]
depE
depL :: [PkgconfigDependency]
depL = (Library -> [PkgconfigDependency])
-> [Library] -> [PkgconfigDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> [PkgconfigDependency]
Cabal.pkgconfigDepends (BuildInfo -> [PkgconfigDependency])
-> (Library -> BuildInfo) -> Library -> [PkgconfigDependency]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
Cabal.libBuildInfo) ([Library] -> [PkgconfigDependency])
-> [Library] -> [PkgconfigDependency]
forall a b. (a -> b) -> a -> b
$ [Library] -> (Library -> [Library]) -> Maybe Library -> [Library]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Library -> [Library]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Library
lib
depE :: [PkgconfigDependency]
depE = (BuildInfo -> [PkgconfigDependency])
-> [BuildInfo] -> [PkgconfigDependency]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap BuildInfo -> [PkgconfigDependency]
Cabal.pkgconfigDepends ((BuildInfo -> Bool) -> [BuildInfo] -> [BuildInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter BuildInfo -> Bool
Cabal.buildable ((Executable -> BuildInfo) -> [Executable] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> BuildInfo
Cabal.buildInfo [Executable]
exes))
resolvePkgConfigs :: Portage.Overlay -> [Cabal.PkgconfigDependency] -> [Portage.Dependency]
resolvePkgConfigs :: Overlay -> [PkgconfigDependency] -> [Dependency]
resolvePkgConfigs Overlay
overlay [PkgconfigDependency]
cdeps =
[ case Overlay -> PkgconfigDependency -> Maybe Dependency
resolvePkgConfig Overlay
overlay PkgconfigDependency
pkg of
Just Dependency
d -> Dependency
d
Maybe Dependency
Nothing -> String -> Dependency -> Dependency
forall a. String -> a -> a
trace (String
"WARNING: Could not resolve pkg-config: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PkgconfigDependency -> String
forall a. Pretty a => a -> String
Cabal.prettyShow PkgconfigDependency
pkg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
". Check generated ebuild.")
(String -> String -> Dependency
any_c_p String
"unknown-pkg-config" String
pn)
| pkg :: PkgconfigDependency
pkg@(Cabal.PkgconfigDependency PkgconfigName
cabal_pn PkgconfigVersionRange
_range) <- [PkgconfigDependency]
cdeps
, let pn :: String
pn = PkgconfigName -> String
Cabal.unPkgconfigName PkgconfigName
cabal_pn
]
resolvePkgConfig :: Portage.Overlay -> Cabal.PkgconfigDependency -> Maybe Portage.Dependency
resolvePkgConfig :: Overlay -> PkgconfigDependency -> Maybe Dependency
resolvePkgConfig Overlay
_overlay (Cabal.PkgconfigDependency PkgconfigName
cabal_pn PkgconfigVersionRange
_cabalVersion) = do
(String
cat,String
portname, SlotDepend
slot) <- String
-> [(String, (String, String, SlotDepend))]
-> Maybe (String, String, SlotDepend)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (PkgconfigName -> String
Cabal.unPkgconfigName PkgconfigName
cabal_pn) [(String, (String, String, SlotDepend))]
pkgconfig_table
Dependency -> Maybe Dependency
forall (m :: * -> *) a. Monad m => a -> m a
return (Dependency -> Maybe Dependency) -> Dependency -> Maybe Dependency
forall a b. (a -> b) -> a -> b
$ String -> String -> SlotDepend -> [UseFlag] -> Dependency
any_c_p_s_u String
cat String
portname SlotDepend
slot []
pkgconfig_table :: [(String, (String, String, Portage.SlotDepend))]
pkgconfig_table :: [(String, (String, String, SlotDepend))]
pkgconfig_table =
[
(String
"alsa", (String
"media-libs", String
"alsa-lib", SlotDepend
Portage.AnySlot))
,(String
"atk", (String
"dev-libs", String
"atk", SlotDepend
Portage.AnySlot))
,(String
"gconf-2.0", (String
"gnome-base", String
"gconf", SlotDepend
Portage.AnySlot))
,(String
"gio-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gio-unix-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"glib-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gmodule-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gmodule-export-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gmodule-no-export-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gobject-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gobject-introspection-1.0", (String
"dev-libs", String
"gobject-introspection",
SlotDepend
Portage.AnySlot))
,(String
"gthread-2.0", (String
"dev-libs", String
"glib", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gtk+-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gdk-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gdk-3.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"3"))
,(String
"gdk-pixbuf-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gdk-pixbuf-xlib-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gdk-x11-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gtk+-unix-print-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gtk+-x11-2.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gtk+-3.0", (String
"x11-libs", String
"gtk+", String -> SlotDepend
Portage.GivenSlot String
"3"))
,(String
"webkitgtk-3.0", (String
"net-libs", String
"webkit-gtk", String -> SlotDepend
Portage.GivenSlot String
"3"))
,(String
"cairo", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-gobject", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-ft", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-ps", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-png", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-pdf", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-svg", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-xlib", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"cairo-xlib-xrender", (String
"x11-libs", String
"cairo", SlotDepend
Portage.AnySlot))
,(String
"javascriptcoregtk-4.0", (String
"net-libs", String
"webkit-gtk", String -> SlotDepend
Portage.GivenSlot String
"4"))
,(String
"webkit2gtk-4.0", (String
"net-libs", String
"webkit-gtk", String -> SlotDepend
Portage.GivenSlot String
"4"))
,(String
"pangocairo", (String
"x11-libs", String
"pango", SlotDepend
Portage.AnySlot))
,(String
"pangoft2", (String
"x11-libs", String
"pango", SlotDepend
Portage.AnySlot))
,(String
"pango", (String
"x11-libs", String
"pango", SlotDepend
Portage.AnySlot))
,(String
"pangoxft", (String
"x11-libs", String
"pango", SlotDepend
Portage.AnySlot))
,(String
"pangox", (String
"x11-libs", String
"pango", SlotDepend
Portage.AnySlot))
,(String
"libglade-2.0", (String
"gnome-base", String
"libglade", SlotDepend
Portage.AnySlot))
,(String
"libsoup-2.4", (String
"net-libs", String
"libsoup", String -> SlotDepend
Portage.GivenSlot String
"2.4"))
,(String
"gnome-vfs-2.0", (String
"gnome-base", String
"gnome-vfs", SlotDepend
Portage.AnySlot))
,(String
"gnome-vfs-module-2.0", (String
"gnome-base", String
"gnome-vfs", SlotDepend
Portage.AnySlot))
,(String
"webkit-1.0", (String
"net-libs",String
"webkit-gtk", String -> SlotDepend
Portage.GivenSlot String
"2"))
,(String
"gtksourceview-3.0", (String
"x11-libs", String
"gtksourceview", String -> SlotDepend
Portage.GivenSlot String
"3.0"))
,(String
"gstreamer-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-base-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-check-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-controller-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-dataprotocol-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-net-0.10", (String
"media-libs", String
"gstreamer", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-app-0.10", (String
"media-libs", String
"gst-plugins-base", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-audio-0.10", (String
"media-libs", String
"gst-plugins-base", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-video-0.10", (String
"media-libs", String
"gst-plugins-base", SlotDepend
Portage.AnySlot))
,(String
"gstreamer-plugins-base-0.10", (String
"media-libs", String
"gst-plugins-base", SlotDepend
Portage.AnySlot))
,(String
"gtksourceview-2.0", (String
"x11-libs", String
"gtksourceview", String -> SlotDepend
Portage.GivenSlot String
"2.0"))
,(String
"librsvg-2.0", (String
"gnome-base",String
"librsvg", SlotDepend
Portage.AnySlot))
,(String
"vte", (String
"x11-libs",String
"vte", String -> SlotDepend
Portage.GivenSlot String
"0"))
,(String
"gtkglext-1.0", (String
"x11-libs",String
"gtkglext", SlotDepend
Portage.AnySlot))
,(String
"curl", (String
"net-misc", String
"curl", SlotDepend
Portage.AnySlot))
,(String
"libxml2", (String
"dev-libs", String
"libxml2", SlotDepend
Portage.AnySlot))
,(String
"libgsasl", (String
"virtual", String
"gsasl", SlotDepend
Portage.AnySlot))
,(String
"libzip", (String
"dev-libs", String
"libzip", SlotDepend
Portage.AnySlot))
,(String
"gnutls", (String
"net-libs", String
"gnutls", SlotDepend
Portage.AnySlot))
,(String
"libidn", (String
"net-dns", String
"libidn", SlotDepend
Portage.AnySlot))
,(String
"libxml-2.0", (String
"dev-libs", String
"libxml2", SlotDepend
Portage.AnySlot))
,(String
"yaml-0.1", (String
"dev-libs", String
"libyaml", SlotDepend
Portage.AnySlot))
,(String
"QtCore", (String
"dev-qt", String
"qtcore", SlotDepend
Portage.AnySlot))
,(String
"lua", (String
"dev-lang", String
"lua", SlotDepend
Portage.AnySlot))
,(String
"QtDeclarative", (String
"dev-qt", String
"qtdeclarative", SlotDepend
Portage.AnySlot))
,(String
"QtGui", (String
"dev-qt", String
"qtgui", SlotDepend
Portage.AnySlot))
,(String
"QtOpenGL", (String
"dev-qt", String
"qtopengl", SlotDepend
Portage.AnySlot))
,(String
"QtScript", (String
"dev-qt", String
"qtscript", SlotDepend
Portage.AnySlot))
,(String
"ImageMagick", (String
"media-gfx", String
"imagemagick", SlotDepend
Portage.AnySlot))
,(String
"MagickWand", (String
"media-gfx", String
"imagemagick", SlotDepend
Portage.AnySlot))
,(String
"ncurses", (String
"sys-libs", String
"ncurses", SlotDepend
Portage.AnySlot))
,(String
"ncursesw", (String
"sys-libs", String
"ncurses", SlotDepend
Portage.AnySlot))
,(String
"panel", (String
"sys-libs", String
"ncurses", SlotDepend
Portage.AnySlot))
,(String
"panelw", (String
"sys-libs", String
"ncurses", SlotDepend
Portage.AnySlot))
,(String
"libssh2", (String
"net-libs", String
"libssh2", SlotDepend
Portage.AnySlot))
,(String
"SDL_image", (String
"media-libs", String
"sdl-image", SlotDepend
Portage.AnySlot))
,(String
"libzmq", (String
"net-libs", String
"zeromq", SlotDepend
Portage.AnySlot))
,(String
"taglib_c", (String
"media-libs", String
"taglib", SlotDepend
Portage.AnySlot))
,(String
"libcurl", (String
"net-misc", String
"curl", SlotDepend
Portage.AnySlot))
,(String
"libpq", (String
"dev-db", String
"postgresql", SlotDepend
Portage.AnySlot))
,(String
"poppler-glib", (String
"app-text", String
"poppler", SlotDepend
Portage.AnySlot))
,(String
"gsl", (String
"sci-libs", String
"gsl", SlotDepend
Portage.AnySlot))
,(String
"libvirt", (String
"app-emulation", String
"libvirt", SlotDepend
Portage.AnySlot))
,(String
"Qt5Core", (String
"dev-qt", String
"qtcore", String -> SlotDepend
Portage.GivenSlot String
"5"))
,(String
"Qt5Gui", (String
"dev-qt", String
"qtgui", String -> SlotDepend
Portage.GivenSlot String
"5"))
,(String
"Qt5Qml", (String
"dev-qt", String
"qtdeclarative", String -> SlotDepend
Portage.GivenSlot String
"5"))
,(String
"Qt5Quick", (String
"dev-qt", String
"qtdeclarative", String -> SlotDepend
Portage.GivenSlot String
"5"))
,(String
"Qt5Widgets", (String
"dev-qt", String
"qtwidgets", String -> SlotDepend
Portage.GivenSlot String
"5"))
,(String
"sdl2", (String
"media-libs", String
"libsdl2", SlotDepend
Portage.AnySlot))
,(String
"SDL2_image", (String
"media-libs", String
"sdl2-image", SlotDepend
Portage.AnySlot))
,(String
"SDL2_mixer", (String
"media-libs", String
"sdl2-mixer", SlotDepend
Portage.AnySlot))
,(String
"zlib", (String
"sys-libs", String
"zlib", SlotDepend
Portage.AnySlot))
]