Skip to content
Snippets Groups Projects
Commit a0afb987 authored by Andrey Mokhov's avatar Andrey Mokhov
Browse files

Minor revision

parent 0d8713a4
No related branches found
No related tags found
No related merge requests found
......@@ -16,7 +16,7 @@ module Expression (
-- * Convenient accessors
getContext, getStage, getPackage, getBuilder, getOutputs, getInputs, getWay,
getInput, getOutput,
getInput, getOutput, getSingleton,
-- * Re-exports
module Control.Monad.Trans.Reader,
......@@ -206,7 +206,7 @@ getOutput = do
getSingleton getOutputs $
"getOutput: exactly one output file expected in target " ++ show target
getSingleton :: Expr [a] -> String -> Expr a
getSingleton :: Monad m => m [a] -> String -> m a
getSingleton expr msg = expr >>= \case
[res] -> return res
_ -> error msg
module Rules.Gmp (gmpRules, gmpContext) where
module Rules.Gmp (gmpRules) where
import Base
import Builder
......@@ -81,12 +81,9 @@ gmpRules = do
-- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents.
-- That's because the doc/ directory contents are under the GFDL,
-- which causes problems for Debian.
tarballs <- getDirectoryFiles "" [gmpBase -/- "tarball/gmp*.tar.bz2"]
tarball <- case tarballs of -- TODO: Drop code duplication.
[file] -> return $ unifyPath file
_ -> error $ "gmpRules: exactly one tarball expected"
++ "(found: " ++ show tarballs ++ ")."
let tarballs = gmpBase -/- "tarball/gmp*.tar.bz2"
tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs])
"Exactly one GMP tarball is expected."
withTempDir $ \dir -> do
let tmp = unifyPath dir
need [tarball]
......
......@@ -80,13 +80,9 @@ libffiRules = do
libffiMakefile <.> "in" %> \mkIn -> do
removeDirectory libffiBuildPath
createDirectory $ buildRootPath -/- stageString Stage0
tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"]
tarball <- case tarballs of -- TODO: Drop code duplication.
[file] -> return $ unifyPath file
_ -> error $ "libffiRules: exactly one tarball expected"
++ "(found: " ++ show tarballs ++ ")."
let tarballs = "libffi-tarballs/libffi*.tar.gz"
tarball <- unifyPath <$> getSingleton (getDirectoryFiles "" [tarballs])
"Exactly one LibFFI tarball is expected."
need [tarball]
let libname = dropExtension . dropExtension $ takeFileName tarball
......
......@@ -9,9 +9,9 @@ import Base
import Context
import Expression
import Flavour
import GHC
import Oracles.PackageData
import Rules.Actions
import Rules.Gmp
import Settings
import Settings.Paths
import Target
......@@ -96,7 +96,7 @@ hSources context = do
extraObjects :: Context -> Action [FilePath]
extraObjects context
| context == gmpContext = do
| package context == integerGmp = do
need [gmpLibraryH]
map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"]
| otherwise = return []
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment