Builds with cabal, but not with GHC

I'm getting some weird errors when I try to compile this with GHC, or load it in GHCi, but it compiles (and runs) just fine using cabal. Here's the file... ********** FILE Test.hs: ********** module Main where import Control.Monad.Error ( runErrorT, ErrorT, join, liftIO ) import Data.ConfigFile ( get, CPError, emptyCP, readfile ) data Configuration = Configuration { popDir :: FilePath, username :: String, sleepTime :: Int } deriving Show parseConfig :: ErrorT CPError IO Configuration parseConfig = do cp <- join $ liftIO $ readfile emptyCP "/etc/creatur-daemon.conf" u <- Data.ConfigFile.get cp "DEFAULT" "user" pd <- Data.ConfigFile.get cp "DEFAULT" "dir" st <- Data.ConfigFile.get cp "DEFAULT" "sleeptime" return $ Configuration { popDir = pd, username = u, sleepTime = st } main :: IO () main = do rv <- runErrorT parseConfig case rv of Left (_, msg) -> putStrLn msg Right config -> print config ********** When I compile it with ghc, I get the following: $ ghc -hide-package monads-fd Test.hs [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:20:9: No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError CPError (ErrorT CPError IO)) arising from a use of `get' Possible fix: add an instance declaration for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError CPError (ErrorT CPError IO)) In a stmt of a 'do' expression: st <- get cp "DEFAULT" "sleeptime" In the expression: do { cp <- join $ liftIO $ readfile emptyCP "/etc/creatur-daemon.conf"; u <- get cp "DEFAULT" "user"; pd <- get cp "DEFAULT" "dir"; st <- get cp "DEFAULT" "sleeptime"; .... } In an equation for `parseConfig': parseConfig = do { cp <- join $ liftIO $ readfile emptyCP "/etc/creatur-daemon.conf"; u <- get cp "DEFAULT" "user"; pd <- get cp "DEFAULT" "dir"; .... } Test.hs:21:3: No instance for (Error (CPErrorData, String)) arising from a use of `return' Possible fix: add an instance declaration for (Error (CPErrorData, String)) In the expression: return In the expression: return $ Configuration {popDir = pd, username = u, sleepTime = st} In the expression: do { cp <- join $ liftIO $ readfile emptyCP "/etc/creatur-daemon.conf"; u <- get cp "DEFAULT" "user"; pd <- get cp "DEFAULT" "dir"; st <- get cp "DEFAULT" "sleeptime"; .... } I tried adding the instance declarations, but I don't think I did it right because I then had to add a bunch of imports, and the problems just snowballed. With this cabal file, I can do "cabal install", and the program compiles and runs just fine. ********** FILE: Creatur.cabal ********** Name: Creatur Version: 2.0 Description: Créatúr License: OtherLicense License-file: LICENSE Author: Amy de Buitléir Maintainer: amy@nualeargais.ie Build-Type: Simple Cabal-Version: >=1.2 Executable amy-test Main-Is: Test.hs GHC-Options: -Wall -Werror Build-Depends: base >= 4 && < 5, mtl ==1.1.*, ConfigFile ==1.0.* ********** Can anyone tell me how to modify the code so it will compile? Thank you in advance.

I couldn't get the configfile package to install because of issues
installing MissingH, but looking at the error messages the first thing I'd
do is to change the import list to:
import Control.Monad.Error
import Data.ConfigFile
-deech
On Wed, Sep 28, 2011 at 10:14 AM, Amy de Buitléir
Amy de Buitléir
writes: Can anyone tell me how to modify the code so it will compile? Thank you in advance.
Sorry, I meant to say "Can anyone tell me how to modify the code so it will build in ghc[i]? It already builds with cabal.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

aditya siram
I couldn't get the configfile package to install because of issues installing MissingH, but looking at the error messages the first thing I'd do is to change the import list to: import Control.Monad.Error import Data.ConfigFile
Sorry, I forgot to mention that I had already tried doing that, but it didn't help.

On Wed, Sep 28, 2011 at 03:03:33PM +0000, Amy de Buitléir wrote:
Test.hs:20:9: No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError CPError (ErrorT CPError IO))
I don't know a solution, but just want to point out that this error message smacks of inconsistent package versions being used. Something else used mtl-1.1.1.1 and the current module is being compiled with a different version of mtl, or something like that. Hopefully this can provide a fruitful direction of investigation... -Brent

On Wednesday 28 September 2011, 17:03:33, Amy de Buitléir wrote:
I'm getting some weird errors when I try to compile this with GHC, or load it in GHCi, but it compiles (and runs) just fine using cabal. Here's the file...
<snip>
When I compile it with ghc, I get the following:
$ ghc -hide-package monads-fd Test.hs [1 of 1] Compiling Main ( Test.hs, Test.o )
Test.hs:20:9: No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError CPError (ErrorT CPError IO))
That's a hint. The error message mentions the specific version of the package in which the class is defined. That usually means you are/the compiler is trying to build using incompatible packages. In this case, it looks as though the used ConfigFile was built against something other than mtl-1.1.1.1, maybe mtl-2.* Have you different versions of ConfigFile installed?
I tried adding the instance declarations, but I don't think I did it right because I then had to add a bunch of imports, and the problems just snowballed.
If the used packages are incompatible, the given 'probable fix' will not work, the problem lies deeper. The missing instance is just the place where ghc notices that it won't work, without figuring out the exact cause.
With this cabal file, I can do "cabal install", and the program compiles and runs just fine.
********** FILE: Creatur.cabal **********
Name: Creatur Version: 2.0 Description: Créatúr License: OtherLicense License-file: LICENSE Author: Amy de Buitléir Maintainer: amy@nualeargais.ie Build-Type: Simple Cabal-Version: >=1.2
Executable amy-test Main-Is: Test.hs GHC-Options: -Wall -Werror Build-Depends: base >= 4 && < 5, mtl ==1.1.*, ConfigFile ==1.0.* **********
Yes, Cabal sees the dependencies and chooses a compatible set of versions (if possible, otherwise it fill fail and tell you why). GHC only sees which packages are needed when following the imports during compilation, so it doesn't create a consistent install plan but just chooses the latest available version of each package and hopes for the best.
Can anyone tell me how to modify the code so it will compile? Thank you in advance.
You don't need to change the source, just the command line. You have to tell GHC explicitly which packages to use. $ cabal install --dry-run -v3 in the package directory will give you a lot of output, you're interested in the "selecting xyz-0.1.2" bits. Then $ ghc -hide-all-packages -package base -package mtl-1.1.1.1 -package ConfigFile-1.0.? Test.hs should work.
participants (4)
-
aditya siram
-
Amy de Buitléir
-
Brent Yorgey
-
Daniel Fischer