module Ideas.Text.HTML.W3CSS where
import Data.Char
import Ideas.Text.HTML
import Ideas.Text.XML
import qualified Ideas.Text.XML as XML
w3css :: HTMLPage -> HTMLPage
w3css = addCSS "https://www.w3schools.com/w3css/4/w3.css"
w3class :: BuildXML a => String -> a -> a
w3class s a = ("class" .=. s) <> a
w3classIf :: BuildXML a => Bool -> String -> a -> a
w3classIf b s = if b then w3class s else id
data Color
   = Red | Pink | Purple | DeepPurple | Indigo | Blue | LightBlue
   | Cyan | Aqua | Teal | Green | LightGreen | Lime | Sand | Khaki
   | Yellow | Amber | Orange | DeepOrange | BlueGray | Brown | LightGray
   | Gray | DarkGray | Black | PaleRed | PaleYellow | PaleGreen | PaleBlue | White
 deriving Show
data Size = Tiny | Small | Medium | Large | XL | XXL | XXXL | Jumbo
 deriving (Eq, Ord)
data Position = TopLeft    | Top    | TopRight
              | CenterLeft | Center | CenterRight
              | BottomLeft | Bottom | BottomRight
 deriving (Show, Eq)
onTop, onLeft, onRight, onBottom :: Position -> Bool
onTop    = (`elem` [TopLeft, Top, TopRight])
onLeft   = (`elem` [TopLeft, CenterLeft, BottomLeft])
onRight  = (`elem` [TopRight, CenterRight, BottomRight])
onBottom = (`elem` [BottomLeft, Bottom, BottomRight])
instance Show Size where
   show Tiny   = "tiny"
   show Small  = "small"
   show Medium = "medium"
   show Large  = "large"
   show XL     = "xlarge"
   show XXL    = "xxlarge"
   show XXXL   = "xxxlarge"
   show Jumbo  = "jumbo"
uncamel :: String -> String
uncamel = concatMap f
 where
   f c = if isUpper c then ['-', toLower c] else [c]
container :: BuildXML a => a -> a
container = XML.tag "div" . w3class "w3-container"
panel :: BuildXML a => a -> a
panel = XML.tag "div" . w3class "w3-panel"
badge :: BuildXML a => a -> a
badge = XML.tag "span" . w3class "w3-badge"
tag :: BuildXML a => a -> a
tag = XML.tag "span" . w3class "w3-tag"
ul :: BuildXML a => [a] -> a
ul = ulWith id
ulWith :: BuildXML a => (a -> a) -> [a] -> a
ulWith f = XML.tag "ul" . w3class "w3-ul" . f . mconcat . map (XML.tag "li")
code :: BuildXML a => a -> a
code = XML.tag "div" . w3class "w3-code"
codespan :: BuildXML a => a -> a
codespan = XML.tag "code" . w3class "w3-codespan"
table :: BuildXML a => a -> a
table = XML.tag "table" .  w3class "w3-table"
tableAll :: BuildXML a => a -> a
tableAll = XML.tag "table" . w3class "w3-table-all"
striped :: BuildXML a => a -> a
striped = w3class "w3-striped"
bordered :: BuildXML a => a -> a
bordered = w3class "w3-bordered"
centered :: BuildXML a => a -> a
centered = w3class "w3-centered"
hoverable :: BuildXML a => a -> a
hoverable = w3class "w3-hoverable"
responsive :: BuildXML a => a -> a
responsive = w3class "w3-responsive"
card :: BuildXML a => a -> a
card = w3class "w3-card"
card2 :: BuildXML a => a -> a
card2 = w3class "w3-card-2"
card4 :: BuildXML a => a -> a
card4 = w3class "w3-card-4"
row :: BuildXML a => a -> a
row = w3class "w3-row"
rowPadding :: BuildXML a => a -> a
rowPadding = w3class "w3-row-padding"
content :: BuildXML a => a -> a
content = w3class "w3-content"
half :: BuildXML a => a -> a
half = w3class "w3-half"
third :: BuildXML a => a -> a
third = w3class "w3-third"
twothird :: BuildXML a => a -> a
twothird = w3class "w3-twothird"
quarter :: BuildXML a => a -> a
quarter = w3class "w3-quarter"
threequarter :: BuildXML a => a -> a
threequarter = w3class "w3-threequarter"
col :: BuildXML a => a -> a
col = w3class "w3-col"
rest :: BuildXML a => a -> a
rest = w3class "w3-rest"
hideSmall :: BuildXML a => a -> a
hideSmall = w3class "w3-hide-small"
hideMedium :: BuildXML a => a -> a
hideMedium = w3class "w3-hide-medium"
hideLarge :: BuildXML a => a -> a
hideLarge = w3class "w3-hide-large"
image :: BuildXML a => a -> a
image = w3class "w3-image"
mobile :: BuildXML a => a -> a
mobile = w3class "w3-mobile"
cellRow :: BuildXML a => a -> a
cellRow = w3class "w3-cell-row"
cell :: BuildXML a => a -> a
cell = w3class "w3-cell"
cellTop :: BuildXML a => a -> a
cellTop = w3class "w3-cell-top"
cellMiddle :: BuildXML a => a -> a
cellMiddle = w3class "w3-cell-middle"
cellBottom :: BuildXML a => a -> a
cellBottom = w3class "w3-cell-bottom"
bar :: BuildXML a => a -> a
bar = w3class "w3-bar"
barBlock :: BuildXML a => a -> a
barBlock = w3class "w3-bar-block"
barItem :: BuildXML a => a -> a
barItem = w3class "w3-bar-item"
sidebar :: BuildXML a => a -> a
sidebar = w3class "w3-sidebar"
collapse :: BuildXML a => a -> a
collapse = w3class "w3-collapse"
mainPage :: BuildXML a => a -> a
mainPage = w3class "w3-main"
dropdownClick :: BuildXML a => a -> a
dropdownClick = w3class "w3-dropdown-click"
dropdownHover :: BuildXML a => a -> a
dropdownHover = w3class "w3-dropdown-hover"
button :: BuildXML a => String -> a -> a
button url = link url . w3class "w3-button"
btn :: BuildXML a => String -> a -> a
btn url = link url . w3class "w3-btn"
ripple :: BuildXML a => String -> a -> a
ripple url = link url . w3class "w3-ripple"
input :: BuildXML a => a -> a
input = w3class "w3-input"
check :: BuildXML a => a -> a
check = w3class "w3-check"
radio :: BuildXML a => a -> a
radio = w3class "w3-radio"
select :: BuildXML a => a -> a
select = w3class "w3-select"
modal :: BuildXML a => a -> a
modal = w3class "w3-modal"
modalContent :: BuildXML a => a -> a
modalContent = w3class "w3-modal-content"
tooltip :: BuildXML a => a -> a
tooltip = w3class "w3-tooltip"
tooltipText :: BuildXML a => a -> a
tooltipText = w3class "w3-text"
animate :: BuildXML a => Position -> a -> a
animate p = w3classIf (onTop p)    "w3-animate-top"
          . w3classIf (onLeft p)   "w3-animate-left"
          . w3classIf (onBottom p) "w3-animate-bottom"
          . w3classIf (onRight p)  "w3-animate-right"
