{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies, OverloadedStrings, CPP #-}
{-
Define the web application's foundation, in the usual Yesod style.
See a default Yesod app's comments for more details of each part.
-}
module Hledger.Web.Foundation
    ( App (..)
    , Route (..)
    , AppRoute
    -- , AppMessage (..)
    , resourcesApp
    , Handler
    , Widget
    , module Yesod.Core
    , liftIO
    ) where
import Prelude
import Yesod.Core hiding (Route)
import Yesod.Default.Config
#ifndef DEVELOPMENT
import Yesod.Default.Util (addStaticContentExternal)
#endif
import Yesod.Static
import Yesod.Logger (Logger, logMsg, formatLogText)
import Control.Monad.IO.Class (liftIO)
import Web.ClientSession (getKey)
import Hledger.Web.Options
import Hledger.Web.Settings
import Hledger.Web.Settings.StaticFiles
-- | The web application's configuration and data, available to all request handlers.
data App = App
    { settings :: AppConfig DefaultEnv Extra
    , getLogger :: Logger
    , getStatic :: Static -- ^ Settings for static file serving.
    , appOpts    :: WebOpts
    -- , appJournal :: Journal
    }
-- Set up i18n messages.
-- mkMessage "App" "messages" "en"
-- The web application's routes (urls).
mkYesodData "App" $(parseRoutesFile "routes")
-- | A convenience alias.
type AppRoute = Route App
-- More configuration, including the default page layout.
instance Yesod App where
    -- approot = Hledger.Web.Settings.appRoot . settings
    approot = ApprootMaster $ appRoot . settings
    -- Place the session key file in the config folder
    encryptKey _ = fmap Just $ getKey "client_session_key.aes"
    defaultLayout widget = do
        -- master <- getYesod
        -- mmsg <- getMessage
        -- We break up the default layout into two components:
        -- default-layout is the contents of the body tag, and
        -- default-layout-wrapper is the entire page. Since the final
        -- value passed to hamletToRepHtml cannot be a widget, this allows
        -- you to use normal widget features in default-layout.
        -- pc <- widgetToPageContent $ do
        --     $(widgetFile "normalize")
        --     $(widgetFile "default-layout")
        -- hamletToRepHtml $(hamletFile "templates/default-layout-wrapper.hamlet")
        pc <- widgetToPageContent $ do
          widget
        hamletToRepHtml [hamlet|
!!!
#{pageTitle pc}
  ^{pageHead pc}