{-# LANGUAGE OverloadedStrings #-}
module Clay.Common where
import Clay.Property
import Data.String (IsString)
import Data.Monoid (Monoid, (<>))
class All a where all :: a
class Auto a where auto :: a
class Baseline a where baseline :: a
class Center a where center :: a
class Inherit a where inherit :: a
class None a where none :: a
class Normal a where normal :: a
class Visible a where visible :: a
class Hidden a where hidden :: a
class Initial a where initial :: a
class Unset a where unset :: a
class Other a where other :: Value -> a
allValue :: Value
allValue = "all"
autoValue :: Value
autoValue = "auto"
baselineValue :: Value
baselineValue = "baseline"
centerValue :: Value
centerValue = "center"
inheritValue :: Value
inheritValue = "inherit"
normalValue :: Value
normalValue = "normal"
noneValue :: Value
noneValue = "none"
visibleValue :: Value
visibleValue = "visible"
hiddenValue :: Value
hiddenValue = "hidden"
initialValue :: Value
initialValue = "initial"
unsetValue :: Value
unsetValue = "unset"
instance All Value where all = allValue
instance Auto Value where auto = autoValue
instance Baseline Value where baseline = baselineValue
instance Center Value where center = centerValue
instance Inherit Value where inherit = inheritValue
instance Normal Value where normal = normalValue
instance None Value where none = noneValue
instance Visible Value where visible = visibleValue
instance Hidden Value where hidden = hiddenValue
instance Other Value where other = id
instance Initial Value where initial = initialValue
instance Unset Value where unset = unsetValue
browsers :: Prefixed
browsers = Prefixed
[ ( "-webkit-", "" )
, ( "-moz-", "" )
, ( "-ms-", "" )
, ( "-o-", "" )
, ( "", "" )
]
call :: (IsString s, Monoid s) => s -> s -> s
call fn arg = fn <> "(" <> arg <> ")"
fracMod :: RealFrac a => a -> a -> a
fracMod x y = (x -) . (* y) $ evenMultiples x y
where evenMultiples x' y' = fromIntegral (truncate (x' / y') :: Integer)
decimalRound :: RealFrac a => a -> Int -> a
decimalRound x decimalPlaces = shiftedAndRounded x / powersOf10
where powersOf10 = 10 ^ decimalPlaces
shiftedAndRounded x' = fromIntegral (round $ x' * powersOf10 :: Integer)