{-|

The @accounts@ command lists account names:

- in flat mode (default), it lists the full names of accounts posted to by matched postings,
  clipped to the specified depth, possibly with leading components dropped.

- in tree mode, it shows the indented short names of accounts posted to by matched postings,
  and their parents, to the specified depth.

-}

{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}

module Hledger.Cli.Commands.Accounts (
  accountsmode
 ,accounts
) where

import Data.List
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.Console.CmdArgs.Explicit as C

import Hledger
import Hledger.Cli.CliOptions
import Control.Monad (forM_)
import Data.Maybe (fromMaybe)
import Safe (headDef)


-- | Command line options for this command.
accountsmode :: Mode RawOpts
accountsmode = CommandDoc
-> [Flag RawOpts]
-> [(CommandDoc, [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Accounts.txt")
  (
  [[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"used",CommandDoc
"u"]     (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"used")       CommandDoc
"show only accounts used by transactions"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"declared",CommandDoc
"d"] (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"declared")   CommandDoc
"show only accounts declared by account directive"  -- no s to avoid line wrap
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"unused"]       (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"unused")     CommandDoc
"show only accounts declared but not used"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"undeclared"]   (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"undeclared") CommandDoc
"show only accounts used but not declared"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"types"]        (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"types")      CommandDoc
"also show account types when known"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"positions"]    (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"positions")  CommandDoc
"also show where accounts were declared"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"directives"]   (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"directives") CommandDoc
"show as account directives, for use in journals"
  ,[CommandDoc] -> (RawOpts -> RawOpts) -> CommandDoc -> Flag RawOpts
forall a. [CommandDoc] -> (a -> a) -> CommandDoc -> Flag a
flagNone [CommandDoc
"find"]         (CommandDoc -> RawOpts -> RawOpts
setboolopt CommandDoc
"find")       CommandDoc
"find the first account matched by the first argument (a case-insensitive infix regexp or account name)"
  ]
  [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++ Bool -> [Flag RawOpts]
flattreeflags Bool
False [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++
  [[CommandDoc]
-> Update RawOpts -> CommandDoc -> CommandDoc -> Flag RawOpts
forall a.
[CommandDoc] -> Update a -> CommandDoc -> CommandDoc -> Flag a
flagReq  [CommandDoc
"drop"] (\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
"drop" CommandDoc
s RawOpts
opts) CommandDoc
"N" CommandDoc
"flat mode: omit N leading account name parts"]
  )
  [(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]")

-- | The accounts command.
accounts :: CliOpts -> Journal -> IO ()
accounts :: CliOpts -> Journal -> IO ()
accounts CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts, reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query,_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts}} Journal
j = do

  -- 1. identify the accounts we'll show
  let tree :: Bool
tree     = ReportOpts -> Bool
tree_ ReportOpts
ropts
      used :: Bool
used = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"used"     RawOpts
rawopts
      decl :: Bool
decl = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"declared" RawOpts
rawopts
      unused :: Bool
unused = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"unused" RawOpts
rawopts
      undecl :: Bool
undecl = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"undeclared" RawOpts
rawopts
      find_ :: Bool
find_ = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"find" RawOpts
rawopts
      types :: Bool
types = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"types"    RawOpts
rawopts
      positions :: Bool
positions = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"positions" RawOpts
rawopts
      directives :: Bool
directives = CommandDoc -> RawOpts -> Bool
boolopt CommandDoc
"directives" RawOpts
rawopts
      -- a depth limit will clip and exclude account names later, but we don't want to exclude accounts at this stage
      nodepthq :: Query
nodepthq = CommandDoc -> Query -> Query
forall a. Show a => CommandDoc -> a -> a
dbg4 CommandDoc
"nodepthq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDepth) Query
query
      -- just the acct: part of the query will be reapplied later, after clipping
      acctq :: Query
acctq = CommandDoc -> Query -> Query
forall a. Show a => CommandDoc -> a -> a
dbg4 CommandDoc
"acctq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsAcct Query
query
      dep :: Maybe Int
dep = CommandDoc -> Maybe Int -> Maybe Int
forall a. Show a => CommandDoc -> a -> a
dbg4 CommandDoc
"depth" (Maybe Int -> Maybe Int) -> Maybe Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Query -> Maybe Int
queryDepth (Query -> Maybe Int) -> Query -> Maybe Int
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDepth Query
query
      matcheddeclaredaccts :: [Text]
