{-|

A ledger-compatible @print@ command.

-}

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}

module Hledger.Cli.Commands.Print (
  printmode
 ,print'
 -- ,entriesReportAsText
 ,originalTransaction
)
where

import Data.Text (Text)
import Data.List (intersperse)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Lens.Micro (_Just, has)
import System.Console.CmdArgs.Explicit

import Hledger
import Hledger.Read.CsvReader (CSV, printCSV)
import Hledger.Cli.CliOptions
import Hledger.Cli.Utils


printmode :: Mode RawOpts
printmode = CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Print.txt")
  ([let arg :: CommandDoc
arg = CommandDoc
"STR" in
   [CommandDoc]
-> Update RawOpts -> CommandDoc -> CommandDoc -> Flag RawOpts
forall a.
[CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagReq  [CommandDoc
"match",CommandDoc
"m"] (\CommandDoc
s RawOpts
opts -> RawOpts -> Either CommandDoc RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either CommandDoc RawOpts)
-> RawOpts -> Either CommandDoc RawOpts
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc -> RawOpts -> RawOpts
setopt CommandDoc
"match" CommandDoc
s RawOpts
opts) CommandDoc
arg
    (CommandDoc
"show the transaction whose description is most similar to "CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++CommandDoc
argCommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++CommandDoc
", and is most recent")
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"explicit",CommandDoc
"x"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"explicit")
    CommandDoc
"show all amounts explicitly"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"new"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"new")
    CommandDoc
"show only newer-dated transactions added in each file since last run"
  ,[CommandDoc] -> Flag RawOpts
outputFormatFlag [CommandDoc
"txt",CommandDoc
"csv",CommandDoc
"json",CommandDoc
"sql"]
  ,Flag RawOpts
outputFileFlag
  ])
  [(CommandDoc, [Flag RawOpts])
generalflagsgroup1]
  [Flag RawOpts]
hiddenflags
  ([], Arg RawOpts -> Maybe (Arg RawOpts)
forall a. a -> Maybe a
Just (Arg RawOpts -> Maybe (Arg RawOpts))
-> Arg RawOpts -> Maybe (Arg RawOpts)
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Arg RawOpts
argsFlag CommandDoc
"[QUERY]")

-- | Print journal transactions in standard format.
print' :: CliOpts -> Journal -> IO ()
print' :: CliOpts -> Journal -> IO ()
print' CliOpts
opts Journal
j = do
  -- The print command should show all amounts with their original decimal places,
  -- but as part of journal reading the posting amounts have already been normalised
  -- according to commodity display styles, and currently it's not easy to avoid
  -- that. For now we try to reverse it by increasing all amounts' decimal places 
  -- sufficiently to show the amount exactly. The displayed amounts may have minor
  -- differences from the originals, such as trailing zeroes added.
  let j' :: Journal
j' = (MixedAmount -> MixedAmount) -> Journal -> Journal
journalMapPostingAmounts MixedAmount -> MixedAmount
mixedAmountSetFullPrecision Journal
j
  case CommandDoc -> RawOpts -> Maybe CommandDoc
maybestringopt CommandDoc
"match" (RawOpts -> Maybe CommandDoc) -> RawOpts -> Maybe CommandDoc
forall a b. (a -> b) -> a -> b
$ CliOpts -> RawOpts
rawopts_ CliOpts
opts of
    Maybe CommandDoc
Nothing   -> CliOpts -> Journal -> IO ()
printEntries CliOpts
opts Journal
j'
    Just CommandDoc
