{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}

-----------------------------------------------------------------------------
-- |
-- Module: Layout.Bootstrap.Starter
-- 
-- Bootstrap-starter template. Not a real thing yet.
--
-----------------------------------------------------------------------------

module Layout.Bootstrap.Starter where

import Prelude
import qualified Prelude as P
import Data.Monoid (mempty)
import Control.Monad (msum)

import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Data.Map as HM

import Text.Blaze.Html5
import qualified Text.Blaze.Html5 as H
import Text.Blaze.Html5.Attributes
import qualified Text.Blaze.Html5.Attributes as A

-- | Template configuration goes here.
type Context = HM.Map T.Text T.Text

-- | Render a basic <html> wrapper wich loads styles and js.
template :: Context -> Html -> Html
template context templateBody =
    let ctx key = fromMaybe "" $ HM.lookup key context

        static kind path = toValue $ T.concat [ctx "STATIC_URL", kind, "/", path]

        css = static "css"
        img = static "img"
        script srcURL = H.script ! src (static "js" srcURL) $ mempty

    in do
        docType
        html ! lang "en" $ do
            H.head $ do
                meta ! charset "utf-8"
                H.title $ toHtml $ ctx "title"
                meta ! name "description" ! content ""
                meta ! name "author" ! content ""

                --  Le HTML5 shim, for IE6-8 support of HTML elements
                -- [if lt IE 9]>
                --       <script src="http://html5shim.googlecode.com/svn/trunk/html5.js"></script>
                --     <![endif]

                --  Le styles
                link ! href (css "bootstrap.min.css") ! rel "stylesheet"
                H.style "body { padding-top: 60px; }"

                --  Le fav and touch icons
                link ! rel "shortcut icon" ! href (img "favicon.ico")
                link ! rel "apple-touch-icon" ! href (img "/apple-touch-icon.png")
                link ! rel "apple-touch-icn" ! sizes "72x72" ! href (img "apple-touch-icon-72x72.png")
                link ! rel "apple-touch-icon" ! sizes "114x114" ! href (img "apple-touch-icon-114x114.png")

            body $ do
                H.div ! class_ "navbar navbar-fixed-top" $ H.div ! class_ "navbar-inner" $ H.div ! class_ "container" $ do
                    a ! class_ "btn btn-navbar" $ do
                        H.span ! class_ "icon-bar" $ mempty
                        H.span ! class_ "icon-bar" $ mempty
                        H.span ! class_ "icon-bar" $ mempty

                    a ! class_ "brand" ! href "/" $ toHtml (ctx "title")

                    H.div ! class_ "nav-collapse" $ ul ! class_ "nav" $ do
                        li $ a ! href "/api" $ "API"
                        li $ a ! href "/contact" $ "Contact"

                H.div ! class_ "container" $ templateBody

                --  Le javascript
                --  ==========================================================
                --  Placed at the end of the document so the pages load faster
                mapM_ script [ "jquery.js", "bootstrap.js" ]