2014-04-25 01:28:20 +04:00
-- {-# LANGUAGE CPP #-}
2008-10-03 06:04:15 +04:00
{- |
2012-04-14 02:24:55 +04:00
A 'Journal' is a set of transactions , plus optional related data . This is
hledger's primary data object . It is usually parsed from a journal file or
other data format ( see " Hledger.Read " ) .
2008-10-03 06:04:15 +04:00
- }
2012-04-14 02:24:55 +04:00
module Hledger.Data.Journal (
-- * Parsing helpers
addHistoricalPrice ,
addModifierTransaction ,
addPeriodicTransaction ,
addTimeLogEntry ,
addTransaction ,
journalApplyAliases ,
2012-05-27 22:14:20 +04:00
journalBalanceTransactions ,
2012-04-14 02:24:55 +04:00
journalCanonicaliseAmounts ,
journalConvertAmountsToCost ,
journalFinalise ,
-- * Filtering
filterJournalTransactions ,
2014-02-28 05:47:47 +04:00
filterJournalPostings ,
2014-05-24 00:10:36 +04:00
filterJournalAmounts ,
filterTransactionAmounts ,
2014-02-28 05:47:47 +04:00
filterPostingAmount ,
2012-04-14 02:24:55 +04:00
-- * Querying
2012-05-27 22:14:20 +04:00
journalAccountNames ,
2012-04-14 02:24:55 +04:00
journalAccountNamesUsed ,
2012-11-20 01:20:10 +04:00
-- journalAmountAndPriceCommodities,
2012-04-14 02:24:55 +04:00
journalAmounts ,
2012-11-20 01:20:10 +04:00
-- journalCanonicalCommodities,
2012-04-14 02:24:55 +04:00
journalDateSpan ,
2014-02-28 05:47:47 +04:00
journalDescriptions ,
2012-04-14 02:24:55 +04:00
journalFilePath ,
journalFilePaths ,
journalPostings ,
2012-04-14 05:12:42 +04:00
-- * Standard account types
2012-05-16 11:37:24 +04:00
journalBalanceSheetAccountQuery ,
journalProfitAndLossAccountQuery ,
2012-04-15 04:05:10 +04:00
journalIncomeAccountQuery ,
journalExpenseAccountQuery ,
journalAssetAccountQuery ,
journalLiabilityAccountQuery ,
journalEquityAccountQuery ,
2012-04-17 21:32:56 +04:00
journalCashAccountQuery ,
2012-04-14 02:24:55 +04:00
-- * Misc
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
canonicalStyles ,
2012-04-14 02:24:55 +04:00
matchpats ,
nullctx ,
nulljournal ,
-- * Tests
2012-05-27 22:14:20 +04:00
samplejournal ,
2012-04-14 02:24:55 +04:00
tests_Hledger_Data_Journal ,
)
2007-07-02 23:15:39 +04:00
where
2013-05-29 03:25:00 +04:00
import Control.Monad
2011-05-28 08:11:44 +04:00
import Data.List
2012-11-20 01:20:10 +04:00
-- import Data.Map (findWithDefault)
2013-05-29 03:25:00 +04:00
import Data.Maybe
2011-05-28 08:11:44 +04:00
import Data.Ord
2014-07-02 18:35:06 +04:00
import Safe ( headMay )
2011-05-28 08:11:44 +04:00
import Data.Time.Calendar
import Data.Time.LocalTime
import Data.Tree
2010-09-24 05:56:11 +04:00
import Safe ( headDef )
2009-08-12 13:21:46 +04:00
import System.Time ( ClockTime ( TOD ) )
2011-05-28 08:11:44 +04:00
import Test.HUnit
import Text.Printf
2012-11-20 01:20:10 +04:00
import qualified Data.Map as M
2011-05-28 08:11:44 +04:00
import Hledger.Utils
2010-05-20 03:08:53 +04:00
import Hledger.Data.Types
import Hledger.Data.AccountName
import Hledger.Data.Amount
2012-11-20 01:20:10 +04:00
-- import Hledger.Data.Commodity
2012-05-27 22:14:20 +04:00
import Hledger.Data.Dates
import Hledger.Data.Transaction
2010-05-20 03:08:53 +04:00
import Hledger.Data.Posting
import Hledger.Data.TimeLog
2012-05-16 11:57:10 +04:00
import Hledger.Query
2007-07-02 23:15:39 +04:00
2009-12-16 10:00:43 +03:00
instance Show Journal where
2013-12-07 01:51:19 +04:00
show j
| debugLevel < 3 = printf " Journal %s with %d transactions, %d accounts "
( journalFilePath j )
( length ( jtxns j ) +
length ( jmodifiertxns j ) +
length ( jperiodictxns j ) )
( length accounts )
| debugLevel < 6 = printf " Journal %s with %d transactions, %d accounts: %s "
( journalFilePath j )
( length ( jtxns j ) +
length ( jmodifiertxns j ) +
length ( jperiodictxns j ) )
( length accounts )
( show accounts )
| otherwise = printf " Journal %s with %d transactions, %d accounts: %s, commodity styles: %s "
2010-09-24 05:56:11 +04:00
( journalFilePath j )
2009-12-21 08:23:07 +03:00
( length ( jtxns j ) +
length ( jmodifiertxns j ) +
length ( jperiodictxns j ) )
2008-10-09 13:25:58 +04:00
( length accounts )
( show accounts )
2012-11-20 01:20:10 +04:00
( show $ jcommoditystyles j )
2009-12-16 10:00:43 +03:00
-- ++ (show $ journalTransactions l)
2015-06-29 00:14:56 +03:00
where accounts = filter ( /= " root " ) $ flatten $ journalAccountNameTree j
2008-10-03 16:10:05 +04:00
2012-04-14 02:24:55 +04:00
-- showJournalDebug j = unlines [
-- show j
-- ,show (jtxns j)
-- ,show (jmodifiertxns j)
-- ,show (jperiodictxns j)
-- ,show $ open_timelog_entries j
-- ,show $ historical_prices j
-- ,show $ final_comment_lines j
-- ,show $ jContext j
-- ,show $ map fst $ files j
-- ]
2011-08-03 03:27:41 +04:00
2009-12-20 18:50:54 +03:00
nulljournal :: Journal
nulljournal = Journal { jmodifiertxns = []
, jperiodictxns = []
, jtxns = []
, open_timelog_entries = []
, historical_prices = []
, final_comment_lines = []
2010-11-13 18:03:40 +03:00
, jContext = nullctx
2010-09-24 05:56:11 +04:00
, files = []
2009-12-20 18:50:54 +03:00
, filereadtime = TOD 0 0
2012-11-20 01:20:10 +04:00
, jcommoditystyles = M . fromList []
2009-12-20 18:50:54 +03:00
}
2008-12-08 04:48:03 +03:00
2010-11-13 18:03:40 +03:00
nullctx :: JournalContext
2014-07-03 04:41:33 +04:00
nullctx = Ctx { ctxYear = Nothing , ctxDefaultCommodityAndStyle = Nothing , ctxAccount = [] , ctxAliases = [] }
2010-11-13 18:03:40 +03:00
2010-09-24 05:56:11 +04:00
journalFilePath :: Journal -> FilePath
journalFilePath = fst . mainfile
journalFilePaths :: Journal -> [ FilePath ]
journalFilePaths = map fst . files
mainfile :: Journal -> ( FilePath , String )
mainfile = headDef ( " " , " " ) . files
2009-12-16 11:07:26 +03:00
addTransaction :: Transaction -> Journal -> Journal
2014-11-03 09:00:02 +03:00
addTransaction t j = j { jtxns = t : jtxns j }
2008-12-08 04:48:03 +03:00
2009-12-16 10:00:43 +03:00
addModifierTransaction :: ModifierTransaction -> Journal -> Journal
2014-11-03 09:00:02 +03:00
addModifierTransaction mt j = j { jmodifiertxns = mt : jmodifiertxns j }
2008-12-08 04:48:03 +03:00
2009-12-16 10:00:43 +03:00
addPeriodicTransaction :: PeriodicTransaction -> Journal -> Journal
2014-11-03 09:00:02 +03:00
addPeriodicTransaction pt j = j { jperiodictxns = pt : jperiodictxns j }
2008-12-08 04:48:03 +03:00
2009-12-16 10:00:43 +03:00
addHistoricalPrice :: HistoricalPrice -> Journal -> Journal
2014-11-03 09:00:02 +03:00
addHistoricalPrice h j = j { historical_prices = h : historical_prices j }
2008-12-16 13:54:20 +03:00
2009-12-16 10:00:43 +03:00
addTimeLogEntry :: TimeLogEntry -> Journal -> Journal
2014-11-03 09:00:02 +03:00
addTimeLogEntry tle j = j { open_timelog_entries = tle : open_timelog_entries j }
2008-12-08 04:48:03 +03:00
2014-02-28 05:47:47 +04:00
-- | Unique transaction descriptions used in this journal.
journalDescriptions :: Journal -> [ String ]
journalDescriptions = nub . sort . map tdescription . jtxns
-- | All postings from this journal's transactions, in order.
2009-12-19 08:57:54 +03:00
journalPostings :: Journal -> [ Posting ]
journalPostings = concatMap tpostings . jtxns
2008-10-03 16:10:05 +04:00
2014-02-28 05:47:47 +04:00
-- | Unique account names posted to in this journal.
2009-12-16 10:00:43 +03:00
journalAccountNamesUsed :: Journal -> [ AccountName ]
2011-07-17 19:54:21 +04:00
journalAccountNamesUsed = sort . accountNamesFromPostings . journalPostings
2008-10-03 16:10:05 +04:00
2014-02-28 05:47:47 +04:00
-- | Unique account names in this journal, including parent accounts containing no postings.
2009-12-16 10:00:43 +03:00
journalAccountNames :: Journal -> [ AccountName ]
journalAccountNames = sort . expandAccountNames . journalAccountNamesUsed
2008-10-03 16:10:05 +04:00
2009-12-16 10:00:43 +03:00
journalAccountNameTree :: Journal -> Tree AccountName
journalAccountNameTree = accountNameTreeFrom . journalAccountNames
2008-10-10 08:23:25 +04:00
2012-04-14 05:12:42 +04:00
-- standard account types
2012-04-15 04:05:10 +04:00
-- | A query for Profit & Loss accounts in this journal.
-- Cf <http://en.wikipedia.org/wiki/Chart_of_accounts#Profit_.26_Loss_accounts>.
2012-05-16 11:12:49 +04:00
journalProfitAndLossAccountQuery :: Journal -> Query
journalProfitAndLossAccountQuery j = Or [ journalIncomeAccountQuery j
2012-04-15 04:05:10 +04:00
, journalExpenseAccountQuery j
]
-- | A query for Income (Revenue) accounts in this journal.
-- This is currently hard-coded to the case-insensitive regex @^(income|revenue)s?(:|$)@.
2012-05-16 11:12:49 +04:00
journalIncomeAccountQuery :: Journal -> Query
journalIncomeAccountQuery _ = Acct " ^(income|revenue)s?(:|$) "
2012-04-15 04:05:10 +04:00
-- | A query for Expense accounts in this journal.
-- This is currently hard-coded to the case-insensitive regex @^expenses?(:|$)@.
2012-05-16 11:12:49 +04:00
journalExpenseAccountQuery :: Journal -> Query
journalExpenseAccountQuery _ = Acct " ^expenses?(:|$) "
2012-04-14 05:12:42 +04:00
2012-05-16 11:37:24 +04:00
-- | A query for Asset, Liability & Equity accounts in this journal.
2012-04-14 05:12:42 +04:00
-- Cf <http://en.wikipedia.org/wiki/Chart_of_accounts#Balance_Sheet_Accounts>.
2012-05-16 11:12:49 +04:00
journalBalanceSheetAccountQuery :: Journal -> Query
journalBalanceSheetAccountQuery j = Or [ journalAssetAccountQuery j
2012-04-15 04:05:10 +04:00
, journalLiabilityAccountQuery j
, journalEquityAccountQuery j
]
-- | A query for Asset accounts in this journal.
-- This is currently hard-coded to the case-insensitive regex @^assets?(:|$)@.
2012-05-16 11:12:49 +04:00
journalAssetAccountQuery :: Journal -> Query
journalAssetAccountQuery _ = Acct " ^assets?(:|$) "
2012-04-15 04:05:10 +04:00
-- | A query for Liability accounts in this journal.
2015-07-04 15:15:30 +03:00
-- This is currently hard-coded to the case-insensitive regex @^(debts?|liabilit(y|ies))(:|$)@.
2012-05-16 11:12:49 +04:00
journalLiabilityAccountQuery :: Journal -> Query
2015-07-04 15:15:30 +03:00
journalLiabilityAccountQuery _ = Acct " ^(debts?|liabilit(y|ies))(:|$) "
2012-04-15 04:05:10 +04:00
-- | A query for Equity accounts in this journal.
-- This is currently hard-coded to the case-insensitive regex @^equity(:|$)@.
2012-05-16 11:12:49 +04:00
journalEquityAccountQuery :: Journal -> Query
journalEquityAccountQuery _ = Acct " ^equity(:|$) "
2012-04-14 05:12:42 +04:00
2012-04-17 21:32:56 +04:00
-- | A query for Cash (-equivalent) accounts in this journal (ie,
-- accounts which appear on the cashflow statement.) This is currently
-- hard-coded to be all the Asset accounts except for those containing the
-- case-insensitive regex @(receivable|A/R)@.
journalCashAccountQuery :: Journal -> Query
journalCashAccountQuery j = And [ journalAssetAccountQuery j , Not $ Acct " (receivable|A/R) " ]
2009-12-21 08:23:07 +03:00
-- Various kinds of filtering on journals. We do it differently depending
-- on the command.
2011-06-04 03:14:26 +04:00
-------------------------------------------------------------------------------
-- filtering V2
2014-05-24 00:10:36 +04:00
-- | Keep only transactions matching the query expression.
filterJournalTransactions :: Query -> Journal -> Journal
filterJournalTransactions q j @ Journal { jtxns = ts } = j { jtxns = filter ( q ` matchesTransaction ` ) ts }
2011-06-04 03:14:26 +04:00
-- | Keep only postings matching the query expression.
-- This can leave unbalanced transactions.
2012-05-27 22:14:20 +04:00
filterJournalPostings :: Query -> Journal -> Journal
filterJournalPostings q j @ Journal { jtxns = ts } = j { jtxns = map filtertransactionpostings ts }
2011-06-05 22:36:32 +04:00
where
2012-05-27 22:14:20 +04:00
filtertransactionpostings t @ Transaction { tpostings = ps } = t { tpostings = filter ( q ` matchesPosting ` ) ps }
2011-06-05 22:36:32 +04:00
2014-05-24 00:10:36 +04:00
-- | Within each posting's amount, keep only the parts matching the query.
2014-02-28 05:47:47 +04:00
-- This can leave unbalanced transactions.
2014-05-24 00:10:36 +04:00
filterJournalAmounts :: Query -> Journal -> Journal
filterJournalAmounts q j @ Journal { jtxns = ts } = j { jtxns = map ( filterTransactionAmounts q ) ts }
-- | Filter out all parts of this transaction's amounts which do not match the query.
-- This can leave the transaction unbalanced.
filterTransactionAmounts :: Query -> Transaction -> Transaction
filterTransactionAmounts q t @ Transaction { tpostings = ps } = t { tpostings = map ( filterPostingAmount q ) ps }
2014-02-28 05:47:47 +04:00
-- | Filter out all parts of this posting's amount which do not match the query.
filterPostingAmount :: Query -> Posting -> Posting
filterPostingAmount q p @ Posting { pamount = Mixed as } = p { pamount = Mixed $ filter ( q ` matchesAmount ` ) as }
2012-05-27 22:14:20 +04:00
{-
2011-06-04 03:14:26 +04:00
-------------------------------------------------------------------------------
-- filtering V1
2011-06-03 06:14:36 +04:00
-- | Keep only transactions we are interested in, as described by the
-- filter specification.
2009-12-21 08:23:07 +03:00
filterJournalTransactions :: FilterSpec -> Journal -> Journal
filterJournalTransactions FilterSpec { datespan = datespan
, cleared = cleared
-- ,real=real
-- ,empty=empty
, acctpats = apats
, descpats = dpats
, depth = depth
2012-05-09 19:34:05 +04:00
, fMetadata = md
2009-12-21 08:23:07 +03:00
} =
filterJournalTransactionsByClearedStatus cleared .
filterJournalPostingsByDepth depth .
filterJournalTransactionsByAccount apats .
2012-04-09 00:43:48 +04:00
filterJournalTransactionsByMetadata md .
2009-12-21 08:23:07 +03:00
filterJournalTransactionsByDescription dpats .
2011-06-03 06:14:36 +04:00
filterJournalTransactionsByDate datespan
2009-12-21 08:23:07 +03:00
2011-06-03 06:14:36 +04:00
-- | Keep only postings we are interested in, as described by the filter
-- specification. This can leave unbalanced transactions.
2009-12-21 08:23:07 +03:00
filterJournalPostings :: FilterSpec -> Journal -> Journal
filterJournalPostings FilterSpec { datespan = datespan
, cleared = cleared
, real = real
, empty = empty
, acctpats = apats
, descpats = dpats
, depth = depth
2012-05-09 19:34:05 +04:00
, fMetadata = md
2009-12-21 08:23:07 +03:00
} =
filterJournalPostingsByRealness real .
filterJournalPostingsByClearedStatus cleared .
filterJournalPostingsByEmpty empty .
filterJournalPostingsByDepth depth .
filterJournalPostingsByAccount apats .
2012-04-09 00:43:48 +04:00
filterJournalTransactionsByMetadata md .
2009-12-21 08:23:07 +03:00
filterJournalTransactionsByDescription dpats .
2011-06-03 06:14:36 +04:00
filterJournalTransactionsByDate datespan
2009-04-03 14:58:05 +04:00
2012-04-09 00:43:48 +04:00
-- | Keep only transactions whose metadata matches all metadata specifications.
filterJournalTransactionsByMetadata :: [ ( String , String ) ] -> Journal -> Journal
filterJournalTransactionsByMetadata pats j @ Journal { jtxns = ts } = j { jtxns = filter matchmd ts }
where matchmd t = all ( ` elem ` tmetadata t ) pats
2010-07-13 10:30:06 +04:00
-- | Keep only transactions whose description matches the description patterns.
2009-12-16 11:07:26 +03:00
filterJournalTransactionsByDescription :: [ String ] -> Journal -> Journal
2009-12-21 08:43:10 +03:00
filterJournalTransactionsByDescription pats j @ Journal { jtxns = ts } = j { jtxns = filter matchdesc ts }
2009-12-16 20:58:51 +03:00
where matchdesc = matchpats pats . tdescription
2009-04-03 14:58:05 +04:00
2010-07-13 10:30:06 +04:00
-- | Keep only transactions which fall between begin and end dates.
2009-04-03 14:58:05 +04:00
-- We include transactions on the begin date and exclude transactions on the end
2008-10-10 08:23:25 +04:00
-- date, like ledger. An empty date string means no restriction.
2009-12-16 11:07:26 +03:00
filterJournalTransactionsByDate :: DateSpan -> Journal -> Journal
2009-12-21 08:43:10 +03:00
filterJournalTransactionsByDate ( DateSpan begin end ) j @ Journal { jtxns = ts } = j { jtxns = filter match ts }
where match t = maybe True ( tdate t >= ) begin && maybe True ( tdate t < ) end
2008-10-10 08:23:25 +04:00
2010-07-13 10:30:06 +04:00
-- | Keep only transactions which have the requested cleared/uncleared
-- status, if there is one.
2009-12-21 08:23:07 +03:00
filterJournalTransactionsByClearedStatus :: Maybe Bool -> Journal -> Journal
filterJournalTransactionsByClearedStatus Nothing j = j
2009-12-21 08:43:10 +03:00
filterJournalTransactionsByClearedStatus ( Just val ) j @ Journal { jtxns = ts } = j { jtxns = filter match ts }
where match = ( == val ) . tstatus
2009-12-21 08:23:07 +03:00
-- | Keep only postings which have the requested cleared/uncleared status,
-- if there is one.
2009-12-16 10:58:06 +03:00
filterJournalPostingsByClearedStatus :: Maybe Bool -> Journal -> Journal
2009-12-19 08:57:54 +03:00
filterJournalPostingsByClearedStatus Nothing j = j
2009-12-21 08:23:07 +03:00
filterJournalPostingsByClearedStatus ( Just c ) j @ Journal { jtxns = ts } = j { jtxns = map filterpostings ts }
where filterpostings t @ Transaction { tpostings = ps } = t { tpostings = filter ( ( == c ) . postingCleared ) ps }
2008-10-15 04:34:02 +04:00
2009-04-03 14:58:05 +04:00
-- | Strip out any virtual postings, if the flag is true, otherwise do
2008-10-17 04:57:00 +04:00
-- no filtering.
2009-12-16 10:00:43 +03:00
filterJournalPostingsByRealness :: Bool -> Journal -> Journal
2012-04-16 20:43:58 +04:00
filterJournalPostingsByRealness False j = j
2009-12-21 08:43:10 +03:00
filterJournalPostingsByRealness True j @ Journal { jtxns = ts } = j { jtxns = map filterpostings ts }
2009-12-21 08:23:07 +03:00
where filterpostings t @ Transaction { tpostings = ps } = t { tpostings = filter isReal ps }
-- | Strip out any postings with zero amount, unless the flag is true.
filterJournalPostingsByEmpty :: Bool -> Journal -> Journal
2012-04-16 20:43:58 +04:00
filterJournalPostingsByEmpty True j = j
2009-12-21 08:43:10 +03:00
filterJournalPostingsByEmpty False j @ Journal { jtxns = ts } = j { jtxns = map filterpostings ts }
2009-12-21 08:23:07 +03:00
where filterpostings t @ Transaction { tpostings = ps } = t { tpostings = filter ( not . isEmptyPosting ) ps }
2012-04-14 02:24:55 +04:00
-- -- | Keep only transactions which affect accounts deeper than the specified depth.
-- filterJournalTransactionsByDepth :: Maybe Int -> Journal -> Journal
-- filterJournalTransactionsByDepth Nothing j = j
-- filterJournalTransactionsByDepth (Just d) j@Journal{jtxns=ts} =
-- j{jtxns=(filter (any ((<= d+1) . accountNameLevel . paccount) . tpostings) ts)}
2009-04-03 14:58:05 +04:00
-- | Strip out any postings to accounts deeper than the specified depth
2010-07-13 10:30:06 +04:00
-- (and any transactions which have no postings as a result).
2009-12-21 08:23:07 +03:00
filterJournalPostingsByDepth :: Maybe Int -> Journal -> Journal
filterJournalPostingsByDepth Nothing j = j
2009-12-21 08:43:10 +03:00
filterJournalPostingsByDepth ( Just d ) j @ Journal { jtxns = ts } =
j { jtxns = filter ( not . null . tpostings ) $ map filtertxns ts }
2009-12-16 20:58:51 +03:00
where filtertxns t @ Transaction { tpostings = ps } =
2009-12-21 08:23:07 +03:00
t { tpostings = filter ( ( <= d ) . accountNameLevel . paccount ) ps }
2009-04-03 14:58:05 +04:00
2012-05-27 22:14:20 +04:00
-- | Keep only postings which affect accounts matched by the account patterns.
-- This can leave transactions unbalanced.
filterJournalPostingsByAccount :: [ String ] -> Journal -> Journal
filterJournalPostingsByAccount apats j @ Journal { jtxns = ts } = j { jtxns = map filterpostings ts }
where filterpostings t @ Transaction { tpostings = ps } = t { tpostings = filter ( matchpats apats . paccount ) ps }
2009-12-21 08:23:07 +03:00
-- | Keep only transactions which affect accounts matched by the account patterns.
2010-04-16 03:08:27 +04:00
-- More precisely: each positive account pattern excludes transactions
-- which do not contain a posting to a matched account, and each negative
-- account pattern excludes transactions containing a posting to a matched
-- account.
2009-12-21 08:23:07 +03:00
filterJournalTransactionsByAccount :: [ String ] -> Journal -> Journal
2010-04-16 03:08:27 +04:00
filterJournalTransactionsByAccount apats j @ Journal { jtxns = ts } = j { jtxns = filter tmatch ts }
where
tmatch t = ( null positives || any positivepmatch ps ) && ( null negatives || not ( any negativepmatch ps ) ) where ps = tpostings t
positivepmatch p = any ( ` amatch ` a ) positives where a = paccount p
negativepmatch p = any ( ` amatch ` a ) negatives where a = paccount p
2011-06-09 01:52:10 +04:00
amatch pat a = regexMatchesCI ( abspat pat ) a
2010-04-16 03:08:27 +04:00
( negatives , positives ) = partition isnegativepat apats
2008-11-22 09:35:10 +03:00
2012-05-27 22:14:20 +04:00
- }
2009-12-21 08:23:07 +03:00
2011-08-05 04:05:39 +04:00
-- | Apply additional account aliases (eg from the command-line) to all postings in a journal.
2014-10-25 02:05:10 +04:00
journalApplyAliases :: [ AccountAlias ] -> Journal -> Journal
journalApplyAliases aliases j @ Journal { jtxns = ts } =
-- (if null aliases
-- then id
-- else (dbgtrace $
-- "applying additional command-line aliases:\n"
-- ++ chomp (unlines $ map (" "++) $ lines $ ppShow aliases))) $
2015-05-14 22:50:32 +03:00
j { jtxns = map dotransaction ts }
2011-08-05 04:05:39 +04:00
where
2015-05-14 22:50:32 +03:00
dotransaction t @ Transaction { tpostings = ps } = t { tpostings = map doposting ps }
doposting p @ Posting { paccount = a } = p { paccount = accountNameApplyAliases aliases a }
2011-08-05 04:05:39 +04:00
2012-04-14 05:12:42 +04:00
-- | Do post-parse processing on a journal to make it ready for use: check
-- all transactions balance, canonicalise amount formats, close any open
2014-07-02 05:26:37 +04:00
-- timelog entries, maybe check balance assertions and so on.
journalFinalise :: ClockTime -> LocalTime -> FilePath -> String -> JournalContext -> Bool -> Journal -> Either String Journal
journalFinalise tclock tlocal path txt ctx assrt j @ Journal { files = fs } = do
2013-05-29 03:25:00 +04:00
( journalBalanceTransactions $
2010-09-24 05:56:11 +04:00
journalCanonicaliseAmounts $
2014-11-03 09:00:02 +03:00
journalCloseTimeLogEntries tlocal $
j { files = ( path , txt ) : fs
, filereadtime = tclock
, jContext = ctx
, jtxns = reverse $ jtxns j -- NOTE: see addTransaction
, jmodifiertxns = reverse $ jmodifiertxns j -- NOTE: see addModifierTransaction
, jperiodictxns = reverse $ jperiodictxns j -- NOTE: see addPeriodicTransaction
, historical_prices = reverse $ historical_prices j -- NOTE: see addHistoricalPrice
, open_timelog_entries = reverse $ open_timelog_entries j -- NOTE: see addTimeLogEntry
} )
2014-07-02 05:26:37 +04:00
>>= if assrt then journalCheckBalanceAssertions else return
2013-05-29 03:25:00 +04:00
-- | Check any balance assertions in the journal and return an error
-- message if any of them fail.
journalCheckBalanceAssertions :: Journal -> Either String Journal
journalCheckBalanceAssertions j = do
let postingsByAccount = groupBy ( \ p1 p2 -> paccount p1 == paccount p2 ) $
sortBy ( comparing paccount ) $
journalPostings j
forM_ postingsByAccount checkBalanceAssertionsForAccount
Right j
-- Check any balance assertions in this sequence of postings to a single account.
checkBalanceAssertionsForAccount :: [ Posting ] -> Either String ()
checkBalanceAssertionsForAccount ps
| null errs = Right ()
| otherwise = Left $ head errs
where
2013-05-31 02:16:54 +04:00
errs = fst $
foldl' checkBalanceAssertion ( [] , nullmixedamt ) $
splitAssertions $
sortBy ( comparing postingDate ) ps
2013-05-29 03:25:00 +04:00
-- Given a starting balance, accumulated errors, and a non-null sequence of
-- postings to a single account with a balance assertion in the last:
-- check that the final balance matches the balance assertion.
-- If it does, return the new balance, otherwise add an error to the
-- error list. Intended to be called from a fold.
checkBalanceAssertion :: ( [ String ] , MixedAmount ) -> [ Posting ] -> ( [ String ] , MixedAmount )
2014-07-02 18:35:06 +04:00
checkBalanceAssertion ( errs , startbal ) ps
| null ps = ( errs , startbal )
| isNothing assertion = ( errs , startbal )
2015-01-11 09:15:21 +03:00
| -- bal' /= assertedbal -- MixedAmount's Eq instance currently gets confused by different precisions
not $ isReallyZeroMixedAmount ( bal - assertedbal ) = ( errs ++ [ err ] , fullbal )
| otherwise = ( errs , fullbal )
2013-05-29 03:25:00 +04:00
where
p = last ps
assertion = pbalanceassertion p
2014-07-02 18:35:06 +04:00
Just assertedbal = dbg2 " assertedbal " assertion
2014-07-18 02:23:03 +04:00
assertedcomm = dbg2 " assertedcomm " $ maybe " " acommodity $ headMay $ amounts assertedbal
2014-07-02 18:35:06 +04:00
fullbal = dbg2 " fullbal " $ sum $ [ dbg2 " startbal " startbal ] ++ map pamount ps
2014-07-18 02:23:03 +04:00
singlebal = dbg2 " singlebal " $ filterMixedAmount ( \ a -> acommodity a == assertedcomm ) fullbal
2014-07-02 18:35:06 +04:00
bal = singlebal -- check single-commodity balance like Ledger; maybe add == FULLBAL later
2014-07-18 02:23:03 +04:00
err = printf " Balance assertion failed for account %s on %s \ n %sAfter posting: \ n %s \ n expected balance in commodity \ " %s \ " is %s, calculated balance was %s. "
2013-05-29 03:25:00 +04:00
( paccount p )
( show $ postingDate p )
2014-04-17 01:45:41 +04:00
( maybe " " ( ( " In transaction: \ n " ++ ) . show ) $ ptransaction p )
2013-05-29 03:25:00 +04:00
( show p )
2014-07-18 02:23:03 +04:00
assertedcomm
2013-05-29 03:25:00 +04:00
( showMixedAmount assertedbal )
2014-07-02 18:35:06 +04:00
( showMixedAmount singlebal )
2013-05-29 03:25:00 +04:00
-- Given a sequence of postings to a single account, split it into
-- sub-sequences consisting of ordinary postings followed by a single
-- balance-asserting posting. Postings not followed by a balance
-- assertion are discarded.
splitAssertions :: [ Posting ] -> [ [ Posting ] ]
splitAssertions ps
2015-01-11 09:15:21 +03:00
| null rest = []
2013-05-29 03:25:00 +04:00
| otherwise = ( ps' ++ [ head rest ] ) : splitAssertions ( tail rest )
where
( ps' , rest ) = break ( isJust . pbalanceassertion ) ps
2014-09-11 00:07:53 +04:00
2010-11-15 01:44:37 +03:00
-- | Fill in any missing amounts and check that all journal transactions
-- balance, or return an error message. This is done after parsing all
-- amounts and working out the canonical commodities, since balancing
-- depends on display precision. Reports only the first error encountered.
journalBalanceTransactions :: Journal -> Either String Journal
2012-11-20 01:20:10 +04:00
journalBalanceTransactions j @ Journal { jtxns = ts , jcommoditystyles = ss } =
2012-12-22 04:24:38 +04:00
case sequence $ map balance ts of Right ts' -> Right j { jtxns = map txnTieKnot ts' }
2010-11-15 01:44:37 +03:00
Left e -> Left e
2012-11-20 01:20:10 +04:00
where balance = balanceTransaction ( Just ss )
2010-11-15 01:44:37 +03:00
2015-08-10 01:12:16 +03:00
-- | Convert all the journal's posting amounts (and historical price
-- amounts, but currently not transaction price amounts) to their
-- canonical display settings. Ie, all amounts in a given commodity
-- will use (a) the display settings of the first, and (b) the
-- greatest precision, of the posting amounts in that commodity.
2010-05-23 03:35:34 +04:00
journalCanonicaliseAmounts :: Journal -> Journal
2015-08-10 01:12:16 +03:00
journalCanonicaliseAmounts j @ Journal { jtxns = ts , historical_prices = hps } = j''
2010-05-23 03:35:34 +04:00
where
2015-08-10 01:12:16 +03:00
j'' = j' { jtxns = map fixtransaction ts , historical_prices = map fixhistoricalprice hps }
2015-05-14 22:49:17 +03:00
j' = j { jcommoditystyles = canonicalStyles $ dbg8 " journalAmounts " $ journalAmounts j }
2010-05-23 03:35:34 +04:00
fixtransaction t @ Transaction { tpostings = ps } = t { tpostings = map fixposting ps }
fixposting p @ Posting { pamount = a } = p { pamount = fixmixedamount a }
2015-08-10 01:12:16 +03:00
fixhistoricalprice hp @ HistoricalPrice { hamount = a } = hp { hamount = fixamount a }
2010-05-23 03:35:34 +04:00
fixmixedamount ( Mixed as ) = Mixed $ map fixamount as
2012-11-20 01:20:10 +04:00
fixamount a @ Amount { acommodity = c } = a { astyle = journalCommodityStyle j' c }
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- | Given a list of amounts in parse order, build a map from commodities
-- to canonical display styles for amounts in that commodity.
canonicalStyles :: [ Amount ] -> M . Map Commodity AmountStyle
canonicalStyles amts = M . fromList commstyles
where
samecomm = \ a1 a2 -> acommodity a1 == acommodity a2
commamts = [ ( acommodity $ head as , as ) | as <- groupBy samecomm $ sortBy ( comparing acommodity ) amts ]
commstyles = [ ( c , canonicalStyleFrom $ map astyle as ) | ( c , as ) <- commamts ]
-- Given an ordered list of amount styles for a commodity, build a canonical style.
canonicalStyleFrom :: [ AmountStyle ] -> AmountStyle
canonicalStyleFrom [] = amountstyle
canonicalStyleFrom ss @ ( first : _ ) =
first { asprecision = prec , asdecimalpoint = mdec , asdigitgroups = mgrps }
where
-- precision is the maximum of all precisions seen
prec = maximum $ map asprecision ss
-- find the first decimal point and the first digit group style seen,
-- or use defaults.
mdec = Just $ headDef '.' $ catMaybes $ map asdecimalpoint ss
mgrps = maybe Nothing Just $ headMay $ catMaybes $ map asdigitgroups ss
2012-11-20 01:20:10 +04:00
-- | Get this journal's canonical amount style for the given commodity, or the null style.
journalCommodityStyle :: Journal -> Commodity -> AmountStyle
journalCommodityStyle j c = M . findWithDefault amountstyle c $ jcommoditystyles j
2010-05-22 23:00:20 +04:00
2012-04-14 02:24:55 +04:00
-- -- | Apply this journal's historical price records to unpriced amounts where possible.
-- journalApplyHistoricalPrices :: Journal -> Journal
-- journalApplyHistoricalPrices j@Journal{jtxns=ts} = j{jtxns=map fixtransaction ts}
-- where
-- fixtransaction t@Transaction{tdate=d, tpostings=ps} = t{tpostings=map fixposting ps}
-- where
-- fixposting p@Posting{pamount=a} = p{pamount=fixmixedamount a}
-- fixmixedamount (Mixed as) = Mixed $ map fixamount as
-- fixamount = fixprice
-- fixprice a@Amount{price=Just _} = a
-- fixprice a@Amount{commodity=c} = a{price=maybe Nothing (Just . UnitPrice) $ journalHistoricalPriceFor j d c}
-- -- | Get the price for a commodity on the specified day from the price database, if known.
-- -- Does only one lookup step, ie will not look up the price of a price.
-- journalHistoricalPriceFor :: Journal -> Day -> Commodity -> Maybe MixedAmount
-- journalHistoricalPriceFor j d Commodity{symbol=s} = do
-- let ps = reverse $ filter ((<= d).hdate) $ filter ((s==).hsymbol) $ sortBy (comparing hdate) $ historical_prices j
-- case ps of (HistoricalPrice{hamount=a}:_) -> Just a
-- _ -> Nothing
2010-05-23 00:23:36 +04:00
2010-05-23 03:35:34 +04:00
-- | Close any open timelog sessions in this journal using the provided current time.
journalCloseTimeLogEntries :: LocalTime -> Journal -> Journal
journalCloseTimeLogEntries now j @ Journal { jtxns = ts , open_timelog_entries = es } =
j { jtxns = ts ++ ( timeLogEntriesToTransactions now es ) , open_timelog_entries = [] }
2010-05-23 00:23:36 +04:00
-- | Convert all this journal's amounts to cost by applying their prices, if any.
journalConvertAmountsToCost :: Journal -> Journal
journalConvertAmountsToCost j @ Journal { jtxns = ts } = j { jtxns = map fixtransaction ts }
where
2010-11-15 02:29:04 +03:00
-- similar to journalCanonicaliseAmounts
2010-05-23 00:23:36 +04:00
fixtransaction t @ Transaction { tpostings = ps } = t { tpostings = map fixposting ps }
fixposting p @ Posting { pamount = a } = p { pamount = fixmixedamount a }
fixmixedamount ( Mixed as ) = Mixed $ map fixamount as
2012-11-20 01:20:10 +04:00
fixamount = canonicaliseAmount ( jcommoditystyles j ) . costOfAmount
-- -- | Get this journal's unique, display-preference-canonicalised commodities, by symbol.
-- journalCanonicalCommodities :: Journal -> M.Map String Commodity
-- journalCanonicalCommodities j = canonicaliseCommodities $ journalAmountCommodities j
2010-05-23 00:23:36 +04:00
2012-11-20 01:20:10 +04:00
-- -- | Get all this journal's amounts' commodities, in the order parsed.
-- journalAmountCommodities :: Journal -> [Commodity]
-- journalAmountCommodities = map acommodity . concatMap amounts . journalAmounts
2010-05-23 00:23:36 +04:00
2012-11-20 01:20:10 +04:00
-- -- | Get all this journal's amount and price commodities, in the order parsed.
-- journalAmountAndPriceCommodities :: Journal -> [Commodity]
-- journalAmountAndPriceCommodities = concatMap amountCommodities . concatMap amounts . journalAmounts
2010-05-23 00:23:36 +04:00
2012-11-20 01:20:10 +04:00
-- -- | Get this amount's commodity and any commodities referenced in its price.
-- amountCommodities :: Amount -> [Commodity]
-- amountCommodities Amount{acommodity=c,aprice=p} =
-- case p of Nothing -> [c]
-- Just (UnitPrice ma) -> c:(concatMap amountCommodities $ amounts ma)
-- Just (TotalPrice ma) -> c:(concatMap amountCommodities $ amounts ma)
2010-05-23 00:23:36 +04:00
2012-11-20 01:20:10 +04:00
-- | Get all this journal's (mixed) amounts, in the order parsed.
journalMixedAmounts :: Journal -> [ MixedAmount ]
journalMixedAmounts = map pamount . journalPostings
2010-05-23 00:23:36 +04:00
2012-11-20 01:20:10 +04:00
-- | Get all this journal's component amounts, roughly in the order parsed.
journalAmounts :: Journal -> [ Amount ]
journalAmounts = concatMap flatten . journalMixedAmounts where flatten ( Mixed as ) = as
2008-11-22 23:35:17 +03:00
2014-04-25 01:44:30 +04:00
-- | The fully specified date span enclosing the dates (primary or secondary)
-- of all this journal's transactions and postings, or DateSpan Nothing Nothing
2014-04-25 01:28:20 +04:00
-- if there are none.
2014-04-25 01:44:30 +04:00
journalDateSpan :: Bool -> Journal -> DateSpan
journalDateSpan secondary j
2014-04-25 01:28:20 +04:00
| null ts = DateSpan Nothing Nothing
| otherwise = DateSpan ( Just earliest ) ( Just $ addDays 1 latest )
2009-04-04 15:19:15 +04:00
where
2014-04-25 01:28:20 +04:00
earliest = minimum dates
latest = maximum dates
dates = pdates ++ tdates
2014-04-25 01:44:30 +04:00
tdates = map ( if secondary then transactionDate2 else tdate ) ts
pdates = concatMap ( catMaybes . map ( if secondary then ( Just . postingDate2 ) else pdate ) . tpostings ) ts
2014-04-25 01:28:20 +04:00
ts = jtxns j
-- #ifdef TESTS
test_journalDateSpan = do
" journalDateSpan " ~: do
assertEqual " " ( DateSpan ( Just $ fromGregorian 2014 1 10 ) ( Just $ fromGregorian 2014 10 11 ) )
2014-04-25 01:44:30 +04:00
( journalDateSpan True j )
2014-04-25 01:28:20 +04:00
where
j = nulljournal { jtxns = [ nulltransaction { tdate = parsedate " 2014/02/01 "
, tpostings = [ posting { pdate = Just ( parsedate " 2014/01/10 " ) } ]
}
, nulltransaction { tdate = parsedate " 2014/09/01 "
2014-04-25 01:44:30 +04:00
, tpostings = [ posting { pdate2 = Just ( parsedate " 2014/10/10 " ) } ]
2014-04-25 01:28:20 +04:00
}
] }
-- #endif
2009-05-29 15:31:51 +04:00
2012-04-14 05:12:42 +04:00
-- Misc helpers
2010-07-13 10:30:06 +04:00
-- | Check if a set of hledger account/description filter patterns matches the
2009-05-29 15:31:51 +04:00
-- given account name or entry description. Patterns are case-insensitive
2010-04-14 20:19:01 +04:00
-- regular expressions. Prefixed with not:, they become anti-patterns.
2009-05-29 15:31:51 +04:00
matchpats :: [ String ] -> String -> Bool
matchpats pats str =
( null positives || any match positives ) && ( null negatives || not ( any match negatives ) )
where
( negatives , positives ) = partition isnegativepat pats
match " " = True
2011-06-09 01:52:10 +04:00
match pat = regexMatchesCI ( abspat pat ) str
2010-04-16 03:08:27 +04:00
negateprefix = " not: "
isnegativepat = ( negateprefix ` isPrefixOf ` )
abspat pat = if isnegativepat pat then drop ( length negateprefix ) pat else pat
2009-12-21 08:23:07 +03:00
2011-08-30 15:37:36 +04:00
-- debug helpers
2012-11-20 01:20:10 +04:00
-- traceAmountPrecision a = trace (show $ map (precision . acommodity) $ amounts a) a
-- tracePostingsCommodities ps = trace (show $ map ((map (precision . acommodity) . amounts) . pamount) ps) ps
2011-08-30 15:37:36 +04:00
2012-04-14 05:12:42 +04:00
-- tests
2012-05-27 22:14:20 +04:00
-- A sample journal for testing, similar to data/sample.journal:
--
-- 2008/01/01 income
-- assets:bank:checking $1
-- income:salary
--
-- 2008/06/01 gift
-- assets:bank:checking $1
-- income:gifts
--
-- 2008/06/02 save
-- assets:bank:saving $1
-- assets:bank:checking
--
-- 2008/06/03 * eat & shop
-- expenses:food $1
-- expenses:supplies $1
-- assets:cash
--
-- 2008/12/31 * pay off
-- liabilities:debts $1
-- assets:bank:checking
--
2014-09-11 00:07:53 +04:00
Right samplejournal = journalBalanceTransactions $
2012-11-20 01:20:10 +04:00
nulljournal
{ jtxns = [
2012-05-27 22:14:20 +04:00
txnTieKnot $ Transaction {
2014-08-01 04:32:42 +04:00
tsourcepos = nullsourcepos ,
2012-05-27 22:14:20 +04:00
tdate = parsedate " 2008/01/01 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Nothing ,
2015-05-16 21:51:35 +03:00
tstatus = Uncleared ,
2012-05-27 22:14:20 +04:00
tcode = " " ,
tdescription = " income " ,
tcomment = " " ,
2012-05-28 02:59:06 +04:00
ttags = [] ,
2012-12-06 04:03:07 +04:00
tpostings =
[ " assets:bank:checking " ` post ` usd 1
, " income:salary " ` post ` missingamt
] ,
2012-05-27 22:14:20 +04:00
tpreceding_comment_lines = " "
}
,
txnTieKnot $ Transaction {
2014-08-01 04:32:42 +04:00
tsourcepos = nullsourcepos ,
2012-05-27 22:14:20 +04:00
tdate = parsedate " 2008/06/01 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Nothing ,
2015-05-16 21:51:35 +03:00
tstatus = Uncleared ,
2012-05-27 22:14:20 +04:00
tcode = " " ,
tdescription = " gift " ,
tcomment = " " ,
2012-05-28 02:59:06 +04:00
ttags = [] ,
2012-12-06 04:03:07 +04:00
tpostings =
[ " assets:bank:checking " ` post ` usd 1
, " income:gifts " ` post ` missingamt
] ,
2012-05-27 22:14:20 +04:00
tpreceding_comment_lines = " "
}
,
txnTieKnot $ Transaction {
2014-08-01 04:32:42 +04:00
tsourcepos = nullsourcepos ,
2012-05-27 22:14:20 +04:00
tdate = parsedate " 2008/06/02 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Nothing ,
2015-05-16 21:51:35 +03:00
tstatus = Uncleared ,
2012-05-27 22:14:20 +04:00
tcode = " " ,
tdescription = " save " ,
tcomment = " " ,
2012-05-28 02:59:06 +04:00
ttags = [] ,
2012-12-06 04:03:07 +04:00
tpostings =
[ " assets:bank:saving " ` post ` usd 1
, " assets:bank:checking " ` post ` usd ( - 1 )
] ,
2012-05-27 22:14:20 +04:00
tpreceding_comment_lines = " "
}
,
txnTieKnot $ Transaction {
2014-08-01 04:32:42 +04:00
tsourcepos = nullsourcepos ,
2012-05-27 22:14:20 +04:00
tdate = parsedate " 2008/06/03 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Nothing ,
2015-05-16 21:51:35 +03:00
tstatus = Cleared ,
2012-05-27 22:14:20 +04:00
tcode = " " ,
tdescription = " eat & shop " ,
tcomment = " " ,
2012-05-28 02:59:06 +04:00
ttags = [] ,
2012-12-06 04:03:07 +04:00
tpostings = [ " expenses:food " ` post ` usd 1
, " expenses:supplies " ` post ` usd 1
, " assets:cash " ` post ` missingamt
] ,
2012-05-27 22:14:20 +04:00
tpreceding_comment_lines = " "
}
,
txnTieKnot $ Transaction {
2014-08-01 04:32:42 +04:00
tsourcepos = nullsourcepos ,
2012-05-27 22:14:20 +04:00
tdate = parsedate " 2008/12/31 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Nothing ,
2015-05-16 21:51:35 +03:00
tstatus = Uncleared ,
2012-05-27 22:14:20 +04:00
tcode = " " ,
tdescription = " pay off " ,
tcomment = " " ,
2012-05-28 02:59:06 +04:00
ttags = [] ,
2012-12-06 04:03:07 +04:00
tpostings = [ " liabilities:debts " ` post ` usd 1
, " assets:bank:checking " ` post ` usd ( - 1 )
] ,
2012-05-27 22:14:20 +04:00
tpreceding_comment_lines = " "
}
]
2012-11-20 01:20:10 +04:00
}
2012-05-27 22:14:20 +04:00
tests_Hledger_Data_Journal = TestList $
2012-10-21 21:18:18 +04:00
[
2014-04-25 01:28:20 +04:00
test_journalDateSpan
2012-04-14 05:12:42 +04:00
-- "query standard account types" ~:
-- do
-- let j = journal1
-- journalBalanceSheetAccountNames j `is` ["assets","assets:a","equity","equity:q","equity:q:qq","liabilities","liabilities:l"]
-- journalProfitAndLossAccountNames j `is` ["expenses","expenses:e","income","income:i"]
2012-10-21 21:18:18 +04:00
]