-- | -- Module: Data.CSS.Render -- Copyright: (c) 2013 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez module Data.CSS.Render ( -- * Rendering renderCSS, renderCSST, -- ** Helpers fromCSS ) where import qualified Data.Map as M import qualified Data.Set as S import Blaze.ByteString.Builder import Blaze.ByteString.Builder.Char.Utf8 import Control.Monad.Writer import Data.CSS.Types import Data.CSS.Utils import Data.Foldable (fold, foldMap) import Data.List -- | Render the given raw stylesheet to a 'Builder'. fromCSS :: CSS -> Builder fromCSS (CSS imports medias) = foldMap (uncurry fromImport) (M.toAscList imports) <> foldMap (uncurry media) (M.toAscList medias) where bs = fromByteString fromImport uri mts | S.member "all" mts = bs "@import url(" <> cssString uri <> bs ");" | otherwise = bs "@import url(" <> cssString uri <> fromChar ')' <> (fold . intersperse (fromChar ',') . map (bs . _mediaTypeStr) . S.toAscList) mts <> fromChar ';' media mts props | null props = mempty | S.null mts = mempty | S.member "all" mts = properties0 props | otherwise = bs "@media " <> (commasBS . map _mediaTypeStr . S.toList) mts <> fromChar '{' <> properties0 props <> fromChar '}' properties0 [] = mempty properties0 (Property sels (PropName name) (PropValue val) imp : props) = (commasBS . map _selectorStr) sels <> fromChar '{' <> bs name <> fromChar ':' <> bs val <> (if imp then fromByteString " !important" else mempty) <> properties sels props properties _ [] = fromChar '}' properties sels' props0@(Property sels (PropName name) (PropValue val) imp : props) | sels' == sels = fromChar ';' <> bs name <> fromChar ':' <> bs val <> (if imp then fromByteString " !important" else mempty) <> properties sels props | otherwise = fromChar '}' <> properties0 props0 -- | Render the given stylesheet. renderCSS :: Writer CSS a -> Builder renderCSS = fromCSS . execWriter -- | Render the given stylesheet. renderCSST :: (Monad m) => WriterT CSS m a -> m Builder renderCSST = liftM fromCSS . execWriterT