module Hasmin.Types.BgSize (
BgSize(..)
, Auto(..)
) where
import Control.Monad.Reader (ask)
import Data.Monoid ((<>))
import Data.Text.Lazy.Builder (singleton)
import Hasmin.Types.Class
import Hasmin.Types.PercentageLength
data Auto = Auto
deriving (Eq, Show)
instance ToText Auto where
toBuilder Auto = "auto"
data BgSize = Cover
| Contain
| BgSize (Either PercentageLength Auto) (Maybe (Either PercentageLength Auto))
deriving Show
instance Eq BgSize where
Cover == Cover = True
Contain == Contain = True
BgSize a b == BgSize c d = ftsArgEq a c && b `equals` d
where equals (Just (Right Auto)) Nothing = True
equals Nothing (Just (Right Auto)) = True
equals (Just (Left x)) (Just (Left y)) = isZero x && isZero y || x == y
equals x y = x == y
ftsArgEq (Left x) (Left y) = isZero x && isZero y || x == y
ftsArgEq x y = x == y
_ == _ = False
instance ToText BgSize where
toBuilder Cover = "cover"
toBuilder Contain = "contain"
toBuilder (BgSize x y) = toBuilder x <> maybe mempty (\a -> singleton ' ' <> toBuilder a) y
instance Minifiable BgSize where
minifyWith (BgSize x y) = do
conf <- ask
nx <- minFirst x
ny <- mapM minFirst y
let b = BgSize nx ny
pure $ if True
then minifyBgSize b
else b
where minFirst (Left a) = Left <$> minifyWith a
minFirst (Right Auto) = pure (Right Auto)
minifyWith x = pure x
minifyBgSize :: BgSize -> BgSize
minifyBgSize (BgSize l (Just (Right Auto))) = BgSize l Nothing
minifyBgSize x = x