Skip to content

Commit

Permalink
first stab at DEPEND / RDEPEND tracking
Browse files Browse the repository at this point in the history
Introduces variables HASKELLDEPS, BUILDTOOLS and EXTRALIBS in the ebuild.
I think the best would be to just merge them all together into DEPEND and
REDPEND.
  • Loading branch information
kolmodin committed Dec 22, 2009
1 parent fe19025 commit bd75ad0
Show file tree
Hide file tree
Showing 2 changed files with 74 additions and 29 deletions.
44 changes: 34 additions & 10 deletions Cabal2Ebuild.hs
Expand Up @@ -39,6 +39,7 @@ import qualified Distribution.Text as Cabal (display)
--import qualified Distribution.Compiler as Cabal (CompilerFlavor(..))

import Data.Char (toLower,isUpper)
import Data.Maybe ( isJust )

import Portage.Dependency
import Portage.Version
Expand All @@ -53,8 +54,13 @@ data EBuild = EBuild {
slot :: String,
keywords :: [String],
iuse :: [String],
depend :: [Dependency],
rdepend :: [Dependency],
haskell_deps :: [Dependency],
build_tools :: [Dependency],
extra_libs :: [Dependency],
cabal_dep :: Dependency,
ghc_dep :: Dependency,
depend :: [String],
rdepend :: [String],
features :: [String],
-- comments on various fields for communicating stuff to the user
licenseComments :: String,
Expand All @@ -72,6 +78,11 @@ ebuildTemplate = EBuild {
slot = "0",
keywords = ["~amd64","~x86"],
iuse = [],
haskell_deps = [],
build_tools = [],
extra_libs = [],
cabal_dep = AnyVersionOf "dev-haskell/cabal",
ghc_dep = defaultDepGHC,
depend = [],
rdepend = [],
features = [],
Expand All @@ -89,22 +100,22 @@ cabal2ebuild pkg = ebuildTemplate {
src_uri = Cabal.pkgUrl pkg,
license = convertLicense (Cabal.license pkg),
licenseComments = licenseComment (Cabal.license pkg),
depend = defaultDepGHC
: (simplify_deps $
convertDependency (Cabal.Dependency (Cabal.PackageName "Cabal")
(Cabal.descCabalVersion pkg))
++ convertDependencies (Cabal.buildDepends pkg)),
haskell_deps = simplify_deps $ convertDependencies (Cabal.buildDepends pkg),
cabal_dep = head $ convertDependency (Cabal.Dependency (Cabal.PackageName "Cabal")
(Cabal.descCabalVersion pkg)),
my_pn = if any isUpper cabalPkgName then Just cabalPkgName else Nothing,
features = features ebuildTemplate
++ (if null (Cabal.executables pkg) then [] else ["bin"])
++ (if hasExe then ["bin"] else [])
++ maybe [] (const (["lib","profile","haddock"]
++ if cabalPkgName == "hscolour" then [] else ["hscolour"])
) (Cabal.library pkg) -- hscolour can't colour its own sources
} where
cabalPkgName = Cabal.display $ Cabal.pkgName (Cabal.package pkg)
hasLib = isJust (Cabal.library pkg)
hasExe = (not . null) (Cabal.executables pkg)

defaultDepGHC :: Dependency
defaultDepGHC = OrLaterVersionOf (Version [6,6,1] Nothing [] 0) "dev-lang/ghc"
defaultDepGHC = OrLaterVersionOf (Version [6,6,1] Nothing [] 0) "dev-lang/ghc"

-- map the cabal license type to the gentoo license string format
convertLicense :: Cabal.License -> String
Expand Down Expand Up @@ -208,7 +219,20 @@ showEBuild ebuild =
ss "KEYWORDS=". quote' (sepBy " " $ keywords ebuild).nl.
ss "IUSE=". quote' (sepBy ", " $ iuse ebuild). nl.
nl.
ss "DEPEND=". quote' (sepBy "\n\t\t" $ map showDepend $ depend ebuild). nl.
( if (not . null . build_tools $ ebuild)
then ss "BUILDTOOLS=". quote' (sepBy "\n\t\t" $ map showDepend $ build_tools ebuild). nl
else id
).
( if (not . null . extra_libs $ ebuild )
then ss "EXTRALIBS=". quote' (sepBy "\n\t\t" $ map showDepend $ extra_libs ebuild). nl
else id
).
( if (not . null . haskell_deps $ ebuild)
then ss "HASKELLDEPS=". quote' (sepBy "\n\t\t" $ map showDepend $ haskell_deps ebuild). nl
else id
).
ss "RDEPEND=". quote' (sepBy "\n\t\t" $ rdepend ebuild). nl.
ss "DEPEND=". quote' (sepBy "\n\t\t" $ depend ebuild). nl.
(case my_pn ebuild of
Nothing -> id
Just _ -> nl. ss "S=". quote ("${WORKDIR}/${MY_P}"). nl)
Expand Down
59 changes: 40 additions & 19 deletions Merge.hs
Expand Up @@ -37,7 +37,8 @@ RDEPEND="${EXTRALIBS}"
DEPEND="${RDEPEND} ghc cabal ${DEPS} ${BUILDTOOLS}"
-}
module Merge where
module Merge
( merge ) where

import Control.Monad.Error
import Control.Exception
Expand All @@ -49,8 +50,10 @@ import Distribution.PackageDescription ( PackageDescription(..)
, FlagName(..)
, libBuildInfo
, buildInfo
, buildable
, extraLibs
, buildTools )
, buildTools
, hasLibs )
import Distribution.PackageDescription.Configuration
( finalizePackageDescription )
import Distribution.Text (display)
Expand All @@ -63,6 +66,7 @@ import System.Cmd (system)
import System.FilePath ((</>))

