Skip to content
Snippets Groups Projects
Commit cbc2ad16 authored by Hannes Siebenhandl's avatar Hannes Siebenhandl Committed by Daniel Gröber (dxld)
Browse files

Re-design test-cases for show-build-info

parent 7931e2f3
No related branches found
No related tags found
No related merge requests found
Showing
with 262 additions and 0 deletions
cabal-version: 2.4
name: A
version: 0.1.0.0
license: BSD-3-Clause
library
exposed-modules: A
build-depends: base >=4
hs-source-dirs: src
default-language: Haskell2010
executable A
main-is: Main.hs
build-depends: base >=4
hs-source-dirs: src
default-language: Haskell2010
test-suite A-tests
type: exitcode-stdio-1.0
main-is: Test.hs
build-depends: base >=4, A
hs-source-dirs: src
default-language: Haskell2010
cabal-version: 2.4
name: B
version: 0.1.0.0
license: BSD-3-Clause
library
exposed-modules: B
build-depends: base >=4.0.0.0, A
hs-source-dirs: lib
default-language: Haskell2010
module B where
foo :: Int -> Int
foo = id
# cabal build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- A-0.1.0.0 (lib) (first run)
- A-0.1.0.0 (exe:A) (first run)
- B-0.1.0.0 (lib) (first run)
- A-0.1.0.0 (test:A-tests) (first run)
Configuring library for A-0.1.0.0..
Preprocessing library for A-0.1.0.0..
Building library for A-0.1.0.0..
Configuring executable 'A' for A-0.1.0.0..
Preprocessing executable 'A' for A-0.1.0.0..
Building executable 'A' for A-0.1.0.0..
Configuring library for B-0.1.0.0..
Preprocessing library for B-0.1.0.0..
Building library for B-0.1.0.0..
Configuring test suite 'A-tests' for A-0.1.0.0..
Preprocessing test suite 'A-tests' for A-0.1.0.0..
Building test suite 'A-tests' for A-0.1.0.0..
{-# LANGUAGE OverloadedStrings #-}
import Test.Cabal.Prelude
import Test.Cabal.DecodeShowBuildInfo
main = cabalTest $ do
runShowBuildInfo ["all", "--enable-tests"]
withPlan $ do
assertComponent "A" (exe "A")
defCompAssertion
{ sourceFiles = ["Main.hs"]
, sourceDirs = ["src"]
}
assertComponent "A" mainLib
defCompAssertion
{ modules = ["A"]
, sourceDirs = ["src"]
}
assertComponent "B" mainLib
defCompAssertion
{ modules = ["B"]
, sourceDirs = ["lib"]
}
assertComponent "A" (test "A-tests")
defCompAssertion
{ sourceFiles = ["Test.hs"]
, sourceDirs = ["src"]
}
# cabal build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- A-0.1.0.0 (exe:A) (first run)
Configuring executable 'A' for A-0.1.0.0..
Preprocessing executable 'A' for A-0.1.0.0..
Building executable 'A' for A-0.1.0.0..
{-# LANGUAGE OverloadedStrings #-}
import Test.Cabal.Prelude
import Test.Cabal.DecodeShowBuildInfo
main = cabalTest $ do
runShowBuildInfo ["exe:A"]
withPlan $ do
assertComponent "A" (exe "A")
defCompAssertion
{ sourceFiles = ["Main.hs"]
, sourceDirs = ["src"]
-- does not list lib as a target
, compilerArgsPred = all (/= "A-0.1.0.0-inplace")
}
packages: . ./B/
# cabal build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- A-0.1.0.0 (exe:A) (first run)
Configuring executable 'A' for A-0.1.0.0..
Preprocessing executable 'A' for A-0.1.0.0..
Building executable 'A' for A-0.1.0.0..
# cabal v2-build
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- A-0.1.0.0 (exe:A) (configuration changed)
Configuring executable 'A' for A-0.1.0.0..
Preprocessing executable 'A' for A-0.1.0.0..
Building executable 'A' for A-0.1.0.0..
{-# LANGUAGE OverloadedStrings #-}
import Test.Cabal.Prelude
import Test.Cabal.DecodeShowBuildInfo
import Test.Cabal.Plan
import Control.Monad.Trans.Reader
import System.Directory
main = cabalTest $ do
runShowBuildInfo ["exe:A"]
withPlan $ do
assertComponent "A" (exe "A")
defCompAssertion
{ sourceFiles = ["Main.hs"]
, sourceDirs = ["src"]
-- does not list lib as a target
, compilerArgsPred = all (/= "A-0.1.0.0-inplace")
}
cabal' "v2-build" ["exe:A", "--disable-build-info"]
withPlan $ do
Just plan <- fmap testPlan ask
let fp = buildInfoFile plan "A" (exe "A")
shouldNotExist fp
module A where
foo = 2
module Main where
main = return ()
module Main where
main :: IO ()
main = return ()
cabal-version: 2.4
name: Complex
version: 0.1.0.0
license: MIT
library
build-depends: base
hs-source-dirs: src doesnt-exist
default-language: Haskell2010
exposed-modules:
A
B
autogen-modules: Paths_Complex
other-modules:
C
D
Paths_Complex
ghc-options: -Wall
executable Complex
main-is: Main.lhs
build-depends:
, base
, Complex
hs-source-dirs: app
autogen-modules: Paths_Complex
other-modules:
Other
Paths_Complex
ghc-options:
-threaded -rtsopts "-with-rtsopts=-N -T" -Wredundant-constraints
default-language: Haskell2010
test-suite unit-test
type: exitcode-stdio-1.0
hs-source-dirs: test
build-depends:
, another-framework
, base
main-is: UnitMain.hs
default-language: Haskell2010
test-suite func-test
type: exitcode-stdio-1.0
hs-source-dirs: test
build-depends:
, base
, Complex
, test-framework
main-is: FuncMain.hs
default-language: Haskell2010
benchmark complex-benchmarks
type: exitcode-stdio-1.0
main-is: Main.hs
other-modules: Paths_Complex
autogen-modules: Paths_Complex
hs-source-dirs: benchmark
ghc-options: -Wall -rtsopts -threaded -with-rtsopts=-N
build-depends:
, base
, Complex
, criterion ^>=1.1.4
default-language: Haskell2010
> module Main where
>
> import A
> import Other
>
> main = do
> print foo
> print bar
module Other where
bar = ()
module Main where
main = pure ()
packages: .
tests: True
benchmarks: True
name: another-framework
version: 0.8.1.1
build-type: Simple
cabal-version: >= 1.10
library
build-depends: base
default-language: Haskell2010
name: criterion
version: 1.1.4.0
build-type: Simple
cabal-version: >= 1.10
library
build-depends: base, ghc-prim
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