{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
module Hledger.Data.Account
where
import Data.List
import Data.List.Extra (groupSort, groupOn)
import Data.Maybe
import Data.Ord
import qualified Data.Map as M
import Data.Text (pack,unpack)
import Safe (headMay, lookupJustDef)
import Text.Printf
import Hledger.Data.AccountName
import Hledger.Data.Amount
import Hledger.Data.Posting()
import Hledger.Data.Types
import Hledger.Utils
instance Show Account where
show Account{..} = printf "Account %s (boring:%s, postings:%d, ebalance:%s, ibalance:%s)"
(pack $ regexReplace ":" "_" $ unpack aname)
(if aboring then "y" else "n" :: String)
anumpostings
(showMixedAmount aebalance)
(showMixedAmount aibalance)
instance Eq Account where
(==) a b = aname a == aname b
nullacct = Account
{ aname = ""
, adeclarationorder = Nothing
, aparent = Nothing
, asubs = []
, anumpostings = 0
, aebalance = nullmixedamt
, aibalance = nullmixedamt
, aboring = False
}
accountsFromPostings :: [Posting] -> [Account]
accountsFromPostings ps =
let
grouped = groupSort [(paccount p,pamount p) | p <- ps]
counted = [(aname, length amts) | (aname, amts) <- grouped]
summed = [(aname, sumStrict amts) | (aname, amts) <- grouped]
acctstree = accountTree "root" $ map fst summed
acctswithnumps = mapAccounts setnumps acctstree where setnumps a = a{anumpostings=fromMaybe 0 $ lookup (aname a) counted}
acctswithebals = mapAccounts setebalance acctswithnumps where setebalance a = a{aebalance=lookupJustDef nullmixedamt (aname a) summed}
acctswithibals = sumAccounts acctswithebals
acctswithparents = tieAccountParents acctswithibals
acctsflattened = flattenAccounts acctswithparents
in
acctsflattened
accountTree :: AccountName -> [AccountName] -> Account
accountTree rootname as = nullacct{aname=rootname, asubs=map (uncurry accountTree') $ M.assocs m }
where
T m = treeFromPaths $ map expandAccountName as :: FastTree AccountName
accountTree' a (T m) = nullacct{aname=a, asubs=map (uncurry accountTree') $ M.assocs m}
tieAccountParents :: Account -> Account
tieAccountParents = tie Nothing
where
tie parent a@Account{..} = a'
where
a' = a{aparent=parent, asubs=map (tie (Just a')) asubs}
parentAccounts :: Account -> [Account]
parentAccounts Account{aparent=Nothing} = []
parentAccounts Account{aparent=Just a} = a:parentAccounts a
accountsLevels :: Account -> [[Account]]
accountsLevels = takeWhile (not . null) . iterate (concatMap asubs) . (:[])
mapAccounts :: (Account -> Account) -> Account -> Account
mapAccounts f a = f a{asubs = map (mapAccounts f) $ asubs a}
anyAccounts :: (Account -> Bool) -> Account -> Bool
anyAccounts p a
| p a = True
| otherwise = any (anyAccounts p) $ asubs a
sumAccounts :: Account -> Account
sumAccounts a
| null $ asubs a = a{aibalance=aebalance a}
| otherwise = a{aibalance=ibal, asubs=subs}
where
subs = map sumAccounts $ asubs a
ibal = sum $ aebalance a : map aibalance subs
clipAccounts :: Int -> Account -> Account
clipAccounts 0 a = a{asubs=[]}
clipAccounts d a = a{asubs=subs}
where
subs = map (clipAccounts (d-1)) $ asubs a
clipAccountsAndAggregate :: Int -> [Account] -> [Account]
clipAccountsAndAggregate d as = combined
where
clipped = [a{aname=clipOrEllipsifyAccountName d $ aname a} | a <- as]
combined = [a{aebalance=sum (map aebalance same)}
| same@(a:_) <- groupOn aname clipped]
pruneAccounts :: (Account -> Bool) -> Account -> Maybe Account
pruneAccounts p = headMay . prune
where
prune a
| null prunedsubs = if p a then [] else [a']
| otherwise = [a']
where
prunedsubs = concatMap prune $ asubs a
a' = a{asubs=prunedsubs}
flattenAccounts :: Account -> [Account]
flattenAccounts a = squish a []
where squish a as = a : Prelude.foldr squish as (asubs a)
filterAccounts :: (Account -> Bool) -> Account -> [Account]
filterAccounts p a
| p a = a : concatMap (filterAccounts p) (asubs a)
| otherwise = concatMap (filterAccounts p) (asubs a)
sortAccountTreeByAmount :: NormalSign -> Account -> Account
sortAccountTreeByAmount normalsign a
| null $ asubs a = a
| otherwise = a{asubs=
sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . aibalance)) $
map (sortAccountTreeByAmount normalsign) $ asubs a}
where
maybeflip | normalsign==NormallyNegative = id
| otherwise = flip
accountSetDeclarationOrder :: Journal -> Account -> Account
accountSetDeclarationOrder j a@Account{..} =
a{adeclarationorder = findIndex (==aname) (jdeclaredaccounts j)}
sortAccountNamesByDeclaration :: Journal -> Bool -> [AccountName] -> [AccountName]
sortAccountNamesByDeclaration j keepparents as =
(if keepparents then id else filter (`elem` as)) $
map aname $
drop 1 $
flattenAccounts $
sortAccountTreeByDeclaration $
mapAccounts (accountSetDeclarationOrder j) $
accountTree "root"
as
sortAccountTreeByDeclaration :: Account -> Account
sortAccountTreeByDeclaration a
| null $ asubs a = a
| otherwise = a{asubs=
sortBy (comparing accountDeclarationOrderAndName) $
map sortAccountTreeByDeclaration $ asubs a
}
accountDeclarationOrderAndName a = (adeclarationorder', aname a)
where
adeclarationorder' = fromMaybe maxBound (adeclarationorder a)
lookupAccount :: AccountName -> [Account] -> Maybe Account
lookupAccount a = find ((==a).aname)
printAccounts :: Account -> IO ()
printAccounts = putStrLn . showAccounts
showAccounts = unlines . map showAccountDebug . flattenAccounts
showAccountsBoringFlag = unlines . map (show . aboring) . flattenAccounts
showAccountDebug a = printf "%-25s %4s %4s %s"
(aname a)
(showMixedAmount $ aebalance a)
(showMixedAmount $ aibalance a)
(if aboring a then "b" else " " :: String)