
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.