{-# LANGUAGE OverloadedStrings #-}
module Hasmin.Types.Shadow
( Shadow(..)
) where
import Data.Monoid ((<>))
import Data.Text.Lazy.Builder (singleton)
import Data.Bool (bool)
import Hasmin.Class
import Hasmin.Types.Color
import Hasmin.Types.Dimension
data Shadow = Shadow { _inset :: Bool
, _sOffsetX :: Length
, _sOffsetY :: Length
, _blurRadius :: Maybe Length
, _spreadRadius :: Maybe Length
, _sColor :: Maybe Color
} deriving (Eq, Show)
instance ToText Shadow where
toBuilder (Shadow i ox oy br sr c) =
bool mempty "inset " i
<> toBuilder ox <> singleton ' '
<> toBuilder oy <> prependSpace br
<> prependSpace sr <> prependSpace c
where prependSpace x = maybe mempty (\y -> singleton ' ' <> toBuilder y) x
instance Minifiable Shadow where
minify (Shadow i ox oy br sr c) = do
x <- minify ox
y <- minify oy
nb <- mapM minify br
ns <- mapM minify sr
c2 <- mapM minify c
pure $ if True
then let (a, b) = minifyBlurAndSpread nb ns
in Shadow i x y a b c2
else Shadow i x y nb ns c2
where minifyBlurAndSpread :: Maybe Length -> Maybe Length -> (Maybe Length, Maybe Length)
minifyBlurAndSpread (Just br') Nothing
| isZeroLen br' = (Nothing, Nothing)
| otherwise = (Just br', Nothing)
minifyBlurAndSpread (Just br') (Just sr')
| isZeroLen sr' = minifyBlurAndSpread (Just br') Nothing
| otherwise = (Just br', Just sr')
minifyBlurAndSpread x y = (x, y)