{-# LANGUAGE OverloadedStrings #-}
module Hasmin.Parser.Selector
( selectors
, selector
) where
import Control.Applicative ((<|>), many, some, empty, optional)
import Data.Attoparsec.Combinator (sepBy)
import Data.Attoparsec.Text (asciiCI, char, Parser, satisfy, string)
import qualified Data.Attoparsec.Text as A
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Functor (($>))
import qualified Data.Text.Lazy.Builder as LB
import Data.List.NonEmpty (NonEmpty( (:|) ))
import Hasmin.Parser.Utils
import Hasmin.Parser.String
import Hasmin.Utils
import Hasmin.Types.Selector
import Hasmin.Types.String
selector :: Parser Selector
selector = Selector <$> compoundSelector <*> combinatorsAndSelectors
where combinatorsAndSelectors = many $ mzip (combinator <* skipComments) compoundSelector
combinator :: Parser Combinator
combinator = (skipComments *> ((string ">>" $> DescendantBrackets)
<|> (char '>' $> Child)
<|> (char '+' $> AdjacentSibling)
<|> (char '~' $> GeneralSibling)))
<|> (satisfy ws $> DescendantSpace)
where ws c = c == ' ' || c == '\t' || c == '\n' || c == '\r' || c == '\f'
compoundSelector :: Parser CompoundSelector
compoundSelector = cs1 <|> cs2
where cs1 = do
sel <- typeSelector <|> universal
sels <- many p
pure $ sel:|sels
cs2 = (Universal mempty :|) <$> some p
p = idSel <|> classSel <|> attributeSel <|> pseudo
idSel :: Parser SimpleSelector
idSel = do
_ <- char '#'
name <- mconcat <$> some nmchar
pure . IdSel . TL.toStrict $ LB.toLazyText name
classSel :: Parser SimpleSelector
classSel = char '.' *> (ClassSel <$> ident)
attributeSel :: Parser SimpleSelector
attributeSel = do
_ <- char '['
attId <- lexeme ident
g <- A.option Attribute attValue
_ <- char ']'
pure $ AttributeSel (g attId)
where attValue = do
f <- ((string "^=" $> (:^=:)) <|>
(string "$=" $> (:$=:)) <|>
(string "*=" $> (:*=:)) <|>
(string "=" $> (:=:)) <|>
(string "~=" $> (:~=:)) <|>
(string "|=" $> (:|=:))) <* skipComments
attval <- identOrString <* skipComments
pure (`f` attval)
typeSelector :: Parser SimpleSelector
typeSelector = Type <$> opt namespacePrefix <*> ident
universal :: Parser SimpleSelector
universal = Universal <$> opt namespacePrefix <* char '*'
namespacePrefix :: Parser Text
namespacePrefix = opt (ident <|> string "*") <* char '|'
pseudo :: Parser SimpleSelector
pseudo = char ':' *> (pseudoElementSelector <|> pseudoClassSelector)
where pseudoClassSelector = do
i <- ident
c <- A.peekChar
case c of
Just '(' -> char '(' *> case Map.lookup (T.toLower i) fpcMap of
Just p -> functionParser p
Nothing -> functionParser (FunctionalPseudoClass i <$> A.takeWhile (/= ')'))
_ -> pure $ PseudoClass i
pseudoElementSelector =
(char ':' *> (PseudoElem <$> ident)) <|> (ident >>= handleSpecialCase)
where
handleSpecialCase :: Text -> Parser SimpleSelector
handleSpecialCase t
| isSpecialPseudoElement = pure $ PseudoElem t
| otherwise = empty
where isSpecialPseudoElement = T.toLower t `elem` specialPseudoElements
anplusb :: Parser AnPlusB
anplusb = (asciiCI "even" $> Even)
<|> (asciiCI "odd" $> Odd)
<|> do
s <- optional parseSign
dgts <- A.option mempty digits
case dgts of
[] -> ciN *> skipComments *> A.option (A s Nothing) (AB s Nothing <$> bValue)
_ -> let n = read dgts :: Int
in (ciN *> skipComments *> A.option (A s $ Just n) (AB s (Just n) <$> bValue))
<|> (pure . B $ getSign s * n)
where ciN = satisfy (\c -> c == 'N' || c == 'n')
parseSign = (char '-' $> Minus) <|> (char '+' $> Plus)
getSign (Just Minus) = -1
getSign _ = 1
bValue = do
readPlus <- (char '-' $> False) <|> (char '+' $> True)
d <- skipComments *> digits
if readPlus
then pure $ read d
else pure $ read ('-':d)
fpcMap :: Map Text (Parser SimpleSelector)
fpcMap = Map.fromList
[buildTuple "nth-of-type" (\x -> FunctionalPseudoClass2 x <$> anplusb)
,buildTuple "nth-last-of-type" (\x -> FunctionalPseudoClass2 x <$> anplusb)
,buildTuple "nth-column" (\x -> FunctionalPseudoClass2 x <$> anplusb)
,buildTuple "nth-last-column" (\x -> FunctionalPseudoClass2 x <$> anplusb)
,buildTuple "not" (\x -> FunctionalPseudoClass1 x <$> compoundSelectorList)
,buildTuple "matches" (\x -> FunctionalPseudoClass1 x <$> compoundSelectorList)
,buildTuple "nth-child" (anbAndSelectors . FunctionalPseudoClass3)
,buildTuple "nth-last-child" (anbAndSelectors . FunctionalPseudoClass3)
,buildTuple "lang" (const (Lang <$> identOrString))
]
where buildTuple t c = (t, c t)
compoundSelectorList = (:) <$> compoundSelector <*> many (comma *> compoundSelector)
anbAndSelectors constructor = do
a <- anplusb <* skipComments
o <- A.option [] (asciiCI "of" *> skipComments *> compoundSelectorList)
pure $ constructor a o
selectors :: Parser [Selector]
selectors = lexeme selector `sepBy` char ','
identOrString :: Parser (Either Text StringType)
identOrString = (Left <$> ident) <|> (Right <$> stringtype)