
Here's the three main functions involved. Let me know if I am missing pertinent information. I'm having difficulty unraveling this error message. Help?
obtainCookies :: Curl -> String -> IO () obtainCookies curl responseBody = do return $ last $ liftM $ mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody
screenScraping :: String -> [URLString] screenScraping responseBody = let collectedStrings = processHTML responseBody collectedIDLists = createIDList collectedStrings in constructedResourceURIs urlBase collectedIDLists
constructedResourceURIs :: String -> [String] -> [URLString] constructedResourceURIs url resourceIDs = let frontURI = url ++ "/launchWebForward.do?" midURI = map (frontURI ++) resourceIDs in map (++ "&policy=0&returnTo=%2FshowWebForwards.do") midURI
HtmlParsing.lhs:81:22: Couldn't match expected type `[URLString]' against inferred type `String -> [URLString]' In the second argument of `mapM', namely `screenScraping' In the second argument of `($)', namely `mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody' In the second argument of `($)', namely `liftM $ mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'

It seems like you're being bitten by precedence rules. Your expression
mapM (...) screenScraping responseBody evaluates like this: (mapM
(...) screenScraping) responseBody. You probably want parentheses
aroung screenScraping responseBody. So something like:
mapM (flip ....) (screenScraping responseBody)
or
mapM (flip ...) $ screenScraping responseBody
On Tue, Feb 8, 2011 at 5:48 PM, Michael Litchard
Here's the three main functions involved. Let me know if I am missing pertinent information.
I'm having difficulty unraveling this error message. Help?
obtainCookies :: Curl -> String -> IO ()
obtainCookies curl responseBody = do return $ last $ liftM $
mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody
screenScraping :: String -> [URLString] screenScraping responseBody = let collectedStrings = processHTML responseBody
collectedIDLists = createIDList collectedStrings in constructedResourceURIs urlBase collectedIDLists
constructedResourceURIs :: String -> [String] -> [URLString] constructedResourceURIs url resourceIDs =
let frontURI = url ++ "/launchWebForward.do?" midURI = map (frontURI ++) resourceIDs
in map (++ "&policy=0&returnTo=%2FshowWebForwards.do") midURI
HtmlParsing.lhs:81:22: Couldn't match expected type `[URLString]'
against inferred type `String -> [URLString]' In the second argument of `mapM', namely `screenScraping'
In the second argument of `($)', namely `mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
In the second argument of `($)', namely `liftM $ mapM
(flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wednesday 09 February 2011 00:48:52, Michael Litchard wrote:
Here's the three main functions involved. Let me know if I am missing pertinent information.
I'm having difficulty unraveling this error message. Help?
obtainCookies :: Curl -> String -> IO () obtainCookies curl responseBody = do return $ last $ liftM $
mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody
This is parsed as (mapM (flip (curlResp2 curl) resourceOpts) screenScraping) responseBody which of course doesn't make sense, since screenScraping is a function, not a list. You forgot a ($) or parentheses, mapM (flip (curlResp2 curl) resourceOpts) $ screenScraping responseBody But then you get another error, liftM :: Monad m => (a -> b) -> m a -> m b so it expects a function as first argument, but it gets an (IO [a]). You probably meant liftM last $ mapM ... but that already is an IO (), so the return shouldn't be there (it would make obtainCookies an IO (IO ()), which isn't what you want. However, curlResp2 :: Curl -> String -> [CurlOpts {- or whatever opts they were -}] -> IO () so it doesn't return any meaningful value. Then don't use mapM. mapM should only be used if one really wants to collect the results of the mapM'ed action, if the result type of action is IO () [more generally, Monad m => m ()] or one isn't interested in the results, only in the effects of running the actions, one should use mapM_ :: Monad m => (a -> m b) -> [a] -> m () which discards the results of the actions and is much more efficient (since it needn't keep book). So, obtainCookies curl responseBody = mapM_ (flip (curlResp2 curl) resourceOpts) (screenScraping responseBody)
screenScraping :: String -> [URLString] screenScraping responseBody = let collectedStrings = processHTML responseBody collectedIDLists = createIDList collectedStrings in constructedResourceURIs urlBase collectedIDLists
What about screenScraping = constructedResourceURIs urlBase . createIDList . processHTML ? Or, if you prefer, with (>>>) [from Control.Arrow or defined yourself as flip (.)], in left-to-right order: screenScraping = processHTML >>> createIDList >>> constructedResourceURIs urlBase
constructedResourceURIs :: String -> [String] -> [URLString] constructedResourceURIs url resourceIDs = let frontURI = url ++ "/launchWebForward.do?" midURI = map (frontURI ++) resourceIDs in map (++ "&policy=0&returnTo=%2FshowWebForwards.do") midURI
constructedResourceURIs url resourceIDs = [frontURI ++ str ++ uriEnd | str <- resourceIDs] where frontURI = url ++ "/launchWebForward.do?" uriEnd = "&policy=0&returnTo=%2FshowWebForwards.do" or constructedResourceURIs url = map ((frontURI ++) . (++ uriEnd)) where frontURI = url ++ "/launchWebForward.do?" uriEnd = "&policy=0&returnTo=%2FshowWebForwards.do" if you develop a taste for partial pointfreeness.
HtmlParsing.lhs:81:22: Couldn't match expected type `[URLString]' against inferred type `String -> [URLString]' In the second argument of `mapM', namely `screenScraping' In the second argument of `($)', namely `mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody' In the second argument of `($)', namely `liftM $ mapM (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
participants (3)
-
aditya siram
-
Daniel Fischer
-
Michael Litchard