[Haskell-beginners] Either Monadic Trouble

Daniel Fischer daniel.is.fischer at web.de
Tue Nov 10 10:13:52 EST 2009


Am Montag 09 November 2009 10:01:43 schrieb iæfai:
> With the below code, I am getting an error that I cannot resolve…

Everybody was so busy discussing whether Either (or rather (Either e)) is a monad that 
nobody looked at the code, so:

>
>
> Chess.hs:52:82:
>      Couldn't match expected type `Map [Char] [Char]'
>             against inferred type `Either ParseError ConfigMap'
>      In the third argument of `findWithDefault', namely `c'
>      In the `documentRoot' field of a record
>      In the first argument of `return', namely
>          `Config {documentRoot = (findWithDefault "web" "Document-
> Root" c)}'
>
>
> The specific code is:
>
> getConf :: FilePath -> IO (Either ParseError Config)
> getConf filePath
>      = return $ do
>          c <- readConfig filePath  -- (Either ParseError ConfigMap)

I believe the type of readConfig is

FilePath -> IO (Either ParseError ConfigMap)

, thus the binding of c, (c <-), still takes place in IO and c is one of (Left parseerror) 
or (Right configmap), hence c is not a suitable argument for findWithDefault.

>          return Config { documentRoot = Map.findWithDefault "web"
> "Document-Root" c }

The inner return also lives in IO, so had c a suitable type, your getConf would have type

FilePath -> IO (IO something).

I think you want 

getConf filePath = do
    r <- readConfig filePath
    return $ do
        c <- r       -- *now* we're using the monad (Either ParseError)
        return Config{ documentRoot = Map.findWithDefault "web" "Document-Root" c }

(if you have instance Monad (Either ParseError) in scope) or the equivalent using Pattern 
matching on the result of readConfig filePath.

>
>
> The type of c should be Either ParseError ConfigMap, which by my
> understanding of the Either monad would cause the c to be the Right
> side stripped, or skipped if Left.
>
> Full source for the module is below, and full project is hosted at
> http://patch-tag.com/r/iaefai/chess
>
> For some general information, I am replacing ConfigFile dependancy
> with a Parsec based config parser (I call it SimpleConfig) that suits
> my needs - it came from
>
> http://www.serpentine.com/blog/2007/01/31/parsing-a-simple-config-file-in-h
>askell/ originally and I modified it. On windows ConfigFile's dependancy on
> a posix regex library was causing trouble, so this is the effort to get rid
> of that dependancy.
>
> Any thoughts would be useful.
>
> There is one associated thought…
>
> The original function used to get configuration back to the program is
> -- Mostly from Chris Done's Blog
> getConf :: FilePath -> IO (Either (C.CPErrorData, String) Config)
> getConf filePath = runErrorT $ do
>      let cp = C.emptyCP { optionxform = id }
>      contents <- liftIO $ readFile filePath
>      config <- C.readstring cp contents
>      let get = C.get config "DEFAULT"
>      Config <$> get "Document-Root"
>
> I noted it used <$> and in the code that I retrieved originally from
> Chris Done's blog (no longer able to find it) used <*> for additional
> items. I would like some easy method of constructing the new Config
> structure in my new code, especially if it can be done without the
> record syntax like this thing gets away with. I am not sure how this
> thing associated "Document-Root" with documentRoot mind you.
>
> Thank you again.
> iæfai.



More information about the Beginners mailing list