module Hledger.Cli.Accounts (
  accountsmode
 ,accounts
 ,tests_Hledger_Cli_Accounts
) where
import Data.List
import Data.Monoid
import qualified Data.Text as T
import System.Console.CmdArgs.Explicit as C
import Test.HUnit
import Hledger
import Prelude hiding (putStrLn)
import Hledger.Utils.UTF8IOCompat (putStrLn)
import Hledger.Cli.CliOptions
accountsmode = (defCommandMode $ ["accounts"] ++ aliases) {
  modeHelp = "show account names" `withAliases` aliases
 ,modeHelpSuffix = [
    "This command lists the accounts referenced by matched postings (and in tree mode, their parents as well). The accounts can be depth-clipped (--depth N) or have their leading parts trimmed (--drop N)."
   ]
 ,modeGroupFlags = C.Group {
     groupUnnamed = [
      flagNone ["tree"] (\opts -> setboolopt "tree" opts) "show short account names, as a tree"
     ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show full account names, as a list (default)"
     ,flagReq  ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts"
     ]
    ,groupHidden = []
    ,groupNamed = [generalflagsgroup1]
    }
 }
  where aliases = []
accounts :: CliOpts -> Journal -> IO ()
accounts CliOpts{reportopts_=ropts} j = do
  d <- getCurrentDay
  let q = queryFromOpts d ropts
      nodepthq = dbg1 "nodepthq" $ filterQuery (not . queryIsDepth) q
      depth    = dbg1 "depth" $ queryDepth $ filterQuery queryIsDepth q
      ps = dbg1 "ps" $ journalPostings $ filterJournalPostings nodepthq j
      as = dbg1 "as" $ nub $ filter (not . T.null) $ map (clipAccountName depth) $ sort $ map paccount ps
      as' | tree_ ropts = expandAccountNames as
          | otherwise   = as
      render a | tree_ ropts = T.replicate (2 * (accountNameLevel a  1)) " " <> accountLeafName a
               | otherwise   = maybeAccountNameDrop ropts a
  mapM_ (putStrLn . T.unpack . render) as'
tests_Hledger_Cli_Accounts = TestList []