desc -> CliOpts -> Journal -> Text -> IO ()
printMatch CliOpts
opts Journal
j' (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Text
T.pack (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc -> CommandDoc
forall a. Show a => CommandDoc -> a -> a
dbg1 CommandDoc
"finding best match for description" CommandDoc
desc

printEntries :: CliOpts -> Journal -> IO ()
printEntries :: CliOpts -> Journal -> IO ()
printEntries opts :: CliOpts
opts@CliOpts{reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec
rspec} Journal
j =
    CliOpts -> Text -> IO ()
writeOutputLazyText CliOpts
opts (Text -> IO ())
-> (EntriesReport -> Text) -> EntriesReport -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntriesReport -> Text
render (EntriesReport -> IO ()) -> EntriesReport -> IO ()
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> EntriesReport
entriesReport ReportSpec
rspec Journal
j
  where
    fmt :: CommandDoc
fmt = CliOpts -> CommandDoc
outputFormatFromOpts CliOpts
opts
    render :: EntriesReport -> Text
render | CommandDoc
fmtCommandDoc -> CommandDoc -> Bool
forall a. Eq a => a -> a -> Bool
==CommandDoc
"txt"  = CliOpts -> EntriesReport -> Text
entriesReportAsText CliOpts
opts
           | CommandDoc
fmtCommandDoc -> CommandDoc -> Bool
forall a. Eq a => a -> a -> Bool
==CommandDoc
"csv"  = CSV -> Text
printCSV (CSV -> Text) -> (EntriesReport -> CSV) -> EntriesReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntriesReport -> CSV
entriesReportAsCsv
           | CommandDoc
fmtCommandDoc -> CommandDoc -> Bool
forall a. Eq a => a -> a -> Bool
==CommandDoc
"json" = EntriesReport -> Text
forall a. ToJSON a => a -> Text
toJsonText
           | CommandDoc
fmtCommandDoc -> CommandDoc -> Bool
forall a. Eq a => a -> a -> Bool
==CommandDoc
"sql"  = EntriesReport -> Text
entriesReportAsSql
           | Bool
otherwise   = CommandDoc -> EntriesReport -> Text
forall a. CommandDoc -> a
error' (CommandDoc -> EntriesReport -> Text)
-> CommandDoc -> EntriesReport -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
unsupportedOutputFormatError CommandDoc
fmt  -- PARTIAL:

entriesReportAsText :: CliOpts -> EntriesReport -> TL.Text
entriesReportAsText :: CliOpts -> EntriesReport -> Text
entriesReportAsText CliOpts
opts = Builder -> Text
TB.toLazyText (Builder -> Text)
-> (EntriesReport -> Builder) -> EntriesReport -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> Builder) -> EntriesReport -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text -> Builder
TB.fromText (Text -> Builder)
-> (Transaction -> Text) -> Transaction -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
showTransaction (Transaction -> Text)
-> (Transaction -> Transaction) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Transaction
whichtxn)
  where
    whichtxn :: Transaction -> Transaction
whichtxn
      -- With -x, use the fully-inferred txn with all amounts & txn prices explicit.
      | CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"explicit" (CliOpts -> RawOpts
rawopts_ CliOpts
opts) = Transaction -> Transaction
forall a. a -> a
id
      -- Or also, if any of -B/-V/-X/--value are active.
      -- Because of #551, and because of print -V valuing only one
      -- posting when there's an implicit txn price.
      -- So -B/-V/-X/--value implies -x. Is this ok ?
      | Getting Any CliOpts ValuationType -> CliOpts -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe ValuationType -> Const Any (Maybe ValuationType))
-> CliOpts -> Const Any CliOpts
forall c. HasReportOptsNoUpdate c => Lens' c (Maybe ValuationType)
value ((Maybe ValuationType -> Const Any (Maybe ValuationType))
 -> CliOpts -> Const Any CliOpts)
-> ((ValuationType -> Const Any ValuationType)
    -> Maybe ValuationType -> Const Any (Maybe ValuationType))
-> Getting Any CliOpts ValuationType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValuationType -> Const Any ValuationType)
-> Maybe ValuationType -> Const Any (Maybe ValuationType)
forall a a'. Traversal (Maybe a) (Maybe a') a a'
_Just) CliOpts
opts = Transaction -> Transaction
forall a. a -> a
id
      -- By default, use the original as-written-in-the-journal txn.
      | Bool
otherwise = Transaction -> Transaction
originalTransaction

-- Replace this transaction's postings with the original postings if any, but keep the
-- current possibly rewritten account names, and the inferred values of any auto postings
originalTransaction :: Transaction -> Transaction
originalTransaction Transaction
t = Transaction
t { tpostings :: [Posting]
tpostings = (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
originalPostingPreservingAccount ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t }

-- Get the original posting if any, but keep the current possibly rewritten account name, and
-- the inferred values of any auto postings
originalPostingPreservingAccount :: Posting -> Posting
originalPostingPreservingAccount Posting
p = Posting
orig
    { paccount :: Text
paccount = Posting -> Text
paccount Posting
p
    , pamount :: MixedAmount
pamount = Posting -> MixedAmount
pamount (Posting -> MixedAmount) -> Posting -> MixedAmount
forall a b. (a -> b) -> a -> b
$ if Bool
isGenerated then Posting
p else Posting
orig }
  where
    orig :: Posting
orig = Posting -> Posting
originalPosting Posting
p
    isGenerated :: Bool
isGenerated = Text
"generated-posting" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text) -> Text
forall a b. (a, b) -> a
fst (Posting -> [(Text, Text)]
ptags Posting
p)

