Skip to content
Snippets Groups Projects
Commit 9d821594 authored by Edward Z. Yang's avatar Edward Z. Yang
Browse files

Don't specify hs-libraries when none exists!

This fixes GHC bug
https://ghc.haskell.org/trac/ghc/ticket/13268



Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
parent 63ccb88c
No related branches found
No related tags found
No related merge requests found
......@@ -462,9 +462,10 @@ generalInstalledPackageInfo adjustRelIncDirs pkg abi_hash lib lbi clbi installDi
(absinc, relinc) = partition isAbsolute (includeDirs bi)
hasModules = not $ null (allLibModules lib clbi)
comp = compiler lbi
hasLibrary = hasModules || not (null (cSources bi))
|| (not (null (jsSources bi)) &&
compilerFlavor comp == GHCJS)
hasLibrary = (hasModules || not (null (cSources bi))
|| (not (null (jsSources bi)) &&
compilerFlavor comp == GHCJS))
&& not (componentIsIndefinite clbi)
(libdirs, dynlibdirs)
| not hasLibrary
= (extraLibDirs bi, [])
......
signature A where
{-# LANGUAGE TemplateHaskell #-}
module M where
$( [d| x = True |] )
name: bkpth
version: 1.0
build-type: Simple
cabal-version: >= 1.25
library helper
signatures: A
build-depends: base
default-language: Haskell2010
library
exposed-modules: M
build-depends: base, helper
default-language: Haskell2010
# Setup configure
Configuring bkpth-1.0...
# Setup build
Preprocessing library 'helper' for bkpth-1.0..
Building library 'helper' instantiated with A = <A>
for bkpth-1.0..
Preprocessing library for bkpth-1.0..
Building library instantiated with A = <A>
for bkpth-1.0..
import Test.Cabal.Prelude
main = setupAndCabalTest $ do
skipUnless =<< ghcVersionIs (>= mkVersion [8,1])
setup "configure" []
setup "build" []
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