Skip to content
Snippets Groups Projects
Commit 68891ce4 authored by Edward Z. Yang's avatar Edward Z. Yang
Browse files

Force CopyAssumeDepsUpToDate on Windows to test absolute install path behavior.


Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
parent e34235c6
No related branches found
No related tags found
No related merge requests found
......@@ -92,6 +92,7 @@ extra-source-files:
tests/PackageTests/Configure/X11.cabal
tests/PackageTests/CopyAssumeDepsUpToDate/CopyAssumeDepsUpToDate.cabal
tests/PackageTests/CopyAssumeDepsUpToDate/Main.hs
tests/PackageTests/CopyAssumeDepsUpToDate/P.hs
tests/PackageTests/CopyComponent/Exe/Main.hs
tests/PackageTests/CopyComponent/Exe/Main2.hs
tests/PackageTests/CopyComponent/Exe/myprog.cabal
......
......@@ -206,6 +206,11 @@ generate pkg_descr lbi clbi =
where var' = pkgPathEnvVar pkg_descr var
-- In several cases we cannot make relocatable installations
-- WARNING: The CopyOneShot package test hacks
-- @absolute == True@ to disable relocatable programs
-- by giving the package a library as well. If you change
-- this logic (e.g., we start to support relocatable libraries
-- by default) you will need to update this test.
absolute =
hasLibs pkg_descr -- we can only make progs relocatable
|| isNothing flat_bindirrel -- if the bin dir is an absolute path
......
......@@ -8,6 +8,13 @@ cabal-version: >=1.10
data-files: data
-- This library purely exists to convince Cabal on Windows
-- to not attempt to install this as prefix-relative executable.
library
exposed-modules: P
build-depends: base
default-language: Haskell2010
executable myprog
main-is: Main.hs
other-modules: Paths_CopyAssumeDepsUpToDate
......
module P where
......@@ -427,6 +427,10 @@ tests config = do
>>= assertOutputContains "a1 b2"
-- Test copy --assume-deps-up-to-date
-- NB: This test has a HORRIBLE HORRIBLE hack to ensure that
-- on Windows, we don't try to make a prefix relative package;
-- specifically, we give the package under testing a library
-- so that we don't attempt to make it prefix relative.
mtc "CopyAssumeDepsUpToDate" $ \step -> do
withPackageDb $ do
step "Initial build"
......@@ -448,7 +452,7 @@ tests config = do
step "Install executable"
liftIO $ writeFile (pkg_dir </> "data") "bbb"
cabal "copy" ["--assume-deps-up-to-date", "myprog"]
cabal "copy" ["--assume-deps-up-to-date", "exe:myprog"]
runInstalledExe' "myprog" []
>>= assertOutputContains "aaa"
......
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