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

Add test-cases for extracting build-info, even if a component failed to build

parent e1699ce6
No related branches found
No related tags found
No related merge requests found
Showing
with 113 additions and 2 deletions
......@@ -3,7 +3,6 @@ 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"]
......
cabal-version: 3.0
name: CompileFail
version: 0.1.0.0
build-type: Simple
library
exposed-modules: MyLib
build-depends: base
hs-source-dirs: src
default-language: Haskell2010
library failing
exposed-modules: MyLib2
build-depends: base
hs-source-dirs: src
default-language: Haskell2010
test-suite CompileFail-test
default-language: Haskell2010
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Main.hs
build-depends: base, CompileFail
executable CompileFail-exe
default-language: Haskell2010
hs-source-dirs: app
main-is: Main.hs
build-depends: base, failing
module Main where
import MyLib2 (someFunc2)
main :: IO ()
main = someFunc2
packages: ./
# cabal build
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- CompileFail-0.1.0.0 (lib) (first run)
- CompileFail-0.1.0.0 (test:CompileFail-test) (first run)
Configuring library for CompileFail-0.1.0.0..
Preprocessing library for CompileFail-0.1.0.0..
Building library for CompileFail-0.1.0.0..
Configuring test suite 'CompileFail-test' for CompileFail-0.1.0.0..
Preprocessing test suite 'CompileFail-test' for CompileFail-0.1.0.0..
Building test suite 'CompileFail-test' for CompileFail-0.1.0.0..
# cabal build
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- CompileFail-0.1.0.0 (lib:failing) (first run)
- CompileFail-0.1.0.0 (exe:CompileFail-exe) (first run)
Configuring library 'failing' for CompileFail-0.1.0.0..
Preprocessing library 'failing' for CompileFail-0.1.0.0..
Building library 'failing' for CompileFail-0.1.0.0..
cabal: Failed to build CompileFail-0.1.0.0 because it depends on CompileFail-0.1.0.0 which itself failed to build.
Failed to build CompileFail-0.1.0.0-inplace-failing.
{-# LANGUAGE OverloadedStrings #-}
import Test.Cabal.Prelude
import Test.Cabal.DecodeShowBuildInfo
import Test.Cabal.Plan
import Control.Monad.Trans.Reader
main = cabalTest $ do
-- Leaf component fails to compile, should still dump
-- build info for both components.
fails $ runShowBuildInfo ["test:CompileFail-test"]
withPlan $ do
-- Lib has to be built, thus info is dumped
assertComponent "CompileFail" mainLib
defCompAssertion
{ modules = ["MyLib"]
, sourceDirs = ["src"]
}
-- Build Info is still dumped, although compilation failed
assertComponent "CompileFail" (test "CompileFail-test")
defCompAssertion
{ sourceFiles = ["Main.hs"]
, sourceDirs = ["test"]
}
fails $ runShowBuildInfo ["exe:CompileFail-exe"]
withPlan $ do
-- Internal Lib has to be built, thus info is dumped
assertComponent "CompileFail" (lib "failing")
defCompAssertion
{ modules = ["MyLib2"]
, sourceDirs = ["src"]
}
-- However, since the internal lib failed to compile
-- we can not have executable build information.
Just plan <- fmap testPlan ask
let fp = buildInfoFile plan "CompileFail" (exe "CompileFail-exe")
shouldNotExist fp
module MyLib (someFunc) where
someFunc :: IO ()
someFunc = putStrLn "someFunc"
module MyLib2 (someFunc2) where
someFunc2 :: IO ()
-- Intentional typo, should fail to compile
someFunc2 = putStrn "someFunc"
-- ^^------- missing 'L'
module Main (main) where
main :: IO ()
-- Intentional typo, should fail to compile
main = putStrn "Test suite not yet implemented."
-- ^^------- missing 'L'
......@@ -111,7 +111,7 @@ defCompAssertion = ComponentAssertion
, modules = []
, sourceFiles = []
, sourceDirs = []
, compType = mempty
, compType = ""
}
-- | Assert common build information, such as compiler location, compiler version
......
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