Two simple combinators on Element: getAttr and hasAttr.

This commit is contained in:
vi 2014-06-23 14:39:19 +08:00
parent 11b57a4bad
commit 773419b9a0
2 changed files with 32 additions and 0 deletions

View File

@ -0,0 +1,11 @@
module Text.Taggy.Combinators (hasAttr, getAttr) where
import Prelude hiding (lookup)
import Text.Taggy.DOM (Element(..), AttrName, AttrValue)
import Data.HashMap.Strict (lookup, keys)
hasAttr :: Element -> AttrName -> Bool
hasAttr = flip elem . keys . eltAttrs
getAttr :: Element -> AttrName -> Maybe AttrValue
getAttr = flip lookup . eltAttrs

View File

@ -0,0 +1,21 @@
{-# LANGUAGE OverloadedStrings #-}
module Text.Taggy.CombinatorsSpec where
import Text.Taggy.Combinators
import Test.Hspec
import Text.Taggy.DOM
import Data.HashMap.Strict
spec :: Spec
spec = do
let element = Element "html" (fromList [("xmlns", "http://www.w3.org/1999/xhtml")]) []
describe "hasAttr" $ do
it "Tests whether an attribute is present." $ do
(element `hasAttr` "xmlns") `shouldBe` True
(element `hasAttr` "href") `shouldBe` False
describe "getAttr" $ do
it "Retrieves present attributes." $
(element `getAttr` "xmlns") `shouldBe` Just "http://www.w3.org/1999/xhtml"
it "Nothing's missing attributes." $
(element `getAttr` "style") `shouldBe` Nothing