{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings, RecordWildCards #-} {- hledger-web's request handlers, and helpers. -} module Hledger.Web.Handlers ( -- * GET handlers getRootR, getJournalR, getJournalEntriesR, getJournalEditR, getRegisterR, -- ** helpers -- sidebar, -- accountsReportAsHtml, -- accountQuery, -- accountOnlyQuery, -- accountUrl, -- entriesReportAsHtml, -- journalTransactionsReportAsHtml, -- registerReportHtml, -- registerItemsHtml, -- registerChartHtml, -- stringIfLongerThan, -- numberTransactionsReportItems, -- mixedAmountAsHtml, -- * POST handlers postJournalR, postJournalEntriesR, postJournalEditR, postRegisterR, -- * Common page components -- * Utilities ViewData(..), nullviewdata, ) where import Prelude import Control.Applicative ((<$>)) import Data.Either (lefts,rights) import Data.List import Data.Maybe import Data.Text(Text,pack,unpack) import qualified Data.Text (null) 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) #if BLAZE_HTML_0_5 import Text.Blaze.Internal (preEscapedString) import Text.Blaze.Html (toHtml) #else import Text.Blaze (preEscapedString, toHtml) #endif import Text.Hamlet hiding (hamlet) import Text.Printf import Yesod.Core -- import Yesod.Json import Hledger hiding (is) import Hledger.Cli hiding (version) import Hledger.Web.Foundation import Hledger.Web.Options import Hledger.Web.Settings -- routes: -- /static StaticR Static getStatic -- -- /favicon.ico FaviconR GET -- /robots.txt RobotsR GET -- / RootR GET -- /journal JournalR GET POST -- /journal/entries JournalEntriesR GET POST -- /journal/edit JournalEditR GET POST -- /register RegisterR GET POST -- -- /accounts AccountsR GET -- -- /api/accounts AccountsJsonR GET ---------------------------------------------------------------------- -- GET handlers getRootR :: Handler RepHtml getRootR = redirect defaultroute where defaultroute = RegisterR -- | 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 /= Any -- showlastcolumn = if injournal && not filtering then False else True title = case inacct of Nothing -> "Journal"++s2 Just (a,inclsubs) -> "Transactions in "++a++s1++s2 where s1 = if inclsubs then " (and subaccounts)" else "" where s2 = if filtering then ", filtered" else "" maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m defaultLayout $ do setTitle "hledger-web journal" addWidget $ toWidget [hamlet| ^{topbar vd} ^{sidecontent} #{title} ^{searchform vd} ^{maincontent} ^{addform vd} ^{editform vd} ^{importform} |] -- | The journal entries view, with sidebar. getJournalEntriesR :: Handler RepHtml getJournalEntriesR = do vd@VD{..} <- getViewData let sidecontent = sidebar vd title = "Journal entries" ++ if m /= Any then ", filtered" else "" :: String maincontent = entriesReportAsHtml opts vd $ entriesReport (reportopts_ $ cliopts_ opts) Any $ filterJournalTransactions m j defaultLayout $ do setTitle "hledger-web journal" addWidget $ toWidget [hamlet| ^{topbar vd} ^{sidecontent} #{title} ^{searchform vd} ^{maincontent} ^{addform vd} ^{editform vd} ^{importform} |] -- | The journal editform, no sidebar. getJournalEditR :: Handler RepHtml getJournalEditR = do vd <- getViewData defaultLayout $ do setTitle "hledger-web journal edit form" addWidget $ toWidget $ editform vd -- -- | The journal entries view, no sidebar. -- getJournalOnlyR :: Handler RepHtml -- getJournalOnlyR = do -- vd@VD{..} <- getViewData -- defaultLayout $ do -- setTitle "hledger-web journal only" -- addWidget $ toWidget $ entriesReportAsHtml opts vd $ entriesReport (reportopts_ $ cliopts_ opts) nullfilterspec $ filterJournalTransactions2 m j -- | The main journal/account register view, with accounts sidebar. getRegisterR :: Handler RepHtml getRegisterR = do vd@VD{..} <- getViewData let sidecontent = sidebar vd -- injournal = isNothing inacct filtering = m /= Any title = "Transactions in "++a++s1++s2 where (a,inclsubs) = fromMaybe ("all accounts",False) $ inAccount qopts s1 = if inclsubs then " (and subaccounts)" else "" s2 = if filtering then ", filtered" else "" maincontent = registerReportHtml opts vd $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts defaultLayout $ do setTitle "hledger-web register" addWidget $ toWidget [hamlet| ^{topbar vd} ^{sidecontent} #{title} ^{searchform vd} ^{maincontent} ^{addform vd} ^{editform vd} ^{importform} |] -- -- | The register view, no sidebar. -- getRegisterOnlyR :: Handler RepHtml -- getRegisterOnlyR = do -- vd@VD{..} <- getViewData -- defaultLayout $ do -- setTitle "hledger-web register only" -- addWidget $ toWidget $ -- case inAccountQuery qopts of Just m' -> 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" addWidget $ toWidget $ 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')] -} -- helpers -- | Render the sidebar used on most views. sidebar :: ViewData -> HtmlUrl AppRoute sidebar vd@VD{..} = accountsReportAsHtml opts vd $ accountsReport (reportopts_ $ cliopts_ opts) am j -- | Render an "AccountsReport" as html. accountsReportAsHtml :: WebOpts -> ViewData -> AccountsReport -> HtmlUrl AppRoute accountsReportAsHtml _ vd@VD{..} (items',total) = [hamlet| [+]
Add a transaction..
Journal   entries   edit
Accounts $forall i <- items ^{itemAsHtml vd i} #{mixedAmountAsHtml total} |] where l = journalToLedger Any j inacctmatcher = inAccountQuery qopts allaccts = isNothing inacctmatcher items = items' -- maybe items' (\m -> filter (matchesAccount m . \(a,_,_,_)->a) items') showacctmatcher itemAsHtml :: ViewData -> AccountsReportItem -> HtmlUrl AppRoute itemAsHtml _ (acct, adisplay, aindent, abal) = [hamlet| #{indent}
#{adisplay} $if hassubs   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, [(Text, Text)]) accountUrl r a = (r, [("q", pack $ accountQuery a)]) -- | Render an "EntriesReport" as html for the journal entries view. entriesReportAsHtml :: WebOpts -> ViewData -> EntriesReport -> HtmlUrl AppRoute entriesReportAsHtml _ vd items = [hamlet| $forall i <- numbered items ^{itemAsHtml vd i} |] where itemAsHtml :: ViewData -> (Int, EntriesReportItem) -> HtmlUrl 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 a "TransactionsReport" as html for the formatted journal view.
journalTransactionsReportAsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl 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) -> HtmlUrl 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 -> HtmlUrl 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 -> HtmlUrl 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 /= Any
   itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute
   itemAsHtml VD{..} (n, newd, newm, _, (t, _, split, acct, amt, bal)) = [hamlet|

 #{date}
 #{elideRight 30 desc}
 
  
   #{elideRight 40 acct}
   
  
   [+]
 
  $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 :: forall t (t1 :: * -> *) t2 t3 t4 t5.
               --                      Data.Foldable.Foldable t1 =>
               --                      t1 (Transaction, t2, t3, t4, t5, MixedAmount)
               --                      -> t -> Text.Blaze.Internal.HtmlM ()
registerChartHtml :: [TransactionsReportItem] -> HtmlUrl AppRoute
registerChartHtml items =
 -- have to make sure plot is not called when our container (maincontent)
 -- is hidden, eg with add form toggled
 [hamlet|