import qualified Cabal2Ebuild as E
import Cabal2Ebuild
import Error as E

import qualified Distribution.Package as Cabal
Expand All @@ -74,19 +78,20 @@ import Distribution.Simple.Utils

import Network.URI

import Cabal2Ebuild

import Distribution.Client.IndexUtils ( getAvailablePackages )
import Distribution.Client.Fetch ( downloadURI )
import qualified Distribution.Client.PackageIndex as Index
import Distribution.Client.Types

import qualified Portage.PackageId as Portage
import qualified Portage.Version as Portage
import qualified Portage.Dependency as Portage
import qualified Portage.Host as Host
import qualified Portage.Overlay as Overlay
import qualified Portage.Resolve as Portage

import Debug.Trace ( trace )

(<->) :: String -> String -> String
a <-> b = a ++ '-':b

Expand Down Expand Up @@ -189,7 +194,7 @@ merge verbosity repo serverURI args overlayPath = do
-- (FlagName "small_base", True) -- try to use small base
(FlagName "cocoa", False)
]
(\_dependency -> True)
(\dependency -> trace ("accepting dep(?): " ++ display dependency) True)
-- (Nothing :: Maybe (Index.PackageIndex PackageIdentifier))
buildPlatform
(CompilerId GHC (Cabal.Version [6,10,4] []))
Expand All @@ -199,7 +204,13 @@ merge verbosity repo serverURI args overlayPath = do
]
in pkgDesc0 { buildDepends = deps }

bt = [ Cabal.Dependency (Cabal.PackageName pkg') range
hasBuildableExes p =
any (buildable . buildInfo)
. executables $ p
treatAsLibrary = (not . hasBuildableExes) pkgDesc && hasLibs pkgDesc

-- calculate build tools
bt = [ pkg' -- TODO: currently ignoring version range
| Cabal.Dependency (Cabal.PackageName pkg ) range <- buildToolsDeps pkgDesc
, Just pkg' <- return (lookup pkg buildToolsTable)
]
Expand All @@ -223,25 +234,35 @@ merge verbosity repo serverURI args overlayPath = do

-- TODO: more fixes
-- * inherit keywords from previous ebuilds
let d e = if treatAsLibrary
then Portage.showDepend (cabal_dep e)
: "${RDEPEND}"
: [ "${BUILDTOOLS}" | not . null $ build_tools e ]
else Portage.showDepend (cabal_dep e)
: Portage.showDepend (ghc_dep e)
: "${RDEPEND}"
: [ "${BUILDTOOLS}" | not . null $ build_tools e ]
++ [ "${HASKELLDEPS}" | not . null $ haskell_deps e ]
rd e = if treatAsLibrary
then Portage.showDepend (ghc_dep e)
: [ "${HASKELLDEPS}" | not . null $ haskell_deps e ]
++ [ "${EXTRALIBS}" | not . null $ extra_libs e ]
else [ "${EXTRALIBS}" | not . null $ extra_libs e ]
let ebuild = fixSrc serverURI (packageId pkgDesc)
. addDeps extra
. addDeps (convertDependencies bt)
. (\e -> e { depend = d e } )
. (\e -> e { rdepend = rd e } )
. (\e -> e { extra_libs = extra_libs e ++ extra } )
. (\e -> e { build_tools = build_tools e ++ bt } )
$ E.cabal2ebuild pkgDesc
-- ebuildName = display category </> display norm_pkgId

debug verbosity ("Treat as library: " ++ show treatAsLibrary)
mergeEbuild verbosity overlayPath (Portage.unCategory cat) ebuild
fetchAndDigest
verbosity
(overlayPath </> display cat </> display norm_pkgName)
(display cabal_pkgId <.> "tar.gz")
(mkUri cabal_pkgId)

addDeps :: [E.Dependency] -> EBuild -> EBuild
addDeps d e = e { depend = depend e ++ d }

addRDeps :: [E.Dependency] -> EBuild -> EBuild
addRDeps d e = e { rdepend = rdepend e ++ d }

findCLibs :: Verbosity -> (String -> Maybe E.Dependency) -> PackageDescription -> IO [E.Dependency]
findCLibs verbosity portageResolver (PackageDescription { library = lib, executables = exes }) = do
debug verbosity "Mapping extra-libraries into portage packages..."
Expand Down Expand Up @@ -285,11 +306,11 @@ buildToolsDeps (PackageDescription { library = lib, executables = exes }) = caba
depL = maybe [] (buildTools.libBuildInfo) lib
depE = concatMap (buildTools.buildInfo) exes

buildToolsTable :: [(String, String)]
buildToolsTable :: [(String, E.Dependency)]
buildToolsTable =
[ ("happy", "happy") -- TODO: we would like to specify both cat and pkg name
, ("alex", "alex")
, ("c2hs", "c2hs")
[ ("happy", E.AnyVersionOf "dev-haskell/happy")
, ("alex", E.AnyVersionOf "dev-haskell/alex")
, ("c2hs", E.AnyVersionOf "dev-haskell/c2hs")
]

mkUri :: Cabal.PackageIdentifier -> URI
Expand Down

0 comments on commit bd75ad0

Please sign in to comment.