animateOpacity :: BuildXML a => a -> a
animateOpacity = w3class "w3-animate-opacity"
animateZoom :: BuildXML a => a -> a
animateZoom = w3class "w3-animate-zoom"
animateFading :: BuildXML a => a -> a
animateFading = w3class "w3-animate-fading"
spin :: BuildXML a => a -> a
spin = w3class "w3-spin"
animateInput :: BuildXML a => a -> a
animateInput = w3class "w3-animate-input"
fontSize :: BuildXML a => Size -> a -> a
fontSize = w3class . ("w3-" ++) . show
wide :: BuildXML a => a -> a
wide = w3class "w3-wide"
serif :: BuildXML a => a -> a
serif = w3class "w3-serif"
center :: BuildXML a => a -> a
center = w3class "w3-center"
left :: BuildXML a => a -> a
left = w3class "w3-left"
right :: BuildXML a => a -> a
right = w3class "w3-right"
leftAlign :: BuildXML a => a -> a
leftAlign = w3class "w3-left-align"
rightAlign :: BuildXML a => a -> a
rightAlign = w3class "w3-right-align"
justify :: BuildXML a => a -> a
justify = w3class "w3-justify"
circle :: BuildXML a => a -> a
circle = w3class "w3-circle"
hide :: BuildXML a => a -> a
hide = w3class "w3-hide"
showBlock :: BuildXML a => a -> a
showBlock = w3class "w3-show-block"
showInlineBlock :: BuildXML a => a -> a
showInlineBlock = w3class "w3-show-inline-block"
top :: BuildXML a => a -> a
top = w3class "w3-top"
bottom :: BuildXML a => a -> a
bottom = w3class "w3-bottom"
display :: BuildXML a => Position -> a -> a
display p = w3class "w3-display-container" . w3class (f p)
 where
   f TopLeft     = "w3-display-topleft"
   f Top         = "w3-display-topmiddle"
   f TopRight    = "w3-display-topright"
   f CenterLeft  = "w3-display-left"
   f Center      = "w3-display-middle"
   f CenterRight = "w3-display-right"
   f BottomLeft  = "w3-display-bottomleft"
   f Bottom      = "w3-display-bottommiddle"
   f BottomRight = "w3-display-bottomright"
