{-# LANGUAGE AllowAmbiguousTypes #-}
module Web.Atomic.Types.Style where
import Data.String (IsString (..))
import Data.Text (Text, pack, unpack)
import Data.Text qualified as T
import Numeric (showFFloat)
import Text.Casing (kebab)
import Web.Atomic.Types.ClassName (ToClassName (..), className)
newtype Property = Property Text
deriving newtype (Int -> Property -> ShowS
[Property] -> ShowS
Property -> String
(Int -> Property -> ShowS)
-> (Property -> String) -> ([Property] -> ShowS) -> Show Property
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Property -> ShowS
showsPrec :: Int -> Property -> ShowS
$cshow :: Property -> String
show :: Property -> String
$cshowList :: [Property] -> ShowS
showList :: [Property] -> ShowS
Show, Property -> Property -> Bool
(Property -> Property -> Bool)
-> (Property -> Property -> Bool) -> Eq Property
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Property -> Property -> Bool
== :: Property -> Property -> Bool
$c/= :: Property -> Property -> Bool
/= :: Property -> Property -> Bool
Eq, Eq Property
Eq Property =>
(Property -> Property -> Ordering)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Property)
-> (Property -> Property -> Property)
-> Ord Property
Property -> Property -> Bool
Property -> Property -> Ordering
Property -> Property -> Property
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Property -> Property -> Ordering
compare :: Property -> Property -> Ordering
$c< :: Property -> Property -> Bool
< :: Property -> Property -> Bool
$c<= :: Property -> Property -> Bool
<= :: Property -> Property -> Bool
$c> :: Property -> Property -> Bool
> :: Property -> Property -> Bool
$c>= :: Property -> Property -> Bool
>= :: Property -> Property -> Bool
$cmax :: Property -> Property -> Property
max :: Property -> Property -> Property
$cmin :: Property -> Property -> Property
min :: Property -> Property -> Property
Ord, String -> Property
(String -> Property) -> IsString Property
forall a. (String -> a) -> IsString a
$cfromString :: String -> Property
fromString :: String -> Property
IsString, NonEmpty Property -> Property
Property -> Property -> Property
(Property -> Property -> Property)
-> (NonEmpty Property -> Property)
-> (forall b. Integral b => b -> Property -> Property)
-> Semigroup Property
forall b. Integral b => b -> Property -> Property
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Property -> Property -> Property
<> :: Property -> Property -> Property
$csconcat :: NonEmpty Property -> Property
sconcat :: NonEmpty Property -> Property
$cstimes :: forall b. Integral b => b -> Property -> Property
stimes :: forall b. Integral b => b -> Property -> Property
Semigroup)
data Declaration = Property :. Style
deriving (Int -> Declaration -> ShowS
[Declaration] -> ShowS
Declaration -> String
(Int -> Declaration -> ShowS)
-> (Declaration -> String)
-> ([Declaration] -> ShowS)
-> Show Declaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Declaration -> ShowS
showsPrec :: Int -> Declaration -> ShowS
$cshow :: Declaration -> String
show :: Declaration -> String
$cshowList :: [Declaration] -> ShowS
showList :: [Declaration] -> ShowS
Show, Eq Declaration
Eq Declaration =>
(Declaration -> Declaration -> Ordering)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Declaration)
-> (Declaration -> Declaration -> Declaration)
-> Ord Declaration
Declaration -> Declaration -> Bool
Declaration -> Declaration -> Ordering
Declaration -> Declaration -> Declaration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Declaration -> Declaration -> Ordering
compare :: Declaration -> Declaration -> Ordering
$c< :: Declaration -> Declaration -> Bool
< :: Declaration -> Declaration -> Bool
$c<= :: Declaration -> Declaration -> Bool
<= :: Declaration -> Declaration -> Bool
$c> :: Declaration -> Declaration -> Bool
> :: Declaration -> Declaration -> Bool
$c>= :: Declaration -> Declaration -> Bool
>= :: Declaration -> Declaration -> Bool
$cmax :: Declaration -> Declaration -> Declaration
max :: Declaration -> Declaration -> Declaration
$cmin :: Declaration -> Declaration -> Declaration
min :: Declaration -> Declaration -> Declaration
Ord, Declaration -> Declaration -> Bool
(Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool) -> Eq Declaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Declaration -> Declaration -> Bool
== :: Declaration -> Declaration -> Bool
$c/= :: Declaration -> Declaration -> Bool
/= :: Declaration -> Declaration -> Bool
Eq)
newtype Style = Style String
deriving newtype (String -> Style
(String -> Style) -> IsString Style
forall a. (String -> a) -> IsString a
$cfromString :: String -> Style
fromString :: String -> Style
IsString, Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
(Int -> Style -> ShowS)
-> (Style -> String) -> ([Style] -> ShowS) -> Show Style
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Style -> ShowS
showsPrec :: Int -> Style -> ShowS
$cshow :: Style -> String
show :: Style -> String
$cshowList :: [Style] -> ShowS
showList :: [Style] -> ShowS
Show, Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
/= :: Style -> Style -> Bool
Eq, Semigroup Style
Style
Semigroup Style =>
Style
-> (Style -> Style -> Style) -> ([Style] -> Style) -> Monoid Style
[Style] -> Style
Style -> Style -> Style
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Style
mempty :: Style
$cmappend :: Style -> Style -> Style
mappend :: Style -> Style -> Style
$cmconcat :: [Style] -> Style
mconcat :: [Style] -> Style
Monoid, NonEmpty Style -> Style
Style -> Style -> Style
(Style -> Style -> Style)
-> (NonEmpty Style -> Style)
-> (forall b. Integral b => b -> Style -> Style)
-> Semigroup Style
forall b. Integral b => b -> Style -> Style
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Style -> Style -> Style
<> :: Style -> Style -> Style
$csconcat :: NonEmpty Style -> Style
sconcat :: NonEmpty Style -> Style
$cstimes :: forall b. Integral b => b -> Style -> Style
stimes :: forall b. Integral b => b -> Style -> Style
Semigroup, Eq Style
Eq Style =>
(Style -> Style -> Ordering)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Style)
-> (Style -> Style -> Style)
-> Ord Style
Style -> Style -> Bool
Style -> Style -> Ordering
Style -> Style -> Style
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Style -> Style -> Ordering
compare :: Style -> Style -> Ordering
$c< :: Style -> Style -> Bool
< :: Style -> Style -> Bool
$c<= :: Style -> Style -> Bool
<= :: Style -> Style -> Bool
$c> :: Style -> Style -> Bool
> :: Style -> Style -> Bool
$c>= :: Style -> Style -> Bool
>= :: Style -> Style -> Bool
$cmax :: Style -> Style -> Style
max :: Style -> Style -> Style
$cmin :: Style -> Style -> Style
min :: Style -> Style -> Style
Ord)
class ToStyle a where
style :: a -> Style
default style :: (Show a) => a -> Style
style = String -> Style
Style (String -> Style) -> (a -> String) -> a -> Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
kebab ShowS -> (a -> String) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
instance ToStyle String where
style :: String -> Style
style = String -> Style
Style
instance ToStyle Text where
style :: Text -> Style
style = String -> Style
Style (String -> Style) -> (Text -> String) -> Text -> Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack
instance ToStyle Int
instance ToStyle Float where
style :: Float -> Style
style Float
n = String -> Style
Style (String -> Style) -> String -> Style
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2) Float
n String
""
instance ToStyle Style where
style :: Style -> Style
style = Style -> Style
forall a. a -> a
id
class PropertyStyle property value where
propertyStyle :: value -> Style
default propertyStyle :: (ToStyle value) => value -> Style
propertyStyle = value -> Style
forall a. ToStyle a => a -> Style
style
data None = None
deriving (Int -> None -> ShowS
[None] -> ShowS
None -> String
(Int -> None -> ShowS)
-> (None -> String) -> ([None] -> ShowS) -> Show None
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> None -> ShowS
showsPrec :: Int -> None -> ShowS
$cshow :: None -> String
show :: None -> String
$cshowList :: [None] -> ShowS
showList :: [None] -> ShowS
Show, None -> ClassName
(None -> ClassName) -> ToClassName None
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: None -> ClassName
toClassName :: None -> ClassName
ToClassName, None -> Style
(None -> Style) -> ToStyle None
forall a. (a -> Style) -> ToStyle a
$cstyle :: None -> Style
style :: None -> Style
ToStyle)
data Normal = Normal
deriving (Int -> Normal -> ShowS
[Normal] -> ShowS
Normal -> String
(Int -> Normal -> ShowS)
-> (Normal -> String) -> ([Normal] -> ShowS) -> Show Normal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Normal -> ShowS
showsPrec :: Int -> Normal -> ShowS
$cshow :: Normal -> String
show :: Normal -> String
$cshowList :: [Normal] -> ShowS
showList :: [Normal] -> ShowS
Show, Normal -> Style
(Normal -> Style) -> ToStyle Normal
forall a. (a -> Style) -> ToStyle a
$cstyle :: Normal -> Style
style :: Normal -> Style
ToStyle)
instance ToClassName Normal where
toClassName :: Normal -> ClassName
toClassName Normal
Normal = ClassName
"norm"
data Auto = Auto
deriving (Int -> Auto -> ShowS
[Auto] -> ShowS
Auto -> String
(Int -> Auto -> ShowS)
-> (Auto -> String) -> ([Auto] -> ShowS) -> Show Auto
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Auto -> ShowS
showsPrec :: Int -> Auto -> ShowS
$cshow :: Auto -> String
show :: Auto -> String
$cshowList :: [Auto] -> ShowS
showList :: [Auto] -> ShowS
Show, Auto -> Style
(Auto -> Style) -> ToStyle Auto
forall a. (a -> Style) -> ToStyle a
$cstyle :: Auto -> Style
style :: Auto -> Style
ToStyle, Auto -> ClassName
(Auto -> ClassName) -> ToClassName Auto
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: Auto -> ClassName
toClassName :: Auto -> ClassName
ToClassName)
data Length
= PxRem PxRem
| Pct Float
deriving (Int -> Length -> ShowS
[Length] -> ShowS
Length -> String
(Int -> Length -> ShowS)
-> (Length -> String) -> ([Length] -> ShowS) -> Show Length
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Length -> ShowS
showsPrec :: Int -> Length -> ShowS
$cshow :: Length -> String
show :: Length -> String
$cshowList :: [Length] -> ShowS
showList :: [Length] -> ShowS
Show)
instance ToClassName Length where
toClassName :: Length -> ClassName
toClassName (PxRem PxRem
p) = PxRem -> ClassName
forall a. ToClassName a => a -> ClassName
toClassName PxRem
p
toClassName (Pct Float
p) = Float -> ClassName
forall a. ToClassName a => a -> ClassName
toClassName Float
p
newtype PxRem = PxRem' Int
deriving newtype (Int -> PxRem -> ShowS
[PxRem] -> ShowS
PxRem -> String
(Int -> PxRem -> ShowS)
-> (PxRem -> String) -> ([PxRem] -> ShowS) -> Show PxRem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PxRem -> ShowS
showsPrec :: Int -> PxRem -> ShowS
$cshow :: PxRem -> String
show :: PxRem -> String
$cshowList :: [PxRem] -> ShowS
showList :: [PxRem] -> ShowS
Show, PxRem -> ClassName
(PxRem -> ClassName) -> ToClassName PxRem
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: PxRem -> ClassName
toClassName :: PxRem -> ClassName
ToClassName, Integer -> PxRem
PxRem -> PxRem
PxRem -> PxRem -> PxRem
(PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem)
-> (PxRem -> PxRem)
-> (PxRem -> PxRem)
-> (Integer -> PxRem)
-> Num PxRem
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: PxRem -> PxRem -> PxRem
+ :: PxRem -> PxRem -> PxRem
$c- :: PxRem -> PxRem -> PxRem
- :: PxRem -> PxRem -> PxRem
$c* :: PxRem -> PxRem -> PxRem
* :: PxRem -> PxRem -> PxRem
$cnegate :: PxRem -> PxRem
negate :: PxRem -> PxRem
$cabs :: PxRem -> PxRem
abs :: PxRem -> PxRem
$csignum :: PxRem -> PxRem
signum :: PxRem -> PxRem
$cfromInteger :: Integer -> PxRem
fromInteger :: Integer -> PxRem
Num, PxRem -> PxRem -> Bool
(PxRem -> PxRem -> Bool) -> (PxRem -> PxRem -> Bool) -> Eq PxRem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PxRem -> PxRem -> Bool
== :: PxRem -> PxRem -> Bool
$c/= :: PxRem -> PxRem -> Bool
/= :: PxRem -> PxRem -> Bool
Eq, Enum PxRem
Real PxRem
(Real PxRem, Enum PxRem) =>
(PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> (PxRem, PxRem))
-> (PxRem -> PxRem -> (PxRem, PxRem))
-> (PxRem -> Integer)
-> Integral PxRem
PxRem -> Integer
PxRem -> PxRem -> (PxRem, PxRem)
PxRem -> PxRem -> PxRem
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: PxRem -> PxRem -> PxRem
quot :: PxRem -> PxRem -> PxRem
$crem :: PxRem -> PxRem -> PxRem
rem :: PxRem -> PxRem -> PxRem
$cdiv :: PxRem -> PxRem -> PxRem
div :: PxRem -> PxRem -> PxRem
$cmod :: PxRem -> PxRem -> PxRem
mod :: PxRem -> PxRem -> PxRem
$cquotRem :: PxRem -> PxRem -> (PxRem, PxRem)
quotRem :: PxRem -> PxRem -> (PxRem, PxRem)
$cdivMod :: PxRem -> PxRem -> (PxRem, PxRem)
divMod :: PxRem -> PxRem -> (PxRem, PxRem)
$ctoInteger :: PxRem -> Integer
toInteger :: PxRem -> Integer
Integral, Num PxRem
Ord PxRem
(Num PxRem, Ord PxRem) => (PxRem -> Rational) -> Real PxRem
PxRem -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: PxRem -> Rational
toRational :: PxRem -> Rational
Real, Eq PxRem
Eq PxRem =>
(PxRem -> PxRem -> Ordering)
-> (PxRem -> PxRem -> Bool)
-> (PxRem -> PxRem -> Bool)
-> (PxRem -> PxRem -> Bool)
-> (PxRem -> PxRem -> Bool)
-> (PxRem -> PxRem -> PxRem)
-> (PxRem -> PxRem -> PxRem)
-> Ord PxRem
PxRem -> PxRem -> Bool
PxRem -> PxRem -> Ordering
PxRem -> PxRem -> PxRem
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PxRem -> PxRem -> Ordering
compare :: PxRem -> PxRem -> Ordering
$c< :: PxRem -> PxRem -> Bool
< :: PxRem -> PxRem -> Bool
$c<= :: PxRem -> PxRem -> Bool
<= :: PxRem -> PxRem -> Bool
$c> :: PxRem -> PxRem -> Bool
> :: PxRem -> PxRem -> Bool
$c>= :: PxRem -> PxRem -> Bool
>= :: PxRem -> PxRem -> Bool
$cmax :: PxRem -> PxRem -> PxRem
max :: PxRem -> PxRem -> PxRem
$cmin :: PxRem -> PxRem -> PxRem
min :: PxRem -> PxRem -> PxRem
Ord, Int -> PxRem
PxRem -> Int
PxRem -> [PxRem]
PxRem -> PxRem
PxRem -> PxRem -> [PxRem]
PxRem -> PxRem -> PxRem -> [PxRem]
(PxRem -> PxRem)
-> (PxRem -> PxRem)
-> (Int -> PxRem)
-> (PxRem -> Int)
-> (PxRem -> [PxRem])
-> (PxRem -> PxRem -> [PxRem])
-> (PxRem -> PxRem -> [PxRem])
-> (PxRem -> PxRem -> PxRem -> [PxRem])
-> Enum PxRem
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: PxRem -> PxRem
succ :: PxRem -> PxRem
$cpred :: PxRem -> PxRem
pred :: PxRem -> PxRem
$ctoEnum :: Int -> PxRem
toEnum :: Int -> PxRem
$cfromEnum :: PxRem -> Int
fromEnum :: PxRem -> Int
$cenumFrom :: PxRem -> [PxRem]
enumFrom :: PxRem -> [PxRem]
$cenumFromThen :: PxRem -> PxRem -> [PxRem]
enumFromThen :: PxRem -> PxRem -> [PxRem]
$cenumFromTo :: PxRem -> PxRem -> [PxRem]
enumFromTo :: PxRem -> PxRem -> [PxRem]
$cenumFromThenTo :: PxRem -> PxRem -> PxRem -> [PxRem]
enumFromThenTo :: PxRem -> PxRem -> PxRem -> [PxRem]
Enum)
instance Num Length where
PxRem PxRem
p1 + :: Length -> Length -> Length
+ PxRem PxRem
p2 = PxRem -> Length
PxRem (PxRem -> Length) -> PxRem -> Length
forall a b. (a -> b) -> a -> b
$ PxRem
p1 PxRem -> PxRem -> PxRem
forall a. Num a => a -> a -> a
+ PxRem
p2
PxRem PxRem
p1 + Pct Float
pct = PxRem -> Length
PxRem (PxRem -> Length) -> PxRem -> Length
forall a b. (a -> b) -> a -> b
$ Float -> PxRem
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> PxRem) -> Float -> PxRem
forall a b. (a -> b) -> a -> b
$ PxRem -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral PxRem
p1 Float -> Float -> Float
forall a. Num a => a -> a -> a
* (Float
1 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
pct)
Pct Float
pct + PxRem PxRem
p1 = PxRem -> Length
PxRem PxRem
p1 Length -> Length -> Length
forall a. Num a => a -> a -> a
+ Float -> Length
Pct Float
pct
Pct Float
p1 + Pct Float
p2 = Float -> Length
Pct (Float -> Length) -> Float -> Length
forall a b. (a -> b) -> a -> b
$ Float
p1 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
p2
PxRem PxRem
p1 * :: Length -> Length -> Length
* PxRem PxRem
p2 = PxRem -> Length
PxRem (PxRem -> Length) -> PxRem -> Length
forall a b. (a -> b) -> a -> b
$ PxRem
p1 PxRem -> PxRem -> PxRem
forall a. Num a => a -> a -> a
+ PxRem
p2
PxRem PxRem
p1 * Pct Float
pct = PxRem -> Length
PxRem (PxRem -> Length) -> PxRem -> Length
forall a b. (a -> b) -> a -> b
$ Float -> PxRem
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> PxRem) -> Float -> PxRem
forall a b. (a -> b) -> a -> b
$ PxRem -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral PxRem
p1 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
pct
Pct Float
pct * PxRem PxRem
p1 = PxRem -> Length
PxRem PxRem
p1 Length -> Length -> Length
forall a. Num a => a -> a -> a
* Float -> Length
Pct Float
pct
Pct Float
p1 * Pct Float
p2 = Float -> Length
Pct (Float -> Length) -> Float -> Length
forall a b. (a -> b) -> a -> b
$ Float
p1 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
p2
abs :: Length -> Length
abs (PxRem PxRem
a) = PxRem -> Length
PxRem (PxRem -> PxRem
forall a. Num a => a -> a
abs PxRem
a)
abs (Pct Float
a) = Float -> Length
Pct (Float -> Float
forall a. Num a => a -> a
abs Float
a)
signum :: Length -> Length
signum (PxRem PxRem
a) = PxRem -> Length
PxRem (PxRem -> PxRem
forall a. Num a => a -> a
signum PxRem
a)
signum (Pct Float
a) = Float -> Length
Pct (Float -> Float
forall a. Num a => a -> a
signum Float
a)
negate :: Length -> Length
negate (PxRem PxRem
a) = PxRem -> Length
PxRem (PxRem -> PxRem
forall a. Num a => a -> a
negate PxRem
a)
negate (Pct Float
a) = Float -> Length
Pct (Float -> Float
forall a. Num a => a -> a
negate Float
a)
fromInteger :: Integer -> Length
fromInteger Integer
n = PxRem -> Length
PxRem (Integer -> PxRem
forall a. Num a => Integer -> a
fromInteger Integer
n)
instance ToStyle PxRem where
style :: PxRem -> Style
style (PxRem' Int
0) = Style
"0px"
style (PxRem' Int
1) = Style
"1px"
style (PxRem' Int
n) = String -> Style
Style (String -> Style) -> String -> Style
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
3) ((Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n :: Float) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
16.0) String
"" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"rem"
instance ToStyle Length where
style :: Length -> Style
style (PxRem PxRem
p) = PxRem -> Style
forall a. ToStyle a => a -> Style
style PxRem
p
style (Pct Float
n) = String -> Style
Style (String -> Style) -> String -> Style
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) (Float
n Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
100) String
"" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"%"
newtype Ms = Ms Int
deriving (Int -> Ms -> ShowS
[Ms] -> ShowS
Ms -> String
(Int -> Ms -> ShowS)
-> (Ms -> String) -> ([Ms] -> ShowS) -> Show Ms
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ms -> ShowS
showsPrec :: Int -> Ms -> ShowS
$cshow :: Ms -> String
show :: Ms -> String
$cshowList :: [Ms] -> ShowS
showList :: [Ms] -> ShowS
Show)
deriving newtype (Integer -> Ms
Ms -> Ms
Ms -> Ms -> Ms
(Ms -> Ms -> Ms)
-> (Ms -> Ms -> Ms)
-> (Ms -> Ms -> Ms)
-> (Ms -> Ms)
-> (Ms -> Ms)
-> (Ms -> Ms)
-> (Integer -> Ms)
-> Num Ms
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Ms -> Ms -> Ms
+ :: Ms -> Ms -> Ms
$c- :: Ms -> Ms -> Ms
- :: Ms -> Ms -> Ms
$c* :: Ms -> Ms -> Ms
* :: Ms -> Ms -> Ms
$cnegate :: Ms -> Ms
negate :: Ms -> Ms
$cabs :: Ms -> Ms
abs :: Ms -> Ms
$csignum :: Ms -> Ms
signum :: Ms -> Ms
$cfromInteger :: Integer -> Ms
fromInteger :: Integer -> Ms
Num, Ms -> ClassName
(Ms -> ClassName) -> ToClassName Ms
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: Ms -> ClassName
toClassName :: Ms -> ClassName
ToClassName)
instance ToStyle Ms where
style :: Ms -> Style
style (Ms Int
n) = String -> Style
Style (String -> Style) -> String -> Style
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"ms"
data Wrap
= Wrap
| NoWrap
deriving (Int -> Wrap -> ShowS
[Wrap] -> ShowS
Wrap -> String
(Int -> Wrap -> ShowS)
-> (Wrap -> String) -> ([Wrap] -> ShowS) -> Show Wrap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Wrap -> ShowS
showsPrec :: Int -> Wrap -> ShowS
$cshow :: Wrap -> String
show :: Wrap -> String
$cshowList :: [Wrap] -> ShowS
showList :: [Wrap] -> ShowS
Show, Wrap -> ClassName
(Wrap -> ClassName) -> ToClassName Wrap
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: Wrap -> ClassName
toClassName :: Wrap -> ClassName
ToClassName)
instance ToStyle Wrap where
style :: Wrap -> Style
style Wrap
Wrap = Style
"wrap"
style Wrap
NoWrap = Style
"nowrap"
data Sides a
= All a
| TRBL a a a a
| X a
| Y a
| XY a a
| T a
| R a
| B a
| L a
| TR a a
| TL a a
| BR a a
| BL a a
instance (Num a) => Num (Sides a) where
Sides a
a + :: Sides a -> Sides a -> Sides a
+ Sides a
_ = Sides a
a
Sides a
a * :: Sides a -> Sides a -> Sides a
* Sides a
_ = Sides a
a
abs :: Sides a -> Sides a
abs Sides a
a = Sides a
a
negate :: Sides a -> Sides a
negate Sides a
a = Sides a
a
signum :: Sides a -> Sides a
signum Sides a
a = Sides a
a
fromInteger :: Integer -> Sides a
fromInteger Integer
n = a -> Sides a
forall a. a -> Sides a
All (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
n)
class ToColor a where
colorValue :: a -> HexColor
colorName :: a -> Text
default colorName :: (Show a) => a -> Text
colorName = Text -> Text
T.toLower (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
newtype HexColor = HexColor Text
deriving (Int -> HexColor -> ShowS
[HexColor] -> ShowS
HexColor -> String
(Int -> HexColor -> ShowS)
-> (HexColor -> String) -> ([HexColor] -> ShowS) -> Show HexColor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HexColor -> ShowS
showsPrec :: Int -> HexColor -> ShowS
$cshow :: HexColor -> String
show :: HexColor -> String
$cshowList :: [HexColor] -> ShowS
showList :: [HexColor] -> ShowS
Show)
instance ToColor HexColor where
colorValue :: HexColor -> HexColor
colorValue HexColor
c = HexColor
c
colorName :: HexColor -> Text
colorName (HexColor Text
a) = (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') Text
a
instance ToStyle HexColor where
style :: HexColor -> Style
style (HexColor Text
s) = String -> Style
Style (String -> Style) -> String -> Style
forall a b. (a -> b) -> a -> b
$ String
"#" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack ((Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') Text
s)
instance IsString HexColor where
fromString :: String -> HexColor
fromString = Text -> HexColor
HexColor (Text -> HexColor) -> (String -> Text) -> String -> HexColor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance ToClassName HexColor where
toClassName :: HexColor -> ClassName
toClassName = Text -> ClassName
className (Text -> ClassName) -> (HexColor -> Text) -> HexColor -> ClassName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HexColor -> Text
forall a. ToColor a => a -> Text
colorName