
With the below code, I am getting an error that I cannot resolve… 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) return Config { documentRoot = Map.findWithDefault "web" "Document-Root" c } 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-ha... 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. -- import Network.Shed.Httpd import Network.URI import Data.List.Split import Data.Either import Data.Map as Map import Text.ParserCombinators.Parsec import Control.Monad.Error import Control.Applicative import System.Directory import ChessBoard import SimpleConfig data Config = Config { documentRoot :: String } deriving (Read, Show) main :: IO () main = do let docPath = "" let config = Config { documentRoot = "" } putStrLn $ "Using document root: " ++ docPath putStrLn "Starting up httpd on port 6666" server <- initServer 6666 (request config) return () request :: Config -> Request -> IO Response request config req = do putStrLn $ "Recieved " ++ (show $ uriPath $ reqURI req) case url of "ajax" : _ -> return $ Response 404 [] "Not found." _ -> do str <- readFile ((documentRoot config) ++ uri) return $ Response 200 [] str where url = drop 1 $ splitOn "/" uri uri = uriPath $ reqURI req getConf :: FilePath -> IO (Either ParseError Config) getConf filePath = return $ do c <- readConfig filePath -- (Either ParseError ConfigMap) return Config { documentRoot = Map.findWithDefault "web" "Document-Root" c } -- **** ERROR

Either is not a monad, you can check this by typing
:i Either
in GHCi; you will not see a line like
instance Monad Either
in the result. Compare this to
:i Maybe
getConf could be something like:
getConf :: FilePath -> IO (Either ParseError Config)
getConf filePath =
do
c <- readConfig filePath -- (Either ParseError ConfigMap)
return $
case c of
Right c' -> Right $ Config $ Map.findWithDefault "web"
"Document-Root" c'
Left _ -> c
Met vriendelijke groet,
Henk-Jan van Tuyl
--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--
On Mon, 09 Nov 2009 10:01:43 +0100, iæfai
With the below code, I am getting an error that I cannot resolve…
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) return Config { documentRoot = Map.findWithDefault "web" "Document-Root" c }
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-ha... 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.
--

Excerpts from Henk-Jan van Tuyl's message of Mon Nov 09 11:10:07 +0100 2009:
Either is not a monad, you can check this by typing :i Either in GHCi; you will not see a line like instance Monad Either in the result. Compare this to :i Maybe
In fact the Either Monad instance is defined in the 'transformers' (or 'mtl') packages. However for this reason among others you may want to use the 'attempt'[1] package instead of Either. [1]: http://hackage.haskell.org/package/attempt-0.0.0 -- Nicolas Pouillard http://nicolaspouillard.fr

Nicolas Pouillard
Either is not a monad, you can check this by typing :i Either in GHCi; you will not see a line like instance Monad Either in the result. Compare this to :i Maybe
In fact the Either Monad instance is defined in the 'transformers' (or 'mtl') packages.
Either is still not a monad. Have a look at its kind. Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Excerpts from Ertugrul Soeylemez's message of Mon Nov 09 21:44:44 +0100 2009:
Nicolas Pouillard
wrote: Either is not a monad, you can check this by typing :i Either in GHCi; you will not see a line like instance Monad Either in the result. Compare this to :i Maybe
In fact the Either Monad instance is defined in the 'transformers' (or 'mtl') packages.
Either is still not a monad. Have a look at its kind.
OK, right Either is not but (Either e), where e must be in the Error type class. -- Nicolas Pouillard http://nicolaspouillard.fr

This is all very confusing. You say that it is defined in the transformers. Does this mean it is possible to use the code I am trying to get to work to do what I want? You also mention the attempt package, I must admit that I am not entirely sure how to use it either. Note that I haven't done a lot of error handling in haskell (the extent usually involved Maybe) - iæfai. On 2009-11-09, at 4:00 PM, Nicolas Pouillard wrote:
Excerpts from Ertugrul Soeylemez's message of Mon Nov 09 21:44:44 +0100 2009:
Nicolas Pouillard
wrote: Either is not a monad, you can check this by typing :i Either in GHCi; you will not see a line like instance Monad Either in the result. Compare this to :i Maybe
In fact the Either Monad instance is defined in the 'transformers' (or 'mtl') packages.
Either is still not a monad. Have a look at its kind.
OK, right Either is not but (Either e), where e must be in the Error type class.
-- Nicolas Pouillard http://nicolaspouillard.fr _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Excerpts from iæfai's message of Tue Nov 10 00:05:04 +0100 2009:
This is all very confusing. You say that it is defined in the transformers. Does this mean it is possible to use the code I am trying to get to work to do what I want?
Yes by importing Control.Monad.Error
You also mention the attempt package, I must admit that I am not entirely sure how to use it either. Note that I haven't done a lot of error handling in haskell (the extent usually involved Maybe)
A new version should be released (on Haskell Cafe) pretty soon, some documentation links will be provided as well. If you find the documentation not clear enough then let me know. -- Nicolas Pouillard http://nicolaspouillard.fr

On Tue, Nov 10, 2009 at 1:12 AM, Nicolas Pouillard < nicolas.pouillard@gmail.com> wrote:
Excerpts from iæfai's message of Tue Nov 10 00:05:04 +0100 2009:
This is all very confusing. You say that it is defined in the transformers. Does this mean it is possible to use the code I am trying to get to work to do what I want?
Yes by importing Control.Monad.Error
You also mention the attempt package, I must admit that I am not entirely sure how to use it either. Note that I haven't done a lot of error handling in haskell (the extent usually involved Maybe)
A new version should be released (on Haskell Cafe) pretty soon, some documentation links will be provided as well. If you find the documentation not clear enough then let me know.
Update: attempt-0.0.1 *has* been released.
Michael

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.
participants (6)
-
Daniel Fischer
-
Ertugrul Soeylemez
-
Henk-Jan van Tuyl
-
iæfai
-
Michael Snoyman
-
Nicolas Pouillard