pkg!: Remove Hledger.Utils.Tree module.

This very small module was only used in Hledger.Data.Account, so the
code was moved into that module instead.
This commit is contained in:
Stephen Morgan 2021-08-29 00:15:54 +10:00 committed by Simon Michael
parent 1ed06f3bc8
commit f1994d5aa8
5 changed files with 20 additions and 36 deletions

View File

@ -13,18 +13,16 @@ module Hledger.Data.Account
where where
import qualified Data.HashSet as HS import qualified Data.HashSet as HS
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.List (find, sortOn) import Data.List (find, foldl', sortOn)
import Data.List.Extra (groupOn) import Data.List.Extra (groupOn)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Ord (Down(..)) import Data.Ord (Down(..))
import Safe (headMay) import Safe (headMay)
import Text.Printf import Text.Printf (printf)
import Hledger.Data.AccountName import Hledger.Data.AccountName (expandAccountName, clipOrEllipsifyAccountName)
import Hledger.Data.Amount import Hledger.Data.Amount
import Hledger.Data.Posting ()
import Hledger.Data.Types import Hledger.Data.Types
import Hledger.Utils
-- deriving instance Show Account -- deriving instance Show Account
@ -91,6 +89,22 @@ accountTree rootname as = nullacct{aname=rootname, asubs=map (uncurry accountTre
,asubs=map (uncurry accountTree') $ M.assocs m ,asubs=map (uncurry accountTree') $ M.assocs m
} }
-- | An efficient-to-build tree suggested by Cale Gibbard, probably
-- better than accountNameTreeFrom.
newtype FastTree a = T (M.Map a (FastTree a))
deriving (Show, Eq, Ord)
mergeTrees :: (Ord a) => FastTree a -> FastTree a -> FastTree a
mergeTrees (T m) (T m') = T (M.unionWith mergeTrees m m')
treeFromPath :: [a] -> FastTree a
treeFromPath [] = T M.empty
treeFromPath (x:xs) = T (M.singleton x (treeFromPath xs))
treeFromPaths :: (Ord a) => [[a]] -> FastTree a
treeFromPaths = foldl' mergeTrees (T M.empty) . map treeFromPath
-- | Tie the knot so all subaccounts' parents are set correctly. -- | Tie the knot so all subaccounts' parents are set correctly.
tieAccountParents :: Account -> Account tieAccountParents :: Account -> Account
tieAccountParents = tie Nothing tieAccountParents = tie Nothing

View File

@ -25,7 +25,6 @@ module Hledger.Utils (---- provide these frequently used modules - or not, for c
module Hledger.Utils.Text, module Hledger.Utils.Text,
module Hledger.Utils.Test, module Hledger.Utils.Test,
module Hledger.Utils.Color, module Hledger.Utils.Color,
module Hledger.Utils.Tree,
-- Debug.Trace.trace, -- Debug.Trace.trace,
-- module Data.PPrint, -- module Data.PPrint,
-- the rest need to be done in each module I think -- the rest need to be done in each module I think
@ -60,7 +59,6 @@ import Hledger.Utils.String
import Hledger.Utils.Text import Hledger.Utils.Text
import Hledger.Utils.Test import Hledger.Utils.Test
import Hledger.Utils.Color import Hledger.Utils.Color
import Hledger.Utils.Tree
-- tuples -- tuples

View File

@ -1,26 +0,0 @@
module Hledger.Utils.Tree
( FastTree(..)
, treeFromPaths
) where
-- import Data.Char
import Data.List (foldl')
import qualified Data.Map as M
-- | An efficient-to-build tree suggested by Cale Gibbard, probably
-- better than accountNameTreeFrom.
newtype FastTree a = T (M.Map a (FastTree a))
deriving (Show, Eq, Ord)
emptyTree :: FastTree a
emptyTree = T M.empty
mergeTrees :: (Ord a) => FastTree a -> FastTree a -> FastTree a
mergeTrees (T m) (T m') = T (M.unionWith mergeTrees m m')
treeFromPath :: [a] -> FastTree a
treeFromPath [] = T M.empty
treeFromPath (x:xs) = T (M.singleton x (treeFromPath xs))
treeFromPaths :: (Ord a) => [[a]] -> FastTree a
treeFromPaths = foldl' mergeTrees emptyTree . map treeFromPath

View File

@ -85,7 +85,6 @@ library
Hledger.Utils.String Hledger.Utils.String
Hledger.Utils.Test Hledger.Utils.Test
Hledger.Utils.Text Hledger.Utils.Text
Hledger.Utils.Tree
Text.Tabular.AsciiWide Text.Tabular.AsciiWide
other-modules: other-modules:
Text.Megaparsec.Custom Text.Megaparsec.Custom

View File

@ -137,7 +137,6 @@ library:
- Hledger.Utils.String - Hledger.Utils.String
- Hledger.Utils.Test - Hledger.Utils.Test
- Hledger.Utils.Text - Hledger.Utils.Text
- Hledger.Utils.Tree
- Text.Tabular.AsciiWide - Text.Tabular.AsciiWide
# other-modules: # other-modules:
# - Ledger.Parser.Text # - Ledger.Parser.Text