{-# LANGUAGE
OverloadedStrings
, GeneralizedNewtypeDeriving
, FlexibleInstances
, ExistentialQuantification
, StandaloneDeriving
, TypeFamilies
, EmptyDataDecls
#-}
module Clay.Size
(
Size
, LengthUnit
, Percentage
, nil
, unitless
, cm
, mm
, inches
, px
, pt
, pc
, em
, ex
, pct
, rem
, vw
, vh
, vmin
, vmax
, (@+@)
, (@-@)
, (@*)
, (*@)
, (@/)
, sym
, sym2
, sym3
, Angle
, Deg
, Rad
, Grad
, Turn
, deg
, rad
, grad
, turn
)
where
import Data.Monoid
import Prelude hiding (rem)
import Data.Text (Text)
import Clay.Common
import Clay.Property
import Clay.Stylesheet
data LengthUnit
data Percentage
data Combination
data Size a =
SimpleSize Text |
forall b c. SumSize (Size b) (Size c) |
forall b c. DiffSize (Size b) (Size c) |
MultSize Double (Size a) |
DivSize Double (Size a) |
OtherSize Value
deriving instance Show (Size a)
sizeToText :: Size a -> Text
sizeToText (SimpleSize txt) = txt
sizeToText (SumSize a b) = mconcat ["(", sizeToText a, " + ", sizeToText b, ")"]
sizeToText (DiffSize a b) = mconcat ["(", sizeToText a, " - ", sizeToText b, ")"]
sizeToText (MultSize a b) = mconcat ["(", cssDoubleText a, " * ", sizeToText b, ")"]
sizeToText (DivSize a b) = mconcat ["(", sizeToText b, " / ", cssDoubleText a, ")"]
sizeToText (OtherSize a) = plain $ unValue a
instance Val (Size a) where
value (SimpleSize a) = value a
value (OtherSize a) = a
value s = Value $ browsers <> Plain ("calc" <> sizeToText s)
instance Auto (Size a) where auto = OtherSize Clay.Common.autoValue
instance Normal (Size a) where normal = OtherSize Clay.Common.normalValue
instance Inherit (Size a) where inherit = OtherSize Clay.Common.inheritValue
instance None (Size a) where none = OtherSize Clay.Common.noneValue
instance Other (Size a) where other a = OtherSize a
nil :: Size a
nil = SimpleSize "0"
unitless :: Double -> Size a
unitless i = SimpleSize ((plain . unValue . value) i)
cm, mm, inches, px, pt, pc :: Double -> Size LengthUnit
cm i = SimpleSize (cssDoubleText i <> "cm")
mm i = SimpleSize (cssDoubleText i <> "mm")
inches i = SimpleSize (cssDoubleText i <> "in")
px i = SimpleSize (cssDoubleText i <> "px")
pt i = SimpleSize (cssDoubleText i <> "pt")
pc i = SimpleSize (cssDoubleText i <> "pc")
em, ex, rem, vw, vh, vmin, vmax :: Double -> Size LengthUnit
em i = SimpleSize (cssDoubleText i <> "em")
ex i = SimpleSize (cssDoubleText i <> "ex")
rem i = SimpleSize (cssDoubleText i <> "rem")
vw i = SimpleSize (cssDoubleText i <> "vw")
vh i = SimpleSize (cssDoubleText i <> "vh")
vmin i = SimpleSize (cssDoubleText i <> "vmin")
vmax i = SimpleSize (cssDoubleText i <> "vmax")
pct :: Double -> Size Percentage
pct i = SimpleSize (cssDoubleText i <> "%")
instance Num (Size LengthUnit) where
fromInteger = px . fromInteger
(+) = error "plus not implemented for Size"
(*) = error "times not implemented for Size"
abs = error "abs not implemented for Size"
signum = error "signum not implemented for Size"
negate = error "negate not implemented for Size"
instance Fractional (Size LengthUnit) where
fromRational = px . fromRational
recip = error "recip not implemented for Size"
instance Num (Size Percentage) where
fromInteger = pct . fromInteger
(+) = error "plus not implemented for Size"
(*) = error "times not implemented for Size"
abs = error "abs not implemented for Size"
signum = error "signum not implemented for Size"
negate = error "negate not implemented for Size"
instance Fractional (Size Percentage) where
fromRational = pct . fromRational
recip = error "recip not implemented for Size"
type family SizeCombination sa sb where
SizeCombination Percentage Percentage = Percentage
SizeCombination LengthUnit LengthUnit = LengthUnit
SizeCombination a b = Combination
infixl 6 @+@
(@+@) :: Size a -> Size b -> Size (SizeCombination a b)
a @+@ b = SumSize a b
infixl 6 @-@
(@-@) :: Size a -> Size b -> Size (SizeCombination a b)
a @-@ b = DiffSize a b
infixl 7 *@
(*@) :: Double -> Size a -> Size a
a *@ b = MultSize a b
infixl 7 @*
(@*) :: Size a -> Double -> Size a
a @* b = MultSize b a
infixl 7 @/
(@/) :: Size a -> Double -> Size a
a @/ b = DivSize b a
sym :: (a -> a -> a -> a -> Css) -> a -> Css
sym k a = k a a a a
sym3 :: (tb -> l -> tb -> r -> Css) -> tb -> l -> r -> Css
sym3 k tb l r = k tb l tb r
sym2 :: (tb -> lr -> tb -> lr -> Css) -> tb -> lr -> Css
sym2 k tb lr = k tb lr tb lr
data Deg
data Rad
data Grad
data Turn
newtype Angle a = Angle Value
deriving (Val, Auto, Inherit, Other)
deg :: Double -> Angle Deg
deg i = Angle (value i <> "deg")
rad :: Double -> Angle Rad
rad i = Angle (value i <> "rad")
grad :: Double -> Angle Grad
grad i = Angle (value i <> "grad")
turn :: Double -> Angle Turn
turn i = Angle (value i <> "turn")
instance Num (Angle Deg) where
fromInteger = deg . fromInteger
(+) = error "plus not implemented for Angle"
(*) = error "times not implemented for Angle"
abs = error "abs not implemented for Angle"
signum = error "signum not implemented for Angle"
negate = error "negate not implemented for Angle"
instance Fractional (Angle Deg) where
fromRational = deg . fromRational
recip = error "recip not implemented for Angle"
instance Num (Angle Rad) where
fromInteger = rad . fromInteger
(+) = error "plus not implemented for Angle"
(*) = error "times not implemented for Angle"
abs = error "abs not implemented for Angle"
signum = error "signum not implemented for Angle"
negate = error "negate not implemented for Angle"
instance Fractional (Angle Rad) where
fromRational = rad . fromRational
recip = error "recip not implemented for Angle"
instance Num (Angle Grad) where
fromInteger = grad . fromInteger
(+) = error "plus not implemented for Angle"
(*) = error "times not implemented for Angle"
abs = error "abs not implemented for Angle"
signum = error "signum not implemented for Angle"
negate = error "negate not implemented for Angle"
instance Fractional (Angle Grad) where
fromRational = grad . fromRational
recip = error "recip not implemented for Angle"
instance Num (Angle Turn) where
fromInteger = turn . fromInteger
(+) = error "plus not implemented for Angle"
(*) = error "times not implemented for Angle"
abs = error "abs not implemented for Angle"
signum = error "signum not implemented for Angle"
negate = error "negate not implemented for Angle"
instance Fractional (Angle Turn) where
fromRational = turn . fromRational
recip = error "recip not implemented for Angle"