Skip to content
Snippets Groups Projects
Commit beafb5c5 authored by David Himmelstrup's avatar David Himmelstrup
Browse files

Added --with-greencard.

parent 514e0c89
No related branches found
No related tags found
No related merge requests found
......@@ -185,9 +185,14 @@ removePreprocessed searchLocs mods suffixesIn
-- * known preprocessors
-- ------------------------------------------------------------
ppGreenCard :: PreProcessor
ppGreenCard inFile outFile verbose
= rawSystemPath verbose "green-card" ["-tffi", "-o" ++ outFile, inFile]
ppGreenCard :: BuildInfo -> LocalBuildInfo -> PreProcessor
ppGreenCard = ppGreenCard' []
ppGreenCard' :: [String] -> BuildInfo -> LocalBuildInfo -> PreProcessor
ppGreenCard' inputArgs bi lbi
= maybe (ppNone "greencard") pp (withGreencard lbi)
where pp greencard inFile outFile verbose
= rawSystemPath verbose greencard (["-tffi", "-o" ++ outFile, inFile] ++ inputArgs)
-- This one is useful for preprocessors that can't handle literate source.
-- We also need a way to chain preprocessors.
......@@ -273,7 +278,7 @@ ppSuffixes = map fst
-- |Standard preprocessors: GreenCard, c2hs, hsc2hs, happy, alex and cpphs.
knownSuffixHandlers :: [ PPSuffixHandler ]
knownSuffixHandlers =
[ ("gc", \ _ _ -> ppGreenCard)
[ ("gc", ppGreenCard)
, ("chs", ppC2hs)
, ("hsc", ppHsc2hs)
, ("x", ppAlex)
......
......@@ -113,6 +113,7 @@ data ConfigFlags = ConfigFlags {
configHsc2hs :: Maybe FilePath, -- ^Hsc2hs path
configC2hs :: Maybe FilePath, -- ^C2hs path
configCpphs :: Maybe FilePath, -- ^Cpphs path
configGreencard:: Maybe FilePath, -- ^GreenCard path
configProfLib :: Bool, -- ^Enable profiling in the library
configProfExe :: Bool, -- ^Enable profiling in the executables.
configPrefix :: Maybe FilePath, -- ^installation prefix
......@@ -134,6 +135,7 @@ emptyConfigFlags = ConfigFlags {
configProfLib = False,
configProfExe = False,
configCpphs = Nothing,
configGreencard= Nothing,
configPrefix = Nothing,
configVerbose = 0,
configUser = False
......@@ -144,6 +146,7 @@ data Flag a = GhcFlag | NhcFlag | HugsFlag
| WithCompiler FilePath | WithHcPkg FilePath | Prefix FilePath
| WithHaddock FilePath | WithHappy FilePath | WithAlex FilePath
| WithHsc2hs FilePath | WithC2hs FilePath | WithCpphs FilePath
| WithGreencard FilePath
| WithProfLib | WithoutProfLib
| WithProfExe | WithoutProfExe
-- For install, register, and unregister:
......@@ -271,6 +274,8 @@ configureCmd = Cmd {
"give the path to c2hs",
Option "" ["with-cpphs"] (ReqArg WithCpphs "PATH")
"give the path to cpphs",
Option "" ["with-greencard"] (ReqArg WithGreencard "PATH")
"give the path to greencard",
Option "p" ["enable-library-profiling"] (NoArg WithProfLib)
"Enable library profiling",
Option "" ["disable-library-profiling"] (NoArg WithoutProfLib)
......@@ -312,6 +317,7 @@ parseConfigureArgs cfg args customOpts =
WithHsc2hs path -> t { configHsc2hs = Just path }
WithC2hs path -> t { configC2hs = Just path }
WithCpphs path -> t { configCpphs = Just path }
WithGreencard path-> t { configGreencard= Just path }
WithProfLib -> t { configProfLib = True }
WithoutProfLib -> t { configProfLib = False }
WithProfExe -> t { configProfExe = True }
......
......@@ -147,24 +147,26 @@ configure pkg_descr cfg
unless (null exts) $ putStrLn $ -- Just warn, FIXME: Should this be an error?
"Warning: " ++ show f' ++ " does not support the following extensions:\n " ++
concat (intersperse ", " (map show exts))
haddock <- findProgram "haddock" (configHaddock cfg)
happy <- findProgram "happy" (configHappy cfg)
alex <- findProgram "alex" (configAlex cfg)
hsc2hs <- findProgram "hsc2hs" (configHsc2hs cfg)
c2hs <- findProgram "c2hs" (configC2hs cfg)
cpphs <- findProgram "cpphs" (configCpphs cfg)
haddock <- findProgram "haddock" (configHaddock cfg)
happy <- findProgram "happy" (configHappy cfg)
alex <- findProgram "alex" (configAlex cfg)
hsc2hs <- findProgram "hsc2hs" (configHsc2hs cfg)
c2hs <- findProgram "c2hs" (configC2hs cfg)
cpphs <- findProgram "cpphs" (configCpphs cfg)
greencard <- findProgram "greencard" (configGreencard cfg)
-- FIXME: maybe this should only be printed when verbose?
message $ "Using install prefix: " ++ pref
message $ "Using compiler: " ++ p'
message $ "Compiler flavor: " ++ (show f')
message $ "Compiler version: " ++ showVersion ver
message $ "Using package tool: " ++ pkg
reportProgram "haddock" haddock
reportProgram "happy" happy
reportProgram "alex" alex
reportProgram "hsc2hs" hsc2hs
reportProgram "c2hs" c2hs
reportProgram "cpphs" cpphs
reportProgram "haddock" haddock
reportProgram "happy" happy
reportProgram "alex" alex
reportProgram "hsc2hs" hsc2hs
reportProgram "c2hs" c2hs
reportProgram "cpphs" cpphs
reportProgram "greencard" greencard
-- FIXME: currently only GHC has hc-pkg
dep_pkgs <- if f' == GHC && ver >= Version [6,3] [] then do
ipkgs <- getInstalledPackagesAux comp cfg
......@@ -177,6 +179,7 @@ configure pkg_descr cfg
withHappy=happy, withAlex=alex,
withHsc2hs=hsc2hs, withC2hs=c2hs,
withCpphs=cpphs,
withGreencard=greencard,
withProfLib=configProfLib cfg,
withProfExe=configProfExe cfg
}
......
......@@ -67,6 +67,7 @@ data LocalBuildInfo = LocalBuildInfo {
withHsc2hs :: Maybe FilePath, -- ^Might be the location of the Hsc2hs executable.
withC2hs :: Maybe FilePath, -- ^Might be the location of the C2hs executable.
withCpphs :: Maybe FilePath, -- ^Might be the location of the Cpphs executable.
withGreencard :: Maybe FilePath, -- ^Might be the location of the GreenCard executable.
withProfLib :: Bool,
withProfExe :: Bool
}
......
......@@ -10,8 +10,6 @@
** which Distribution.* things won't change?
** document
* add withGreencard=
* Fix up sdist? hide sdist? bdist?
** if there's a flag, --include-preprocessed-sources (or something
better) run the preprocessing phase and include both the
......
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