module Hakyll.Web.CompressCss
( compressCssCompiler
, compressCss
) where
import Data.Char (isSpace)
import Data.List (dropWhileEnd, isPrefixOf)
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Core.Util.String
compressCssCompiler :: Compiler (Item String)
compressCssCompiler = fmap compressCss <$> getResourceString
compressCss :: String -> String
compressCss = withoutStrings (handleCalcExpressions compressSeparators . compressWhitespace)
. dropWhileEnd isSpace
. dropWhile isSpace
. stripComments
compressSeparators :: String -> String
compressSeparators =
replaceAll "; *}" (const "}") .
replaceAll ";+" (const ";") .
replaceAll " *[{};,>+~!] *" (take 1 . dropWhile isSpace) .
replaceAll ": *" (take 1)
handleCalcExpressions :: (String -> String) -> String -> String
handleCalcExpressions transform = top transform
where
top f "" = f ""
top f str | "calc(" `isPrefixOf` str = f "calc" ++ nested 0 compressCalcExpression (drop 4 str)
top f (x:xs) = top (f . (x:)) xs
nested :: Int -> (String -> String) -> String -> String
nested _ f "" = f ""
nested depth f str | "calc(" `isPrefixOf` str = nested depth f (drop 4 str)
nested 1 f (')':xs) = f ")" ++ top transform xs
nested depth f (x:xs) = nested (case x of
'(' -> depth + 1
')' -> depth - 1
_ -> depth
) (f . (x:)) xs
compressCalcExpression :: String -> String
compressCalcExpression =
replaceAll " *[*/] *| *\\)|\\( *" (take 1 . dropWhile isSpace)
compressWhitespace :: String -> String
compressWhitespace = replaceAll "[ \t\n\r]+" (const " ")
stripComments :: String -> String
stripComments "" = ""
stripComments ('/':'*':str) = stripComments $ eatComment str
stripComments (x:xs) | x `elem` "\"'" = retainString x xs stripComments
| otherwise = x : stripComments xs
eatComment :: String -> String
eatComment "" = ""
eatComment ('*':'/':str) = str
eatComment (_:str) = eatComment str
withoutStrings :: (String -> String) -> String -> String
withoutStrings f str = case span (`notElem` "\"'") str of
(text, "") -> f text
(text, d:rest) -> f text ++ retainString d rest (withoutStrings f)
retainString :: Char -> String -> (String -> String) -> String
retainString delim str cont = case span (/= delim) str of
(val, "") -> delim : val
(val, _:rest) -> delim : val ++ delim : cont rest