module Hakyll.Web.CompressCss
( compressCssCompiler
, compressCss
) where
import Data.Char (isSpace)
import Data.List (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 = compressSeparators . stripComments . compressWhitespace
compressSeparators :: String -> String
compressSeparators =
replaceAll "; *}" (const "}") .
replaceAll " *([{};:]) *" (take 1 . dropWhile isSpace) .
replaceAll ";+" (const ";")
compressWhitespace :: String -> String
compressWhitespace = replaceAll "[ \t\n\r]+" (const " ")
stripComments :: String -> String
stripComments [] = []
stripComments str
| isPrefixOf "/*" str = stripComments $ eatComments $ drop 2 str
| otherwise = head str : stripComments (drop 1 str)
where
eatComments str'
| null str' = []
| isPrefixOf "*/" str' = drop 2 str'
| otherwise = eatComments $ drop 1 str'