module Text.HTML.Scalpel.Internal.Select.Combinators (
    (//)
,   (@:)
,   (@=)
,   (@=~)
,   hasClass
,   notP
,   match
) where
import Text.HTML.Scalpel.Internal.Select.Types
import qualified Data.Text as T
import qualified Text.Regex.Base.RegexLike as RE
import qualified Text.StringLike as TagSoup
(@:) :: TagName -> [AttributePredicate] -> Selector
(@:) tag attrs = MkSelector [toSelectNode tag attrs]
infixl 9 @:
(@=) :: AttributeName -> String -> AttributePredicate
(@=) key value = anyAttrPredicate $ \(attrKey, attrValue) ->
                                      matchKey key attrKey
                                      && TagSoup.fromString value == attrValue
infixl 6 @=
(@=~) :: RE.RegexLike re String
      => AttributeName -> re -> AttributePredicate
(@=~) key re = anyAttrPredicate $ \(attrKey, attrValue) ->
       matchKey key attrKey
    && RE.matchTest re (TagSoup.toString attrValue)
infixl 6 @=~
(//) :: Selector -> Selector -> Selector
(//) a b = MkSelector (as ++ bs)
    where (MkSelector as) = a
          (MkSelector bs) = b
infixl 5 //
hasClass :: String -> AttributePredicate
hasClass clazz = anyAttrPredicate hasClass'
    where
        hasClass' (attrName, classes)
            | "class" == TagSoup.toString attrName = textClass `elem` classList
            | otherwise                            = False
            where textClass   = TagSoup.castString clazz
                  textClasses = TagSoup.castString classes
                  classList   = T.split (== ' ') textClasses
notP :: AttributePredicate -> AttributePredicate
notP (MkAttributePredicate p) = MkAttributePredicate $ not . p
match :: (String -> String -> Bool) -> AttributePredicate
match f = anyAttrPredicate $ \(attrKey, attrValue) ->
              f (TagSoup.toString attrKey) (TagSoup.toString attrValue)