Combinator on Element: innerText.

This commit is contained in:
vi 2014-06-23 15:03:51 +08:00
parent 773419b9a0
commit b46ea8b696
2 changed files with 15 additions and 5 deletions

View File

@ -1,7 +1,9 @@
module Text.Taggy.Combinators (hasAttr, getAttr) where
module Text.Taggy.Combinators (hasAttr, getAttr, innerText) where
import Prelude hiding (lookup)
import Text.Taggy.DOM (Element(..), AttrName, AttrValue)
import Data.Monoid (mconcat)
import Data.Text (Text)
import Text.Taggy.DOM (Element(..), Node(..), AttrName, AttrValue)
import Data.HashMap.Strict (lookup, keys)
hasAttr :: Element -> AttrName -> Bool
@ -9,3 +11,8 @@ hasAttr = flip elem . keys . eltAttrs
getAttr :: Element -> AttrName -> Maybe AttrValue
getAttr = flip lookup . eltAttrs
innerText :: Element -> Text
innerText = mconcat . map decons . eltChildren
where decons (NodeElement e) = innerText e
decons (NodeContent x) = x

View File

@ -4,12 +4,12 @@ module Text.Taggy.CombinatorsSpec where
import Text.Taggy.Combinators
import Test.Hspec
import Text.Taggy.DOM
import Data.HashMap.Strict
import Text.Taggy
spec :: Spec
spec = do
let element = Element "html" (fromList [("xmlns", "http://www.w3.org/1999/xhtml")]) []
let element = (\(NodeElement e) -> e) . head . domify . taggyWith False $
"<html xmlns=\"http://www.w3.org/1999/xhtml\">foo<bar>baz</bar></html>"
describe "hasAttr" $ do
it "Tests whether an attribute is present." $ do
(element `hasAttr` "xmlns") `shouldBe` True
@ -19,3 +19,6 @@ spec = do
(element `getAttr` "xmlns") `shouldBe` Just "http://www.w3.org/1999/xhtml"
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." $
innerText element `shouldBe` "foobaz"