{-# LANGUAGE OverloadedStrings #-}
module Clay.Geometry
(
size, top, left, bottom, right
, width, height, minWidth, minHeight, maxWidth, maxHeight
, AspectRatio
, aspectRatio
, (%)
, withFallback
, padding
, paddingTop, paddingLeft, paddingRight, paddingBottom
, margin
, marginTop, marginLeft, marginRight, marginBottom
)
where
import qualified Data.Ratio as R
import Data.String (fromString)
import Clay.Common
import Clay.Property
import Clay.Stylesheet
import Clay.Size
size, top, left, bottom, right :: Size a -> Css
size :: forall a. Size a -> Css
size = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"size"
top :: forall a. Size a -> Css
top = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"top"
left :: forall a. Size a -> Css
left = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"left"
bottom :: forall a. Size a -> Css
bottom = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"bottom"
right :: forall a. Size a -> Css
right = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"right"
width, height, minWidth, minHeight, maxWidth, maxHeight :: Size a -> Css
width :: forall a. Size a -> Css
width = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"width"
height :: forall a. Size a -> Css
height = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"height"
minWidth :: forall a. Size a -> Css
minWidth = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"min-width"
minHeight :: forall a. Size a -> Css
minHeight = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"min-height"
maxWidth :: forall a. Size a -> Css
maxWidth = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"max-width"
maxHeight :: forall a. Size a -> Css
maxHeight = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"max-height"
data AspectRatio = AspectRatio Rational
| AspectRatioValue Value
| AspectRatioWithFallback (AspectRatio, AspectRatio)
instance Auto AspectRatio where auto :: AspectRatio
auto = Value -> AspectRatio
AspectRatioValue Value
forall a. Auto a => a
auto
instance Inherit AspectRatio where inherit :: AspectRatio
inherit = Value -> AspectRatio
AspectRatioValue Value
forall a. Inherit a => a
inherit
instance Initial AspectRatio where initial :: AspectRatio
initial = Value -> AspectRatio
AspectRatioValue Value
forall a. Initial a => a
initial
instance Unset AspectRatio where unset :: AspectRatio
unset = Value -> AspectRatio
AspectRatioValue Value
forall a. Unset a => a
unset
instance Other AspectRatio where other :: Value -> AspectRatio
other = Value -> AspectRatio
AspectRatioValue
instance Num AspectRatio where
fromInteger :: Integer -> AspectRatio
fromInteger = Rational -> AspectRatio
AspectRatio (Rational -> AspectRatio)
-> (Integer -> Rational) -> Integer -> AspectRatio
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Rational
forall a. Real a => a -> Rational
toRational
+ :: AspectRatio -> AspectRatio -> AspectRatio
(+) = [Char] -> AspectRatio -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"plus not implemented for AspectRatio"
* :: AspectRatio -> AspectRatio -> AspectRatio
(*) = [Char] -> AspectRatio -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"times not implemented for AspectRatio"
abs :: AspectRatio -> AspectRatio
abs = [Char] -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"abs not implemented for AspectRatio"
signum :: AspectRatio -> AspectRatio
signum = [Char] -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"signum not implemented for AspectRatio"
negate :: AspectRatio -> AspectRatio
negate = [Char] -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"negate not implemented for AspectRatio"
instance Fractional AspectRatio where
fromRational :: Rational -> AspectRatio
fromRational = Rational -> AspectRatio
AspectRatio
recip :: AspectRatio -> AspectRatio
recip = [Char] -> AspectRatio -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"recip not implemented for AspectRatio"
instance Val AspectRatio where
value :: AspectRatio -> Value
value (AspectRatioValue Value
v) = Value
v
value (AspectRatio Rational
r) = Value
v
where v :: Value
v = [Char] -> Value
forall a. IsString a => [Char] -> a
fromString ([Char] -> Value) -> [Char] -> Value
forall a b. (a -> b) -> a -> b
$ [Char]
numerator [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/" [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
denominator :: Value
numerator :: [Char]
numerator = Integer -> [Char]
forall a. Show a => a -> [Char]
show (Rational -> Integer
forall a. Ratio a -> a
R.numerator Rational
r)
denominator :: [Char]
denominator = Integer -> [Char]
forall a. Show a => a -> [Char]
show (Rational -> Integer
forall a. Ratio a -> a
R.denominator Rational
r)
value (AspectRatioWithFallback (AspectRatio
a, AspectRatio
b)) = AspectRatio -> Value
forall a. Val a => a -> Value
value AspectRatio
a Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Value
" " Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> AspectRatio -> Value
forall a. Val a => a -> Value
value AspectRatio
b
aspectRatio :: AspectRatio -> Css
aspectRatio :: AspectRatio -> Css
aspectRatio = Key AspectRatio -> AspectRatio -> Css
forall a. Val a => Key a -> a -> Css
key Key AspectRatio
"aspect-ratio"
(%) :: Integer -> Integer -> AspectRatio
% :: Integer -> Integer -> AspectRatio
(%) Integer
m Integer
n = Rational -> AspectRatio
forall a. Fractional a => Rational -> a
fromRational (Rational -> AspectRatio) -> Rational -> AspectRatio
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
(R.%) Integer
m Integer
n
infixl 7 %
withFallback :: AspectRatio -> AspectRatio -> AspectRatio
withFallback :: AspectRatio -> AspectRatio -> AspectRatio
withFallback x :: AspectRatio
x@(AspectRatioValue Value
"auto") y :: AspectRatio
y@(AspectRatio Rational
_) =
(AspectRatio, AspectRatio) -> AspectRatio
AspectRatioWithFallback (AspectRatio
x, AspectRatio
y)
withFallback x :: AspectRatio
x@(AspectRatio Rational
_) y :: AspectRatio
y@(AspectRatioValue Value
"auto") =
(AspectRatio, AspectRatio) -> AspectRatio
AspectRatioWithFallback (AspectRatio
x, AspectRatio
y)
withFallback AspectRatio
_ AspectRatio
_ =
[Char] -> AspectRatio
forall a. HasCallStack => [Char] -> a
error [Char]
"Arguments for aspectRatio . withFallback must be auto and a ratio in either order"
padding :: Size a -> Size a -> Size a -> Size a -> Css
padding :: forall a. Size a -> Size a -> Size a -> Size a -> Css
padding Size a
a Size a
b Size a
c Size a
d = Key (Size a, (Size a, (Size a, Size a)))
-> (Size a, (Size a, (Size a, Size a))) -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a, (Size a, (Size a, Size a)))
"padding" (Size a
a Size a
-> (Size a, (Size a, Size a))
-> (Size a, (Size a, (Size a, Size a)))
forall a b. a -> b -> (a, b)
! Size a
b Size a -> (Size a, Size a) -> (Size a, (Size a, Size a))
forall a b. a -> b -> (a, b)
! Size a
c Size a -> Size a -> (Size a, Size a)
forall a b. a -> b -> (a, b)
! Size a
d)
paddingTop, paddingLeft, paddingRight, paddingBottom :: Size a -> Css
paddingTop :: forall a. Size a -> Css
paddingTop = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"padding-top"
paddingLeft :: forall a. Size a -> Css
paddingLeft = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"padding-left"
paddingRight :: forall a. Size a -> Css
paddingRight = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"padding-right"
paddingBottom :: forall a. Size a -> Css
paddingBottom = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"padding-bottom"
margin :: Size a -> Size a -> Size a -> Size a -> Css
margin :: forall a. Size a -> Size a -> Size a -> Size a -> Css
margin Size a
a Size a
b Size a
c Size a
d = Key (Size a, (Size a, (Size a, Size a)))
-> (Size a, (Size a, (Size a, Size a))) -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a, (Size a, (Size a, Size a)))
"margin" (Size a
a Size a
-> (Size a, (Size a, Size a))
-> (Size a, (Size a, (Size a, Size a)))
forall a b. a -> b -> (a, b)
! Size a
b Size a -> (Size a, Size a) -> (Size a, (Size a, Size a))
forall a b. a -> b -> (a, b)
! Size a
c Size a -> Size a -> (Size a, Size a)
forall a b. a -> b -> (a, b)
! Size a
d)
marginTop, marginLeft, marginRight, marginBottom :: Size a -> Css
marginTop :: forall a. Size a -> Css
marginTop = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"margin-top"
marginLeft :: forall a. Size a -> Css
marginLeft = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"margin-left"
marginRight :: forall a. Size a -> Css
marginRight = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"margin-right"
marginBottom :: forall a. Size a -> Css
marginBottom = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"margin-bottom"