pinealservo-com/css/normalize.hs.no

131 lines
3.5 KiB
Plaintext

{-# LANGUAGE OverloadedStrings #-}
import Clay
import Clay.Size
import Data.Monoid
import Data.Text (Text)
import Prelude hiding ((**))
selectors :: [Selector] -> Selector
selectors = foldl1 (<>)
pseudoNot :: Text -> Refinement
pseudoNot n = func "not" [n]
main = putCss $ do
html5display
baseStyle
linksStyle
typographyStyle
embeddedContentStyle
formStyle
tableStyle
html5display = do
selectors [ article, aside, details, figcaption, figure, footer
, header, hgroup, nav, section, summary, "main"
] ? display block
selectors [ audio, canvas, video ] ? display inlineBlock
audio # pseudoNot "[controls]" ? do
display none
height $ px 0
star # "hidden" <> "template" ? display none
baseStyle = do
html ? do
fontFamily [] [sansSerif]
"-ms-text-size-adjust" -: "100%"
"-webkit-text-size-adjust" -: "100%"
body ? margin (px 0) (px 0) (px 0) (px 0)
linksStyle = do
a ? background transparent
a # focus ? do
outlineStyle dotted
"outline-width" -: "thin"
a # active <> a # hover ?
outlineWidth (px 0)
typographyStyle = do
h1 ? do
fontSize (em 2)
margin (em 0.67) (em 0) (em 0) (em 0.67)
abbr # title ? do
borderBottomWidth (px 1)
borderBottomStyle dotted
b <> strong ? fontWeight bold
dfn ? fontStyle italic
hr ? do
boxSizing contentBox
height (px 0)
mark ? do
backgroundColor (rgb 0xf 0xf 0x0)
color (rgb 0 0 0)
selectors [code, kbd, pre, samp] ? do
fontFamily [] [monospace, serif]
fontSize (em 1)
pre ? whiteSpace preWrap
"q" -: "quotes \"\\201C\" \"\\201D\" \"\\2018\" \"\\2019\""
small ? fontSize (pct 80)
sub <> sup ? do
fontSize (pct 75)
lineHeight (px 0)
position relative
"vertical-align" -: "baseline"
sub ? top (em (-0.5))
sup ? bottom (em (-0.25))
embeddedContentStyle = do
img ? borderWidth (px 0)
"svg" # pseudoNot ":root" ? overflow hidden
figure ? margin (px 0) (px 0) (px 0) (px 0)
formStyle = do
fieldset ? do
borderWidth (px 1)
borderStyle solid
borderColor (rgb 0xc0 0xc0 0xc0)
margin (px 0) (px 2) (px 2) (px 0)
padding (em 0.35) (em 0.625) (em 0.75) (em 0)
legend ? do
borderWidth (px 0)
padding (px 0) (px 0) (px 0) (px 0)
selectors [button, input, select, textarea] ? do
"font-family" -: "inherit"
fontSize (pct 100)
margin (px 0) (px 0) (px 0) (px 0)
button <> input ? lineHeight normal
button <> select ? textTransform none
selectors [ button, html ** input # ("type" @= "button")
, input # ("type" @= "reset")
, input # ("type" @= "submit")
] ? do
"-webkit-appearance" -: "button"
"cursor" -: "pointer"
button # "@disabled" <> html ** input # "@disabled" ? do
"cursor" -: "default"
input # ("type" @= "checkbox") <> input # ("type" @= "radio") ? do
boxSizing borderBox
padding (px 0) (px 0) (px 0) (px 0)
input # ("type" @= "search") ? do
"-webkit-appearance" -: "textfield"
"-moz-box-sizing" -: "content-box"
"-webkit-box-sizing" -: "content-box"
"box-sizing" -: "content-box"
input # ("type" @= "search") # "::-webkit-search-cancel-button"
<> input # ("type" @= "search") # "::-webkit-search-decoration" ? do
"-webkit-appearance" -: "none"
button # "::-moz-focus-inner" <> input # "::-moz-focus-inner" ? do
borderWidth (px 0)
padding (px 0) (px 0) (px 0) (px 0)
textarea ? do
overflow auto
"vertical-align" -: "top"
tableStyle = table ? do
"border-collapse" -: "collapse"
"border-spacing" -: "0px"