module Distribution.RpmDeps where -- -> Version import Distribution.Version -- -> intersperse import Data.List -- -> readPackageDescription import Distribution.PackageDescription -- -> PackageIdentifier import Distribution.Simple -- -> maybeGetPersistBuildConfig import Distribution.Simple.Configure -- -> packageDeps import Distribution.Simple.LocalBuildInfo -- -> GetDirectoryContents import Directory dep_prefix = "haskell" rpmrequires :: IO [String] rpmrequires = do buildinfo <- maybeGetPersistBuildConfig return $ case buildinfo of Nothing -> [] Just bi -> map package2rpmdep (packageDeps bi) rpmprovides :: Maybe String -> IO [String] rpmprovides cabalfile = do mycabal <- readPackageDescription =<< findcabal cabalfile return $ [package2rpmdep (package mycabal)] rpmbuildrequires :: Maybe String -> IO [String] rpmbuildrequires cabalfile = do mycabal <- readPackageDescription =<< findcabal cabalfile return $ map dependency2rpmdep (buildDepends mycabal) findcabal file = do cfiles <- cabalfiles `fmap` getDirectoryContents "." case (file, cfiles) of (Just a, _) -> return a (Nothing, c:_) -> return c _ -> error $ "Please specify one of " ++ show cfiles where cabalfiles = filter (isSuffixOf ".cabal") package2rpmdep :: PackageIdentifier -> String package2rpmdep pkg = dep_prefix ++ "(" ++ pkgName pkg ++ ") = " ++ (version2string $ pkgVersion pkg) dependency2rpmdep :: Dependency -> String dependency2rpmdep (Dependency name vers) = dep_prefix ++ "(" ++ name ++ ")" ++ vers2st where vers2st = case vers of AnyVersion -> "" ThisVersion v -> " " ++ (versionrange2sign vers) ++ " " ++ (version2string v) LaterVersion v -> " " ++ (versionrange2sign vers) ++ " " ++ (version2string v) EarlierVersion v -> " " ++ (versionrange2sign vers) ++ " " ++ (version2string v) UnionVersionRanges v v' -> " " ++ (versionrange2sign vers) ++ " " ++ (version2string $ case v of ThisVersion y@_ -> y LaterVersion y@_ -> y EarlierVersion y@_ -> y _ -> Version [] [] ) IntersectVersionRanges v v' -> " IV " versionrange2sign :: VersionRange -> String versionrange2sign vr = case vr of AnyVersion -> "" ThisVersion v -> "=" LaterVersion v -> ">" EarlierVersion v -> "<" UnionVersionRanges v v' -> case v of ThisVersion _ -> versionrange2sign v' ++ versionrange2sign v _ -> versionrange2sign v ++ versionrange2sign v' IntersectVersionRanges v v' -> "IV" version2string :: Version -> String version2string version = concat . intersperse "." $ map show $ versionBranch version