-- XXX
-- tests_showTransactions = [
--   "showTransactions" ~: do

--    -- "print expenses" ~:
--    do
--     let opts = defreportopts{query_="expenses"}
--     d <- getCurrentDay
--     showTransactions opts (queryFromOpts d opts) samplejournal `is` unlines
--      ["2008/06/03 * eat & shop"
--      ,"    expenses:food                $1"
--      ,"    expenses:supplies            $1"
--      ,"    assets:cash                 $-2"
--      ,""
--      ]

--   -- , "print report with depth arg" ~:
--    do
--     let opts = defreportopts{depth_=Just 2}
--     d <- getCurrentDay
--     showTransactions opts (queryFromOpts d opts) samplejournal `is` unlines
--       ["2008/01/01 income"
--       ,"    assets:bank:checking            $1"
--       ,"    income:salary                  $-1"
--       ,""
--       ,"2008/06/01 gift"
--       ,"    assets:bank:checking            $1"
--       ,"    income:gifts                   $-1"
--       ,""
--       ,"2008/06/03 * eat & shop"
--       ,"    expenses:food                $1"
--       ,"    expenses:supplies            $1"
--       ,"    assets:cash                 $-2"
--       ,""
--       ,"2008/12/31 * pay off"
--       ,"    liabilities:debts               $1"
--       ,"    assets:bank:checking           $-1"
--       ,""
--       ]
--  ]

entriesReportAsSql :: EntriesReport -> TL.Text
entriesReportAsSql :: EntriesReport -> Text
entriesReportAsSql EntriesReport
txns = Builder -> Text
TB.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$ [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat
    [ Text -> Builder
TB.fromText Text
"create table if not exists postings(id serial,txnidx int,date1 date,date2 date,status text,code text,description text,comment text,account text,amount numeric,commodity text,credit numeric,debit numeric,posting_status text,posting_comment text);\n"
    , Text -> Builder
TB.fromText Text
"insert into postings(txnidx,date1,date2,status,code,description,comment,account,amount,commodity,credit,debit,posting_status,posting_comment) values\n"
    , [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Builder)
-> ([Builder] -> [Builder]) -> [Builder] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
intersperse (Text -> Builder
TB.fromText Text
",") ([Builder] -> Builder) -> [Builder] -> Builder
forall a b. (a -> b) -> a -> b
$ ([Text] -> Builder) -> CSV -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map [Text] -> Builder
values CSV
csv
    , Text -> Builder
TB.fromText Text
";\n"
    ]
  where
    values :: [Text] -> Builder
values [Text]
vs = Text -> Builder
TB.fromText Text
"(" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat (Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
intersperse (Text -> Builder
TB.fromText Text
",") ([Builder] -> [Builder]) -> [Builder] -> [Builder]
forall a b. (a -> b) -> a -> b
$ (Text -> Builder) -> [Text] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Builder
toSql [Text]
vs) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TB.fromText Text
")\n"
    toSql :: Text -> Builder
toSql Text
"" = Text -> Builder
TB.fromText Text
"NULL"
    toSql Text
s  = Text -> Builder
TB.fromText Text
"'" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TB.fromText (Text -> Text -> Text -> Text
T.replace Text
"'" Text
"''" Text
s) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TB.fromText Text
"'"
    csv :: CSV
csv = (Transaction -> CSV) -> EntriesReport -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Transaction -> CSV
transactionToCSV (Transaction -> CSV)
-> (Transaction -> Transaction) -> Transaction -> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MixedAmount -> MixedAmount) -> Transaction -> Transaction
transactionMapPostingAmounts ((Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount Amount -> Amount
setDecimalPoint)) EntriesReport
txns
      where
        setDecimalPoint :: Amount -> Amount
setDecimalPoint Amount
a = Amount
a{astyle :: AmountStyle
astyle=(Amount -> AmountStyle
astyle Amount
a){asdecimalpoint :: Maybe Char
asdecimalpoint=Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'.'}}

entriesReportAsCsv :: EntriesReport -> CSV
entriesReportAsCsv :: EntriesReport -> CSV
entriesReportAsCsv EntriesReport
txns =
  [Text
"txnidx",Text
"date",Text
"date2",Text
"status",Text
"code",Text
"description",Text
"comment",Text
"account",Text
"amount",Text
"commodity",Text
"credit",Text
"debit",Text
"posting-status",Text
"posting-comment"] [Text] -> CSV -> CSV
forall a. a -> [a] -> [a]
:
  (Transaction -> CSV) -> EntriesReport -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Transaction -> CSV
transactionToCSV EntriesReport
txns

-- | Generate one CSV record per posting, duplicating the common transaction fields.
-- The txnidx field (transaction index) allows postings to be grouped back into transactions.
transactionToCSV :: Transaction -> CSV
transactionToCSV :: Transaction -> CSV
transactionToCSV Transaction
t =
  ([Text] -> [Text]) -> CSV -> CSV
