module Web.Atomic.CSS.Box where
import Web.Atomic.Types
pad :: (Styleable h) => Sides Length -> CSS h -> CSS h
pad :: forall h. Styleable h => Sides Length -> CSS h -> CSS h
pad =
ClassName
-> (Property -> Property) -> Sides Length -> CSS h -> CSS h
forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
ClassName -> (Property -> Property) -> Sides a -> CSS h -> CSS h
sides ClassName
"p" (Property
"padding" Property -> Property -> Property
forall a. Semigroup a => a -> a -> a
<>)
gap :: (Styleable h) => Length -> CSS h -> CSS h
gap :: forall h. Styleable h => Length -> CSS h -> CSS h
gap Length
n = ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"gap" ClassName -> Length -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. Length
n) [Property
"gap" Property -> Style -> Declaration
:. Length -> Style
forall a. ToStyle a => a -> Style
style Length
n]
margin :: (Styleable h) => Sides Length -> CSS h -> CSS h
margin :: forall h. Styleable h => Sides Length -> CSS h -> CSS h
margin =
ClassName
-> (Property -> Property) -> Sides Length -> CSS h -> CSS h
forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
ClassName -> (Property -> Property) -> Sides a -> CSS h -> CSS h
sides ClassName
"m" (Property
"margin" Property -> Property -> Property
forall a. Semigroup a => a -> a -> a
<>)
shadow :: (Styleable h, PropertyStyle Shadow a, ToClassName a) => a -> CSS h -> CSS h
shadow :: forall h a.
(Styleable h, PropertyStyle Shadow a, ToClassName a) =>
a -> CSS h -> CSS h
shadow a
a =
ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"shadow" ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property
"box-shadow" Property -> Style -> Declaration
:. forall {k} (property :: k) value.
PropertyStyle property value =>
value -> Style
forall property value.
PropertyStyle property value =>
value -> Style
propertyStyle @Shadow a
a]
data Shadow
data Inner = Inner
deriving (Int -> Inner -> ShowS
[Inner] -> ShowS
Inner -> String
(Int -> Inner -> ShowS)
-> (Inner -> String) -> ([Inner] -> ShowS) -> Show Inner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Inner -> ShowS
showsPrec :: Int -> Inner -> ShowS
$cshow :: Inner -> String
show :: Inner -> String
$cshowList :: [Inner] -> ShowS
showList :: [Inner] -> ShowS
Show, Inner -> ClassName
(Inner -> ClassName) -> ToClassName Inner
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: Inner -> ClassName
toClassName :: Inner -> ClassName
ToClassName)
instance PropertyStyle Shadow () where
propertyStyle :: () -> Style
propertyStyle ()
_ = Style
"0 1px 3px 0 rgb(0 0 0 / 0.1), 0 1px 2px -1px rgb(0 0 0 / 0.1);"
instance PropertyStyle Shadow None where
propertyStyle :: None -> Style
propertyStyle None
_ = Style
"0 0 #0000;"
instance PropertyStyle Shadow Inner where
propertyStyle :: Inner -> Style
propertyStyle Inner
_ = Style
"inset 0 2px 4px 0 rgb(0 0 0 / 0.05);"
bg :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
bg :: forall clr h. (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
bg clr
c = ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"bg" ClassName -> Text -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. clr -> Text
forall a. ToColor a => a -> Text
colorName clr
c) [Property
"background-color" Property -> Style -> Declaration
:. HexColor -> Style
forall a. ToStyle a => a -> Style
style (clr -> HexColor
forall a. ToColor a => a -> HexColor
colorValue clr
c)]
rounded :: (Styleable h) => Length -> CSS h -> CSS h
rounded :: forall h. Styleable h => Length -> CSS h -> CSS h
rounded Length
n = ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"rnd" ClassName -> Length -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. Length
n) [Property
"border-radius" Property -> Style -> Declaration
:. Length -> Style
forall a. ToStyle a => a -> Style
style Length
n]
border :: (Styleable h) => Sides PxRem -> CSS h -> CSS h
border :: forall h. Styleable h => Sides PxRem -> CSS h -> CSS h
border Sides PxRem
s = Sides PxRem -> CSS h -> CSS h
forall h. Styleable h => Sides PxRem -> CSS h -> CSS h
borderWidth Sides PxRem
s (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BorderStyle -> CSS h -> CSS h
forall h. Styleable h => BorderStyle -> CSS h -> CSS h
borderStyle BorderStyle
Solid
borderStyle :: (Styleable h) => BorderStyle -> CSS h -> CSS h
borderStyle :: forall h. Styleable h => BorderStyle -> CSS h -> CSS h
borderStyle BorderStyle
s = ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"brds" ClassName -> BorderStyle -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. BorderStyle
s) [Property
"border-style" Property -> Style -> Declaration
:. BorderStyle -> Style
forall a. ToStyle a => a -> Style
style BorderStyle
s]
data BorderStyle
= Solid
| Dashed
deriving (Int -> BorderStyle -> ShowS
[BorderStyle] -> ShowS
BorderStyle -> String
(Int -> BorderStyle -> ShowS)
-> (BorderStyle -> String)
-> ([BorderStyle] -> ShowS)
-> Show BorderStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BorderStyle -> ShowS
showsPrec :: Int -> BorderStyle -> ShowS
$cshow :: BorderStyle -> String
show :: BorderStyle -> String
$cshowList :: [BorderStyle] -> ShowS
showList :: [BorderStyle] -> ShowS
Show, BorderStyle -> Style
(BorderStyle -> Style) -> ToStyle BorderStyle
forall a. (a -> Style) -> ToStyle a
$cstyle :: BorderStyle -> Style
style :: BorderStyle -> Style
ToStyle, BorderStyle -> ClassName
(BorderStyle -> ClassName) -> ToClassName BorderStyle
forall a. (a -> ClassName) -> ToClassName a
$ctoClassName :: BorderStyle -> ClassName
toClassName :: BorderStyle -> ClassName
ToClassName)
borderWidth :: (Styleable h) => Sides PxRem -> CSS h -> CSS h
borderWidth :: forall h. Styleable h => Sides PxRem -> CSS h -> CSS h
borderWidth =
ClassName
-> (Property -> Property) -> Sides PxRem -> CSS h -> CSS h
forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
ClassName -> (Property -> Property) -> Sides a -> CSS h -> CSS h
sides ClassName
"brd" Property -> Property
forall {a}. (Eq a, IsString a, Semigroup a) => a -> a
prop
where
prop :: a -> a
prop a
"" = a
"border-width"
prop a
p = a
"border" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
p a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"-width"
borderColor :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
borderColor :: forall clr h. (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
borderColor clr
c =
ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"brdc" ClassName -> Text -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. clr -> Text
forall a. ToColor a => a -> Text
colorName clr
c) [Property
"border-color" Property -> Style -> Declaration
:. HexColor -> Style
forall a. ToStyle a => a -> Style
style (clr -> HexColor
forall a. ToColor a => a -> HexColor
colorValue clr
c)]
opacity :: (Styleable h) => Float -> CSS h -> CSS h
opacity :: forall h. Styleable h => Float -> CSS h -> CSS h
opacity Float
n =
ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
"opacity" ClassName -> Float -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. Float
n) [Property
"opacity" Property -> Style -> Declaration
:. Float -> Style
forall a. ToStyle a => a -> Style
style Float
n]
sides :: (Styleable h, ToStyle a, ToClassName a, Num a) => ClassName -> (Property -> Property) -> Sides a -> CSS h -> CSS h
sides :: forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
ClassName -> (Property -> Property) -> Sides a -> CSS h -> CSS h
sides ClassName
c Property -> Property
toProp =
(a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> Sides a
-> CSS h
-> CSS h
forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
(a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> Sides a
-> CSS h
-> CSS h
sides'
(\a
a -> ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
c ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property -> Property
toProp Property
"" Property -> Style -> Declaration
:. a -> Style
forall a. ToStyle a => a -> Style
style a
a])
(\a
a -> ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
c ClassName -> ClassName -> ClassName
forall a. Semigroup a => a -> a -> a
<> ClassName
"t" ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property -> Property
toProp Property
"-top" Property -> Style -> Declaration
:. a -> Style
forall a. ToStyle a => a -> Style
style a
a])
(\a
a -> ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
c ClassName -> ClassName -> ClassName
forall a. Semigroup a => a -> a -> a
<> ClassName
"r" ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property -> Property
toProp Property
"-right" Property -> Style -> Declaration
:. a -> Style
forall a. ToStyle a => a -> Style
style a
a])
(\a
a -> ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
c ClassName -> ClassName -> ClassName
forall a. Semigroup a => a -> a -> a
<> ClassName
"b" ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property -> Property
toProp Property
"-bottom" Property -> Style -> Declaration
:. a -> Style
forall a. ToStyle a => a -> Style
style a
a])
(\a
a -> ClassName -> [Declaration] -> CSS h -> CSS h
forall h.
Styleable h =>
ClassName -> [Declaration] -> CSS h -> CSS h
utility (ClassName
c ClassName -> ClassName -> ClassName
forall a. Semigroup a => a -> a -> a
<> ClassName
"l" ClassName -> a -> ClassName
forall a. ToClassName a => ClassName -> a -> ClassName
-. a
a) [Property -> Property
toProp Property
"-left" Property -> Style -> Declaration
:. a -> Style
forall a. ToStyle a => a -> Style
style a
a])
sides' :: (Styleable h, ToStyle a, ToClassName a, Num a) => (a -> CSS h -> CSS h) -> (a -> CSS h -> CSS h) -> (a -> CSS h -> CSS h) -> (a -> CSS h -> CSS h) -> (a -> CSS h -> CSS h) -> Sides a -> CSS h -> CSS h
sides' :: forall h a.
(Styleable h, ToStyle a, ToClassName a, Num a) =>
(a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> (a -> CSS h -> CSS h)
-> Sides a
-> CSS h
-> CSS h
sides' a -> CSS h -> CSS h
all_ a -> CSS h -> CSS h
top a -> CSS h -> CSS h
right a -> CSS h -> CSS h
bottom a -> CSS h -> CSS h
left Sides a
s =
case Sides a
s of
(All a
n) -> a -> CSS h -> CSS h
all_ a
n
(Y a
n) -> a -> CSS h -> CSS h
top a
n (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
bottom a
n
(X a
n) -> a -> CSS h -> CSS h
left a
n (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
right a
n
(XY a
x a
y) -> a -> CSS h -> CSS h
top a
y (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
bottom a
y (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
left a
x (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
right a
x
(TRBL a
t a
r a
b a
l) ->
a -> CSS h -> CSS h
top a
t (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
right a
r (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
bottom a
b (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
left a
l
(T a
x) -> a -> CSS h -> CSS h
top a
x
(R a
x) -> a -> CSS h -> CSS h
right a
x
(B a
x) -> a -> CSS h -> CSS h
bottom a
x
(L a
x) -> a -> CSS h -> CSS h
left a
x
(TR a
t a
r) -> a -> CSS h -> CSS h
top a
t (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
right a
r
(TL a
t a
l) -> a -> CSS h -> CSS h
top a
t (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
left a
l
(BR a
b a
r) -> a -> CSS h -> CSS h
bottom a
b (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
right a
r
(BL a
b a
l) -> a -> CSS h -> CSS h
bottom a
b (CSS h -> CSS h) -> (CSS h -> CSS h) -> CSS h -> CSS h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CSS h -> CSS h
left a
l