displayHover :: BuildXML a => a -> a
displayHover = w3class "w3-display-hover"
opacity :: BuildXML a => a -> a
opacity = w3class "w3-opacity"
opacityOff :: BuildXML a => a -> a
opacityOff = w3class "w3-opacity-off"
opacityMin :: BuildXML a => a -> a
opacityMin = w3class "w3-opacity-min"
opacityMax :: BuildXML a => a -> a
opacityMax = w3class "w3-opacity-max"
grayscaleMin :: BuildXML a => a -> a
grayscaleMin = w3class "w3-grayscale-min"
grayscale :: BuildXML a => a -> a
grayscale = w3class "w3-grayscale"
grayscaleMax :: BuildXML a => a -> a
grayscaleMax = w3class "w3-grayscale-max"
sepiaMin :: BuildXML a => a -> a
sepiaMin = w3class "w3-sepia-min"
sepia :: BuildXML a => a -> a
sepia = w3class "w3-sepia"
sepiaMax :: BuildXML a => a -> a
sepiaMax = w3class "w3-sepia-max"
overlay :: BuildXML a => a -> a
overlay = w3class "w3-overlay"
background :: BuildXML a => Color -> a -> a
background = w3class . ("w3" ++) .  uncamel . show
transparent :: BuildXML a => a -> a
transparent = w3class "w3-transparent"
hover :: BuildXML a => Color -> a -> a
hover = w3class . ("w3-hover" ++) .  uncamel . show
textColor :: BuildXML a => Color -> a -> a
textColor = w3class . ("w3-text" ++) .  uncamel . show
hoverColor :: BuildXML a => Color -> a -> a
hoverColor = w3class . ("w3-hover-text" ++) .  uncamel . show
hoverOpacity :: BuildXML a => a -> a
hoverOpacity = w3class "w3-hover-opacity"
hoverOpacityOff :: BuildXML a => a -> a
hoverOpacityOff = w3class "w3-hover-opacity-off"
hoverShadow :: BuildXML a => a -> a
hoverShadow = w3class "w3-hover-shadow"
hoverGrayscale :: BuildXML a => a -> a
hoverGrayscale = w3class "w3-hover-grayscale"
hoverSepia :: BuildXML a => a -> a
hoverSepia = w3class "w3-hover-sepia"
hoverNone :: BuildXML a => a -> a
hoverNone = w3class "w3-hover-none"
rounded :: BuildXML a => Size -> a -> a
rounded s = w3class "w3-round" . w3class ("w3-round-" ++ show s)
padding :: BuildXML a => Size -> a -> a
padding s
   | s < Medium = w3class "w3-padding-small"
   | s > Medium = w3class "w3-padding-large"
   | otherwise  = w3class "w3-padding-small"
vpadding :: BuildXML a => Size -> a -> a
vpadding s
   | s <= Medium = w3class "w3-padding-16"
   | s == Large  = w3class "w3-padding-24"
   | s == XL     = w3class "w3-padding-32"
   | s == XXL    = w3class "w3-padding-48"
   | otherwise   = w3class "w3-padding-64"
margin :: BuildXML a => a -> a
margin = w3class "w3-margin"
marginPos :: BuildXML a => Position -> a -> a
marginPos p = w3classIf (onTop p)    "w3-margin-top"
            . w3classIf (onLeft p)   "w3-margin-left"
            . w3classIf (onBottom p) "w3-margin-bottom"
            . w3classIf (onRight p)  "w3-margin-right"
section :: BuildXML a => a -> a
section = w3class "w3-section"
border :: BuildXML a => a -> a
border = w3class "w3-border"
borderPos :: BuildXML a => Position -> a -> a
borderPos p = w3classIf (onTop p)    "w3-border-top"
            . w3classIf (onLeft p)   "w3-border-left"
            . w3classIf (onBottom p) "w3-border-bottom"
            . w3classIf (onRight p)  "w3-border-right"
noBorder :: BuildXML a => a -> a
noBorder = w3class "w3-border-0"
borderColor :: BuildXML a => Color -> a -> a
borderColor = w3class . ("w3-border" ++) .  uncamel . show
barPos :: BuildXML a => Position -> a -> a
barPos p = w3classIf (onTop p)    "w3-topbar"
         . w3classIf (onLeft p)   "w3-leftbar"
         . w3classIf (onBottom p) "w3-bottombar"
         . w3classIf (onRight p)  "w3-rightbar"
data ColorTheme
   = L1 | L2 | L3 | L4 | L5 
   | D1 | D2 | D3 | D4 | D5 
 deriving Show
theme_, textTheme, borderTheme :: BuildXML a => a -> a
theme_      = w3class "w3-theme"
textTheme   = w3class "w3-text-theme"
borderTheme = w3class "w3-border-theme"
theme :: BuildXML a => ColorTheme -> a -> a
theme = w3class . ("w3-theme-" ++) . map toLower . show