{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Web.View.Types where
import Data.Map (Map)
import Data.String (IsString (..))
import Data.Text (Text, pack, unpack)
import Data.Text qualified as T
import GHC.Generics (Generic)
import Numeric (showFFloat)
import Text.Casing (kebab)
data Content
= Node Element
| Text Text
|
Raw Text
data Element = Element
{ Element -> Name
name :: Name
, Element -> Attributes
attributes :: Attributes
, Element -> [Content]
children :: [Content]
}
data Attributes = Attributes
{ Attributes -> [Class]
classes :: [Class]
, Attributes -> Map Name Name
other :: Map Name AttValue
}
instance Semigroup Attributes where
Attributes
a1 <> :: Attributes -> Attributes -> Attributes
<> Attributes
a2 = [Class] -> Map Name Name -> Attributes
Attributes (Attributes
a1.classes [Class] -> [Class] -> [Class]
forall a. Semigroup a => a -> a -> a
<> Attributes
a2.classes) (Attributes
a1.other Map Name Name -> Map Name Name -> Map Name Name
forall a. Semigroup a => a -> a -> a
<> Attributes
a2.other)
instance Monoid Attributes where
mempty :: Attributes
mempty = [Class] -> Map Name Name -> Attributes
Attributes [] Map Name Name
forall a. Monoid a => a
mempty
type Attribute = (Name, AttValue)
type Name = Text
type AttValue = Text
type Mod = Attributes -> Attributes
type CSS = Map Selector Class
data Class = Class
{ Class -> Selector
selector :: Selector
, Class -> Styles
properties :: Styles
}
type Styles = Map Name StyleValue
data Selector = Selector
{ Selector -> Maybe Name
parent :: Maybe Text
, Selector -> Maybe Pseudo
pseudo :: Maybe Pseudo
, Selector -> Maybe Media
media :: Maybe Media
, Selector -> ClassName
className :: ClassName
}
deriving (Selector -> Selector -> Bool
(Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool) -> Eq Selector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Selector -> Selector -> Bool
== :: Selector -> Selector -> Bool
$c/= :: Selector -> Selector -> Bool
/= :: Selector -> Selector -> Bool
Eq, Eq Selector
Eq Selector
-> (Selector -> Selector -> Ordering)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Selector)
-> (Selector -> Selector -> Selector)
-> Ord Selector
Selector -> Selector -> Bool
Selector -> Selector -> Ordering
Selector -> Selector -> Selector
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 :: Selector -> Selector -> Ordering
compare :: Selector -> Selector -> Ordering
$c< :: Selector -> Selector -> Bool
< :: Selector -> Selector -> Bool
$c<= :: Selector -> Selector -> Bool
<= :: Selector -> Selector -> Bool
$c> :: Selector -> Selector -> Bool
> :: Selector -> Selector -> Bool
$c>= :: Selector -> Selector -> Bool
>= :: Selector -> Selector -> Bool
$cmax :: Selector -> Selector -> Selector
max :: Selector -> Selector -> Selector
$cmin :: Selector -> Selector -> Selector
min :: Selector -> Selector -> Selector
Ord)
instance IsString Selector where
fromString :: String -> Selector
fromString String
s = Maybe Name -> Maybe Pseudo -> Maybe Media -> ClassName -> Selector
Selector Maybe Name
forall a. Maybe a
Nothing Maybe Pseudo
forall a. Maybe a
Nothing Maybe Media
forall a. Maybe a
Nothing (String -> ClassName
forall a. IsString a => String -> a
fromString String
s)
selector :: ClassName -> Selector
selector :: ClassName -> Selector
selector = Maybe Name -> Maybe Pseudo -> Maybe Media -> ClassName -> Selector
Selector Maybe Name
forall a. Maybe a
Nothing Maybe Pseudo
forall a. Maybe a
Nothing Maybe Media
forall a. Maybe a
Nothing
newtype ClassName = ClassName
{ ClassName -> Name
text :: Text
}
deriving newtype (ClassName -> ClassName -> Bool
(ClassName -> ClassName -> Bool)
-> (ClassName -> ClassName -> Bool) -> Eq ClassName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClassName -> ClassName -> Bool
== :: ClassName -> ClassName -> Bool
$c/= :: ClassName -> ClassName -> Bool
/= :: ClassName -> ClassName -> Bool
Eq, Eq ClassName
Eq ClassName
-> (ClassName -> ClassName -> Ordering)
-> (ClassName -> ClassName -> Bool)
-> (ClassName -> ClassName -> Bool)
-> (ClassName -> ClassName -> Bool)
-> (ClassName -> ClassName -> Bool)
-> (ClassName -> ClassName -> ClassName)
-> (ClassName -> ClassName -> ClassName)
-> Ord ClassName
ClassName -> ClassName -> Bool
ClassName -> ClassName -> Ordering
ClassName -> ClassName -> ClassName
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 :: ClassName -> ClassName -> Ordering
compare :: ClassName -> ClassName -> Ordering
$c< :: ClassName -> ClassName -> Bool
< :: ClassName -> ClassName -> Bool
$c<= :: ClassName -> ClassName -> Bool
<= :: ClassName -> ClassName -> Bool
$c> :: ClassName -> ClassName -> Bool
> :: ClassName -> ClassName -> Bool
$c>= :: ClassName -> ClassName -> Bool
>= :: ClassName -> ClassName -> Bool
$cmax :: ClassName -> ClassName -> ClassName
max :: ClassName -> ClassName -> ClassName
$cmin :: ClassName -> ClassName -> ClassName
min :: ClassName -> ClassName -> ClassName
Ord, String -> ClassName
(String -> ClassName) -> IsString ClassName
forall a. (String -> a) -> IsString a
$cfromString :: String -> ClassName
fromString :: String -> ClassName
IsString)
class ToClassName a where
toClassName :: a -> Text
default toClassName :: (Show a) => a -> Text
toClassName = Name -> Name
T.toLower (Name -> Name) -> (a -> Name) -> a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Name
T.pack (String -> Name) -> (a -> String) -> a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
instance ToClassName Int
instance ToClassName Text where
toClassName :: Name -> Name
toClassName = Name -> Name
forall a. a -> a
id
instance ToClassName Float where
toClassName :: Float -> Name
toClassName Float
f = String -> Name
pack (String -> Name) -> String -> Name
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
noDot (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
3) Float
f String
""
where
noDot :: Char -> Char
noDot Char
'.' = Char
'-'
noDot Char
c = Char
c
data Pseudo
= Hover
| Active
| Even
| Odd
deriving (Int -> Pseudo -> String -> String
[Pseudo] -> String -> String
Pseudo -> String
(Int -> Pseudo -> String -> String)
-> (Pseudo -> String)
-> ([Pseudo] -> String -> String)
-> Show Pseudo
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Pseudo -> String -> String
showsPrec :: Int -> Pseudo -> String -> String
$cshow :: Pseudo -> String
show :: Pseudo -> String
$cshowList :: [Pseudo] -> String -> String
showList :: [Pseudo] -> String -> String
Show, Pseudo -> Pseudo -> Bool
(Pseudo -> Pseudo -> Bool)
-> (Pseudo -> Pseudo -> Bool) -> Eq Pseudo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pseudo -> Pseudo -> Bool
== :: Pseudo -> Pseudo -> Bool
$c/= :: Pseudo -> Pseudo -> Bool
/= :: Pseudo -> Pseudo -> Bool
Eq, Eq Pseudo
Eq Pseudo
-> (Pseudo -> Pseudo -> Ordering)
-> (Pseudo -> Pseudo -> Bool)
-> (Pseudo -> Pseudo -> Bool)
-> (Pseudo -> Pseudo -> Bool)
-> (Pseudo -> Pseudo -> Bool)
-> (Pseudo -> Pseudo -> Pseudo)
-> (Pseudo -> Pseudo -> Pseudo)
-> Ord Pseudo
Pseudo -> Pseudo -> Bool
Pseudo -> Pseudo -> Ordering
Pseudo -> Pseudo -> Pseudo
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 :: Pseudo -> Pseudo -> Ordering
compare :: Pseudo -> Pseudo -> Ordering
$c< :: Pseudo -> Pseudo -> Bool
< :: Pseudo -> Pseudo -> Bool
$c<= :: Pseudo -> Pseudo -> Bool
<= :: Pseudo -> Pseudo -> Bool
$c> :: Pseudo -> Pseudo -> Bool
> :: Pseudo -> Pseudo -> Bool
$c>= :: Pseudo -> Pseudo -> Bool
>= :: Pseudo -> Pseudo -> Bool
$cmax :: Pseudo -> Pseudo -> Pseudo
max :: Pseudo -> Pseudo -> Pseudo
$cmin :: Pseudo -> Pseudo -> Pseudo
min :: Pseudo -> Pseudo -> Pseudo
Ord)
newtype StyleValue = StyleValue String
deriving newtype (String -> StyleValue
(String -> StyleValue) -> IsString StyleValue
forall a. (String -> a) -> IsString a
$cfromString :: String -> StyleValue
fromString :: String -> StyleValue
IsString, Int -> StyleValue -> String -> String
[StyleValue] -> String -> String
StyleValue -> String
(Int -> StyleValue -> String -> String)
-> (StyleValue -> String)
-> ([StyleValue] -> String -> String)
-> Show StyleValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> StyleValue -> String -> String
showsPrec :: Int -> StyleValue -> String -> String
$cshow :: StyleValue -> String
show :: StyleValue -> String
$cshowList :: [StyleValue] -> String -> String
showList :: [StyleValue] -> String -> String
Show)
class ToStyleValue a where
toStyleValue :: a -> StyleValue
default toStyleValue :: (Show a) => a -> StyleValue
toStyleValue = String -> StyleValue
StyleValue (String -> StyleValue) -> (a -> String) -> a -> StyleValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
kebab (String -> String) -> (a -> String) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
instance ToStyleValue String where
toStyleValue :: String -> StyleValue
toStyleValue = String -> StyleValue
StyleValue
instance ToStyleValue Text where
toStyleValue :: Name -> StyleValue
toStyleValue = String -> StyleValue
StyleValue (String -> StyleValue) -> (Name -> String) -> Name -> StyleValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
unpack
instance ToStyleValue Int
instance ToStyleValue Float where
toStyleValue :: Float -> StyleValue
toStyleValue Float
n = String -> StyleValue
StyleValue (String -> StyleValue) -> String -> StyleValue
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2) Float
n String
""
data Length
=
PxRem PxRem
| Pct Float
deriving (Int -> Length -> String -> String
[Length] -> String -> String
Length -> String
(Int -> Length -> String -> String)
-> (Length -> String)
-> ([Length] -> String -> String)
-> Show Length
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Length -> String -> String
showsPrec :: Int -> Length -> String -> String
$cshow :: Length -> String
show :: Length -> String
$cshowList :: [Length] -> String -> String
showList :: [Length] -> String -> String
Show)
instance ToClassName Length where
toClassName :: Length -> Name
toClassName (PxRem PxRem
p) = PxRem -> Name
forall a. ToClassName a => a -> Name
toClassName PxRem
p
toClassName (Pct Float
p) = Float -> Name
forall a. ToClassName a => a -> Name
toClassName Float
p
newtype PxRem = PxRem' Int
deriving newtype (Int -> PxRem -> String -> String
[PxRem] -> String -> String
PxRem -> String
(Int -> PxRem -> String -> String)
-> (PxRem -> String) -> ([PxRem] -> String -> String) -> Show PxRem
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PxRem -> String -> String
showsPrec :: Int -> PxRem -> String -> String
$cshow :: PxRem -> String
show :: PxRem -> String
$cshowList :: [PxRem] -> String -> String
showList :: [PxRem] -> String -> String
Show, PxRem -> Name
(PxRem -> Name) -> ToClassName PxRem
forall a. (a -> Name) -> ToClassName a
$ctoClassName :: PxRem -> Name
toClassName :: PxRem -> Name
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
Length
a + :: Length -> Length -> Length
+ Length
_ = Length
a
Length
a * :: Length -> Length -> Length
* Length
_ = Length
a
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 ToStyleValue PxRem where
toStyleValue :: PxRem -> StyleValue
toStyleValue (PxRem' Int
0) = StyleValue
"0px"
toStyleValue (PxRem' Int
1) = StyleValue
"1px"
toStyleValue (PxRem' Int
n) = String -> StyleValue
StyleValue (String -> StyleValue) -> String -> StyleValue
forall a b. (a -> b) -> a -> b
$ Float -> String
forall a. Show a => a -> String
show ((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 -> String
forall a. Semigroup a => a -> a -> a
<> String
"rem"
instance ToStyleValue Length where
toStyleValue :: Length -> StyleValue
toStyleValue (PxRem PxRem
p) = PxRem -> StyleValue
forall a. ToStyleValue a => a -> StyleValue
toStyleValue PxRem
p
toStyleValue (Pct Float
n) = String -> StyleValue
StyleValue (String -> StyleValue) -> String -> StyleValue
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
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 -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"%"
newtype Ms = Ms Int
deriving (Int -> Ms -> String -> String
[Ms] -> String -> String
Ms -> String
(Int -> Ms -> String -> String)
-> (Ms -> String) -> ([Ms] -> String -> String) -> Show Ms
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Ms -> String -> String
showsPrec :: Int -> Ms -> String -> String
$cshow :: Ms -> String
show :: Ms -> String
$cshowList :: [Ms] -> String -> String
showList :: [Ms] -> String -> String
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 -> Name
(Ms -> Name) -> ToClassName Ms
forall a. (a -> Name) -> ToClassName a
$ctoClassName :: Ms -> Name
toClassName :: Ms -> Name
ToClassName)
instance ToStyleValue Ms where
toStyleValue :: Ms -> StyleValue
toStyleValue (Ms Int
n) = String -> StyleValue
StyleValue (String -> StyleValue) -> String -> StyleValue
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"ms"
data Media
= MinWidth Int
| MaxWidth Int
deriving (Media -> Media -> Bool
(Media -> Media -> Bool) -> (Media -> Media -> Bool) -> Eq Media
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Media -> Media -> Bool
== :: Media -> Media -> Bool
$c/= :: Media -> Media -> Bool
/= :: Media -> Media -> Bool
Eq, Eq Media
Eq Media
-> (Media -> Media -> Ordering)
-> (Media -> Media -> Bool)
-> (Media -> Media -> Bool)
-> (Media -> Media -> Bool)
-> (Media -> Media -> Bool)
-> (Media -> Media -> Media)
-> (Media -> Media -> Media)
-> Ord Media
Media -> Media -> Bool
Media -> Media -> Ordering
Media -> Media -> Media
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 :: Media -> Media -> Ordering
compare :: Media -> Media -> Ordering
$c< :: Media -> Media -> Bool
< :: Media -> Media -> Bool
$c<= :: Media -> Media -> Bool
<= :: Media -> Media -> Bool
$c> :: Media -> Media -> Bool
> :: Media -> Media -> Bool
$c>= :: Media -> Media -> Bool
>= :: Media -> Media -> Bool
$cmax :: Media -> Media -> Media
max :: Media -> Media -> Media
$cmin :: Media -> Media -> Media
min :: Media -> Media -> Media
Ord)
data Sides a
= All a
| TRBL a a a a
| X a
| Y a
| XY 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)
newtype FlatAttributes = FlatAttributes {FlatAttributes -> Map Name Name
attributes :: Map Name AttValue}
deriving ((forall x. FlatAttributes -> Rep FlatAttributes x)
-> (forall x. Rep FlatAttributes x -> FlatAttributes)
-> Generic FlatAttributes
forall x. Rep FlatAttributes x -> FlatAttributes
forall x. FlatAttributes -> Rep FlatAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FlatAttributes -> Rep FlatAttributes x
from :: forall x. FlatAttributes -> Rep FlatAttributes x
$cto :: forall x. Rep FlatAttributes x -> FlatAttributes
to :: forall x. Rep FlatAttributes x -> FlatAttributes
Generic)
class ToColor a where
colorValue :: a -> HexColor
colorName :: a -> Text
default colorName :: (Show a) => a -> Text
colorName = Name -> Name
T.toLower (Name -> Name) -> (a -> Name) -> a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Name
pack (String -> Name) -> (a -> String) -> a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
instance ToColor HexColor where
colorValue :: HexColor -> HexColor
colorValue HexColor
c = HexColor
c
colorName :: HexColor -> Name
colorName (HexColor Name
a) = (Char -> Bool) -> Name -> Name
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') Name
a
newtype HexColor = HexColor Text
instance ToStyleValue HexColor where
toStyleValue :: HexColor -> StyleValue
toStyleValue (HexColor Name
s) = String -> StyleValue
StyleValue (String -> StyleValue) -> String -> StyleValue
forall a b. (a -> b) -> a -> b
$ String
"#" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Name -> String
unpack ((Char -> Bool) -> Name -> Name
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') Name
s)
instance IsString HexColor where
fromString :: String -> HexColor
fromString = Name -> HexColor
HexColor (Name -> HexColor) -> (String -> Name) -> String -> HexColor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Name -> Name
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') (Name -> Name) -> (String -> Name) -> String -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Name
T.pack
data Align
= Center
deriving (Int -> Align -> String -> String
[Align] -> String -> String
Align -> String
(Int -> Align -> String -> String)
-> (Align -> String) -> ([Align] -> String -> String) -> Show Align
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Align -> String -> String
showsPrec :: Int -> Align -> String -> String
$cshow :: Align -> String
show :: Align -> String
$cshowList :: [Align] -> String -> String
showList :: [Align] -> String -> String
Show, Align -> Name
(Align -> Name) -> ToClassName Align
forall a. (a -> Name) -> ToClassName a
$ctoClassName :: Align -> Name
toClassName :: Align -> Name
ToClassName, Align -> StyleValue
(Align -> StyleValue) -> ToStyleValue Align
forall a. (a -> StyleValue) -> ToStyleValue a
$ctoStyleValue :: Align -> StyleValue
toStyleValue :: Align -> StyleValue
ToStyleValue)