Skip to content

Commit 2334bcb

Browse files
committed
Add a ‘NonignoredConfigs’ test that fails without our fix.
1 parent b547ead commit 2334bcb

File tree

5 files changed

+147
-0
lines changed

5 files changed

+147
-0
lines changed
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module Basic where
2+
3+
funcs :: (a -> b -> c) -> ((a -> b -> c) -> a -> b -> c) -> b -> a -> c
4+
funcs f g = \a b -> (g f) b a
5+
6+
name :: String
7+
name = "Basic"
8+
9+
number :: Integer
10+
number = 8
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
cabal-version: >= 1.10
2+
name: basic
3+
version: 0.1
4+
build-type: Simple
5+
6+
library
7+
default-language: Haskell2010
8+
build-depends: base
9+
exposed-modules:
10+
Basic
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
packages: basic
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
# cabal v2-install
2+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
3+
Resolving dependencies...
4+
Build profile: -w ghc-<GHCVER> -O1
5+
In order, the following will be built:
6+
- basic-0.1 (lib) (requires build)
7+
Configuring library for basic-0.1..
8+
Preprocessing library for basic-0.1..
9+
Building library for basic-0.1..
10+
Installing library in <PATH>
11+
# cabal v2-install
12+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
13+
Resolving dependencies...
14+
Build profile: -w ghc-<GHCVER> -O1
15+
In order, the following will be built:
16+
- basic-0.1 (lib) (requires build)
17+
Configuring library for basic-0.1..
18+
Preprocessing library for basic-0.1..
19+
Building library for basic-0.1..
20+
Installing library in <PATH>
21+
# cabal v2-install
22+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
23+
Resolving dependencies...
24+
# cabal v2-install
25+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
26+
Resolving dependencies...
Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
import Test.Cabal.Prelude
2+
3+
-- This test ensures the following fix holds:
4+
-- > Fix project-local build flags being ignored.
5+
-- >
6+
-- > I noticed that running ‘cabal install’ with two separate sets of dynamic /
7+
-- > static build flags (e.g. one with none, and one with ‘--enable-shared
8+
-- > --enable-executable-dynamic --disable-library-vanilla’) produced packages with
9+
-- > the same hash, instead of different hashes.
10+
-- >
11+
-- > After debugging this issue I found that this command (with no explicit cabal
12+
-- > project file) was resulting in these build configuration flags being ignored,
13+
-- > because in ProjectPlanning.hs, the sdist was not considered a local package, so
14+
-- > the (non-shared) local-package-only configuration was being dropped.
15+
-- >
16+
-- > This fix ensures that these command-line arguments properly make it through to
17+
-- > where they belong in cases like this.
18+
--
19+
-- Basically, take a simple package, build it under two sets of build flags:
20+
-- > (nothing)
21+
-- > --enable-shared --enable-executable-dynamic --disable-library-vanilla
22+
--
23+
-- And ensure that whereas before they produced the same hash, now the package
24+
-- hashes produced are different. (And also supplementarily ensure that
25+
-- re-running the same build with the same flags a second time produces a
26+
-- deterministic hash too; the hash should differ only when we change these
27+
-- flags.)
28+
--
29+
-- Based on the UniqueIPID test.
30+
31+
import Control.Monad (forM, foldM_)
32+
import Data.List (isPrefixOf, tails)
33+
34+
data Linking = Static | Dynamic deriving (Eq, Ord, Show)
35+
36+
links :: [Linking]
37+
links = [Static, Dynamic]
38+
39+
linkConfigFlags :: Linking -> [String]
40+
linkConfigFlags Static =
41+
[
42+
]
43+
linkConfigFlags Dynamic =
44+
[
45+
"--enable-shared",
46+
"--enable-executable-dynamic",
47+
"--disable-library-vanilla"
48+
]
49+
50+
lrun :: [Linking]
51+
lrun = [Static, Dynamic, Static, Dynamic]
52+
53+
main = cabalTest $ do
54+
-- TODO: Debug this failure on Windows.
55+
skipIfWindows
56+
57+
withPackageDb $ do
58+
-- Phase 1: get 4 hashes according to config flags.
59+
results <- forM (zip [0..] lrun) $ \(idx, linking) -> do
60+
withDirectory "basic" $ do
61+
withSourceCopyDir ("basic" ++ show idx) $ do
62+
cwd <- fmap testSourceCopyDir getTestEnv
63+
-- (Now do ‘cd ..’, since withSourceCopyDir made our previous
64+
-- previous such withDirectories now accumulate to be
65+
-- relative to setup.dist/basic0, not testSourceDir
66+
-- (see 'testCurrentDir').)
67+
withDirectory ".." $ do
68+
packageEnv <- (</> ("basic" ++ show idx ++ ".env")) . testWorkDir <$> getTestEnv
69+
cabal "v2-install" $ ["--disable-deterministic", "--lib", "--package-env=" ++ packageEnv] ++ linkConfigFlags linking ++ ["basic"]
70+
let exIPID s = takeWhile (/= '\n') . head . filter ("basic-0.1-" `isPrefixOf`) $ tails s
71+
hashedIpid <- exIPID <$> liftIO (readFile packageEnv)
72+
return $ ((idx, linking), hashedIpid)
73+
-- Phase 2: make sure we have different hashes iff we have different config flags.
74+
-- In particular make sure the dynamic config flags weren't silently
75+
-- dropped and ignored, since this is the bug that prompted this test.
76+
(\step -> foldM_ step (const $ return ()) results) $ \acc x -> do
77+
acc x
78+
return $ \future -> acc future >> do
79+
let
80+
((thisIdx, thisLinking), thisHashedIpid) = x
81+
((futureIdx, futureLinking), futureHashedIpid) = future
82+
when ((thisHashedIpid == futureHashedIpid) /= (thisLinking == futureLinking)) $ do
83+
assertFailure . unlines $
84+
if thisLinking /= futureLinking
85+
then
86+
-- What we are primarily concerned with testing
87+
-- here.
88+
[
89+
"Error: static and dynamic config flags produced an IPID with the same hash; were the dynamic flags silently dropped?",
90+
"\thashed IPID: " ++ thisHashedIpid
91+
]
92+
else
93+
-- Help test our test can also make equal
94+
-- hashes.
95+
[
96+
"Error: config flags were equal, yet a different IPID hash was produced.",
97+
"\thashed IPID 1 : " ++ thisHashedIpid,
98+
"\thashed IPID 2 : " ++ futureHashedIpid,
99+
"\tlinking flags : " ++ show thisLinking
100+
]

0 commit comments

Comments
 (0)