module FilterHtml (filterHtml) where
import Import
import Data.Maybe (mapMaybe)
import Data.String (IsString)
import Text.HTML.SanitizeXSS (sanitizeAttribute)
import Text.HTML.TagSoup
import qualified Data.Map as Map
import qualified Data.Text.Lazy as TL
filterHtml :: TL.Text -> TL.Text
filterHtml = renderTags . balance Map.empty . safeTags . parseTags
allowedTags :: [TL.Text]
allowedTags = ["div", "p", "br", "blockquote"]
safeTags :: [Tag TL.Text] -> [Tag TL.Text]
safeTags [] = []
safeTags (TagOpen name attrs:ts) | name `elem` allowedTags = TagOpen name (safeAttrs attrs) : safeTags ts
safeTags (TagOpen _ _ :ts) = safeTags ts
safeTags (t@(TagClose name):ts) | name `elem` allowedTags = t : safeTags ts
safeTags (TagClose _:ts) = safeTags ts
safeTags (t:ts) = t : safeTags ts
safeAttrs :: [Attribute TL.Text] -> [Attribute TL.Text]
safeAttrs = sanitizeAttribute' . filterAttrs
where
filterAttrs = filter $ \(n,_) -> n `elem` okAttrs
okAttrs = ["style", "class"]
sanitizeAttribute' :: [Attribute TL.Text] -> [Attribute TL.Text]
sanitizeAttribute' = map fromStrict . mapMaybe sanitizeAttribute . map toStrict
where
fromStrict (a,b) = (TL.fromStrict a, TL.fromStrict b)
toStrict (a,b) = (TL.toStrict a, TL.toStrict b)
balance :: (IsString a, Ord a) => Map.Map a Int -> [Tag a] -> [Tag a]
balance m [] =
concatMap go $ Map.toList m
where
go (name, i) | name == "br" = []
| otherwise = replicate i $ TagClose name
balance m (t@(TagClose name):tags) =
case Map.lookup name m of
Nothing -> TagOpen name [] : TagClose name : balance m tags
Just i ->
let m' = if i == 1
then Map.delete name m
else Map.insert name (i 1) m
in t : balance m' tags
balance m (TagOpen name as : tags) =
TagOpen name as : balance m' tags
where
m' = case Map.lookup name m of
Nothing -> Map.insert name 1 m
Just i -> Map.insert name (i + 1) m
balance m (t:ts) = t : balance m ts