-- | Common page components and rendering helpers. -- For global page layout, see Application.hs. module Handler.Common where import Import import Data.List import Data.Maybe import Data.Text(pack) import Data.Time.Calendar import System.FilePath (takeFileName) #if BLAZE_HTML_0_4 import Text.Blaze (preEscapedString) #else import Text.Blaze.Internal (preEscapedString) #endif import Text.Printf import Text.JSON import Hledger.Utils import Hledger.Data import Hledger.Query import Hledger.Reports import Hledger.Cli.Options import Hledger.Web.Options import Handler.Utils ------------------------------------------------------------------------------- -- Page components -- | Global toolbar/heading area. topbar :: ViewData -> HtmlUrl AppRoute topbar VD{..} = [hamlet| hledger-web
#{version} manual

#{title} $maybe m' <- msg #{m'} |] where title = takeFileName $ journalFilePath j -- | The sidebar used on most views. sidebar :: ViewData -> HtmlUrl AppRoute sidebar vd@VD{..} = balanceReportAsHtml opts vd $ balanceReport (reportopts_ $ cliopts_ opts){empty_=True} am j -- -- | Navigation link, preserving parameters and possibly highlighted. -- navlink :: ViewData -> String -> AppRoute -> String -> HtmlUrl AppRoute -- navlink VD{..} s dest title = [hamlet| -- #{s} -- |] -- where u' = (dest, if null q then [] else [("q", pack q)]) -- style | dest == here = "navlinkcurrent" -- | otherwise = "navlink" :: Text -- -- | Links to the various journal editing forms. -- editlinks :: HtmlUrl AppRoute -- editlinks = [hamlet| -- edit -- \ | # -- add -- import transactions -- |] -- | Search form for entering custom queries to filter journal data. searchform :: ViewData -> HtmlUrl AppRoute searchform VD{..} = [hamlet|
$if filtering \ # clear \ # help
Leave blank to see journal (all transactions), or click account links to see transactions under that account.
Transactions/postings may additionally be filtered by acct:REGEXP (target account), # code:REGEXP (transaction code), # desc:REGEXP (description), # date:PERIODEXP (date), # date2:PERIODEXP (secondary date), # tag:TAG[=REGEX] (tag and optionally tag value), # depth:N (accounts at or above this depth), # status:*, status:!, status: (cleared status), # real:BOOL (real/virtual-ness), # empty:BOOL (is amount zero), # amt:N, amt:N (test magnitude of single-commodity amount). sym:REGEXP (commodity symbol), #
Prepend not: to negate, enclose multi-word patterns in quotes, multiple search terms are AND'ed. |] where filtering = not $ null q -- | Add transaction form. addform :: Text -> ViewData -> HtmlUrl AppRoute addform _ vd@VD{..} = [hamlet|