{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses, PackageImports, ScopedTypeVariables, StandaloneDeriving, TupleSections, TypeSynonymInstances #-} {-# OPTIONS -Wall -fno-warn-orphans #-} -- | -- Module : Distribution.Package.Debian -- Copyright : David Fox 2008 -- -- Maintainer : David Fox -- Stability : alpha -- Portability : portable -- -- Explanation: Support for generating Debianization from Cabal data. -- This software may be used and distributed according to the terms of -- the GNU General Public License, incorporated herein by reference. module Distribution.Package.Debian.Relations ( allBuildDepends , buildDependencies , docDependencies , cabalDependencies , versionSplits ) where import Data.Char (isSpace) import Data.List import qualified Data.Map as Map import Data.Maybe import Data.Version (Version(Version)) import qualified Debian.Relation as D import Distribution.Simple.Compiler (Compiler(..)) import Distribution.Package (PackageName(..), Dependency(..)) import Distribution.PackageDescription (PackageDescription(..), allBuildInfo, buildTools, pkgconfigDepends, extraLibs) import Distribution.Version (anyVersion) import Distribution.Package.Debian.Setup (Flags(..)) import Distribution.Package.Debian.Dependencies (PackageType(..), VersionSplits(..), dependencies, mkPkgName) import System.Exit (ExitCode(ExitSuccess)) import System.IO.Unsafe (unsafePerformIO) import System.Process (readProcessWithExitCode) cabalDependencies :: Flags -> PackageDescription -> [Dependency] cabalDependencies flags pkgDesc = catMaybes $ map unboxDependency $ allBuildDepends flags pkgDesc -- |Debian packages don't have per binary package build dependencies, -- so we just gather them all up here. allBuildDepends :: Flags -> PackageDescription -> [Dependency_] allBuildDepends flags pkgDesc = nub $ map BuildDepends (buildDepends pkgDesc) ++ concat (map (map BuildTools . buildTools) (allBuildInfo pkgDesc) ++ map (map PkgConfigDepends . pkgconfigDepends) (allBuildInfo pkgDesc) ++ map (map ExtraLibs . (fixDeps . extraLibs)) (allBuildInfo pkgDesc)) where fixDeps :: [String] -> [D.BinPkgName] fixDeps xs = concatMap (\ cab -> fromMaybe [D.BinPkgName (D.PkgName ("lib" ++ cab ++ "-dev"))] (Map.lookup cab (depMap flags))) xs -- The build dependencies for a package include the profiling -- libraries and the documentation packages, used for creating cross -- references. buildDependencies :: Flags -> Compiler -> Dependency_ -> D.Relations buildDependencies flags compiler (BuildDepends (Dependency name ranges)) = dependencies flags compiler versionSplits Development (Right name) ranges ++ dependencies flags compiler versionSplits Profiling (Right name) ranges buildDependencies flags compiler dep@(ExtraLibs _) = concat (map (\ x -> dependencies flags compiler versionSplits Extra (Left x) anyVersion) $ adapt flags dep) buildDependencies flags compiler dep = case unboxDependency dep of Just (Dependency _name ranges) -> concat (map (\ x -> dependencies flags compiler versionSplits Extra (Left x) ranges) $ adapt flags dep) Nothing -> [] adapt :: Flags -> Dependency_ -> [D.BinPkgName] adapt flags (PkgConfigDepends (Dependency (PackageName pkg) _)) = maybe (aptFile pkg) (: []) (Map.lookup pkg (execMap flags)) adapt flags (BuildTools (Dependency (PackageName pkg) _)) = maybe (aptFile pkg) (: []) (Map.lookup pkg (execMap flags)) adapt _flags (ExtraLibs x) = [x] {- maybe (error ("No mapping from library " ++ x ++ " to debian binary package name")) (map (\ s -> PackageName ("lib" ++ s ++ "-dev"))) (Map.lookup x (depMap flags)) -} adapt _flags (BuildDepends (Dependency (PackageName pkg) _)) = [D.BinPkgName (D.PkgName pkg)] -- |There are two reasons this may not work, or may work -- incorrectly: (1) the build environment may be a different -- distribution than the parent environment (the environment the -- autobuilder was run from), so the packages in that -- environment might have different names, and (2) the package -- we are looking for may not be installed in the parent -- environment. aptFile :: String -> [D.BinPkgName] -- Maybe would probably be more correct aptFile pkg = unsafePerformIO $ do ret <- readProcessWithExitCode "apt-file" ["-l", "search", pkg ++ ".pc"] "" return $ case ret of (ExitSuccess, out, _) -> [D.BinPkgName (D.PkgName (takeWhile (not . isSpace) out))] _ -> [] -- The documentation dependencies for a package include the documentation -- package for any libraries which are build dependencies, so we have access -- to all the cross references. docDependencies :: Flags -> Compiler -> Dependency_ -> D.Relations docDependencies flags compiler (BuildDepends (Dependency name ranges)) = dependencies flags compiler versionSplits Documentation (Right name) ranges docDependencies _ _ _ = [] data Dependency_ = BuildDepends Dependency | BuildTools Dependency | PkgConfigDepends Dependency | ExtraLibs D.BinPkgName deriving (Eq, Show) unboxDependency :: Dependency_ -> Maybe Dependency unboxDependency (BuildDepends d) = Just d unboxDependency (BuildTools d) = Just d unboxDependency (PkgConfigDepends d) = Just d unboxDependency (ExtraLibs _) = Nothing -- Dependency (PackageName d) anyVersion -- | These are the instances of debian names changing that we know about. versionSplits :: PackageType -> [VersionSplits] versionSplits typ = [ VersionSplits { packageName = PackageName "parsec" , oldestPackage = mkPkgName "parsec2" typ , splits = [(Version [3] [], mkPkgName "parsec3" typ)] } , VersionSplits { packageName = PackageName "QuickCheck" , oldestPackage = mkPkgName "quickcheck1" typ , splits = [(Version [2] [], mkPkgName "quickcheck2" typ)] } ]