module Hasmin.Parser.Internal (
stylesheet
, atRule
, declaration
, declarations
, selector
) where
import Control.Arrow (first)
import Control.Applicative ((<|>), many)
import Control.Monad (mzero)
import Data.Functor (($>))
import Data.Attoparsec.Combinator (lookAhead, sepBy, endOfInput)
import Data.Attoparsec.Text (asciiCI, char, many1, manyTill,
option, Parser, satisfy, string)
import Data.List.NonEmpty (NonEmpty( (:|) ))
import Data.Monoid ((<>))
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Text.Lazy.Builder as LB
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Data.Attoparsec.Text as A
import qualified Data.Char as C
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Hasmin.Parser.Utils
import Hasmin.Parser.Value
import Hasmin.Selector
import Hasmin.Types.Stylesheet
import Hasmin.Types.Declaration
selector :: Parser Selector
selector = Selector <$> compoundSelector
<*> many ((,) <$> (combinator <* skipComments) <*> compoundSelector)
combinator :: Parser Combinator
combinator = (skipComments *> ((string ">>" $> Descendant)
<|> (char '>' $> Child)
<|> (char '+' $> AdjacentSibling)
<|> (char '~' $> GeneralSibling)))
<|> (satisfy ws $> Descendant)
where ws c = c == ' ' || c == '\t' || c == '\n' || c == '\r' || c == '\f'
compoundSelector :: Parser CompoundSelector
compoundSelector =
(:|) <$> (typeSelector <|> universal)
<*> many p
<|> ((Universal mempty :|) <$> many1 p)
where p = idSel <|> classSel <|> attributeSel <|> pseudo
idSel :: Parser SimpleSelector
idSel = do
_ <- char '#'
name <- mconcat <$> many1 nmchar
pure $ IdSel (TL.toStrict (toLazyText name))
classSel :: Parser SimpleSelector
classSel = char '.' *> (ClassSel <$> ident)
attributeSel :: Parser SimpleSelector
attributeSel = do
_ <- char '[' *> skipComments
attId <- ident <* skipComments
g <- option Attribute attValue
_ <- char ']'
pure $ AttributeSel (g attId)
where attValue = do
f <- ((string "^=" $> (:^=:)) <|>
(string "$=" $> (:$=:)) <|>
(string "*=" $> (:*=:)) <|>
(string "=" $> (:=:)) <|>
(string "~=" $> (:~=:)) <|>
(string "|=" $> (:|=:))) <* skipComments
attval <- ((Left <$> ident) <|> (Right <$> stringtype)) <* 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.toCaseFold i) fpcMap of
Just p -> functionParser p
Nothing -> functionParser (FunctionalPseudoClass i <$> A.takeWhile (/= ')'))
_ -> pure $ PseudoClass i
pseudoElementSelector = do
parsedColon <- option False (char ':' $> True)
if parsedColon
then PseudoElem <$> ident
else ident >>= handleSpecialCase
where handleSpecialCase :: Text -> Parser SimpleSelector
handleSpecialCase t = if T.toCaseFold t `elem` specialPseudoElements
then pure $ PseudoElem t
else mzero
anplusb :: Parser AnPlusB
anplusb = (asciiCI "even" $> Even)
<|> (asciiCI "odd" $> Odd)
<|> do
s <- option Nothing (Just <$> parseSign)
x <- option mempty digits
case x of
[] -> ciN *> (AB (Nwith s Nothing) <$> (skipComments *> option Nothing (Just <$> bValue)))
_ -> do n <- option False (ciN $> True)
let a = read x :: Int
if n
then AB (Nwith s (Just a)) <$> (skipComments *> option Nothing (Just <$> bValue))
else pure $ AB NoValue (Just $ getSign s * a)
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 $ fmap (first T.toCaseFold)
[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)
]
where buildTuple t c = (t, c t)
compoundSelectorList = (:) <$> compoundSelector <*> many (comma *> compoundSelector)
anbAndSelectors constructor = do
a <- anplusb <* skipComments
o <- option [] (asciiCI "of" *> skipComments *> compoundSelectorList)
pure $ constructor a o
selectors :: Parser [Selector]
selectors = lexeme selector `sepBy` char ','
declaration :: Parser Declaration
declaration = do
p <- property <* colon
v <- values p <|> valuesFallback
i <- important <* skipComments
ie <- iehack <* skipComments
pure $ Declaration p v i ie
property :: Parser Text
property = mappend <$> opt ie7orLessHack <*> ident
where ie7orLessHack = T.singleton <$> satisfy (`Set.member` ie7orLessHacks)
ie7orLessHacks = Set.fromList ("!$&*()=%+@,./`[]#~?:<>|" :: String)
important :: Parser Bool
important = option False (char '!' *> skipComments *> asciiCI "important" $> True)
iehack :: Parser Bool
iehack = option False (string "\\9" $> True)
declarations :: Parser [Declaration]
declarations = many (declaration <* handleSemicolons)
where handleSemicolons = many (string ";" *> skipComments)
atRule :: Parser Rule
atRule = do
_ <- char '@'
ruleType <- ident
fromMaybe (atBlock ruleType) (Map.lookup ruleType m)
where m = Map.fromList [("charset", atCharset)
,("import", atImport)
,("namespace", atNamespace)
,("media", atMedia)
,("font-face", skipComments *> atBlock "font-face")
,("keyframes", atKeyframe mempty )
,("-webkit-keyframes", atKeyframe "-webkit-")
,("-moz-keyframes", atKeyframe "-moz-")
,("-o-keyframes", atKeyframe "-o-")
]
atImport :: Parser Rule
atImport = do
esu <- skipComments *> stringOrUrl
mql <- option [] mediaQueryList
_ <- skipComments <* char ';'
pure $ AtImport esu mql
atCharset :: Parser Rule
atCharset = do
st <- skipComments *> stringtype <* skipComments <* char ';'
pure $ AtCharset st
atNamespace :: Parser Rule
atNamespace = do
i <- skipComments *> option mempty ident
ret <- if T.null i
then (AtNamespace i . Left) <$> stringtype
else decideBasedOn i
_ <- skipComments <* char ';'
pure ret
where decideBasedOn x =
let urltext = T.toCaseFold "url"
in if T.toCaseFold x == urltext
then do c <- A.peekChar
case c of
Just '(' -> AtNamespace mempty <$> (char '(' *> (Right <$> url))
_ -> AtNamespace x <$> (skipComments *> stringOrUrl)
else AtNamespace x <$> (skipComments *> stringOrUrl)
atKeyframe :: Text -> Parser Rule
atKeyframe t = do
_ <- skipComments
name <- ident <* skipComments <* char '{'
bs <- many (keyframeBlock <* skipComments)
_ <- char '}'
pure $ AtKeyframes t name bs
keyframeBlock :: Parser KeyframeBlock
keyframeBlock = do
sel <- skipComments *> kfsList <* skipComments
ds <- char '{' *> skipComments *> declarations <* char '}'
pure $ KeyframeBlock sel ds
where from = asciiCI "from" $> From
to = asciiCI "to" $> To
keyframeSelector = from <|> to <|> (KFPercentage <$> percentage)
kfsList = (:) <$> keyframeSelector <*> many (comma *> keyframeSelector)
atMedia :: Parser Rule
atMedia = do
m <- satisfy C.isSpace *> mediaQueryList
_ <- char '{' <* skipComments
r <- manyTill (rule <* skipComments) (lookAhead (char '}'))
_ <- char '}'
pure $ AtMedia m r
atBlock :: Text -> Parser Rule
atBlock i = do
t <- mappend i <$> A.takeWhile (/= '{') <* char '{'
r <- skipComments *> ((AtBlockWithDec t <$> declarations) <|> (AtBlockWithRules t <$> manyTill (rule <* skipComments) (lookAhead (char '}'))))
_ <- char '}'
pure r
styleRule :: Parser Rule
styleRule = do
sels <- selectors <* char '{' <* skipComments
decs <- declarations <* char '}'
pure $ StyleRule sels decs
rule :: Parser Rule
rule = atRule <|> styleRule
rules :: Parser [Rule]
rules = manyTill (rule <* skipComments) endOfInput
stylesheet :: Parser [Rule]
stylesheet = do
charset <- option [] ((:[]) <$> atCharset <* skipComments)
imports <- many (atImport <* skipComments)
namespaces <- many (atNamespace <* skipComments)
_ <- skipComments
rest <- rules
pure $ charset <> imports <> namespaces <> rest
mediaQueryList :: Parser [MediaQuery]
mediaQueryList = lexeme ((:) <$> mediaQuery <*> many (char ',' *> skipComments *> mediaQuery))
mediaQuery :: Parser MediaQuery
mediaQuery = mediaQuery1 <|> mediaQuery2
where mediaQuery1 = MediaQuery1 <$> optionalNotOrOnly <*> mediaType <*> andExpressions
mediaQuery2 = MediaQuery2 <$> ((:) <$> expression <*> andExpressions)
mediaType = lexeme ident
andExpressions = many (h *> expression)
h = skipComments *> asciiCI "and" *> satisfy C.isSpace *> skipComments
optionalNotOrOnly = option mempty (asciiCI "not" <|> asciiCI "only")
expression :: Parser Expression
expression = char '(' *> skipComments *> (expr <|> expFallback)
where expr = do
e <- ident <* skipComments
v <- option Nothing (char ':' *> lexeme (Just <$> value))
_ <- char ')'
pure $ Expression e v
expFallback = InvalidExpression <$> A.takeWhile (/= ')') <* char ')'