
Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download": TagSoupExtensions.lhs:24:2: Warning: In the use of `openItem' (imported from Text.HTML.Download): Deprecated: "Use package HTTP, module Network.HTTP, getResponseBody =<< simpleHTTP (getRequest url)" TagSoupExtensions.lhs:24:2: Warning: In the use of `openURL' (imported from Text.HTML.Download): Deprecated: "Use package HTTP, module Network.HTTP, getResponseBody =<< simpleHTTP (getRequest url)" Ok, modules loaded: TQ.TagSoup.TagSoupExtensions. *TQ.TagSoup.TagSoupExtensions> From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ralph Hodgson Sent: Wednesday, May 19, 2010 10:30 AM To: 'Malcolm Wallace' Cc: haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] TagSoup 0.9 Thanks Malcolm, Providing a 'String' type argument worked:
type Bundle = [Tag String]
extractTags :: Tag String -> Tag String -> Bundle -> Bundle
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
From: Malcolm Wallace [mailto:malcolm.wallace@me.com]
Sent: Wednesday, May 19, 2010 1:48 AM
To: rhodgson@topquadrant.com
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] TagSoup 0.9
Neil says that the API of TagSoup changed in 0.9.
All usages of the type Tag should now take a type argument, e.g. Tag String.
Regards,
Malcolm
On Wednesday, May 19, 2010, at 08:05AM, "Ralph Hodgson"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Hello Neil , I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error: TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' Failed, modules loaded: TQ.Common.TextAndListHandling. where line 29 is the type declaration for 'bundle' in the following code:
module TQ.TagSoup.TagSoupExtensions where
import TQ.Common.TextAndListHandling
import Text.HTML.TagSoup
import Text.HTML.Download
import Control.Monad
import Data.List
import Data.Char
type Bundle = [Tag]
[snip]
tagsOnPage :: String -> IO(String)
tagsOnPage url = do
tags <- liftM parseTags $ openURL url
let results = unlines $ map(show) $ tags
return (results)
extractTags :: Tag -> Tag -> [Tag] -> [Tag]
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
extractTagsBetween :: Tag -> [Tag] -> [Tag]
extractTagsBetween _ [] = []
extractTagsBetween markerTag tags = if startTags == []
then []
else [head startTags] ++ (takeWhile (~/= markerTag ) $ tail startTags)
where
startTags = dropWhile (~/= markerTag ) tags
I need to repair this code quickly. I am hoping you can quickly help me resolve this. Thanks. Ralph Hodgson, @ralphtq http://twitter.com/ralphtq