Two new combinators: hasName and (/&).

This commit is contained in:
vi 2014-06-23 16:13:42 +08:00
parent 1f60b9c9b5
commit a4e6b9466a
2 changed files with 22 additions and 4 deletions

View File

@ -1,4 +1,4 @@
module Text.Taggy.Combinators (hasAttr, getAttr, innerText, (//)) where
module Text.Taggy.Combinators (hasName, hasAttr, getAttr, innerText, (//), (/&)) where
import Prelude hiding (lookup)
import Data.Monoid (mconcat)
@ -6,6 +6,9 @@ import Data.Text (Text)
import Text.Taggy.DOM (Element(..), Node(..), AttrName, AttrValue)
import Data.HashMap.Strict (lookup, keys)
hasName :: Element -> Text -> Bool
hasName = (==) . eltName
hasAttr :: Element -> AttrName -> Bool
hasAttr = flip elem . keys . eltAttrs
@ -22,3 +25,10 @@ innerText = mconcat . map decons . eltChildren
where expand = concat . map decons . eltChildren
decons (NodeElement e) = e : expand e
decons _ = []
(/&) :: Element -> [(Element -> Bool)] -> [Element]
(/&) element [] = [element]
(/&) element (x:xs) = concat . map (/& xs) . filter x . immediateChildren $ eltChildren element
where immediateChildren = map (\(NodeElement e) -> e) . filter isElement
isElement (NodeElement _) = True
isElement _ = False

View File

@ -2,6 +2,7 @@
module Text.Taggy.CombinatorsSpec where
import Data.Monoid
import Text.Taggy.Combinators
import Test.Hspec
import Text.Taggy
@ -9,7 +10,10 @@ import Text.Taggy
spec :: Spec
spec = do
let element = (\(NodeElement e) -> e) . head . domify . taggyWith False $
"<html xmlns=\"http://www.w3.org/1999/xhtml\">foo<bar class=\"el\">baz</bar><qux class=\"el\"></qux></html>"
"<html xmlns=\"http://www.w3.org/1999/xhtml\">foo<bar class=\"el\">baz</bar><qux class=\"el\"><quux></quux></qux></html>"
describe "hasName" $ do
it "Test whether an element has a given name." $ do
(element `hasName` "html") `shouldBe` True
describe "hasAttr" $ do
it "Tests whether an attribute is present." $ do
(element `hasAttr` "xmlns") `shouldBe` True
@ -20,7 +24,7 @@ spec = do
it "Nothing's missing attributes." $
(element `getAttr` "style") `shouldBe` Nothing
describe "innerText" $ do
it "Should concatenate the NodeContent of the target element and all its children." $
it "Should concatenate the NodeContent of the target element and all its children." $
innerText element `shouldBe` "foobaz"
describe "(//)" $ do
it "Should return all children satisfying the predicate." $ do
@ -28,4 +32,8 @@ spec = do
result = element // predicate
result `shouldSatisfy` not . null
result `shouldSatisfy` all predicate
describe "(/&)" $ do
it "Should traverse an element's children, selecting only those matching provided predicates at each point." $ do
element /& [] `shouldBe` [element]
element /& [const False] `shouldBe` []
element /& [flip hasAttr "class", flip hasName "quux"] `shouldBe` [Element "quux" mempty mempty]