我有一个字符串r
,其值低于,我想提取字符串"index.htm"
。
"<a id=\"ctl00_HyperLink_home\" href=\"index.htm\"> " ++
"<font color=\"#FFFFFF\">Home</font>" ++
"</a>"
我的代码是
parseHref :: String -> String
parseHref ('h':'r':'e':'f':'=':'\"':xs) = takeWhile( '\"'>) xs
parseHref (_:xs) = parseHref xs
但是parseHref r
是空字符串。有人可以帮忙吗?提前谢谢。
答案 0 :(得分:8)
"
是ASCII 32
i
是ASCII 105
因为"
不大于i
,所以takeWhile什么也不做,并返回一个空字符串。
也许您应该使用('\"' /=)
?
答案 1 :(得分:3)
1)您应该使用'"'
'\"'
内容
2)你的功能错过了空列表[]
的情况,例如
parseHref [] = []
3)takeWhile
中的条件是错误的。您希望在找到'"'
时停止,因此('"' /=)
- 正确的条件
4)也许您应该使用Maybe String
表示失败:
parseHref :: String -> Maybe String
parseHref [] = Nothing
parseHref ('h':'r':'e':'f':'=':'"':xs) = Just $ takeWhile ('"' /=) xs
parseHref (_:xs) = parseHref xs
答案 2 :(得分:2)
手工解析HTML或甚至使用正则表达式都非常容易出错。考虑使用TagSoup等库。
第一次切割看起来像
import Text.HTML.TagSoup
ctl00_HyperLink_home_url s =
map (fromAttrib "href") $
filter (~== "<a id=ctl00_HyperLink_home href=''>") $
parseTags s
它的类型为String -> [String]
,因此界面有点笨拙。
为界面添加一些灵活性
{-# LANGUAGE ViewPatterns #-}
import Control.Monad (MonadPlus(..))
import Text.HTML.TagSoup
ctl00_HyperLink_home_url :: (MonadPlus m) => String -> m String
ctl00_HyperLink_home_url (anchors -> tags) = popSome tags
where popSome [] = mzero
popSome (t:_) = return $ fromAttrib "href" t
anchors :: String -> [Tag String]
anchors = filter (~== "<a id=ctl00_HyperLink_home href=''>") . parseTags
在行动中,这看起来像
ghci> ctl00_HyperLink_home_url r :: Maybe String
Just "index.htm"
ghci> ctl00_HyperLink_home_url r :: [String]
["index.htm"]
ghci> ctl00_HyperLink_home_url "x" :: Maybe String
Nothing
ghci> ctl00_HyperLink_home_url "x" :: [String]
[]
在范围Control.Monad.STM的情况下,我们可以
ghci> atomically $ ctl00_HyperLink_home_url r
"index.htm"
要提取内部文本,我们需要的不仅仅是open标记。假设参数包含锚标记和仅子项,您可以从“Drinking TagSoup By Example”借用并写入
ctl00 :: String -> (String,String)
ctl00 html =
let as = head $
sections (~== "<a id='ctl00_HyperLink_home' href=''") $
parseTags html
text = unwords . words . innerText
in (fromAttrib "href" $ head as, text as)
行动中:
ghci> ctl00 r
("index.htm","Home")
部分函数head
的多个应用程序令人担忧。让我们把它放回MonadPlus
里面,观察在末尾追加大写字母M的惯例,以表示一元善良。
import Control.Arrow ((&&&))
import Control.Monad
import Data.List (foldl')
ctl00M :: (MonadPlus m) => String -> m (String, String)
ctl00M = foldl' mplus mzero
. map (return . (fromAttrib "href" . head &&& text))
. sections (~== "<a id='ctl00_HyperLink_home' href=''")
. parseTags
where text = unwords . words . innerText
最后,对于一个通用函数,其应用程序提供一个字典,其键是控件标识符,其值是表单对( url ,内部文本),使用< / p>
controls :: String -> Map String (String,String)
controls = fromList
. concatMap idHrefText
. sections (~== "<a id='' href=''>")
. parseTags
where
idHrefText (a:tags)
| isControl a = [(ctlId a, (href a, text tags))]
| otherwise = []
isControl = ("ctl" `isPrefixOf`) . ctlId
ctlId = fromAttrib "id"
href = fromAttrib "href"
text tags = let (a,_) = break (~== "</a>") tags
extract = unwords . words . innerText
in extract a
打破</a>
是为了避免抓取太多文字。
例如
ghci> (controls r) ! "ctl00_HyperLink_home"
("index.htm","Home")