matcheddeclaredaccts = CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"matcheddeclaredaccts" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
        [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
        (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Maybe AccountType)
-> (Text -> [Tag]) -> Query -> Text -> Bool
matchesAccountExtra (Journal -> Text -> Maybe AccountType
journalAccountType Journal
j) (Journal -> Text -> [Tag]
journalInheritedAccountTags Journal
j) Query
nodepthq) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
        ((Text, AccountDeclarationInfo) -> Text)
-> [(Text, AccountDeclarationInfo)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, AccountDeclarationInfo) -> Text
forall a b. (a, b) -> a
fst ([(Text, AccountDeclarationInfo)] -> [Text])
-> [(Text, AccountDeclarationInfo)] -> [Text]
forall a b. (a -> b) -> a -> b
$ Journal -> [(Text, AccountDeclarationInfo)]
jdeclaredaccounts Journal
j
      matchedusedaccts :: [Text]
matchedusedaccts = CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"matchedusedaccts" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Posting -> Text) -> [Posting] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Text
paccount ([Posting] -> [Text]) -> [Posting] -> [Text]
forall a b. (a -> b) -> a -> b
$ Journal -> [Posting]
journalPostings (Journal -> [Posting]) -> Journal -> [Posting]
forall a b. (a -> b) -> a -> b
$ Query -> Journal -> Journal
filterJournalPostings Query
nodepthq Journal
j
      matchedunusedaccts :: [Text]
matchedunusedaccts = CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"matchedunusedaccts" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text]
matcheddeclaredaccts [Text] -> [Text] -> [Text]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Text]
matchedusedaccts
      matchedundeclaredaccts :: [Text]
matchedundeclaredaccts = CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"matchedundeclaredaccts" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text]
matchedusedaccts [Text] -> [Text] -> [Text]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Text]
matcheddeclaredaccts
      -- keep synced with aregister
      matchedacct :: Text
matchedacct = CommandDoc -> Text -> Text
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"matchedacct" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
        Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (CommandDoc -> Text
forall a. CommandDoc -> a
error' (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ CommandDoc -> CommandDoc
forall a. Show a => a -> CommandDoc
show CommandDoc
apat CommandDoc -> CommandDoc -> CommandDoc
forall a. [a] -> [a] -> [a]
++ CommandDoc
" did not match any account.")   -- PARTIAL:
            (Maybe Text -> Text) -> ([Text] -> Maybe Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Maybe Text
firstMatch ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Journal -> [Text]
journalAccountNamesDeclaredOrImplied Journal
j
        where
          firstMatch :: [Text] -> Maybe Text
firstMatch = case Text -> Either CommandDoc Regexp
toRegexCI (Text -> Either CommandDoc Regexp)
-> Text -> Either CommandDoc Regexp
forall a b. (a -> b) -> a -> b
$ CommandDoc -> Text
T.pack CommandDoc
apat of
              Right Regexp
re -> (Text -> Bool) -> [Text] -> Maybe Text
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Regexp -> Text -> Bool
regexMatchText Regexp
re)
              Left  CommandDoc
_  -> Maybe Text -> [Text] -> Maybe Text
forall a b. a -> b -> a
const Maybe Text
forall a. Maybe a
Nothing
          apat :: CommandDoc
apat = CommandDoc -> [CommandDoc] -> CommandDoc
forall a. a -> [a] -> a
headDef
            (CommandDoc -> CommandDoc
forall a. CommandDoc -> a
error' CommandDoc
"With --find, please provide an account name or\naccount pattern (case-insensitive, infix, regexp) as first command argument.")
            ([CommandDoc] -> CommandDoc) -> [CommandDoc] -> CommandDoc
forall a b. (a -> b) -> a -> b
$ CommandDoc -> RawOpts -> [CommandDoc]
listofstringopt CommandDoc
"args" RawOpts
rawopts

      accts :: [Text]
accts = CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg5 CommandDoc
"accts to show" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ if
        | Bool -> Bool
not Bool
decl Bool -> Bool -> Bool
&& Bool
used     -> [Text]
matchedusedaccts
        | Bool
decl     Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
used -> [Text]
matcheddeclaredaccts
        | Bool
unused               -> [Text]
matchedunusedaccts
        | Bool
undecl               -> [Text]
matchedundeclaredaccts
        | Bool
find_                -> [Text
matchedacct]
        | Bool
