{-# LANGUAGE FlexibleContexts, OverloadedStrings, RecordWildCards, QuasiQuotes #-} module Theme where import Clckwrks import Clckwrks.Authenticate.Plugin (authenticatePlugin) import Clckwrks.Authenticate.URL (AuthURL(Auth)) import Clckwrks.Types (NamedLink(..)) import Clckwrks.NavBar.API (getNavBarData) import Clckwrks.NavBar.Types (NavBar(..), NavBarItem(..)) import Clckwrks.Monad import Control.Monad.State (get) import Data.Maybe (fromMaybe) import Data.Text.Lazy (Text) import qualified Data.Text as T import Happstack.Authenticate.Password.URL (PasswordURL(UsernamePasswordCtrl), passwordAuthenticationMethod) import HSP.JMacro import HSP.XMLGenerator import HSP.XML import Language.Javascript.JMacro import Language.Haskell.HSX.QQ (hsx) import Paths_clckwrks_theme_bootstrap (getDataDir) import Web.Plugins.Core (pluginName, getPluginRouteFn) -- | this `Theme` theme :: Theme theme = Theme { themeName = "bootstrap-theme" , themeStyles = [defaultStyle] , themeDataDir = getDataDir } -- | function te generate the navigation bar genNavBar :: GenXML (Clck ClckURL) genNavBar = do menu <- lift getNavBarData mName <- query GetSiteName navBarHTML (fromMaybe "clckwrks" mName) menu -- | helper function to generate a navigation bar from the navigation bar data navBarHTML :: T.Text -- ^ brand -> NavBar -- ^ navigation bar links -> GenXML (Clck ClckURL) navBarHTML brand (NavBar menuItems) = [hsx| |] mkNavBarItem :: NavBarItem -> GenXML (Clck ClckURL) mkNavBarItem (NBLink (NamedLink ttl lnk)) = [hsx|
  • <% ttl %>
  • |] -- | default template for this theme defaultTemplate :: ( EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers , EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body ) => T.Text -- ^ title to stick in \ tag -> headers -- ^ extra values to stick in \ tag -> body -- ^ value to stick in \ tag -> XMLGenT (ClckT ClckURL (ServerPartT IO)) XML defaultTemplate ttl hdr bdy = do p <- plugins <$> get (Just authRouteFn) <- getPluginRouteFn p (pluginName authenticatePlugin) [hsx| -- the meta tags must come first <% ttl %> <% hdr %> <% googleAnalytics %>
    <% genNavBar %>
    <% bdy %>
    |] -- | default `ThemeStyle` for this theme defaultStyle :: ThemeStyle defaultStyle = ThemeStyle { themeStyleName = "default" , themeStyleDescription = "default view" , themeStylePreview = Nothing , themeStyleTemplate = defaultTemplate }