{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Library of styles
--
-- https://leerob.io/blog/how-stripe-designs-beautiful-websites
module Biz.Look
  ( -- | Base stylesheets
    fuckingStyle,
    -- | Clay.Media extensions
    prefersLight,
    whenLight,
    prefersDark,
    whenDark,
    noColorPreference,
    -- | Font
    fontStack,
    fontSmoothing,
    -- | Clay.Text extensions
    textDecorationThickness,
    textDecorationWidth,
    -- | Elements
    hoverButton,
    -- | Geometry
    marginAll,
    marginX,
    marginY,
    paddingAll,
    paddingX,
    paddingY,
    -- | Border
    borderRadiusAll,
    -- | Grid
    gridArea,
    gridTemplateAreas,
    gridTemplateRows,
    columnGap,
    rowGap,
    -- | Alignment
    justifySelf,
  )
where

import Alpha
import Clay
import qualified Clay.Flexbox as Flexbox
import qualified Clay.Property as Property
import qualified Clay.Stylesheet as Stylesheet

fontStack :: Css
fontStack = do
  -- i like adobe source pro, maybe use that instead of camphor
  fontFamily ["Camphor", "Open Sans", "Segoe UI"] [sansSerif]
  textRendering optimizeLegibility

fontSmoothing :: Css
fontSmoothing = do
  Stylesheet.key "-webkit-font-smoothing" ("antialiased" :: Text)
  Stylesheet.key "-moz-osx-font-smoothing" ("grayscale" :: Text)

hoverButton :: Css
hoverButton =
  button # hover ? do
    color "#7795f8"
    transform <| translateY <| px (-1)
    boxShadow
      [ bsColor (rgba 50 50 93 0.1)
          <| shadow
            (px 7)
            (px 14),
        bsColor
          (rgba 0 0 0 0.08)
          <| shadow
            (px 3)
            (px 6)
      ]

prefersDark :: Stylesheet.Feature
prefersDark =
  Stylesheet.Feature "prefers-color-scheme" (Just (Clay.value ("dark" :: Text)))

prefersLight :: Stylesheet.Feature
prefersLight =
  Stylesheet.Feature "prefers-color-scheme" (Just (Clay.value ("light" :: Text)))

noColorPreference :: Stylesheet.Feature
noColorPreference =
  Stylesheet.Feature
    "prefers-color-scheme"
    (Just (Clay.value ("no-preference" :: Text)))

whenDark :: Css -> Css
whenDark = query Clay.all [prefersDark]

whenLight :: Css -> Css
whenLight = query Clay.all [prefersLight]

-- | The stylesheet from <https://perfectmotherfuckingwebsite.com> ported to
-- Clay, to be used as the base for other styles.
--
-- Differences from the original:
--   - expects use of header/main/footer
--   - has a sticky footer
--   - wider, with a bit of body padding
fuckingStyle :: Css
fuckingStyle = do
  "body" ? do
    display flex
    minHeight (vh 100)
    flexDirection column
    color "#444"
    margin (px 0) 0 0 0
    padding (em 0.5) (em 0.5) (em 0.5) (em 0.5)
    fontSize (px 18)
    lineHeight (em 1.5)
    fontFamily
      [ "Segoe UI",
        "Roboto",
        "Helvetica Neue",
        "Arial",
        "Noto Sans",
        "Apple Color Emoji",
        "Segoe UI Emoji",
        "Segoe UI Symbol",
        "Noto Color Emoji"
      ]
      [sansSerif]
  "main" ? Flexbox.flex 1 0 auto
  "main" <> "header" <> "footer" ? do
    maxWidth (px 900)
    width (pct 100)
    margin (em 1) auto 1 auto
    padding (em 0) 0 0 0
  "h1" <> "h2" <> "h3" ? lineHeight (em 1.2)
  query Clay.all [prefersDark] <| do
    "body" ? do
      color white
      background ("#444" :: Color)
    "a:link" ? color ("#5bf" :: Color)
    "a:visited" ? color ("#ccf" :: Color)

textDecorationThickness :: Size LengthUnit -> Css
textDecorationThickness = Stylesheet.key "text-decoration-thickness"

textDecorationWidth :: Size LengthUnit -> Css
textDecorationWidth = Stylesheet.key "text-decoration-width"

marginAll :: Size a -> Css
marginAll x = margin x x x x

marginX :: Size a -> Css
marginX n = marginLeft n <> marginRight n

marginY :: Size a -> Css
marginY n = marginTop n <> marginBottom n

paddingAll :: Size a -> Css
paddingAll x = Clay.padding x x x x

paddingX :: Size a -> Css
paddingX n = paddingLeft n <> paddingRight n

paddingY :: Size a -> Css
paddingY n = paddingTop n <> paddingBottom n

borderRadiusAll :: Size a -> Css
borderRadiusAll x = Clay.borderRadius x x x x

gridArea :: Text -> Css
gridArea = Stylesheet.key "grid-area"

gridTemplateAreas :: [Property.Literal] -> Css
gridTemplateAreas = Stylesheet.key "grid-template-areas" <. noCommas

gridTemplateRows :: [Property.Literal] -> Css
gridTemplateRows = Stylesheet.key "grid-template-columns" <. noCommas

columnGap :: Size a -> Css
columnGap = Stylesheet.key "column-gap"

rowGap :: Size a -> Css
rowGap = Stylesheet.key "row-gap"

justifySelf :: JustifyContentValue -> Css
justifySelf = Stylesheet.key "justify-self"