{-# 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 Safe import System.FilePath (takeFileName, ()) import System.IO.Storage (putValue, getValue) import System.Locale (defaultTimeLocale) 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} #{title} ^{searchform vd} #{title} ^{searchform vd} #{title} ^{searchform vd} registerReportHtml opts vd $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m m' Nothing -> registerReportHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m ---------------------------------------------------------------------- -- | A simple accounts view. This one is json-capable, returning the chart -- of accounts as json if the Accept header specifies json. getAccountsR :: Handler RepHtmlJson getAccountsR = do vd@VD{..} <- getViewData let j' = filterJournalPostings2 m j html = do setTitle "hledger-web accounts" addHamlet $ accountsReportAsHtml opts vd $ accountsReport2 (reportopts_ $ cliopts_ opts) am j' json = jsonMap [("accounts", toJSON $ journalAccountNames j')] defaultLayoutJson html json -- | A json-only version of "getAccountsR", does not require the special Accept header. getAccountsJsonR :: Handler RepJson getAccountsJsonR = do VD{..} <- getViewData let j' = filterJournalPostings2 m j jsonToRepJson $ jsonMap [("accounts", toJSON $ journalAccountNames j')] ---------------------------------------------------------------------- -- view helpers -- | Render the sidebar used on most views. sidebar :: ViewData -> Hamlet AppRoute sidebar vd@VD{..} = accountsReportAsHtml opts vd $ accountsReport2 (reportopts_ $ cliopts_ opts) am j -- | Render a "AccountsReport" as HTML. accountsReportAsHtml :: WebOpts -> ViewData -> AccountsReport -> Hamlet AppRoute accountsReportAsHtml _ vd@VD{..} (items',total) = [$hamlet| [+] Add a transaction.. Journal entries   edit   (edit) Accounts $forall i <- items ^{itemAsHtml vd i} #{mixedAmountAsHtml total} |] where l = journalToLedger nullfilterspec j inacctmatcher = inAccountMatcher qopts allaccts = isNothing inacctmatcher items = items' -- maybe items' (\m -> filter (matchesAccount m . \(a,_,_,_)->a) items') showacctmatcher itemAsHtml :: ViewData -> AccountsReportItem -> Hamlet AppRoute itemAsHtml _ (acct, adisplay, aindent, abal) = [$hamlet| #{adisplay} only #{mixedAmountAsHtml abal} (#{numpostings}) |] where hassubs = not $ null $ ledgerSubAccounts l $ ledgerAccount l acct numpostings = length $ apostings $ ledgerAccount l acct depthclass = "depth"++show aindent inacctclass = case inacctmatcher of Just m -> if m `matchesAccount` acct then "inacct" else "notinacct" Nothing -> "" :: String indent = preEscapedString $ concat $ replicate (2 * (1+aindent)) " " acctquery = (RegisterR, [("q", pack $ accountQuery acct)]) acctonlyquery = (RegisterR, [("q", pack $ accountOnlyQuery acct)]) accountQuery :: AccountName -> String accountQuery a = "inacct:" ++ quoteIfSpaced a -- (accountNameToAccountRegex a) accountOnlyQuery :: AccountName -> String accountOnlyQuery a = "inacctonly:" ++ quoteIfSpaced a -- (accountNameToAccountRegex a) -- accountUrl :: AppRoute -> AccountName -> (AppRoute,[(String,ByteString)]) accountUrl r a = (r, [("q",pack $ accountQuery a)]) -- | Render a "EntriesReport" as HTML for the journal entries view. entriesReportAsHtml :: WebOpts -> ViewData -> EntriesReport -> Hamlet AppRoute entriesReportAsHtml _ vd items = [$hamlet| $forall i <- numbered items ^{itemAsHtml vd i} |] where itemAsHtml :: ViewData -> (Int, EntriesReportItem) -> Hamlet AppRoute itemAsHtml _ (n, t) = [$hamlet|
#{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 -> Hamlet AppRoute
journalTransactionsReportAsHtml _ vd (_,items) = [$hamlet|
Date
  Description
  Accounts
  Amount
 $forall i <- numberTransactionsReportItems items
  ^{itemAsHtml vd i}
 |]
 where
-- .#{datetransition}
   itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> Hamlet AppRoute
   itemAsHtml VD{..} (n, _, _, _, (t, _, split, _, amt, _)) = [$hamlet|
#{date}
 #{elideRight 60 desc}
 
  $if showamt
   #{mixedAmountAsHtml amt}
$forall p <- tpostings t
   #{elideRight 40 $ paccount p}
   #{mixedAmountAsHtml $ pamount p}
|]
     where
       evenodd = if even n then "even" else "odd" :: String
       -- datetransition | newm = "newmonth"
       --                | newd = "newday"
       --                | otherwise = "" :: String
       (firstposting, date, desc) = (False, show $ tdate t, tdescription t)
       -- acctquery = (here, [("q", pack $ accountQuery acct)])
       showamt = not split || not (isZeroMixedAmount amt)

-- Generate html for an account register, including a balance chart and transaction list.
registerReportHtml :: WebOpts -> ViewData -> TransactionsReport -> Hamlet AppRoute
registerReportHtml opts vd r@(_,items) = [$hamlet|
 ^{registerChartHtml items}
 ^{registerItemsHtml opts vd r}
|]

-- Generate html for a transaction list from an "TransactionsReport".
registerItemsHtml :: WebOpts -> ViewData -> TransactionsReport -> Hamlet AppRoute
registerItemsHtml _ vd (balancelabel,items) = [$hamlet|
Date
  Description
  To/From Account
    
  Amount
  #{balancelabel}

 $forall i <- numberTransactionsReportItems items
  ^{itemAsHtml vd i}
 |]
 where
   -- inacct = inAccount qopts
   -- filtering = m /= MatchAny
   itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> Hamlet AppRoute
   itemAsHtml VD{..} (n, newd, newm, _, (t, _, split, acct, amt, bal)) = [$hamlet|
#{date}
 #{elideRight 30 desc}
 
  $if showamt
   #{mixedAmountAsHtml amt}
 #{mixedAmountAsHtml bal}
$forall p <- tpostings t
  #{elideRight 40 $ paccount p}
   #{mixedAmountAsHtml $ pamount p}
   
|]
     where
       evenodd = if even n then "even" else "odd" :: String
       datetransition | newm = "newmonth"
                      | newd = "newday"
                      | otherwise = "" :: String
       (firstposting, date, desc) = (False, show $ tdate t, tdescription t)
       -- acctquery = (here, [("q", pack $ accountQuery acct)])
       showamt = not split || not (isZeroMixedAmount amt)
       postingsdisplaystyle = if showpostings then "" else "display:none;" :: String

-- | Generate javascript/html for a register balance line chart based on
-- the provided "TransactionsReportItem"s.
registerChartHtml items = [$hamlet|