module Text.HTML.Scalpel.Internal.Select.Types (
Selector (..)
, AttributePredicate (..)
, checkPred
, AttributeName (..)
, matchKey
, anyAttrPredicate
, TagName (..)
, SelectNode (..)
, tagSelector
, anySelector
, toSelectNode
) where
import Data.Char (toLower)
import Data.String (IsString, fromString)
import qualified Text.HTML.TagSoup as TagSoup
import qualified Text.StringLike as TagSoup
import qualified Data.Text as T
data AttributeName = AnyAttribute | AttributeString String
matchKey :: TagSoup.StringLike str => AttributeName -> str -> Bool
matchKey (AttributeString s) = ((TagSoup.fromString $ map toLower s) ==)
matchKey AnyAttribute = const True
instance IsString AttributeName where
fromString = AttributeString
data AttributePredicate
= MkAttributePredicate
(forall str. TagSoup.StringLike str => [TagSoup.Attribute str]
-> Bool)
checkPred :: TagSoup.StringLike str
=> AttributePredicate -> [TagSoup.Attribute str] -> Bool
checkPred (MkAttributePredicate p) = p
anyAttrPredicate :: (forall str. TagSoup.StringLike str => (str, str) -> Bool)
-> AttributePredicate
anyAttrPredicate p = MkAttributePredicate $ any p
newtype Selector = MkSelector [SelectNode]
tagSelector :: String -> Selector
tagSelector tag = MkSelector [toSelectNode (TagString tag) []]
anySelector :: Selector
anySelector = MkSelector [SelectAny []]
instance IsString Selector where
fromString = tagSelector
data SelectNode = SelectNode !T.Text [AttributePredicate]
| SelectAny [AttributePredicate]
data TagName = AnyTag | TagString String
instance IsString TagName where
fromString = TagString
toSelectNode :: TagName -> [AttributePredicate] -> SelectNode
toSelectNode AnyTag = SelectAny
toSelectNode (TagString str) = SelectNode . TagSoup.fromString $ map toLower str