{-# LANGUAGE NoImplicitPrelude, OverloadedStrings, UnicodeSyntax, QuasiQuotes #-} module Data.Microformats2.Parser.HtmlUtilSpec (spec) where import Prelude.Compat import Test.Hspec import TestCommon import Data.Microformats2.Parser.HtmlUtil spec ∷ Spec spec = do describe "getInnerTextRaw" $ do it "returns textContent without handling imgs" $ do let txtraw = getInnerTextRaw . documentRoot . parseLBS txtraw [xml|
This is text content NOPE without any stuff.
|] `shouldBe` Just "This is text content without any stuff." describe "getInnerTextWithImgs" $ do it "returns textContent with handling imgs" $ do let txtraw = getInnerTextWithImgs . documentRoot . parseLBS txtraw [xml|
This is text content with an alt .
|] `shouldBe` Just "This is text content with an alt and-src." describe "getInnerHtmlSanitized" $ do it "doesn't eat custom properties but eats scripts" $ do let geth = getInnerHtmlSanitized Nothing . documentRoot . parseLBS geth [xml|memes|] `shouldBe` Just "memes"