2021-01-29 15:34:18 +03:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2014-03-20 04:11:48 +04:00
|
|
|
{-|
|
|
|
|
|
2019-05-24 07:43:53 +03:00
|
|
|
An account-centric transactions report.
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
2019-05-24 07:43:53 +03:00
|
|
|
module Hledger.Reports.AccountTransactionsReport (
|
2015-08-20 21:05:42 +03:00
|
|
|
AccountTransactionsReport,
|
|
|
|
AccountTransactionsReportItem,
|
2014-03-20 04:11:48 +04:00
|
|
|
accountTransactionsReport,
|
2019-05-24 07:43:53 +03:00
|
|
|
accountTransactionsReportItems,
|
2018-09-04 22:23:07 +03:00
|
|
|
transactionRegisterDate,
|
2021-06-23 05:00:59 +03:00
|
|
|
triOrigTransaction,
|
|
|
|
triDate,
|
|
|
|
triAmount,
|
|
|
|
triBalance,
|
|
|
|
triCommodityAmount,
|
|
|
|
triCommodityBalance,
|
|
|
|
accountTransactionsReportByCommodity,
|
2019-05-24 07:43:53 +03:00
|
|
|
tests_AccountTransactionsReport
|
2014-03-20 04:11:48 +04:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2021-08-02 06:59:20 +03:00
|
|
|
import Data.List (mapAccumR, nub, partition, sortBy)
|
2021-06-23 05:00:59 +03:00
|
|
|
import Data.List.Extra (nubSort)
|
2021-05-13 12:00:43 +03:00
|
|
|
import Data.Maybe (catMaybes)
|
2021-08-02 06:59:20 +03:00
|
|
|
import Data.Ord (Down(..), comparing)
|
2020-10-27 12:00:12 +03:00
|
|
|
import Data.Text (Text)
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
import qualified Data.Text as T
|
2021-08-04 04:46:31 +03:00
|
|
|
import Data.Time.Calendar (Day)
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
import Hledger.Data
|
|
|
|
import Hledger.Query
|
|
|
|
import Hledger.Reports.ReportOptions
|
2018-09-04 22:23:07 +03:00
|
|
|
import Hledger.Utils
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
|
2014-07-18 03:20:34 +04:00
|
|
|
-- | An account transactions report represents transactions affecting
|
|
|
|
-- a particular account (or possibly several accounts, but we don't
|
2020-07-11 07:52:02 +03:00
|
|
|
-- use that). It is used eg by hledger-ui's and hledger-web's register
|
|
|
|
-- view, and hledger's aregister report, where we want to show one row
|
|
|
|
-- per transaction, in the context of the current account. Report
|
|
|
|
-- items consist of:
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - the transaction, unmodified
|
|
|
|
--
|
|
|
|
-- - the transaction as seen in the context of the current account and query,
|
|
|
|
-- which means:
|
|
|
|
--
|
2021-07-30 22:09:31 +03:00
|
|
|
-- - the transaction date is set to the "transaction context date":
|
|
|
|
-- the earliest of the transaction date and any other posting dates
|
|
|
|
-- of postings to the current account (matched by the report query).
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - the transaction's postings are filtered, excluding any which are not
|
|
|
|
-- matched by the report query
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - a text description of the other account(s) posted to/from
|
|
|
|
--
|
|
|
|
-- - a flag indicating whether there's more than one other account involved
|
|
|
|
--
|
|
|
|
-- - the total increase/decrease to the current account
|
2014-07-18 03:20:34 +04:00
|
|
|
--
|
2016-08-13 03:26:34 +03:00
|
|
|
-- - the report transactions' running total after this transaction;
|
2016-09-06 18:43:25 +03:00
|
|
|
-- or if historical balance is requested (-H), the historical running total.
|
|
|
|
-- The historical running total includes transactions from before the
|
|
|
|
-- report start date if one is specified, filtered by the report query.
|
|
|
|
-- The historical running total may or may not be the account's historical
|
|
|
|
-- running balance, depending on the report query.
|
2016-07-27 22:07:48 +03:00
|
|
|
--
|
2016-09-06 18:43:25 +03:00
|
|
|
-- Items are sorted by transaction register date (the earliest date the transaction
|
|
|
|
-- posts to the current account), most recent first.
|
2016-07-27 22:07:48 +03:00
|
|
|
-- Reporting intervals are currently ignored.
|
2014-07-18 03:20:34 +04:00
|
|
|
--
|
2020-10-27 12:02:47 +03:00
|
|
|
type AccountTransactionsReport = [AccountTransactionsReportItem] -- line items, one per transaction
|
2014-07-18 03:20:34 +04:00
|
|
|
|
|
|
|
type AccountTransactionsReportItem =
|
|
|
|
(
|
2016-07-27 22:07:48 +03:00
|
|
|
Transaction -- the transaction, unmodified
|
|
|
|
,Transaction -- the transaction, as seen from the current account
|
|
|
|
,Bool -- is this a split (more than one posting to other accounts) ?
|
2020-10-27 12:00:12 +03:00
|
|
|
,Text -- a display string describing the other account(s), if any
|
2014-07-18 03:20:34 +04:00
|
|
|
,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
|
2016-07-27 22:07:48 +03:00
|
|
|
,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
|
2014-07-18 03:20:34 +04:00
|
|
|
)
|
|
|
|
|
2021-06-23 05:00:59 +03:00
|
|
|
triOrigTransaction (torig,_,_,_,_,_) = torig
|
|
|
|
triDate (_,tacct,_,_,_,_) = tdate tacct
|
|
|
|
triAmount (_,_,_,_,a,_) = a
|
|
|
|
triBalance (_,_,_,_,_,a) = a
|
|
|
|
triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
|
|
|
|
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
|
|
|
|
|
lib!: lib,cli,ui,web: For accountTransactionsReport, generate the overall
reportq from the ReportSpec, rather than being supplied as a separate
option.
This is the same approach used by the other reports, e.g. EntryReport,
PostingReport, MultiBalanceReport. This reduces code duplication, as
previously the reportq had to be separately tweaked in each of 5
different places.
If you call accountTransactionreport, there is no need to separately
derive the report query.
2021-06-23 05:48:02 +03:00
|
|
|
accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
|
2021-07-23 09:47:48 +03:00
|
|
|
accountTransactionsReport rspec@ReportSpec{_rsReportOpts=ropts} j thisacctq = items
|
2016-06-02 17:03:00 +03:00
|
|
|
where
|
2021-08-02 06:59:20 +03:00
|
|
|
-- A depth limit should not affect the account transactions report; it should show all transactions in/below this account.
|
|
|
|
-- Queries on currency or amount are also ignored at this stage; they are handled earlier, before valuation.
|
2021-08-04 04:46:31 +03:00
|
|
|
reportq = simplifyQuery $ And [aregisterq, periodq]
|
lib!: lib,cli,ui,web: For accountTransactionsReport, generate the overall
reportq from the ReportSpec, rather than being supplied as a separate
option.
This is the same approach used by the other reports, e.g. EntryReport,
PostingReport, MultiBalanceReport. This reduces code duplication, as
previously the reportq had to be separately tweaked in each of 5
different places.
If you call accountTransactionreport, there is no need to separately
derive the report query.
2021-06-23 05:48:02 +03:00
|
|
|
where
|
2021-08-02 06:59:20 +03:00
|
|
|
aregisterq = filterQuery (not . queryIsCurOrAmt) . filterQuery (not . queryIsDepth) $ _rsQuery rspec
|
lib!: lib,cli,ui,web: For accountTransactionsReport, generate the overall
reportq from the ReportSpec, rather than being supplied as a separate
option.
This is the same approach used by the other reports, e.g. EntryReport,
PostingReport, MultiBalanceReport. This reduces code duplication, as
previously the reportq had to be separately tweaked in each of 5
different places.
If you call accountTransactionreport, there is no need to separately
derive the report query.
2021-06-23 05:48:02 +03:00
|
|
|
periodq = Date . periodAsDateSpan $ period_ ropts
|
2021-08-02 06:59:20 +03:00
|
|
|
amtq = filterQuery queryIsCurOrAmt $ _rsQuery rspec
|
|
|
|
queryIsCurOrAmt q = queryIsSym q || queryIsAmt q
|
|
|
|
|
|
|
|
-- Note that within this functions, we are only allowed limited
|
|
|
|
-- transformation of the transaction postings: this is due to the need to
|
|
|
|
-- pass the original transactions into accountTransactionsReportItem.
|
|
|
|
-- Generally, we either include a transaction in full, or not at all.
|
|
|
|
-- Do some limited filtering and valuing of the journal's transactions:
|
|
|
|
-- - filter them by the account query if any,
|
|
|
|
-- - discard amounts not matched by the currency and amount query if any,
|
|
|
|
-- - then apply valuation if any.
|
|
|
|
acctJournal =
|
|
|
|
ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
|
|
|
|
-- maybe convert these transactions to cost or value
|
|
|
|
. journalApplyValuationFromOpts rspec
|
|
|
|
. ptraceAtWith 5 (("ts2:\n"++).pshowTransactions.jtxns)
|
|
|
|
-- apply any cur:SYM filters in reportq
|
|
|
|
. (if queryIsNull amtq then id else filterJournalAmounts amtq)
|
|
|
|
-- only consider transactions which match thisacctq (possibly excluding postings
|
|
|
|
-- which are not real or have the wrong status)
|
|
|
|
. traceAt 3 ("thisacctq: "++show thisacctq)
|
|
|
|
$ ptraceAtWith 5 (("ts1:\n"++).pshowTransactions.jtxns)
|
|
|
|
j{jtxns = filter (matchesTransaction thisacctq . relevantPostings) $ jtxns j}
|
|
|
|
where
|
|
|
|
relevantPostings
|
|
|
|
| queryIsNull realq && queryIsNull statusq = id
|
|
|
|
| otherwise = filterTransactionPostings . simplifyQuery $ And [realq, statusq]
|
|
|
|
realq = filterQuery queryIsReal reportq
|
|
|
|
statusq = filterQuery queryIsStatus reportq
|
2016-06-02 17:03:00 +03:00
|
|
|
|
2020-10-27 12:02:47 +03:00
|
|
|
startbal
|
2021-07-15 02:28:43 +03:00
|
|
|
| balanceaccum_ ropts == Historical = sumPostings priorps
|
2021-08-01 09:06:13 +03:00
|
|
|
| otherwise = nullmixedamt
|
2016-08-13 03:26:34 +03:00
|
|
|
where
|
2021-08-02 06:59:20 +03:00
|
|
|
priorps = dbg5 "priorps" . journalPostings $ filterJournalPostings priorq acctJournal
|
2021-08-01 09:06:13 +03:00
|
|
|
priorq = dbg5 "priorq" $ And [thisacctq, tostartdateq, datelessreportq]
|
2016-09-06 18:43:25 +03:00
|
|
|
tostartdateq =
|
2016-09-06 00:44:16 +03:00
|
|
|
case mstartdate of
|
|
|
|
Just _ -> Date (DateSpan Nothing mstartdate)
|
2016-09-06 18:43:25 +03:00
|
|
|
Nothing -> None -- no start date specified, there are no prior postings
|
lib!: lib,cli,ui,web: For accountTransactionsReport, generate the overall
reportq from the ReportSpec, rather than being supplied as a separate
option.
This is the same approach used by the other reports, e.g. EntryReport,
PostingReport, MultiBalanceReport. This reduces code duplication, as
previously the reportq had to be separately tweaked in each of 5
different places.
If you call accountTransactionreport, there is no need to separately
derive the report query.
2021-06-23 05:48:02 +03:00
|
|
|
mstartdate = queryStartDate (date2_ ropts) reportq
|
|
|
|
datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq
|
2016-06-02 17:03:00 +03:00
|
|
|
|
2021-08-02 06:59:20 +03:00
|
|
|
items =
|
|
|
|
accountTransactionsReportItems reportq thisacctq startbal maNegate
|
2021-08-06 09:30:23 +03:00
|
|
|
-- sort by the transaction's register date, then index, for accurate starting balance
|
2021-08-02 06:59:20 +03:00
|
|
|
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.map snd)
|
2021-08-06 09:30:23 +03:00
|
|
|
. sortBy (comparing (Down . fst) <> comparing (Down . tindex . snd))
|
2021-08-02 06:59:20 +03:00
|
|
|
. map (\t -> (transactionRegisterDate reportq thisacctq t, t))
|
|
|
|
$ jtxns acctJournal
|
2014-07-18 03:20:34 +04:00
|
|
|
|
2020-05-25 02:13:30 +03:00
|
|
|
pshowTransactions :: [Transaction] -> String
|
|
|
|
pshowTransactions = pshow . map (\t -> unwords [show $ tdate t, T.unpack $ tdescription t])
|
|
|
|
|
2014-03-20 04:11:48 +04:00
|
|
|
-- | Generate transactions report items from a list of transactions,
|
2016-06-02 17:03:00 +03:00
|
|
|
-- using the provided user-specified report query, a query specifying
|
2021-08-02 06:59:20 +03:00
|
|
|
-- which account to use as the focus, a starting balance, and a sign-setting
|
|
|
|
-- function.
|
|
|
|
-- Each transaction is accompanied by the date that should be shown for it
|
|
|
|
-- in the report, which is not necessarily the transaction date; it is
|
|
|
|
-- the earliest of the posting dates which match both thisacctq and reportq,
|
|
|
|
-- otherwise the transaction's date if there are no matching postings.
|
|
|
|
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount)
|
|
|
|
-> [(Day, Transaction)] -> [AccountTransactionsReportItem]
|
2019-06-09 18:26:26 +03:00
|
|
|
accountTransactionsReportItems reportq thisacctq bal signfn =
|
2021-08-02 06:59:20 +03:00
|
|
|
catMaybes . snd . mapAccumR (accountTransactionsReportItem reportq thisacctq signfn) bal
|
2019-06-09 18:26:26 +03:00
|
|
|
|
2021-08-02 06:59:20 +03:00
|
|
|
accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount
|
|
|
|
-> (Day, Transaction) -> (MixedAmount, Maybe AccountTransactionsReportItem)
|
|
|
|
accountTransactionsReportItem reportq thisacctq signfn bal (d, torig)
|
2016-06-02 17:03:00 +03:00
|
|
|
-- 201407: I've lost my grip on this, let's just hope for the best
|
|
|
|
-- 201606: we now calculate change and balance from filtered postings, check this still works well for all callers XXX
|
2021-08-02 06:59:20 +03:00
|
|
|
| null reportps = (bal, Nothing) -- no matched postings in this transaction, skip it
|
|
|
|
| otherwise = (b, Just (torig, tacct{tdate=d}, numotheraccts > 1, otheracctstr, a, b))
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
2021-08-02 06:59:20 +03:00
|
|
|
tacct@Transaction{tpostings=reportps} = filterTransactionPostings reportq torig
|
|
|
|
(thisacctps, otheracctps) = partition (matchesPosting thisacctq) reportps
|
|
|
|
numotheraccts = length $ nub $ map paccount otheracctps
|
|
|
|
otheracctstr | thisacctq == None = summarisePostingAccounts reportps -- no current account ? summarise all matched postings
|
|
|
|
| numotheraccts == 0 = summarisePostingAccounts thisacctps -- only postings to current account ? summarise those
|
|
|
|
| otherwise = summarisePostingAccounts otheracctps -- summarise matched postings to other account(s)
|
|
|
|
a = signfn . maNegate $ sumPostings thisacctps
|
|
|
|
b = bal `maPlus` a
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2016-07-27 22:07:48 +03:00
|
|
|
-- | What is the transaction's date in the context of a particular account
|
|
|
|
-- (specified with a query) and report query, as in an account register ?
|
|
|
|
-- It's normally the transaction's general date, but if any posting(s)
|
|
|
|
-- matched by the report query and affecting the matched account(s) have
|
|
|
|
-- their own earlier dates, it's the earliest of these dates.
|
|
|
|
-- Secondary transaction/posting dates are ignored.
|
|
|
|
transactionRegisterDate :: Query -> Query -> Transaction -> Day
|
|
|
|
transactionRegisterDate reportq thisacctq t
|
|
|
|
| null thisacctps = tdate t
|
|
|
|
| otherwise = minimum $ map postingDate thisacctps
|
|
|
|
where
|
|
|
|
reportps = tpostings $ filterTransactionPostings reportq t
|
|
|
|
thisacctps = filter (matchesPosting thisacctq) reportps
|
|
|
|
|
2014-06-13 03:21:26 +04:00
|
|
|
-- -- | Generate a short readable summary of some postings, like
|
|
|
|
-- -- "from (negatives) to (positives)".
|
|
|
|
-- summarisePostings :: [Posting] -> String
|
|
|
|
-- summarisePostings ps =
|
|
|
|
-- case (summarisePostingAccounts froms, summarisePostingAccounts tos) of
|
|
|
|
-- ("",t) -> "to "++t
|
|
|
|
-- (f,"") -> "from "++f
|
|
|
|
-- (f,t) -> "from "++f++" to "++t
|
|
|
|
-- where
|
|
|
|
-- (froms,tos) = partition (fromMaybe False . isNegativeMixedAmount . pamount) ps
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- | Generate a simplified summary of some postings' accounts.
|
2015-08-28 21:58:57 +03:00
|
|
|
-- To reduce noise, if there are both real and virtual postings, show only the real ones.
|
2020-10-27 12:00:12 +03:00
|
|
|
summarisePostingAccounts :: [Posting] -> Text
|
2015-08-28 21:58:57 +03:00
|
|
|
summarisePostingAccounts ps =
|
2020-10-27 12:00:12 +03:00
|
|
|
T.intercalate ", " . map accountSummarisedName . nub $ map paccount displayps
|
2015-08-28 21:58:57 +03:00
|
|
|
where
|
|
|
|
realps = filter isReal ps
|
|
|
|
displayps | null realps = ps
|
|
|
|
| otherwise = realps
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2021-06-23 05:00:59 +03:00
|
|
|
-- | Split an account transactions report whose items may involve several commodities,
|
|
|
|
-- into one or more single-commodity account transactions reports.
|
|
|
|
accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)]
|
|
|
|
accountTransactionsReportByCommodity tr =
|
|
|
|
[(c, filterAccountTransactionsReportByCommodity c tr) | c <- commodities tr]
|
|
|
|
where
|
|
|
|
commodities = nubSort . map acommodity . concatMap (amounts . triAmount)
|
|
|
|
|
|
|
|
-- | Remove account transaction report items and item amount (and running
|
|
|
|
-- balance amount) components that don't involve the specified
|
|
|
|
-- commodity. Other item fields such as the transaction are left unchanged.
|
|
|
|
filterAccountTransactionsReportByCommodity :: CommoditySymbol -> AccountTransactionsReport -> AccountTransactionsReport
|
|
|
|
filterAccountTransactionsReportByCommodity c =
|
|
|
|
fixTransactionsReportItemBalances . concatMap (filterTransactionsReportItemByCommodity c)
|
|
|
|
where
|
|
|
|
filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal)
|
|
|
|
| c `elem` cs = [item']
|
|
|
|
| otherwise = []
|
|
|
|
where
|
|
|
|
cs = map acommodity $ amounts a
|
|
|
|
item' = (t,t2,s,o,a',bal)
|
|
|
|
a' = filterMixedAmountByCommodity c a
|
|
|
|
|
|
|
|
fixTransactionsReportItemBalances [] = []
|
|
|
|
fixTransactionsReportItemBalances [i] = [i]
|
|
|
|
fixTransactionsReportItemBalances items = reverse $ i:(go startbal is)
|
|
|
|
where
|
|
|
|
i:is = reverse items
|
|
|
|
startbal = filterMixedAmountByCommodity c $ triBalance i
|
|
|
|
go _ [] = []
|
|
|
|
go bal ((t,t2,s,o,amt,_):is) = (t,t2,s,o,amt,bal'):go bal' is
|
|
|
|
where bal' = bal `maPlus` amt
|
|
|
|
|
2018-09-04 22:23:07 +03:00
|
|
|
-- tests
|
|
|
|
|
2021-08-30 08:23:23 +03:00
|
|
|
tests_AccountTransactionsReport = testGroup "AccountTransactionsReport" [
|
2018-09-04 22:23:07 +03:00
|
|
|
]
|