Combinators: trees extracts subtrees, including the target parent.

This commit is contained in:
vi 2014-06-24 15:04:04 +08:00
parent 349f7b7d50
commit e7487d337c
2 changed files with 8 additions and 2 deletions

View File

@ -1,6 +1,6 @@
{-# LANGUAGE LambdaCase #-}
module Text.Taggy.Combinators (hasName, hasAttr, getAttr, innerText, (//), (/&), subtrees) where
module Text.Taggy.Combinators (hasName, hasAttr, getAttr, innerText, (//), (/&), trees, subtrees) where
import Prelude hiding (lookup)
import Data.Monoid (mconcat)
@ -29,6 +29,9 @@ innerText = mconcat . map getContent . eltChildren
(/&) element [] = [element]
(/&) element (x:xs) = (/& xs) <=< filter x . catElements $ eltChildren element
trees :: Element -> [Element]
trees = ap (:) subtrees
subtrees :: Element -> [Element]
subtrees = ap (:) subtrees <=< catElements . eltChildren

View File

@ -37,6 +37,9 @@ spec = do
element /& [] `shouldBe` [element]
element /& [const False] `shouldBe` []
element /& [flip hasAttr "class", flip hasName "quux"] `shouldBe` [Element "quux" mempty mempty]
describe "trees" $ do
it "Extracts all subtrees of its target, including the target (parent node)." $ do
trees element `shouldBe` element:subtrees element
describe "subtrees" $ do
it "Extracts all subtrees of it's target." $ do
it "Extracts all subtrees of its target, excluding the target (parent node)." $ do
length (subtrees element) `shouldBe` 3