A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
  I'd like to drop account codes, introduced in hledger 1.9 to control
  the display order of accounts. In my experience,
  - they are tedious to maintain
  - they duplicate/compete with the natural tendency to arrange account
    directives to match your mental chart of accounts
  - they duplicate/compete with the tree structure created by account
    names
  and it gets worse if you think about using them more extensively,
  eg to classify accounts by type.
  Instead, I plan to just let the position (parse order) of account
  directives determine the display order of those declared accounts.
  Undeclared accounts will be displayed after declared accounts,
  sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
		
	
			
		
			
				
	
	
		
			119 lines
		
	
	
		
			3.9 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			119 lines
		
	
	
		
			3.9 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-|
 | |
| 
 | |
| A 'Ledger' is derived from a 'Journal' by applying a filter specification
 | |
| to select 'Transaction's and 'Posting's of interest. It contains the
 | |
| filtered journal and knows the resulting chart of accounts, account
 | |
| balances, and postings in each account.
 | |
| 
 | |
| -}
 | |
| 
 | |
| {-# LANGUAGE OverloadedStrings #-}
 | |
| 
 | |
| module Hledger.Data.Ledger (
 | |
|    nullledger
 | |
|   ,ledgerFromJournal
 | |
|   ,ledgerAccountNames
 | |
|   ,ledgerAccount
 | |
|   ,ledgerRootAccount
 | |
|   ,ledgerTopAccounts
 | |
|   ,ledgerLeafAccounts
 | |
|   ,ledgerAccountsMatching
 | |
|   ,ledgerPostings
 | |
|   ,ledgerDateSpan
 | |
|   ,ledgerCommodities
 | |
|   ,tests_Ledger
 | |
| )
 | |
| where
 | |
| 
 | |
| import qualified Data.Map as M
 | |
| -- import Data.Text (Text)
 | |
| import qualified Data.Text as T
 | |
| import Safe (headDef)
 | |
| import Text.Printf
 | |
| 
 | |
| import Hledger.Utils.Test 
 | |
| import Hledger.Data.Types
 | |
| import Hledger.Data.Account
 | |
| import Hledger.Data.Journal
 | |
| import Hledger.Data.Posting
 | |
| import Hledger.Query
 | |
| 
 | |
| 
 | |
| instance Show Ledger where
 | |
|     show l = printf "Ledger with %d transactions, %d accounts\n" --"%s"
 | |
|              (length (jtxns $ ljournal l) +
 | |
|               length (jtxnmodifiers $ ljournal l) +
 | |
|               length (jperiodictxns $ ljournal l))
 | |
|              (length $ ledgerAccountNames l)
 | |
|              -- (showtree $ ledgerAccountNameTree l)
 | |
| 
 | |
| nullledger :: Ledger
 | |
| nullledger = Ledger {
 | |
|   ljournal = nulljournal,
 | |
|   laccounts = []
 | |
|   }
 | |
| 
 | |
| -- | Filter a journal's transactions with the given query, then derive
 | |
| -- a ledger containing the chart of accounts and balances. If the
 | |
| -- query includes a depth limit, that will affect the ledger's
 | |
| -- journal but not the ledger's account tree.
 | |
| ledgerFromJournal :: Query -> Journal -> Ledger
 | |
| ledgerFromJournal q j = nullledger{ljournal=j'', laccounts=as}
 | |
|   where
 | |
|     (q',depthq)  = (filterQuery (not . queryIsDepth) q, filterQuery queryIsDepth q)
 | |
|     j'  = filterJournalAmounts (filterQuery queryIsSym q) $ -- remove amount parts which the query's sym: terms would exclude
 | |
|           filterJournalPostings q' j
 | |
|     as  = accountsFromPostings $ journalPostings j'
 | |
|     j'' = filterJournalPostings depthq j'
 | |
| 
 | |
| -- | List a ledger's account names.
 | |
| ledgerAccountNames :: Ledger -> [AccountName]
 | |
| ledgerAccountNames = drop 1 . map aname . laccounts
 | |
| 
 | |
| -- | Get the named account from a ledger.
 | |
| ledgerAccount :: Ledger -> AccountName -> Maybe Account
 | |
| ledgerAccount l a = lookupAccount a $ laccounts l
 | |
| 
 | |
| -- | Get this ledger's root account, which is a dummy "root" account
 | |
| -- above all others. This should always be first in the account list,
 | |
| -- if somehow not this returns a null account.
 | |
| ledgerRootAccount :: Ledger -> Account
 | |
| ledgerRootAccount = headDef nullacct . laccounts
 | |
| 
 | |
| -- | List a ledger's top-level accounts (the ones below the root), in tree order.
 | |
| ledgerTopAccounts :: Ledger -> [Account]
 | |
| ledgerTopAccounts = asubs . head . laccounts
 | |
| 
 | |
| -- | List a ledger's bottom-level (subaccount-less) accounts, in tree order.
 | |
| ledgerLeafAccounts :: Ledger -> [Account]
 | |
| ledgerLeafAccounts = filter (null.asubs) . laccounts
 | |
| 
 | |
| -- | Accounts in ledger whose name matches the pattern, in tree order.
 | |
| ledgerAccountsMatching :: [String] -> Ledger -> [Account]
 | |
| ledgerAccountsMatching pats = filter (matchpats pats . T.unpack . aname) . laccounts -- XXX pack
 | |
| 
 | |
| -- | List a ledger's postings, in the order parsed.
 | |
| ledgerPostings :: Ledger -> [Posting]
 | |
| ledgerPostings = journalPostings . ljournal
 | |
| 
 | |
| -- | The (fully specified) date span containing all the ledger's (filtered) transactions,
 | |
| -- or DateSpan Nothing Nothing if there are none.
 | |
| ledgerDateSpan :: Ledger -> DateSpan
 | |
| ledgerDateSpan = postingsDateSpan . ledgerPostings
 | |
| 
 | |
| -- | All commodities used in this ledger.
 | |
| ledgerCommodities :: Ledger -> [CommoditySymbol]
 | |
| ledgerCommodities = M.keys . jinferredcommodities . ljournal
 | |
| 
 | |
| -- tests
 | |
| 
 | |
| tests_Ledger = tests "Ledger" [
 | |
| 
 | |
|   tests "ledgerFromJournal" [
 | |
|      (length $ ledgerPostings $ ledgerFromJournal Any nulljournal) `is` 0
 | |
|     ,(length $ ledgerPostings $ ledgerFromJournal Any samplejournal) `is` 13
 | |
|     ,(length $ ledgerPostings $ ledgerFromJournal (Depth 2) samplejournal) `is` 7
 | |
|   ]
 | |
| 
 | |
|  ]
 |