Skip to content
Snippets Groups Projects
Unverified Commit d9ec979a authored by John Ericson's avatar John Ericson Committed by GitHub
Browse files

Merge pull request #7575 from runeksvendsen/ghcjs-build-runner

Restore GHCJS "-build-runner" option
parents 99e1486e 89e0a68f
No related branches found
No related tags found
No related merge requests found
......@@ -1093,11 +1093,22 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
needProfiling = withProfExe lbi
-- build executables
buildRunner = case clbi of
LibComponentLocalBuildInfo {} -> False
FLibComponentLocalBuildInfo {} -> False
ExeComponentLocalBuildInfo {} -> True
TestComponentLocalBuildInfo {} -> True
BenchComponentLocalBuildInfo {} -> True
baseOpts = (componentGhcOptions verbosity lbi bnfo clbi tmpDir)
`mappend` mempty {
ghcOptMode = toFlag GhcModeMake,
ghcOptInputFiles = toNubListR inputFiles,
ghcOptInputModules = toNubListR inputModules
ghcOptInputModules = toNubListR inputModules,
-- for all executable components (exe/test/bench),
-- GHCJS must be passed the "-build-runner" option
ghcOptExtra =
if buildRunner then ["-build-runner"]
else mempty
}
staticOpts = baseOpts `mappend` mempty {
ghcOptDynLinkMode = toFlag GhcStaticOnly,
......
name: BuildRunner
version: 1.0
build-type: Simple
cabal-version: >= 1.10
test-suite ghcjs-test
type: exitcode-stdio-1.0
main-is: BuildRunner.hs
build-depends: base
default-language: Haskell2010
executable ghcjs-exe
main-is: BuildRunner.hs
build-depends: base
default-language: Haskell2010
benchmark ghcjs-bench
type: exitcode-stdio-1.0
main-is: BuildRunner.hs
build-depends: base
default-language: Haskell2010
module Main where
import System.Exit (exitSuccess)
main :: IO ()
main = do
exitSuccess
This test verifies that the `-build-runner` option is passed to GHCJS when the cabal commands `test`/`run`/`bench` are run with the `--ghcjs` option.
This test was created in order to avoid regressions in running GHCJS executables, e.g.:
* https://github.com/haskell/cabal/issues/6175
* https://github.com/haskell/cabal/issues/6361
packages: .
import Test.Cabal.Prelude
main = cabalTest . recordMode DoNotRecord $ do
skipIfWindows -- disabled because (I presume) Windows doesn't have BASH
cwd <- fmap testCurrentDir getTestEnv
testInvokedWithBuildRunner cwd "test" []
testInvokedWithBuildRunner cwd "run" ["ghcjs-exe"]
testInvokedWithBuildRunner cwd "bench" []
magicString = "SUCCESS! GHCJS was invoked with '-build-runner' option"
testInvokedWithBuildRunner cwd cabalCmd extraArgs = do
output <- fails $ cabal' cabalCmd $ extraArgs ++
[ "--ghcjs"
, "--with-compiler", cwd </> fakeGhcjsPath
]
assertOutputContains magicString output
where
fakeGhcjsPath = "scripts/fake-ghcjs.sh"
#!/usr/bin/env bash
# A script that will print out $MAGIC_STRING when invoked with the
# '-build-runner' option.
#
# When cabal is invoked with the '--ghcjs' option and the '--with-compiler'
# option set to the path of this script, cabal will successfully get to the linking
# stage (where it *should* call this script with the '-build-runner' option).
MAGIC_STRING="SUCCESS! GHCJS was invoked with '-build-runner' option"
if [ "$1" == "--numeric-ghcjs-version" ]; then
ghc --numeric-version
elif [ "$1" == "--numeric-ghc-version" ]; then
ghc --numeric-version
elif [[ "$*" == *-build-runner* ]]; then
echo "$MAGIC_STRING"
else
ghc "$@"
fi
#!/usr/bin/env bash
if [ "$1" == "--numeric-ghcjs-version" ]; then
ghc --numeric-version
elif [ "$1" == "--numeric-ghc-version" ]; then
ghc --numeric-version
else
ghc-pkg "$@"
fi
synopsis: Fix running GHCJS executables
packages: cabal-install
prs: #7575
issues: #6175 #6361
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