hledger/hledger/Hledger/Cli/Commands/Payees.hs
Stephen Morgan e233f001c5 fix!: utf-8: Use with-utf8 to ensure all files are read and written with utf8 encoding. (#1619)
May also fix #1154, #1033, #708, #536, #73: testing is needed.

This aims to solve all problems where misconfigured locales lead to
parsers failing on utf8-encoded data. This should hopefully avoid
encoding issues, but since it fundamentally alters how encoding is dealt
with it may lead to unexpected outcomes. Widespread testing on a number
of different platforms would be useful.
2022-05-22 13:12:19 +10:00

49 lines
1.7 KiB
Haskell

{-|
The @payees@ command lists all unique payees (description part before a |) seen in transactions, sorted alphabetically.
-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Hledger.Cli.Commands.Payees (
payeesmode
,payees
) where
import qualified Data.Set as S
import qualified Data.Text.IO as TIO (putStrLn) -- Only putStr and friends are safe
import System.Console.CmdArgs.Explicit as C
import Hledger
import Hledger.Cli.CliOptions
-- | Command line options for this command.
payeesmode = hledgerCommandMode
$(embedFileRelative "Hledger/Cli/Commands/Payees.txt")
[flagNone ["declared"] (setboolopt "declared") "show payees declared with payee directives"
,flagNone ["used"] (setboolopt "used") "show payees referenced by transactions"
]
[generalflagsgroup1]
hiddenflags
([], Just $ argsFlag "[QUERY]")
-- | The payees command.
payees :: CliOpts -> Journal -> IO ()
payees CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query}} j = do
let
declared = boolopt "declared" rawopts
used = boolopt "used" rawopts
-- XXX matchesPayee is currently an alias for matchesDescription, not sure if it matters
matcheddeclaredpayees = S.fromList . filter (matchesPayeeWIP query) $ journalPayeesDeclared j
matchedusedpayees = S.fromList . map transactionPayee $ filter (matchesTransaction query) $ jtxns j
payees =
if | declared && not used -> matcheddeclaredpayees
| not declared && used -> matchedusedpayees
| otherwise -> matcheddeclaredpayees <> matchedusedpayees
mapM_ TIO.putStrLn payees