{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module       : Web.Skell.Partials
-- Description  : These are little HTML snippets.
-- Copyright    : 2014, Peter Harpending.
-- License      : BSD3
-- Maintainer   : Peter Harpending <pharpend2@gmail.com>
-- Stability    : experimental
-- Portability  : archlinux
--

module Web.Skell.Partials where

import           Data.Monoid ((<>))
import qualified Data.Text.Lazy as L
import           Text.Blaze.Html5 ((!))
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import qualified Web.Skell.MimeTypes as Mt
import           Web.Skell.Saferoute

-- |Bootstrap Wrapper for Skell
defaultWrapper :: H.Html -> H.Html -> H.Html
defaultWrapper headers body = H.html $ do
  H.head $ do
    stylesheetRemote bootstrapCss
    headers
  H.body $ do
    H.div ! A.class_ "container" $ do
      body
    scriptRemote jQueryJs
    scriptRemote bootstrapJs

-- |Wrap a 'Resource' URL in a @link@ tag
stylesheetTag :: Resource r => r -> H.Html
stylesheetTag res = H.link ! A.rel "stylesheet"
                           ! A.type_ (H.toValue $ show Mt.css)
                           ! A.href (getUrl res)

-- |Link to a remote stylesheet
stylesheetRemote :: ForeignResource -> H.Html
stylesheetRemote url = H.link ! A.rel "stylesheet"
                              ! A.type_ (H.toValue $ show Mt.css)
                              ! A.href url

-- |Link to a remote stylesheet
scriptRemote :: ForeignResource -> H.Html
scriptRemote url = H.script ! A.src url $ return ()

-- |Tag for any link
linkTag :: H.AttributeValue -> H.Html -> H.Html
linkTag hrf txt = H.a ! A.href hrf $ do txt

-- |Email tag for any email
emailTag :: L.Text -> H.Html
emailTag email = H.code $ H.span ! A.class_ "email" $ H.toHtml $
  "<" <> L.reverse email <> ">"