forall a b. (a -> b) -> [a] -> [b]
map (\[Text]
p -> CommandDoc -> Text
T.pack (Integer -> CommandDoc
forall a. Show a => a -> CommandDoc
show Integer
idx)Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
dateText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
date2Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
statusText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
codeText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
descriptionText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:Text
commentText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
p)
   ((Posting -> CSV) -> [Posting] -> CSV
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Posting -> CSV
postingToCSV ([Posting] -> CSV) -> [Posting] -> CSV
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t)
  where
    idx :: Integer
idx = Transaction -> Integer
tindex Transaction
t
    description :: Text
description = Transaction -> Text
tdescription Transaction
t
    date :: Text
date = Day -> Text
showDate (Transaction -> Day
tdate Transaction
t)
    date2 :: Text
date2 = Text -> (Day -> Text) -> Maybe Day -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" Day -> Text
showDate (Maybe Day -> Text) -> Maybe Day -> Text
forall a b. (a -> b) -> a -> b
$ Transaction -> Maybe Day
tdate2 Transaction
t
    status :: Text
status = CommandDoc -> Text
T.pack (CommandDoc -> Text) -> (Status -> CommandDoc) -> Status -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> CommandDoc
forall a. Show a => a -> CommandDoc
show (Status -> Text) -> Status -> Text
forall a b. (a -> b) -> a -> b
$ Transaction -> Status
tstatus Transaction
t
    code :: Text
code = Transaction -> Text
tcode Transaction
t
    comment :: Text
comment = Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
tcomment Transaction
t

postingToCSV :: Posting -> CSV
postingToCSV :: Posting -> CSV
postingToCSV Posting
p =
  (Amount -> [Text]) -> [Amount] -> CSV
forall a b. (a -> b) -> [a] -> [b]
map (\(a :: Amount
a@(Amount {aquantity :: Amount -> Quantity
aquantity=Quantity
q,acommodity :: Amount -> Text
acommodity=Text
c})) ->
    -- commodity goes into separate column, so we suppress it, along with digit group
    -- separators and prices
    let a_ :: Amount
a_ = Amount
a{acommodity :: Text
acommodity=Text
"",astyle :: AmountStyle
astyle=(Amount -> AmountStyle
astyle Amount
a){asdigitgroups :: Maybe DigitGroupStyle
asdigitgroups=Maybe DigitGroupStyle
forall a. Maybe a
Nothing},aprice :: Maybe AmountPrice
aprice=Maybe AmountPrice
forall a. Maybe a
Nothing} in
    let showamt :: Amount -> Text
showamt = WideBuilder -> Text
wbToText (WideBuilder -> Text) -> (Amount -> WideBuilder) -> Amount -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts -> Amount -> WideBuilder
showAmountB AmountDisplayOpts
noColour in
    let amount :: Text
amount = Amount -> Text
showamt Amount
a_ in
    let credit :: Text
credit = if Quantity
q Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
< Quantity
0 then Amount -> Text
showamt (Amount -> Text) -> Amount -> Text
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
forall a. Num a => a -> a
negate Amount
a_ else Text
"" in
    let debit :: Text
debit  = if Quantity
q Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
>= Quantity
0 then Amount -> Text
showamt Amount
a_ else Text
"" in
    [Text
account, Text
amount, Text
c, Text
credit, Text
debit, Text
status, Text
comment])
    ([Amount] -> CSV)
-> (MixedAmount -> [Amount]) -> MixedAmount -> CSV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> [Amount]
amounts (MixedAmount -> CSV) -> MixedAmount -> CSV
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
  where
    status :: Text
status = CommandDoc -> Text
T.pack (CommandDoc -> Text) -> (Status -> CommandDoc) -> Status -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> CommandDoc
forall a. Show a => a -> CommandDoc
show (Status -> Text) -> Status -> Text
forall a b. (a -> b) -> a -> b
$ Posting -> Status
pstatus Posting
p
    account :: Text
account = Maybe Int -> PostingType -> Text -> Text
showAccountName Maybe Int
forall a. Maybe a
Nothing (Posting -> PostingType
ptype Posting
p) (Posting -> Text
paccount Posting
p)
    comment :: Text
comment = Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Posting -> Text
pcomment Posting
p

-- --match

-- | Print the transaction most closely and recently matching a description
-- (and the query, if any).
printMatch :: CliOpts -> Journal -> Text -> IO ()
printMatch :: CliOpts -> Journal -> Text -> IO ()
printMatch CliOpts
opts Journal
j Text
desc = do
  case CliOpts -> Journal -> Text -> Maybe Transaction
journalSimilarTransaction CliOpts
opts Journal
j Text
desc of
    Maybe Transaction
Nothing -> CommandDoc -> IO ()
putStrLn CommandDoc
"no matches found."
    Just Transaction
t  -> Text -> IO ()
T.putStr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
showTransaction Transaction
t