
Here's what I'm working with, followed by what I am trying to do, and the type error I get. I'm leaving things out that I do not think are important. Let me know if I'm missing nessecary info.
curlResp :: (MonadError String 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 $ "Error: " ++ show code ++ " -- " ++ show status else return $ respBody resp
screenScraping :: String -> [String] screenScraping responseBody = let collectedStrings = processHTML responseBody collectedIDLists = createIDList collectedStrings in constructedResourceURIs urlBase collectedIDLists
resourceOpts :: [CurlOption] resourceOpts = [ CurlHttpHeaders [ "Accept: text/javascript, text/html, application/xml, text/xml, */*" , "Accept-Language: en-us,en;q=0.5" , "Accept-Charset: ISO-8859-1,utf-8;q=0.7,*;q=0.7" , "Keep-Alive: 115" , "Connection: keep-alive" , "X-Requested-With: XMLHttpRequest" , "X-Prototype-Version: 1.6.0.3" ] , CurlEncoding "gzip,deflate" ]
obtainCookies :: IO Curl -> String -> IO () obtainCookies curl responseBody = do curl' <- curl let collectedResources = screenScraping responseBody in mapM ( curlResp curl' resourceOpts)
collectedResources > return ()
main :: IO () main = do curl <- initCurl user:pass:_ <- getArgs resp <- generateResourceHtml user pass
case resp of Left err -> print err Right body -> obtainCookies curl body
Here's the error I get. Couldn't match expected type `Char' against inferred type `CurlOption' Expected type: URLString Inferred type: [CurlOption] In the second argument of `curlResp', namely `resourceOpts' In the first argument of `mapM', namely `(curlResp curl' resourceOpts)' The problem I see is a misformed mapM. I am trying to do something like this curlResp curl' resourceOpts "-here-be-a-url" where collectedResources is a [String]. Not sure how to map over it correctly. The other problem I see is this
obtainCookies :: IO Curl -> String -> IO () obtainCookies curl responseBody = do curl' <- curl let collectedResources = screenScraping responseBody in mapM ( curlResp curl' resourceOpts)
collectedResources > return ()
this function does a monadic action (all I want is the cookies) and I don't need the return value. I am not sure that the final line return (), is what I want. My primary question is this. how do I map over collectedResources correctly? Secondary question, is the return correct?

On Wednesday 26 January 2011 23:51:18, Michael Litchard wrote:
Here's what I'm working with, followed by what I am trying to do, and the type error I get. I'm leaving things out that I do not think are important. Let me know if I'm missing nessecary info.
obtainCookies :: IO Curl -> String -> IO () obtainCookies curl responseBody = do curl' <- curl let collectedResources = screenScraping responseBody in mapM ( curlResp curl' resourceOpts)
collectedResources
Looks like you need a flip here: in mapM (flip (curlResp curl') resourceOpts) collectedResources
return ()
If you're throwing away the results of the MapM'ed actions, use mapM_ obtainCookies curl responseBody = do curl' <- curl mapM_ (flip (curlResp curl') resourceOpts) $ screenScraping responseBody
this function does a monadic action (all I want is the cookies) and I don't need the return value. I am not sure that the final line return (), is what I want.
My primary question is this. how do I map over collectedResources correctly? Secondary question, is the return correct?
Use mapM_

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' 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. On Wed, Jan 26, 2011 at 3:13 PM, Daniel Fischer < daniel.is.fischer@googlemail.com> wrote:
On Wednesday 26 January 2011 23:51:18, Michael Litchard wrote:
Here's what I'm working with, followed by what I am trying to do, and the type error I get. I'm leaving things out that I do not think are important. Let me know if I'm missing nessecary info.
obtainCookies :: IO Curl -> String -> IO () obtainCookies curl responseBody = do curl' <- curl let collectedResources = screenScraping responseBody in mapM ( curlResp curl' resourceOpts)
collectedResources
Looks like you need a flip here:
in mapM (flip (curlResp curl') resourceOpts) collectedResources
return ()
If you're throwing away the results of the MapM'ed actions, use mapM_
obtainCookies curl responseBody = do curl' <- curl mapM_ (flip (curlResp curl') resourceOpts) $ screenScraping responseBody
this function does a monadic action (all I want is the cookies) and I don't need the return value. I am not sure that the final line return (), is what I want.
My primary question is this. how do I map over collectedResources correctly? Secondary question, is the return correct?
Use mapM_

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
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'
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.
On Wed, Jan 26, 2011 at 3:13 PM, Daniel Fischer < daniel.is.fischer@googlemail.com> wrote:
On Wednesday 26 January 2011 23:51:18, Michael Litchard wrote:
Here's what I'm working with, followed by what I am trying to do, and the type error I get. I'm leaving things out that I do not think are important. Let me know if I'm missing nessecary info.
obtainCookies :: IO Curl -> String -> IO () obtainCookies curl responseBody = do curl' <- curl let collectedResources = screenScraping responseBody in mapM ( curlResp curl' resourceOpts)
collectedResources
Looks like you need a flip here:
in mapM (flip (curlResp curl') resourceOpts) collectedResources
return ()
If you're throwing away the results of the MapM'ed actions, use mapM_
obtainCookies curl responseBody = do curl' <- curl mapM_ (flip (curlResp curl') resourceOpts) $ screenScraping responseBody
this function does a monadic action (all I want is the cookies) and I don't need the return value. I am not sure that the final line return (), is what I want.
My primary question is this. how do I map over collectedResources correctly? Secondary question, is the return correct?
Use mapM_

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
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.
participants (2)
-
Daniel Fischer
-
Michael Litchard