{-# LANGUAGE PostfixOperators #-}
module Stan.Report.Css
( stanCss
) where
import Prelude hiding (div, rem, (&), (**))
import Clay hiding (brown, cols, grid, border, borderRight, borderTop, borderLeft, borderBottom)
import qualified Clay
import qualified Clay.Media as M
import qualified Data.List.NonEmpty as NE
border, borderLeft, borderBottom, borderRight, borderTop
:: Stroke -> Size LengthUnit -> Color -> Css
border :: Stroke -> Size LengthUnit -> Color -> Css
border Stroke
x Size LengthUnit
y = Size LengthUnit -> Stroke -> Color -> Css
Clay.border Size LengthUnit
y Stroke
x
borderLeft :: Stroke -> Size LengthUnit -> Color -> Css
borderLeft Stroke
x Size LengthUnit
y = Size LengthUnit -> Stroke -> Color -> Css
Clay.borderLeft Size LengthUnit
y Stroke
x
borderBottom :: Stroke -> Size LengthUnit -> Color -> Css
borderBottom Stroke
x Size LengthUnit
y = Size LengthUnit -> Stroke -> Color -> Css
Clay.borderBottom Size LengthUnit
y Stroke
x
borderRight :: Stroke -> Size LengthUnit -> Color -> Css
borderRight Stroke
x Size LengthUnit
y = Size LengthUnit -> Stroke -> Color -> Css
Clay.borderRight Size LengthUnit
y Stroke
x
borderTop :: Stroke -> Size LengthUnit -> Color -> Css
borderTop Stroke
x Size LengthUnit
y = Size LengthUnit -> Stroke -> Color -> Css
Clay.borderTop Size LengthUnit
y Stroke
x
stanCss :: Css
stanCss :: Css
stanCss = do
Css
grid
Selector
main_ Selector -> Css -> Css
? Css
marginAuto
Selector
nav Selector -> Css -> Css
? do
Color -> Css
backgroundColor Color
darkGrey
Color -> Css
color Color
yellow
Size Percentage -> Size Percentage -> Css
forall a. Size a -> Size a -> Css
padding2 (Rational
1%) (Rational
0%)
Selector
a Selector -> Css -> Css
? do
TextDecoration -> Css
textDecoration TextDecoration
forall a. None a => a
none
Color -> Css
color Color
yellow
Refinement
"@href" Refinement -> Css -> Css
& do
TextDecoration -> Css
textDecoration TextDecoration
underline
Refinement
":hover" Refinement -> Css -> Css
& FontWeight -> Css
fontWeight FontWeight
bold
Selector
footer Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
header Selector -> Css -> Css
? do
Display -> Css
display Display
block
TextAlign -> Css
textAlign TextAlign
forall a. Center a => a
center
Size Percentage -> Css
forall a. Size a -> Css
width (Rational
100%)
Size Percentage -> Css
forall a. Size a -> Css
maxWidth (Rational
100%)
Color -> Css
backgroundColor Color
lightGrey
Stroke -> Size LengthUnit -> Color -> Css
borderTop Stroke
solid (Number -> Size LengthUnit
px Number
15) Color
darkGrey
Selector
footer Selector -> Css -> Css
? Size Percentage -> Css
forall a. Size a -> Css
marginTop (Rational
2%)
Selector
footer Selector -> Selector -> Selector
|> Selector
".container" Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
marginTopBottom (Number -> Size LengthUnit
px Number
20)
Selector
".footer-link" Selector -> Selector -> Selector
** (Selector
a Selector -> Refinement -> Selector
# Refinement
hover) Selector -> Css -> Css
? (FontWeight -> Css
fontWeight FontWeight
forall a. Normal a => a
normal Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TextDecoration -> Css
textDecoration TextDecoration
forall a. None a => a
none)
Selector
".ins-link" Selector -> Css -> Css
? do
Css -> Css
important (TextDecoration -> Css
textDecoration TextDecoration
forall a. None a => a
none)
Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Css
padding2 (Number -> Size LengthUnit
px Number
2) (Number -> Size LengthUnit
px Number
10)
Color -> Css
backgroundColor Color
darkGrey
Color -> Css
color Color
white
Selector
".ins-link" Selector -> Refinement -> Selector
# Refinement
hover Selector -> Css -> Css
? (Color -> Css
color Color
darkGrey Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Color -> Css
backgroundColor Color
transparent)
Selector
pre Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
code Selector -> Css -> Css
? (Color -> Css
backgroundColor Color
brown Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Color -> Css
color Color
white Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding (Number -> Size LengthUnit
px Number
1) Size LengthUnit
2 Size LengthUnit
1 Size LengthUnit
2)
Selector
pre Selector -> Css -> Css
? do
Size Percentage -> Size Percentage -> Css
forall a b. Size a -> Size b -> Css
margin2 (Rational
2%) (Rational
10%)
Size Percentage -> Css
paddingAll Size Percentage
2
Overflow -> Css
overflowX Overflow
forall a. Auto a => a
auto
Selector
".solutions" Selector -> Css -> Css
? do
Size Percentage -> Size Percentage -> Css
forall a b. Size a -> Size b -> Css
margin2 (Rational
1%) (Rational
10%)
Size Percentage -> Css
paddingAll Size Percentage
1
Color -> Css
backgroundColor (Integer -> Integer -> Integer -> Float -> Color
rgba Integer
255 Integer
246 Integer
143 Float
0.4)
Css -> Css
important (Css -> Css) -> Css -> Css
forall a b. (a -> b) -> a -> b
$ Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
4) Size LengthUnit
4 Size LengthUnit
4 Size LengthUnit
4
(Selector
".solutions" Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
".config-warnings") Selector -> Selector -> Selector
** Selector
ul Selector -> Css -> Css
? ListStyleType -> Css
listStyleType ListStyleType
forall a. None a => a
none
Selector
".solutions" Selector -> Selector -> Selector
** (Selector
li Selector -> Refinement -> Selector
# Refinement
before) Selector -> Css -> Css
? Content -> Css
content (Text -> Content
stringContent Text
"💡")
Selector
".config-warnings" Selector -> Selector -> Selector
** (Selector
li Selector -> Refinement -> Selector
# Refinement
before) Selector -> Css -> Css
? Content -> Css
content (Text -> Content
stringContent Text
"⚙️")
Selector
table Selector -> Css -> Css
? do
Size Percentage -> Css
forall a. Size a -> Css
width (Rational
100%)
Css -> Css
important (Css -> Css) -> Css -> Css
forall a b. (a -> b) -> a -> b
$ Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
4) Size LengthUnit
4 Size LengthUnit
4 Size LengthUnit
4
Visibility -> Css
borderCollapse Visibility
collapse
Selector
th Selector -> Refinement -> Selector
# Refinement
firstChild Selector -> Css -> Css
? Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
4) Size LengthUnit
0 Size LengthUnit
0 Size LengthUnit
0
Selector
th Selector -> Refinement -> Selector
# Refinement
lastChild Selector -> Css -> Css
? Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius Size LengthUnit
0 (Number -> Size LengthUnit
px Number
4) Size LengthUnit
0 Size LengthUnit
0
Selector
td Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
th Selector -> Css -> Css
? Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Css
padding2 Size LengthUnit
forall a. Size a
nil (Number -> Size LengthUnit
px Number
8)
(Selector
".observation" Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
"#configurations" Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
"#stan-info" Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
"#severity") Selector -> Selector -> Selector
** (Selector
tr Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
td Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
th) Selector -> Css -> Css
?
Stroke -> Size LengthUnit -> Color -> Css
border Stroke
solid (Number -> Size LengthUnit
px Number
1) Color
lightGrey
Selector
".border-shadow" Selector -> Css -> Css
? do
NonEmpty BoxShadow -> Css
boxShadow (NonEmpty BoxShadow -> Css) -> NonEmpty BoxShadow -> Css
forall a b. (a -> b) -> a -> b
$ OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall x. One x => OneItem x -> x
one (OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow)
-> OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall a b. (a -> b) -> a -> b
$ Color -> BoxShadow -> BoxShadow
bsColor (Float -> Color -> Color
setA Float
0.3 Color
darkGrey) (BoxShadow -> BoxShadow) -> BoxShadow -> BoxShadow
forall a b. (a -> b) -> a -> b
$ Size LengthUnit
-> Size LengthUnit
-> Size LengthUnit
-> Size LengthUnit
-> BoxShadow
forall a. Size a -> Size a -> Size a -> Size a -> BoxShadow
shadowWithSpread (Number -> Size LengthUnit
px Number
0) Size LengthUnit
0 Size LengthUnit
4 Size LengthUnit
4
Stroke -> Css
borderStyle (Value -> Stroke
forall a. Other a => Value -> a
other (Value -> Stroke) -> Value -> Stroke
forall a b. (a -> b) -> a -> b
$ Prefixed -> Value
Value (Prefixed -> Value) -> Prefixed -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Prefixed
Plain Text
"hidden")
Selector
".info-name" Selector -> Css -> Css
? FontStyle -> Css
fontStyle FontStyle
italic
Selector
".info-data" Selector -> Css -> Css
? FontWeight -> Css
fontWeight FontWeight
bold
Selector
"#stan-info" Selector -> Selector -> Selector
** Selector
table Selector -> Css -> Css
? Css
marginAuto
Selector
blockquote Selector -> Css -> Css
? do
Size Percentage -> Css
forall a. Size a -> Css
paddingLeft (Rational
2%)
Stroke -> Size LengthUnit -> Color -> Css
borderLeft Stroke
solid (Number -> Size LengthUnit
px Number
4) Color
darkGrey
NonEmpty BoxShadow -> Css
boxShadow (NonEmpty BoxShadow -> Css) -> NonEmpty BoxShadow -> Css
forall a b. (a -> b) -> a -> b
$ OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall x. One x => OneItem x -> x
one (OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow)
-> OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall a b. (a -> b) -> a -> b
$ Color -> BoxShadow -> BoxShadow
bsColor Color
lightGrey (BoxShadow -> BoxShadow) -> BoxShadow -> BoxShadow
forall a b. (a -> b) -> a -> b
$ Size LengthUnit -> Size LengthUnit -> BoxShadow
forall a. Size a -> Size a -> BoxShadow
shadow (Number -> Size LengthUnit
px (-Number
4)) Size LengthUnit
0
Selector
".obs-li" Selector -> Css -> Css
? Css -> Css
important (Size Percentage -> Css
marginAll Size Percentage
0)
Selector
"#file" Selector -> Selector -> Selector
|> Selector
h3 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
paddingLeft (Number -> Size LengthUnit
px Number
5)
Selector
"#file" Selector -> Selector -> Selector
|> Selector
ul Selector -> Css -> Css
? ListStyleType -> Css
listStyleType ListStyleType
forall a. None a => a
none
Css
stanCategory
Css
stanSeverity
Css
summarySection
Css
collapsible
stanCategory :: Css
stanCategory :: Css
stanCategory = do
Selector
".cats" Selector -> Css -> Css
? (ListStyleType -> Css
listStyleType ListStyleType
forall a. None a => a
none Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Overflow -> Css
overflow Overflow
forall a. Hidden a => a
hidden Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Percentage -> Css
paddingAll Size Percentage
0)
Selector
".inline" Selector -> Css -> Css
? Display -> Css
display Display
inline
Selector
".cats" Selector -> Selector -> Selector
|> Selector
li Selector -> Css -> Css
? FloatStyle -> Css
float FloatStyle
floatLeft
Selector
td Selector -> Selector -> Selector
|> Selector
".cats" Selector -> Selector -> Selector
|> Selector
li Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
marginTopBottom (Number -> Size LengthUnit
px Number
2)
Selector
".cat" Selector -> Css -> Css
? do
Color -> Css
backgroundColor Color
pink
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
3) (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
3)
Display -> Css
display Display
inlineBlock
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
20) (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
23)
TextDecoration -> Css
textDecoration TextDecoration
forall a. None a => a
none
Position -> Css
position Position
relative
Text -> Css
transitionProperty Text
"color"
Time -> Css
transitionDuration (Double -> Time
sec Double
0.2)
Selector
".cat" Selector -> Refinement -> Selector
# Refinement
before Selector -> Css -> Css
? do
Color -> Css
backgroundColor Color
white
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
10) Size LengthUnit
10 Size LengthUnit
10 Size LengthUnit
10
NonEmpty BoxShadow -> Css
boxShadow (NonEmpty BoxShadow -> Css) -> NonEmpty BoxShadow -> Css
forall a b. (a -> b) -> a -> b
$ OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall x. One x => OneItem x -> x
one (OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow)
-> OneItem (NonEmpty BoxShadow) -> NonEmpty BoxShadow
forall a b. (a -> b) -> a -> b
$ BoxShadow -> BoxShadow
bsInset (BoxShadow -> BoxShadow) -> BoxShadow -> BoxShadow
forall a b. (a -> b) -> a -> b
$ Color -> BoxShadow -> BoxShadow
bsColor (Integer -> Integer -> Integer -> Float -> Color
rgba Integer
0 Integer
0 Integer
0 Float
0.25) (BoxShadow -> BoxShadow) -> BoxShadow -> BoxShadow
forall a b. (a -> b) -> a -> b
$
Size LengthUnit -> Size LengthUnit -> BoxShadow
forall a. Size a -> Size a -> BoxShadow
shadow (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
1)
Content -> Css
content (Text -> Content
stringContent Text
"")
Size LengthUnit -> Css
forall a. Size a -> Css
height (Number -> Size LengthUnit
px Number
6)
Size LengthUnit -> Css
forall a. Size a -> Css
left (Number -> Size LengthUnit
px Number
10)
Position -> Css
position Position
absolute
Size LengthUnit -> Css
forall a. Size a -> Css
width (Number -> Size LengthUnit
px Number
6)
Size LengthUnit -> Css
forall a. Size a -> Css
top (Number -> Size LengthUnit
px Number
10)
Selector -> Color -> Css
catTriangle Selector
".cat" Color
veryLightGrey
(Selector
".inline" Selector -> Selector -> Selector
|> Selector
".cat") Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? Color -> Css
backgroundColor Color
white
where
catTriangle :: Selector -> Color -> Css
catTriangle Selector
cl Color
c = Selector
cl Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? do
Color -> Css
backgroundColor Color
c
Stroke -> Size LengthUnit -> Color -> Css
borderBottom Stroke
solid (Number -> Size LengthUnit
px Number
13) Color
transparent
Stroke -> Size LengthUnit -> Color -> Css
borderLeft Stroke
solid (Number -> Size LengthUnit
px Number
10) Color
pink
Stroke -> Size LengthUnit -> Color -> Css
borderTop Stroke
solid (Number -> Size LengthUnit
px Number
13) Color
transparent
Content -> Css
content (Text -> Content
stringContent Text
"")
Position -> Css
position Position
absolute
Size Percentage -> Css
forall a. Size a -> Css
right (Rational
0%) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Percentage -> Css
forall a. Size a -> Css
top (Rational
0%)
stanSeverity :: Css
stanSeverity :: Css
stanSeverity = do
Selector
".severity" Selector -> Css -> Css
? do
Display -> Css
display Display
inlineBlock
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding (Number -> Size LengthUnit
px Number
1) Size LengthUnit
0 Size LengthUnit
0 Size LengthUnit
0
Stroke -> Size LengthUnit -> Color -> Css
border Stroke
solid (Number -> Size LengthUnit
px Number
1) Color
darkGrey
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
4) (Number -> Size LengthUnit
px Number
4) (Number -> Size LengthUnit
px Number
4) (Number -> Size LengthUnit
px Number
4)
Size Any -> Css
forall a. Size a -> Css
lineHeight (Number -> Size Any
forall a. Number -> Size a
unitless Number
1)
Selector
".severityText" Selector -> Css -> Css
? Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Css
padding2 (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
15)
Selector
".severityStyle" Selector -> Css -> Css
? Color -> Css
severityCss Color
cyan
Selector
".severityPerformance" Selector -> Css -> Css
? Color -> Css
severityCss Color
blue
Selector
".severityPotentialBug" Selector -> Css -> Css
? Color -> Css
severityCss Color
magenta
Selector
".severityWarning" Selector -> Css -> Css
? Color -> Css
severityCss Color
yellow
Selector
".severityError" Selector -> Css -> Css
? Color -> Css
severityCss Color
red
Selector
".remove" Selector -> Css -> Css
? Color -> Css
configActionsCss Color
red
Selector
".include" Selector -> Css -> Css
? Color -> Css
configActionsCss Color
green
Selector
".exclude" Selector -> Css -> Css
? Color -> Css
configActionsCss Color
yellow
Selector
".ignore" Selector -> Css -> Css
? Color -> Css
configActionsCss Color
orange
where
configActionsCss :: Color -> Css
configActionsCss :: Color -> Css
configActionsCss Color
c = Color -> Css
color Color
black Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Color -> Css
backgroundColor (Float -> Color -> Color
setA Float
0.5 Color
c)
severityCss :: Color -> Css
severityCss :: Color -> Css
severityCss Color
c = do
Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Css
padding2 (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
15)
Size Percentage -> Css
forall a. Size a -> Css
height (Rational
100%)
Color -> Css
backgroundColor Color
c
BackgroundClip -> Css
backgroundClip (BackgroundClip -> Css) -> BackgroundClip -> Css
forall a b. (a -> b) -> a -> b
$ BoxType -> BackgroundClip
boxClip BoxType
paddingBox
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Number -> Size LengthUnit
px Number
4) (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
0) (Number -> Size LengthUnit
px Number
4)
Stroke -> Size LengthUnit -> Color -> Css
borderRight Stroke
solid (Number -> Size LengthUnit
px Number
1) Color
darkGrey
collapsible :: Css
collapsible :: Css
collapsible = do
Selector
".collapsible" Selector -> Css -> Css
? do
Size Percentage -> Css
forall a. Size a -> Css
width (Rational
100%)
Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
1.125)
Css -> Css
important (Size Percentage -> Css
forall a. Size a -> Css
marginLeft (Rational
0%) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Percentage -> Css
forall a. Size a -> Css
marginBottom (Rational
0%) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Percentage -> Css
forall a. Size a -> Css
marginRight (Rational
0%))
Color -> Css
backgroundColor Color
darkGrey
Color -> Css
color Color
white
CursorValue Value -> Css
forall a. Cursor a => a -> Css
cursor CursorValue Value
pointer
TextAlign -> Css
textAlign (Side -> TextAlign
alignSide Side
sideLeft)
Selector
".active" Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> (Selector
".collapsible" Selector -> Refinement -> Selector
# Refinement
hover) Selector -> Css -> Css
? Color -> Css
backgroundColor Color
lightGrey
Selector
".collapsible" Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? do
Content -> Css
content (Text -> Content
stringContent Text
"\\002B")
Color -> Css
color Color
white
FontWeight -> Css
fontWeight FontWeight
bold
FloatStyle -> Css
float FloatStyle
floatRight
Size LengthUnit -> Css
forall a. Size a -> Css
marginLeft (Number -> Size LengthUnit
px Number
5)
Selector
".active" Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? Content -> Css
content (Text -> Content
stringContent Text
"\\2212")
Selector
".content" Selector -> Css -> Css
? do
Size Any -> Css
forall a. Size a -> Css
maxHeight Size Any
forall a. Size a
nil
Overflow -> Css
overflow Overflow
forall a. Hidden a => a
hidden
Text -> Css
transitionProperty Text
"max-height"
TimingFunction -> Css
transitionTimingFunction TimingFunction
easeOut
Time -> Css
transitionDuration (Double -> Time
sec Double
0.2)
Color -> Css
backgroundColor Color
veryLightGrey
Selector
".content" Selector -> Selector -> Selector
|> Selector
div Selector -> Css -> Css
?
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding Size LengthUnit
0 Size LengthUnit
0 Size LengthUnit
0 (Number -> Size LengthUnit
px Number
18)
summarySection :: Css
summarySection :: Css
summarySection = do
Selector
".sum" Selector -> Css -> Css
?
(Display -> Css
display Display
block Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Clear -> Css
clear Clear
both Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Position -> Css
position Position
relative)
Selector
".sum" Selector -> Refinement -> Selector
# Refinement
before Selector -> Css -> Css
? do
Content -> Css
content (Text -> Content
stringContent Text
"")
Size LengthUnit -> Css
forall a. Size a -> Css
width (Number -> Size LengthUnit
rem Number
4) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size LengthUnit -> Css
forall a. Size a -> Css
height (Number -> Size LengthUnit
rem Number
4)
FloatStyle -> Css
float FloatStyle
floatLeft
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
margin Size LengthUnit
0 (Number -> Size LengthUnit
rem Number
1.5) (Number -> Size LengthUnit
rem Number
0.75) Size LengthUnit
0
BackgroundImage -> Css
backgroundImage (BackgroundImage -> Css) -> BackgroundImage -> Css
forall a b. (a -> b) -> a -> b
$ Direction -> Ramp -> BackgroundImage
linearGradient (Value -> Direction
forall a. Other a => Value -> a
other (Value -> Direction) -> Value -> Direction
forall a b. (a -> b) -> a -> b
$ Prefixed -> Value
Value (Prefixed -> Value) -> Prefixed -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Prefixed
Plain Text
"to bottom right")
[ (Color
color1, Size Percentage
25)
, (Color
color2, Size Percentage
100)
]
Size LengthUnit
-> Size LengthUnit -> Size LengthUnit -> Color -> Css
forall a. Size a -> Size a -> Size a -> Color -> Css
textShadow Size LengthUnit
0 Size LengthUnit
0 (Number -> Size LengthUnit
px Number
2) Color
color1;
Size Percentage
-> Size Percentage -> Size Percentage -> Size Percentage -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
borderRadius (Rational
50%) Size Percentage
50 Size Percentage
50 Size Percentage
50
Display -> Css
display Display
inlineFlex
AlignItemsValue -> Css
alignItems AlignItemsValue
forall a. Center a => a
center
JustifyContentValue -> Css
justifyContent JustifyContentValue
forall a. Center a => a
center
Key Text
"shape-outside" Key Text -> Text -> Css
-: Text
"ellipse()"
Integer -> Css
zIndex Integer
1
Selector
".sum" Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? do
Size LengthUnit -> Css
forall a. Size a -> Css
width (Number -> Size LengthUnit
rem Number
2) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size LengthUnit -> Css
forall a. Size a -> Css
height (Number -> Size LengthUnit
rem Number
2)
Position -> Css
position Position
absolute
Size LengthUnit -> Css
forall a. Size a -> Css
top (Number -> Size LengthUnit
px Number
0) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size LengthUnit -> Css
forall a. Size a -> Css
left (Number -> Size LengthUnit
px Number
0)
Content -> Css
content (Text -> Content
stringContent Text
"")
Color -> Css
backgroundColor Color
color1
Integer -> Css
zIndex (-Integer
1)
Size LengthUnit -> Size LengthUnit -> Css
forall a. Size a -> Size a -> Css
borderTopLeftRadius (Number -> Size LengthUnit
px Number
3) (Number -> Size LengthUnit
px Number
3)
where
color1, color2 :: Color
color1 :: Color
color1 = Color
darkGrey
color2 :: Color
color2 = Color
veryLightGrey
grid :: Css
grid :: Css
grid = do
(Selector
html Selector -> Selector -> Selector
forall a. Semigroup a => a -> a -> a
<> Selector
body) Selector -> Css -> Css
? do
Size Percentage -> Css
forall a. Size a -> Css
height (Rational
100%)
Size Percentage -> Css
forall a. Size a -> Css
width (Rational
100%)
Size Percentage -> Css
marginAll Size Percentage
0
Size Percentage -> Css
paddingAll Size Percentage
0
Size Percentage -> Css
forall a. Size a -> Css
left (Rational
0%)
Size Percentage -> Css
forall a. Size a -> Css
top (Rational
0%)
[Text] -> [GenericFontFamily] -> Css
fontFamily [] [GenericFontFamily
sansSerif]
Size Percentage -> Css
forall a. Size a -> Css
fontSize (Rational
100%)
Color -> Css
color Color
darkGrey
Size Any -> Css
forall a. Size a -> Css
lineHeight (Number -> Size Any
forall a. Number -> Size a
unitless Number
1.5)
Selector
h1 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
2.5)
Selector
h2 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
2)
Selector
h3 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
1.375)
Selector
h4 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
1.125)
Selector
h5 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
1)
Selector
h6 Selector -> Css -> Css
? Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
0.875)
Selector
p Selector -> Css -> Css
? (Size LengthUnit -> Css
forall a. Size a -> Css
fontSize (Number -> Size LengthUnit
rem Number
1.125) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FontWeight -> Css
fontWeight (Integer -> FontWeight
weight Integer
200) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Any -> Css
forall a. Size a -> Css
lineHeight (Number -> Size Any
forall a. Number -> Size a
unitless Number
1.8))
Selector
".centre" Selector -> Css -> Css
? (TextAlign -> Css
textAlign TextAlign
forall a. Center a => a
center Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Css
marginAuto)
Selector
".container" Selector -> Css -> Css
? (Size Percentage -> Css
forall a. Size a -> Css
width (Rational
90%) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Css
marginAuto)
Selector
".row" Selector -> Css -> Css
? (Position -> Css
position Position
relative Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Percentage -> Css
forall a. Size a -> Css
width (Rational
100%))
Selector
".row [class^='col']" Selector -> Css -> Css
? do
FloatStyle -> Css
float FloatStyle
floatLeft
Size LengthUnit -> Size Percentage -> Css
forall a b. Size a -> Size b -> Css
margin2 (Number -> Size LengthUnit
rem Number
0.5) (Rational
2%)
Size LengthUnit -> Css
forall a. Size a -> Css
minHeight (Number -> Size LengthUnit
rem Number
0.125)
NonEmpty Selector -> Selector
forall a. Semigroup a => NonEmpty a -> a
sconcat NonEmpty Selector
colClasses Selector -> Css -> Css
? Size Percentage -> Css
forall a. Size a -> Css
width (Rational
96%)
NonEmpty Selector -> Css
colsGrid NonEmpty Selector
colClassesSm
Selector
".row" Selector -> Refinement -> Selector
# Refinement
after Selector -> Css -> Css
? do
Content -> Css
content (Text -> Content
stringContent Text
"")
Display -> Css
display Display
displayTable
Clear -> Css
clear Clear
both
Selector
".hidden-sm" Selector -> Css -> Css
? Display -> Css
display Display
displayNone
Number -> Css -> Css
mediaQuery Number
33.75 (Css -> Css) -> Css -> Css
forall a b. (a -> b) -> a -> b
$ Selector
".container" Selector -> Css -> Css
? Size Percentage -> Css
forall a. Size a -> Css
width (Rational
80%)
Number -> Css -> Css
mediaQuery Number
45 (Css -> Css) -> Css -> Css
forall a b. (a -> b) -> a -> b
$ NonEmpty Selector -> Css
colsGrid NonEmpty Selector
colClasses
Number -> Css -> Css
mediaQuery Number
60 (Css -> Css) -> Css -> Css
forall a b. (a -> b) -> a -> b
$ Selector
".container" Selector -> Css -> Css
? (Size Percentage -> Css
forall a. Size a -> Css
width (Rational
75%) Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size LengthUnit -> Css
forall a. Size a -> Css
maxWidth (Number -> Size LengthUnit
rem Number
60))
Selector
".grey-bg" Selector -> Css -> Css
? (Color -> Css
backgroundColor Color
darkGrey Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Color -> Css
color Color
white)
Selector
".very-light-bg" Selector -> Css -> Css
? Color -> Css
backgroundColor Color
veryLightGrey
where
cols :: NonEmpty Text
cols :: NonEmpty Text
cols = (Int -> Text) -> NonEmpty Int -> NonEmpty Text
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Text
".col-" <>) (Text -> Text) -> (Int -> Text) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
forall b a. (Show a, IsString b) => a -> b
show) (NonEmpty Int -> NonEmpty Text) -> NonEmpty Int -> NonEmpty Text
forall a b. (a -> b) -> a -> b
$ (Int
1 :: Int) Int -> [Int] -> NonEmpty Int
forall a. a -> [a] -> NonEmpty a
:| [Int
2..Int
12]
colClasses, colClassesSm :: NonEmpty Selector
colClasses :: NonEmpty Selector
colClasses = (Text -> Selector) -> NonEmpty Text -> NonEmpty Selector
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Selector
element NonEmpty Text
cols
colClassesSm :: NonEmpty Selector
colClassesSm = (Text -> Selector) -> NonEmpty Text -> NonEmpty Selector
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Selector
element (Text -> Selector) -> (Text -> Text) -> Text -> Selector
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-sm")) NonEmpty Text
cols
colsGrid :: NonEmpty Selector -> Css
colsGrid :: NonEmpty Selector -> Css
colsGrid NonEmpty Selector
classes = NonEmpty Css -> Css
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ (NonEmpty Css -> Css) -> NonEmpty Css -> Css
forall a b. (a -> b) -> a -> b
$ (Selector -> Rational -> Css)
-> NonEmpty Selector -> NonEmpty Rational -> NonEmpty Css
forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
NE.zipWith (\Selector
cl Rational
per -> Selector
cl Selector -> Css -> Css
? Size Percentage -> Css
forall a. Size a -> Css
width (Rational
per %)) NonEmpty Selector
classes NonEmpty Rational
w
w :: NonEmpty Rational
w :: NonEmpty Rational
w = Rational
4.33 Rational -> [Rational] -> NonEmpty Rational
forall a. a -> [a] -> NonEmpty a
:| [Rational
12.66, Rational
21, Rational
29.33, Rational
37.66, Rational
46, Rational
54.33, Rational
62.66, Rational
71, Rational
79.33, Rational
87.66, Rational
96]
mediaQuery :: Number -> Css -> Css
mediaQuery Number
x = MediaType -> [Feature] -> Css -> Css
query MediaType
M.screen [Size LengthUnit -> Feature
M.minWidth (Number -> Size LengthUnit
em Number
x)]
marginAuto :: Css
marginAuto :: Css
marginAuto = Size Any -> Css
forall a. Size a -> Css
marginLeft Size Any
forall a. Auto a => a
auto Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size Any -> Css
forall a. Size a -> Css
marginRight Size Any
forall a. Auto a => a
auto
marginAll :: Size Percentage -> Css
marginAll :: Size Percentage -> Css
marginAll Size Percentage
x = Size Percentage
-> Size Percentage -> Size Percentage -> Size Percentage -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
margin Size Percentage
x Size Percentage
x Size Percentage
x Size Percentage
x
margin2 :: Size a -> Size b -> Css
margin2 :: forall a b. Size a -> Size b -> Css
margin2 Size a
x Size b
y = Size a -> Css
forall a. Size a -> Css
marginTopBottom Size a
x Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size b -> Css
forall a. Size a -> Css
marginLeftRight Size b
y
marginTopBottom :: Size a -> Css
marginTopBottom :: forall a. Size a -> Css
marginTopBottom Size a
x = Size a -> Css
forall a. Size a -> Css
marginTop Size a
x Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size a -> Css
forall a. Size a -> Css
marginBottom Size a
x
marginLeftRight :: Size a -> Css
marginLeftRight :: forall a. Size a -> Css
marginLeftRight Size a
x = Size a -> Css
forall a. Size a -> Css
marginLeft Size a
x Css -> Css -> Css
forall a b. StyleM a -> StyleM b -> StyleM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Size a -> Css
forall a. Size a -> Css
marginRight Size a
x
paddingAll :: Size Percentage -> Css
paddingAll :: Size Percentage -> Css
paddingAll Size Percentage
x = Size Percentage
-> Size Percentage -> Size Percentage -> Size Percentage -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding Size Percentage
x Size Percentage
x Size Percentage
x Size Percentage
x
padding2 :: Size a -> Size a -> Css
padding2 :: forall a. Size a -> Size a -> Css
padding2 Size a
x Size a
y = Size a -> Size a -> Size a -> Size a -> Css
forall a. Size a -> Size a -> Size a -> Size a -> Css
padding Size a
x Size a
y Size a
x Size a
y
(%) :: Rational -> Size Percentage
% :: Rational -> Size Percentage
(%) = Rational -> Size Percentage
forall a. Fractional a => Rational -> a
fromRational
lightGrey, darkGrey, veryLightGrey, brown :: Color
lightGrey :: Color
lightGrey = Integer -> Integer -> Integer -> Color
rgb Integer
189 Integer
189 Integer
189
darkGrey :: Color
darkGrey = Integer -> Integer -> Integer -> Color
rgb Integer
97 Integer
97 Integer
97
veryLightGrey :: Color
veryLightGrey = Integer -> Integer -> Integer -> Color
rgb Integer
241 Integer
241 Integer
241
brown :: Color
brown = Integer -> Integer -> Integer -> Color
rgb Integer
78 Integer
52 Integer
46