otherwise            -> [Text]
matcheddeclaredaccts [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
matchedusedaccts

  -- 2. sort them by declaration order (then undeclared accounts alphabetically)
  -- within each group of siblings
      sortedaccts :: [Text]
sortedaccts = Journal -> Bool -> [Text] -> [Text]
sortAccountNamesByDeclaration Journal
j Bool
tree [Text]
accts

  -- 3. if there's a depth limit, depth-clip and remove any no longer useful items
      clippedaccts :: [Text]
clippedaccts =
        CommandDoc -> [Text] -> [Text]
forall a. Show a => CommandDoc -> a -> a
dbg4 CommandDoc
"clippedaccts" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
        (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Text -> Bool
matchesAccount Query
acctq) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$  -- clipping can leave accounts that no longer match the query, remove such
        [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$                            -- clipping can leave duplicates (adjacent, hopefully)
        (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$          -- depth:0 can leave nulls
        (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> Text -> Text
clipAccountName Maybe Int
dep) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$      -- clip at depth if specified
        [Text]
sortedaccts

  -- 4. print what remains as a list or tree, maybe applying --drop in the former case.
  -- Add various bits of info if enabled.
  let
    showKeyword :: Text
showKeyword = if Bool
directives then Text
"account " else Text
""
    -- some contortions here to show types nicely aligned
    showName :: Text -> Text
showName Text
a = case ReportOpts -> AccountListMode
accountlistmode_ ReportOpts
ropts of
      AccountListMode
ALTree -> Text
indent Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
accountLeafName Text
droppedName
      AccountListMode
ALFlat -> Text
droppedName
      where
        indent :: Text
indent      = Int -> Text -> Text
T.replicate (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Text -> Int
accountNameLevel Text
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- ReportOpts -> Int
drop_ ReportOpts
ropts) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) Text
" "
        droppedName :: Text
droppedName = Int -> Text -> Text
accountNameDrop (ReportOpts -> Int
drop_ ReportOpts
ropts) Text
a
    showType :: Text -> Text
showType Text
a 
      | Bool
types     = Text -> Text
pad Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"    ; type: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (AccountType -> Text) -> Maybe AccountType -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (CommandDoc -> Text
T.pack (CommandDoc -> Text)
-> (AccountType -> CommandDoc) -> AccountType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountType -> CommandDoc
forall a. Show a => a -> CommandDoc
show) (Journal -> Text -> Maybe AccountType
journalAccountType Journal
j Text
a)
      | Bool
otherwise = Text
""
    showAcctDeclOrder :: Text -> Text
showAcctDeclOrder Text
a
      | Bool
positions =
        (if Bool
types then Text
"," else Text -> Text
pad Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"    ;") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
        case Text
-> [(Text, AccountDeclarationInfo)] -> Maybe AccountDeclarationInfo
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
a ([(Text, AccountDeclarationInfo)] -> Maybe AccountDeclarationInfo)
-> [(Text, AccountDeclarationInfo)] -> Maybe AccountDeclarationInfo
forall a b. (a -> b) -> a -> b
$ Journal -> [(Text, AccountDeclarationInfo)]
jdeclaredaccounts Journal
j of
          Just AccountDeclarationInfo
adi ->
            Text
" declared at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (CommandDoc -> Text
T.pack (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ SourcePos -> CommandDoc
sourcePosPretty (SourcePos -> CommandDoc) -> SourcePos -> CommandDoc
forall a b. (a -> b) -> a -> b
$ AccountDeclarationInfo -> SourcePos
adisourcepos AccountDeclarationInfo
adi) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>  -- TODO: hide the column number
            Text
", overall declaration order " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (CommandDoc -> Text
T.pack (CommandDoc -> Text) -> CommandDoc -> Text
forall a b. (a -> b) -> a -> b
$ Int -> CommandDoc
forall a. Show a => a -> CommandDoc
show (Int -> CommandDoc) -> Int -> CommandDoc
forall a b. (a -> b) -> a -> b
$ AccountDeclarationInfo -> Int
adideclarationorder AccountDeclarationInfo
adi)
          Maybe AccountDeclarationInfo
Nothing -> Text
" undeclared"
      | Bool
otherwise = Text
""
    pad :: Text -> Text
pad Text
a = Int -> Text -> Text
T.replicate (Int
maxwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length (Text -> Text
showName Text
a)) Text
" "
    maxwidth :: Int
maxwidth = [Int] -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Int
T.length (Text -> Int) -> (Text -> Text) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
showName) [Text]
clippedaccts

  [Text] -> (Text -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Text]
clippedaccts ((Text -> IO ()) -> IO ()) -> (Text -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Text
a -> Text -> IO ()
T.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
showKeyword Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
showName Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
showType Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
showAcctDeclOrder Text
a