imp: web: round amounts to display precision as before (precisiongeddon)
This commit is contained in:
parent
6bd862efbf
commit
5ee2139f18
@ -42,6 +42,7 @@ exchange rates.
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
|
||||
module Hledger.Data.Amount (
|
||||
-- * Commodity
|
||||
@ -1011,6 +1012,10 @@ mixedAmountSetStyles = styleAmounts
|
||||
instance HasAmounts MixedAmount where
|
||||
styleAmounts styles = mapMixedAmountUnsafe (styleAmounts styles)
|
||||
|
||||
instance HasAmounts Account where
|
||||
styleAmounts styles acct@Account{aebalance,aibalance} =
|
||||
acct{aebalance=styleAmounts styles aebalance, aibalance=styleAmounts styles aibalance}
|
||||
|
||||
-- | Reset each individual amount's display style to the default.
|
||||
mixedAmountUnstyled :: MixedAmount -> MixedAmount
|
||||
mixedAmountUnstyled = mapMixedAmountUnsafe amountUnstyled
|
||||
|
||||
@ -132,6 +132,7 @@ instance Yesod App where
|
||||
|
||||
let accounts =
|
||||
balanceReportAsHtml (JournalR, RegisterR) here hideEmptyAccts j qparam qopts $
|
||||
styleAmounts (journalCommodityStylesWith HardRounding j) $
|
||||
balanceReport rspec' j
|
||||
|
||||
topShowmd = if showSidebar then "col-md-4" else "col-any-0" :: Text
|
||||
|
||||
@ -28,7 +28,9 @@ getJournalR = do
|
||||
title' = title <> if q /= Any then ", filtered" else ""
|
||||
acctlink a = (RegisterR, [("q", replaceInacct qparam $ accountQuery a)])
|
||||
rspec = (reportspec_ $ cliopts_ opts){_rsQuery = filterQuery (not . queryIsDepth) q}
|
||||
items = reverse $ entriesReport rspec j
|
||||
items = reverse $
|
||||
styleAmounts (journalCommodityStylesWith HardRounding j) $
|
||||
entriesReport rspec j
|
||||
transactionFrag = transactionFragment j
|
||||
|
||||
defaultLayout $ do
|
||||
|
||||
@ -91,7 +91,9 @@ getAccountsR = do
|
||||
VD{j} <- getViewData
|
||||
require ViewPermission
|
||||
selectRep $ do
|
||||
provideJson $ flattenAccounts $ mapAccounts (accountSetDeclarationInfo j) $ ledgerRootAccount $ ledgerFromJournal Any j
|
||||
provideJson $
|
||||
styleAmounts (journalCommodityStylesWith HardRounding j) $
|
||||
flattenAccounts $ mapAccounts (accountSetDeclarationInfo j) $ ledgerRootAccount $ ledgerFromJournal Any j
|
||||
|
||||
getAccounttransactionsR :: Text -> Handler TypedContent
|
||||
getAccounttransactionsR a = do
|
||||
@ -101,5 +103,7 @@ getAccounttransactionsR a = do
|
||||
rspec = defreportspec
|
||||
thisacctq = Acct $ accountNameToAccountRegex a -- includes subs
|
||||
selectRep $ do
|
||||
provideJson $ accountTransactionsReport rspec{_rsQuery=Any} j thisacctq
|
||||
provideJson $
|
||||
styleAmounts (journalCommodityStylesWith HardRounding j) $
|
||||
accountTransactionsReport rspec{_rsQuery=Any} j thisacctq
|
||||
|
||||
|
||||
@ -45,7 +45,9 @@ getRegisterR = do
|
||||
zip xs $
|
||||
zip (map (T.unpack . accountSummarisedName . paccount) xs) $
|
||||
tail $ (", "<$xs) ++ [""]
|
||||
items = accountTransactionsReport rspec{_rsQuery=q} j acctQuery
|
||||
items =
|
||||
styleAmounts (journalCommodityStylesWith HardRounding j) $
|
||||
accountTransactionsReport rspec{_rsQuery=q} j acctQuery
|
||||
balancelabel
|
||||
| isJust (inAccount qopts), balanceaccum_ (_rsReportOpts rspec) == Historical = "Historical Total"
|
||||
| isJust (inAccount qopts) = "Period Total"
|
||||
|
||||
Loading…
Reference in New Issue
Block a user