{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings, RecordWildCards #-} {- hledger-web's request handlers, and helpers. -} module Hledger.Web.Handlers where import Control.Applicative ((<$>), (<*>)) import Data.Aeson import Data.ByteString (ByteString) import Data.Either (lefts,rights) import Data.List import Data.Maybe import Data.Text(Text,pack,unpack) import Data.Time.Calendar import Data.Time.Clock import Data.Time.Format import System.FilePath (takeFileName, (>)) import System.IO.Storage (putValue, getValue) import System.Locale (defaultTimeLocale) import Text.Blaze (preEscapedString, toHtml) import Text.Hamlet hiding (hamletFile) import Text.Printf import Yesod.Form import Yesod.Json import Hledger hiding (today) import Hledger.Cli import Hledger.Web.App import Hledger.Web.Options import Hledger.Web.Settings getFaviconR :: Handler () getFaviconR = sendFile "image/x-icon" $ Hledger.Web.Settings.staticDir > "favicon.ico" getRobotsR :: Handler RepPlain getRobotsR = return $ RepPlain $ toContent ("User-agent: *" :: ByteString) getRootR :: Handler RepHtml getRootR = redirect RedirectTemporary defaultroute where defaultroute = RegisterR ---------------------------------------------------------------------- -- main views: -- | The formatted journal view, with sidebar. getJournalR :: Handler RepHtml getJournalR = do vd@VD{..} <- getViewData let sidecontent = sidebar vd -- XXX like registerReportAsHtml inacct = inAccount qopts -- injournal = isNothing inacct filtering = m /= MatchAny -- showlastcolumn = if injournal && not filtering then False else True title = case inacct of Nothing -> "Journal"++filter Just (a,subs) -> "Transactions in "++a++andsubs++filter where andsubs = if subs then " (and subaccounts)" else "" where filter = if filtering then ", filtered" else "" maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m defaultLayout $ do setTitle "hledger-web journal" addHamlet [$hamlet| ^{topbar vd}
#{txn}
|]
where
evenodd = if even n then "even" else "odd" :: String
txn = trimnl $ showTransaction t where trimnl = reverse . dropWhile (=='\n') . reverse
-- | Render an "TransactionsReport" as HTML for the formatted journal view.
journalTransactionsReportAsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute
journalTransactionsReportAsHtml _ vd (_,items) = [$hamlet|