{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE ViewPatterns #-} -- | 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 where import Control.Applicative ((<|>)) import Control.Monad (join, when) import qualified Data.ByteString.Char8 as BC import Data.Traversable (for) import Data.IORef (IORef, readIORef, writeIORef) import Data.Maybe (fromMaybe) #if !(MIN_VERSION_base(4,13,0)) import Data.Monoid ((<>)) #endif import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar (Day) import Network.HTTP.Conduit (Manager) import Network.HTTP.Types (status403) import Network.Wai (requestHeaders) import System.FilePath (takeFileName) import Text.Blaze (Markup) import Text.Hamlet (hamletFile) import Yesod import Yesod.Static import Yesod.Default.Config #ifndef DEVELOPMENT import Hledger.Web.Settings (staticDir) import Text.Jasmine (minifym) import Yesod.Default.Util (addStaticContentExternal) #endif import Hledger import Hledger.Cli (CliOpts(..), journalReloadIfChanged) import Hledger.Web.Settings (Extra(..), widgetFile) import Hledger.Web.Settings.StaticFiles import Hledger.Web.WebOptions import Hledger.Web.Widget.Common (balanceReportAsHtml) -- | The site argument for your application. This can be a good place to -- keep settings and values requiring initialization before your application -- starts running, such as database connections. Every handler will have -- access to the data present here. data App = App { settings :: AppConfig DefaultEnv Extra , getStatic :: Static -- ^ Settings for static file serving. , httpManager :: Manager -- , appOpts :: WebOpts , appJournal :: IORef Journal } -- This is where we define all of the routes in our application. For a full -- explanation of the syntax, please see: -- http://www.yesodweb.com/book/handler -- -- This function does three things: -- -- * Creates the route datatype AppRoute. Every valid URL in your -- application can be represented as a value of this type. -- * Creates the associated type: -- type instance Route App = AppRoute -- * Creates the value resourcesApp which contains information on the -- resources declared below. This is used in Handler.hs by the call to -- mkYesodDispatch -- -- What this function does *not* do is create a YesodSite instance for -- App. Creating that instance requires all of the handler functions -- for our application to be in scope. However, the handler functions -- usually require access to the AppRoute datatype. Therefore, we -- split these actions into two functions and place them in separate files. mkYesodData "App" $(parseRoutesFile "config/routes") -- | A convenience alias. type AppRoute = Route App #if MIN_VERSION_yesod(1,6,0) type Form x = Html -> MForm (HandlerFor App) (FormResult x, Widget) #else type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget) #endif -- Please see the documentation for the Yesod typeclass. There are a number -- of settings which can be configured by overriding methods here. instance Yesod App where approot = ApprootMaster $ appRoot . settings makeSessionBackend _ = let sessionexpirysecs = 120 in Just <$> defaultClientSessionBackend sessionexpirysecs ".hledger-web_client_session_key.aes" -- defaultLayout :: WidgetFor site () -> HandlerFor site Html defaultLayout widget = do -- Don't run if server-side UI is disabled. -- This single check probably covers all the HTML-returning handlers, -- but for now they do the check as well. checkServerSideUiEnabled master <- getYesod here <- fromMaybe RootR <$> getCurrentRoute VD {caps, j, m, opts, q, qopts} <- getViewData msg <- getMessage showSidebar <- shouldShowSidebar hideEmptyAccts <- (== Just "1") . lookup "hideemptyaccts" . reqCookies <$> getRequest let ropts = reportopts_ (cliopts_ opts) ropts' = ropts {accountlistmode_ = ALTree -- force tree mode for sidebar ,empty_ = not (empty_ ropts) -- show zero items by default } accounts = balanceReportAsHtml (JournalR, RegisterR) here hideEmptyAccts j q qopts $ balanceReport ropts' m j topShowmd = if showSidebar then "col-md-4" else "col-any-0" :: Text topShowsm = if showSidebar then "col-sm-4" else "" :: Text sideShowmd = if showSidebar then "col-md-4" else "col-any-0" :: Text sideShowsm = if showSidebar then "col-sm-4" else "" :: Text mainShowmd = if showSidebar then "col-md-8" else "col-md-12" :: Text mainShowsm = if showSidebar then "col-sm-8" else "col-sm-12" :: Text -- 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 addStylesheet $ StaticR css_bootstrap_min_css addStylesheet $ StaticR css_bootstrap_datepicker_standalone_min_css -- load these things early, in HEAD: toWidgetHead [hamlet|