Skip to content
Snippets Groups Projects
Commit f4f382ae authored by kristenk's avatar kristenk
Browse files

Add a regression test for issue #4288.

parent ea01b9d5
No related branches found
No related tags found
No related merge requests found
module CustomIssue where
f x = x + 1
import SetupHelper (setupHelperDefaultMain)
main = setupHelperDefaultMain
name: T4288
version: 1.0
build-type: Custom
-- cabal-version is lower than the version of Cabal that will be chosen for the
-- setup script.
cabal-version: >=1.10
-- Setup script only has a transitive dependency on Cabal.
custom-setup
setup-depends: base, setup-helper
library
exposed-modules: CustomIssue
build-depends: base
default-language: Haskell2010
packages: . setup-helper/
import Test.Cabal.Prelude
-- This test is similar to the simplified example in issue #4288. The package's
-- setup script only depends on base and setup-helper. setup-helper exposes a
-- function that is a wrapper for Cabal's defaultMain (similar to
-- cabal-doctest). This test builds the package to check that the flags passed
-- to the setup script are compatible with the version of Cabal that it depends
-- on, even though Cabal is only a transitive dependency.
main = cabalTest $ do
skipUnless =<< hasNewBuildCompatBootCabal
r <- recordMode DoNotRecord $ cabal' "new-build" ["T4288"]
assertOutputContains "This is setup-helper-1.0." r
assertOutputContains
("In order, the following will be built: "
++ " - setup-helper-1.0 (lib:setup-helper) (first run) "
++ " - T4288-1.0 (lib:T4288) (first run)")
r
module SetupHelper (setupHelperDefaultMain) where
import Distribution.Simple
setupHelperDefaultMain = putStrLn "This is setup-helper-1.0." >> defaultMain
name: setup-helper
version: 1.0
build-type: Simple
cabal-version: >= 1.2
library
exposed-modules: SetupHelper
build-depends: base, Cabal
default-language: Haskell2010
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