{-# LANGUAGE OverloadedStrings #-}
module Hasmin.Parser.Internal
( stylesheet
, atRule
, atMedia
, styleRule
, rule
, rules
, declaration
, declarations
, selector
, supportsCondition
) where
import Control.Applicative ((<|>), many, some, optional)
import Data.Functor (($>))
import Data.Attoparsec.Combinator (lookAhead, endOfInput)
import Data.Attoparsec.Text (asciiCI, char, manyTill,
Parser, satisfy)
import Data.List.NonEmpty (NonEmpty)
import Data.Monoid ((<>))
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.List.NonEmpty as NE
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 Hasmin.Parser.Utils
import Hasmin.Parser.Value
import Hasmin.Parser.Selector
import Hasmin.Types.Stylesheet
import Hasmin.Types.Declaration
declaration :: Parser Declaration
declaration = do
p <- property <* colon
v <- valuesFor p <|> valuesFallback
i <- important
ie <- lexeme iehack
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 = A.option False (char '!' *> skipComments *> asciiCI "important" $> True)
iehack :: Parser Bool
iehack = A.option False (A.string "\\9" $> True)
declarations :: Parser [Declaration]
declarations = many (declaration <* handleSemicolons) <* handleSemicolons
where handleSemicolons = many (A.char ';' *> 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)
,("supports", atSupports)
,("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 <- A.option [] mediaQueryList
_ <- skipComments <* char ';'
pure $ AtImport esu mql
atCharset :: Parser Rule
atCharset = AtCharset <$> (lexeme stringtype <* char ';')
atNamespace :: Parser Rule
atNamespace = do
i <- skipComments *> A.option mempty ident
ret <- if T.null i
then (AtNamespace i . Left) <$> stringtype
else decideBasedOn i
_ <- skipComments <* char ';'
pure ret
where decideBasedOn x
| T.toCaseFold x == "url" =
do c <- A.peekChar
case c of
Just '(' -> AtNamespace mempty <$> (char '(' *> (Right <$> url))
_ -> AtNamespace x <$> (skipComments *> stringOrUrl)
| otherwise = AtNamespace x <$> (skipComments *> stringOrUrl)
atKeyframe :: Text -> Parser Rule
atKeyframe t = do
name <- lexeme ident <* char '{'
bs <- many (keyframeBlock <* skipComments)
_ <- char '}'
pure $ AtKeyframes t name bs
keyframeBlock :: Parser KeyframeBlock
keyframeBlock = do
sel <- lexeme kfsList
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
atSupports :: Parser Rule
atSupports = do
sc <- satisfy C.isSpace *> supportsCondition
_ <- lexeme (char '{')
r <- manyTill (rule <* skipComments) (lookAhead (char '}'))
_ <- char '}'
pure $ AtSupports sc r
supportsCondition :: Parser SupportsCondition
supportsCondition = asciiCI "not" *> skipComments *> (Not <$> supportsCondInParens)
<|> supportsConjunction
<|> supportsDisjunction
<|> (Parens <$> supportsCondInParens)
where
supportsDisjunction :: Parser SupportsCondition
supportsDisjunction = supportsHelper Or "or"
supportsConjunction :: Parser SupportsCondition
supportsConjunction = supportsHelper And "and"
supportsCondInParens :: Parser SupportsCondInParens
supportsCondInParens = do
_ <- char '('
x <- lexeme $ (ParensCond <$> supportsCondition) <|> (ParensDec <$> atSupportsDeclaration)
_ <- char ')'
pure x
atSupportsDeclaration :: Parser Declaration
atSupportsDeclaration = do
p <- property <* colon
v <- valuesFor p <|> valuesInParens
pure $ Declaration p v False False
supportsHelper :: (SupportsCondInParens -> NonEmpty SupportsCondInParens -> SupportsCondition)
-> Text -> Parser SupportsCondition
supportsHelper c t = do
x <- supportsCondInParens <* skipComments
xs <- some (asciiCI t *> lexeme supportsCondInParens)
pure $ c x (NE.fromList xs)
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 <- A.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 = lexeme (asciiCI "and" *> satisfy C.isSpace)
optionalNotOrOnly = A.option mempty (asciiCI "not" <|> asciiCI "only")
expression :: Parser Expression
expression = char '(' *> skipComments *> (expr <|> expFallback)
where expr = do
e <- ident <* skipComments
v <- optional (char ':' *> lexeme value)
_ <- char ')'
pure $ Expression e v
expFallback = InvalidExpression <$> A.takeWhile (/= ')') <* char ')'