module Data.Niagra.Selector
(
Selector(..),
buildSelector,
(<||>),
(.>.),
(.+.),
(.~.),
(#),
(!),
(<:>),
(<::>),
(|=|),
(|~=|),
(||=|),
(|^=|),
(|$=|),
(|*=|),
cls,
ident,
pseudoClass,
pseudoType
)
where
import Data.Monoid
import Data.List (intersperse)
import qualified Data.String as S
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder
data Selector = Child Selector Selector
| Precedence Selector Selector
| ImmediatePrecedence Selector Selector
| Descendant Selector Selector
| PseudoClass Selector Text (Maybe Selector)
| PseudoType Selector Text (Maybe Selector)
| AttrExistential Selector Text
| AttrEquality Selector Text Text
| AttrWhitespaceListContains Selector Text Text
| AttrHyphenListContains Selector Text Text
| AttrBeginsWith Selector Text Text
| AttrEndsWith Selector Text Text
| AttrSubstring Selector Text Text
| Class Selector Text
| Id Selector Text
| FontFace
| SelectorList [Selector]
| Raw Text
| Null
deriving (Eq,Show)
instance S.IsString Selector where
fromString = Raw . TL.pack
buildSelector :: Selector -> Builder
buildSelector = f
where
between a e b = singleton a <> b <> singleton e
parens = between '(' ')'
bracketed = between '[' ']'
curlyb = between '{' '}'
quoted = between '"' '"' . fromLazyText
attr e a v = bracketed $ fromLazyText a <> singleton e <> "=" <> quoted v
f Null = mempty
f (Raw v) = fromLazyText v
f (Child a b) = f a <> ">" <> f b
f (Descendant a b) = f a <> " " <> f b
f (ImmediatePrecedence a b) = f a <> "+" <> f b
f (Precedence a b) = f a <> "~" <> f b
f (PseudoClass a n (Just b)) = f (PseudoClass a n Nothing) <> parens (f b)
f (PseudoClass a n Nothing) = f a <> ":" <> fromLazyText n
f (PseudoType a n (Just b)) = f (PseudoType a n Nothing) <> parens (f b)
f (PseudoType a n Nothing) = f a <> "::" <> fromLazyText n
f (Class a cls) = f a <> "." <> fromLazyText cls
f (Id a i) = f a <> "#" <> fromLazyText i
f (SelectorList xs) = mconcat $ map f $ intersperse "," xs
f (AttrExistential s a) = f s <> bracketed (fromLazyText a)
f (AttrEquality s a v) = f s <> bracketed (fromLazyText a <> "=" <> quoted v)
f (AttrWhitespaceListContains s a v) = f s <> attr '~' a v
f (AttrHyphenListContains s a v) = f s <> attr '|' a v
f (AttrBeginsWith s a v) = f s <> attr '^' a v
f (AttrEndsWith s a v) = f s <> attr '$' a v
f (AttrSubstring s a v) = f s <> attr '*' a v
f FontFace = "@font-face"
instance Monoid Selector where
mempty = Null
mappend Null x = x
mappend x Null = x
mappend (SelectorList xs) x = SelectorList $ x:xs
mappend x (SelectorList xs) = SelectorList $ x:xs
mappend a b = SelectorList [a,b]
mconcat xs = SelectorList xs
infixl 5 .>.
(.>.) :: Selector
-> Selector
-> Selector
(.>.) = Child
infixl 5 .+.
(.+.) :: Selector
-> Selector
-> Selector
(.+.) = ImmediatePrecedence
infixl 5 .~.
(.~.) :: Selector
-> Selector
-> Selector
(.~.) = Precedence
infixl 5 .|.
(.|.) :: Selector
-> Selector
-> Selector
(.|.) = Descendant
infixl 4 #
(#) :: Selector
-> Text
-> Selector
(#) = Id
infixl 4 !
(!) :: Selector
-> Text
-> Selector
(!) = Class
infixl 4 <:>
(<:>) :: Selector
-> Text
-> Selector
(<:>) sel n = PseudoClass sel n Nothing
pseudoClass :: Text
-> Maybe Selector
-> Selector
pseudoClass = PseudoClass Null
infixl 4 <::>
(<::>) :: Selector
-> Text
-> Selector
(<::>) sel n = PseudoType sel n Nothing
pseudoType :: Text
-> Maybe Selector
-> Selector
pseudoType = PseudoType Null
infixl 4 <||>
(<||>) :: Selector
-> Selector
-> Selector
(<||>) s Null = s
(<||>) Null s = s
(<||>) s (AttrExistential _ a) = AttrExistential s a
(<||>) s (AttrEquality _ a b) = AttrEquality s a b
(<||>) s (AttrWhitespaceListContains _ a l) = AttrWhitespaceListContains s a l
(<||>) s (AttrHyphenListContains _ a l) = AttrHyphenListContains s a l
(<||>) s (AttrBeginsWith _ a str) = AttrBeginsWith s a str
(<||>) s (AttrEndsWith _ a str) = AttrEndsWith s a str
(<||>) s (AttrSubstring _ a str) = AttrSubstring s a str
(<||>) s (PseudoClass _ c m) = PseudoClass s c m
(<||>) s (PseudoType _ c m) = PseudoType s c m
(<||>) (SelectorList xs) a = SelectorList $ map (\s -> s <||> a) xs
(<||>) s (Id _ i) = Id s i
(<||>) s (Class _ c) = Class s c
(<||>) s s' = Descendant s s'
cls :: Text
-> Selector
cls = Class Null
ident :: Text
-> Selector
ident = Id Null
infixl 3 |=|
(|=|) :: Text
-> Text
-> Selector
(|=|) = AttrEquality Null
infixl 3 |~=|
(|~=|) :: Text
-> Text
-> Selector
(|~=|) = AttrWhitespaceListContains Null
infixl 3 ||=|
(||=|) :: Text
-> Text
-> Selector
(||=|) = AttrHyphenListContains Null
infixl 3 |^=|
(|^=|) :: Text
-> Text
-> Selector
(|^=|) = AttrBeginsWith Null
infixl 3 |$=|
(|$=|) :: Text
-> Text
-> Selector
(|$=|) = AttrEndsWith Null
infixl 3 |*=|
(|*=|) :: Text
-> Text
-> Selector
(|*=|) = AttrSubstring Null