{-# LANGUAGE OverloadedStrings #-}

module Design.Helper
  ( clearFix
  , button
  , waitable
  , input
  , centeredWithMargin
  , verticalCentering
  ) where

import Prelude hiding (span)

import Clay hiding (button, input)

import Design.Constants
import Design.Color as Color

clearFix :: Css
clearFix =
  after & do
    content (stringContent "")
    display displayTable
    clear both

button :: Color -> Color -> Size a -> (Color -> Color) -> Css
button backgroundCol textCol h focusOp = do
  display flex
  alignItems center
  justifyContent center
  backgroundColor backgroundCol
  padding (px 0) (px 10) (px 0) (px 10)
  color textCol
  borderRadius radius radius radius radius
  verticalAlign middle
  cursor pointer
  lineHeight h
  height h
  textAlign (alignSide sideCenter)
  hover & backgroundColor (focusOp backgroundCol)
  focus & backgroundColor (focusOp backgroundCol)
  waitable

waitable :: Css
waitable = do
  svg # ".loader" ? display none
  ".waiting" & do
    ".content" ? do
      display flex
      fontSize (px 0)
      opacity 0
    svg # ".loader" ? do
      display block
      rotateKeyframes
      rotateAnimation

input :: Double -> Css
input h = do
  height (px h)
  padding (px 10) (px 10) (px 10) (px 10)
  borderRadius radius radius radius radius
  border solid (px 1) Color.dustyGray
  focus & borderColor Color.silver
  verticalAlign middle

centeredWithMargin :: Css
centeredWithMargin = do
  width (pct blockPercentWidth)
  marginLeft auto
  marginRight auto

verticalCentering :: Css
verticalCentering = do
  position absolute
  top (pct 50)
  "transform" -: "translateY(-50%)"

rotateAnimation :: Css
rotateAnimation = do
  animationName "rotate"
  animationDuration (sec 1)
  animationTimingFunction easeOut
  animationIterationCount infinite

rotateKeyframes :: Css
rotateKeyframes = keyframes
  "rotate"
  [ (0, "transform" -: "rotate(0deg)")
  , (100, "transform" -: "rotate(360deg)")
  ]