module Penny.Cabin.Balance.Util
( tieredForest
, tieredPostings
, filterForest
, balances
, flatten
, treeWithParents
, forestWithParents
, sumForest
, sumTree
, boxesBalance
, labelLevels
, sortForest
, sortTree
, lastMode
) where
import qualified Penny.Cabin.Options as CO
import qualified Penny.Lincoln as L
import qualified Penny.Steel.NestedMap as NM
import qualified Data.Foldable as Fdbl
import qualified Data.Map as M
import Data.Ord (comparing)
import Data.List (sortBy, maximumBy, groupBy)
import Data.Monoid (mconcat, Monoid)
import Data.Maybe (mapMaybe)
import qualified Data.Tree as T
import qualified Penny.Lincoln.Queries as Q
tieredForest ::
Ord k
=> (a -> [k])
-> [a]
-> T.Forest (k, [a])
tieredForest getKeys ls = fmap (fmap revSnd) . NM.toForest $ nm
where
revSnd (a, xs) = (a, reverse xs)
nm = foldr f NM.empty ls
f a m = NM.relabel m ps
where
ps = case getKeys a of
[] -> []
ks ->
let mkInitPair k = (k, maybe [] id)
mkLastPair k = (k, maybe [a] (a:))
in (map mkInitPair . init $ ks)
++ [(mkLastPair (last ks))]
tieredPostings
:: [(a, L.Posting)]
-> T.Forest (L.SubAccount, [(a, L.Posting)])
tieredPostings = tieredForest e
where
e = Fdbl.toList . L.unAccount . Q.account . snd
filterForest :: (a -> Bool) -> T.Forest a -> T.Forest a
filterForest f = mapMaybe pruneTree
where
pruneTree (T.Node a fs) =
case filterForest f fs of
[] -> if not (f a) then Nothing else Just (T.Node a [])
cs -> Just (T.Node a cs)
balances ::
CO.ShowZeroBalances
-> [(a, L.Posting)]
-> T.Forest (L.SubAccount, L.Balance)
balances (CO.ShowZeroBalances szb) =
remover
. map (fmap (mapSnd boxesBalance))
. tieredPostings
where
remover =
if szb
then id
else filterForest (not . M.null . L.unBalance . snd)
. map (fmap (mapSnd L.removeZeroCommodities))
flatten
:: T.Forest (L.SubAccount, L.Balance)
-> [(L.Account, L.Balance)]
flatten =
concatMap T.flatten
. map (fmap toPair) . forestWithParents
where
toPair ((s, b), ls) =
case reverse . map fst $ ls of
[] -> (L.Account [s], b)
s1:sr -> (L.Account (s1 : (sr ++ [s])), b)
treeWithParents :: T.Tree a -> T.Tree (a, [a])
treeWithParents = treeWithParentsR []
treeWithParentsR :: [a] -> T.Tree a -> T.Tree (a, [a])
treeWithParentsR ls (T.Node n cs) = T.Node (n, ls) cs'
where
cs' = map (treeWithParentsR (n:ls)) cs
forestWithParents :: T.Forest a -> T.Forest (a, [a])
forestWithParents = map (treeWithParentsR [])
sumForest ::
s
-> (s -> s -> s)
-> T.Forest (a, s)
-> (T.Forest (a, s), s)
sumForest z f ts = (ts', s)
where
ts' = map (sumTree z f) ts
s = foldr f z . map (snd . T.rootLabel) $ ts'
sumTree ::
s
-> (s -> s -> s)
-> T.Tree (a, s)
-> T.Tree (a, s)
sumTree z f (T.Node (a, s) cs) = T.Node (a, f s cSum) cs'
where
(cs', cSum) = sumForest z f cs
boxesBalance :: [(a, L.Posting)] -> L.Balance
boxesBalance = mconcat . map L.entryToBalance . map Q.entry
. map snd
mapSnd :: (a -> b) -> (f, a) -> (f, b)
mapSnd f (x, a) = (x, f a)
labelLevels :: T.Tree a -> T.Tree (Int, a)
labelLevels = go 0
where
go l (T.Node x xs) = T.Node (l, x) (map (go (l + 1)) xs)
sortForest ::
(a -> a -> Ordering)
-> T.Forest a
-> T.Forest a
sortForest o f = sortBy o' (map (sortTree o) f)
where
o' x y = o (T.rootLabel x) (T.rootLabel y)
sortTree ::
(a -> a -> Ordering)
-> T.Tree a
-> T.Tree a
sortTree o (T.Node l f) = T.Node l (sortForest o f)
lastMode :: Ord a => [a] -> Maybe a
lastMode = lastModeBy compare
lastModeBy ::
(a -> a -> Ordering)
-> [a]
-> Maybe a
lastModeBy o ls =
case modesBy o' ls' of
[] -> Nothing
ms -> Just . fst . maximumBy fx $ ms
where
fx = comparing snd
ls' = zip ls ([0..] :: [Int])
o' x y = o (fst x) (fst y)
modesBy :: (a -> a -> Ordering) -> [a] -> [a]
modesBy o =
concat
. longestLists
. groupBy (\x y -> o x y == EQ)
. sortBy o
longestLists :: [[a]] -> [[a]]
longestLists as =
let lengths = map (\ls -> (ls, length ls)) as
maxLen = maximum . map snd $ lengths
in map fst . filter (\(_, len) -> len == maxLen) $ lengths