Skip to content

Commit

Permalink
Add a ‘NonignoredConfigs’ test that fails without our fix.
Browse files Browse the repository at this point in the history
  • Loading branch information
bairyn committed Dec 9, 2022
1 parent 17c09e3 commit a087092
Show file tree
Hide file tree
Showing 5 changed files with 144 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Basic where

funcs :: (a -> b -> c) -> ((a -> b -> c) -> a -> b -> c) -> b -> a -> c
funcs f g = \a b -> (g f) b a

name :: String
name = "Basic"

number :: Integer
number = 8
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
cabal-version: >= 1.10
name: basic
version: 0.1
build-type: Simple

library
default-language: Haskell2010
build-depends: base
exposed-modules:
Basic
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: basic
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
# cabal v2-install
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- basic-0.1 (lib) (requires build)
Configuring library for basic-0.1..
Preprocessing library for basic-0.1..
Building library for basic-0.1..
Installing library in <PATH>
# cabal v2-install
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- basic-0.1 (lib) (requires build)
Configuring library for basic-0.1..
Preprocessing library for basic-0.1..
Building library for basic-0.1..
Installing library in <PATH>
# cabal v2-install
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
Resolving dependencies...
# cabal v2-install
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
Resolving dependencies...
Original file line number Diff line number Diff line change
@@ -0,0 +1,97 @@
import Test.Cabal.Prelude

-- This test ensures the following fix holds:
-- > Fix project-local build flags being ignored.
-- >
-- > I noticed that running ‘cabal install’ with two separate sets of dynamic /
-- > static build flags (e.g. one with none, and one with ‘--enable-shared
-- > --enable-executable-dynamic --disable-library-vanilla’) produced packages with
-- > the same hash, instead of different hashes.
-- >
-- > After debugging this issue I found that this command (with no explicit cabal
-- > project file) was resulting in these build configuration flags being ignored,
-- > because in ProjectPlanning.hs, the sdist was not considered a local package, so
-- > the (non-shared) local-package-only configuration was being dropped.
-- >
-- > This fix ensures that these command-line arguments properly make it through to
-- > where they belong in cases like this.
--
-- Basically, take a simple package, build it under two sets of build flags:
-- > (nothing)
-- > --enable-shared --enable-executable-dynamic --disable-library-vanilla
--
-- And ensure that whereas before they produced the same hash, now the package
-- hashes produced are different. (And also supplementarily ensure that
-- re-running the same build with the same flags a second time produces a
-- deterministic hash too; the hash should differ only when we change these
-- flags.)
--
-- Based on the UniqueIPID test.

import Control.Monad (forM, foldM_)
import Data.List (isPrefixOf, tails)

data Linking = Static | Dynamic deriving (Eq, Ord, Show)

links :: [Linking]
links = [Static, Dynamic]

linkConfigFlags :: Linking -> [String]
linkConfigFlags Static =
[
]
linkConfigFlags Dynamic =
[
"--enable-shared",
"--enable-executable-dynamic",
"--disable-library-vanilla"
]

lrun :: [Linking]
lrun = [Static, Dynamic, Static, Dynamic]

main = cabalTest $ do
withPackageDb $ do
-- Phase 1: get 4 hashes according to config flags.
results <- forM (zip [0..] lrun) $ \(idx, linking) -> do
withDirectory "basic" $ do
withSourceCopyDir ("basic" ++ show idx) $ do
cwd <- fmap testSourceCopyDir getTestEnv
-- (Now do ‘cd ..’, since withSourceCopyDir made our previous
-- previous such withDirectories now accumulate to be
-- relative to setup.dist/basic0, not testSourceDir
-- (see 'testCurrentDir').)
withDirectory ".." $ do
packageEnv <- (</> ("basic" ++ show idx ++ ".env")) . testWorkDir <$> getTestEnv
cabal "v2-install" $ ["--disable-deterministic", "--lib", "--package-env=" ++ packageEnv] ++ linkConfigFlags linking ++ ["basic"]
let exIPID s = takeWhile (/= '\n') . head . filter ("basic-0.1-" `isPrefixOf`) $ tails s
hashedIpid <- exIPID <$> liftIO (readFile packageEnv)
return $ ((idx, linking), hashedIpid)
-- Phase 2: make sure we have different hashes iff we have different config flags.
-- In particular make sure the dynamic config flags weren't silently
-- dropped and ignored, since this is the bug that prompted this test.
(\step -> foldM_ step (const $ return ()) results) $ \acc x -> do
acc x
return $ \future -> acc future >> do
let
((thisIdx, thisLinking), thisHashedIpid) = x
((futureIdx, futureLinking), futureHashedIpid) = future
when ((thisHashedIpid == futureHashedIpid) /= (thisLinking == futureLinking)) $ do
assertFailure . unlines $
if thisLinking /= futureLinking
then
-- What we are primarily concerned with testing
-- here.
[
"Error: static and dynamic config flags produced an IPID with the same hash; were the dynamic flags silently dropped?",
"\thashed IPID: " ++ thisHashedIpid
]
else
-- Help test our test can also make equal
-- hashes.
[
"Error: config flags were equal, yet a different IPID hash was produced.",
"\thashed IPID 1 : " ++ thisHashedIpid,
"\thashed IPID 2 : " ++ futureHashedIpid,
"\tlinking flags : " ++ show thisLinking
]

0 comments on commit a087092

Please sign in to comment.