-- | -- Module: Data.CSS.Utils -- Copyright: (c) 2013 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez module Data.CSS.Utils ( -- * Builder utilities commas, commasBS, cssString, showHexInt, showReal ) where import qualified Data.ByteString.Char8 as B import qualified Data.Text as T import Blaze.ByteString.Builder import Blaze.ByteString.Builder.Char.Utf8 import Data.ByteString (ByteString) import Data.Char import Data.Foldable (fold) import Data.List import Data.Monoid import Data.Text (Text) -- | Render the given list of builders separated by commas. commas :: [Builder] -> Builder commas = fold . intersperse (fromChar ',') -- | Render the given list of builders separated by commas. commasBS :: [ByteString] -> Builder commasBS = commas . map fromByteString -- | Renders the given CSS string in double-quotes, escaped as -- necessary. cssString :: Text -> Builder cssString s0 = fromChar '"' <> str s0 <> fromChar '"' where str s' = case T.uncons s' of Nothing -> mempty Just ('"', s) -> fromByteString "\\\"" <> str s Just ('\\', s) -> fromByteString "\\\\" <> str s Just (c, s) | isControl c -> fromChar '\\' <> showHexInt 6 (ord c) <> str s | otherwise -> fromChar c <> str s -- | @showHexInt p n@ builds the hexadecimal representation of @n@ with -- at least @p@ digits. Prepends zeroes to fill. showHexInt :: (Integral a) => Int -> a -> Builder showHexInt p n | n < 0 = fromChar '-' <> showHexInt p (negate n) showHexInt p 0 = fromByteString (B.replicate (max 0 p) '0') showHexInt p' n' = p `seq` showHexInt p n <> fromChar (intToDigit $ fromIntegral r) where (n, r) = quotRem n' 16 p = max 0 (pred p') -- | Lossily convert the given 'Real' number into a decimal -- representation suitable for CSS. showReal :: (Real a) => a -> Builder showReal = showRat . toRational where showRat x | x < 0 = fromChar '-' <> showRat (negate x) showRat x = let (n, f) = properFraction x in (if n == 0 then fromChar '0' else intP n) <> (if f == 0 then mempty else fromChar '.' <> fromString (fracP 6 f)) intP :: Integer -> Builder intP 0 = mempty intP n = let (q, r) = quotRem n 10 in intP q <> fromChar (intToDigit $ fromInteger r) fracP _ 0 = "" fracP 0 _ = "" fracP i f' | all (== '0') res = "" | otherwise = res where (n, f) = properFraction (10*f') res = intToDigit n : fracP (pred i) f