Am 01.03.2014 23:48, schrieb Henning Thielemann:

[6 of 8] Compiling Distribution.HaskellSuite.Compiler (
src/Distribution/HaskellSuite/Compiler.hs,
dist/build/Distribution/HaskellSuite/Compiler.o )

src/Distribution/HaskellSuite/Compiler.hs:21:5:
     Not in scope: `customMain'

I guess this is because it is missing from Cabal.


haskell-packages$ git diff --unified src/Distribution/HaskellSuite/Cabal.hs-boot diff --git a/src/Distribution/HaskellSuite/Cabal.hs-boot b/src/Distribution/HaskellSuite/Cabal.hs-boot
index bc9bdfb..b45cbe5 100644
--- a/src/Distribution/HaskellSuite/Cabal.hs-boot
+++ b/src/Distribution/HaskellSuite/Cabal.hs-boot
@@ -1,7 +1,13 @@
 module Distribution.HaskellSuite.Cabal where

import {-# SOURCE #-} qualified Distribution.HaskellSuite.Compiler as Compiler
+import Options.Applicative

 main
   :: Compiler.Is c
   => c -> IO ()
+
+customMain
+  :: Compiler.Is c
+  => Parser (IO ())
+  -> c -> IO ()


_______________________________________________
cabal-devel mailing list
cabal-devel@haskell.org
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to