[Haskell-beginners] Trying to use map

Daniel Fischer daniel.is.fischer at googlemail.com
Thu Jan 27 01:20:07 CET 2011


On Thursday 27 January 2011 00:36:57, Michael Litchard wrote:
> google hosed my indentation
>
> > obtainCookies :: IO Curl -> String -> IO ()
> > obtainCookies curl responseBody = do
> >               curl' <- curl
> >               mapM_ (flip (curlResp curl') resourceOpts) $
> >                     screenScraping responseBody
>
> On Wed, Jan 26, 2011 at 3:32 PM, Michael Litchard 
<michael at schmong.org>wrote:
> > Thank you.
> >
> > Here is where things stand now
> >
> > > obtainCookies :: IO Curl -> String -> IO ()
> > > obtainCookies curl responseBody = do
> > > curl' <- curl
> > > mapM_ (flip (curlResp curl') resourceOpts) $
> > >
> > > screenScraping responseBody
> >
> > and the error
> >
> > htmlParsing.lhs:78:2:
> >
> > Couldn't match expected type `[Char]'
> > against inferred type `GHC.IO.Exception.IOException'
> > Expected type: String
> >
> > Inferred type: IOError
> > When using functional dependencies to combine
> > MonadError IOError IO,
> > arising from the dependency `m -> e'
> > in the instance declaration at <no location info>
> > MonadError String IO,
> >
> > arising from a use of `curlResp' at HtmlParsing.lhs:80:29-42
> > When generalising the type(s) for `obtainCookies'

You have real problems now.
The MonadError Class has a functional dependency, and there's the

instance MonadError IOException IO where ...

In curlResp, you give the constraint (MonadError String m, MonadIO m), so 
by the functional dependency, m can't be IO.

I see two possibilities

a) modify curlResp,

curlResp :: (Error e, MonadError e m, MonadIO m) =>
       Curl -> URLString -> [CurlOption] -> m String --CurlResponse
curlResp curl url opts = do
  resp <- liftIO $ (do_curl_ curl url opts :: IO CurlResponse)
  let code   = respCurlCode resp
      status = respStatus resp
  if code /= CurlOK || status /= 200
     then throwError $ strMsg $ "Error: " ++ show code ++ " -- " ++ show 
status
     else return $ respBody resp

IOException is an instance of Error, as is String, so this is more general 
than the previous. You can't directly throw the error string, you have to 
pass it to strMsg before throwing.
That's not much of a change, if possible, I'd do that.

b) make a newtype wrapper IOS around IO, provide a MonadIO instance for 
that and an instance MonadError String IOS, then change obtainCookies (and 
what needs to be changed thereafter, such changes tend to propagate):

obtainCookies :: IO Curl -> String -> IOS ()
obtainCookies curl responseBody = do
               curl' <- liftIO curl
               mapM_ (flip (curlResp curl') resourceOpts) $
                     screenScraping responseBody

> >
> > I'm way beyond my ken here, trying to grow. I have to do error
> > handling (this will be production code when it grows up), got some
> > suggestions on how to do so, but am flying blind in new territory.
> >
> > Any suggestions on how to proceed would be much appreciated.
> >



More information about the Beginners mailing list