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

module Hledger.Cli.Commands.Close (
  closemode
 ,close
)
where

import Control.Monad (when)
import Data.Function (on)
import Data.List (groupBy)
import Data.Maybe
import qualified Data.Text as T (pack)
import Data.Time.Calendar
import System.Console.CmdArgs.Explicit as C

import Hledger
import Hledger.Cli.CliOptions

defclosingdesc :: [Char]
defclosingdesc = [Char]
"closing balances"
defopeningdesc :: [Char]
defopeningdesc = [Char]
"opening balances"
defclosingacct :: [Char]
defclosingacct = [Char]
"equity:opening/closing balances"
defopeningacct :: [Char]
defopeningacct = [Char]
defclosingacct

closemode :: Mode RawOpts
closemode = [Char]
-> [Flag RawOpts]
-> [([Char], [Flag RawOpts])]
-> [Flag RawOpts]
-> ([Arg RawOpts], Maybe (Arg RawOpts))
-> Mode RawOpts
hledgerCommandMode
  $(embedFileRelative "Hledger/Cli/Commands/Close.txt")
  [[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"close"]        ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"close") [Char]
"show just closing transaction"
  ,[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"open"]         ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"open") [Char]
"show just opening transaction"
  ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-desc"]   (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"close-desc" [Char]
s RawOpts
opts) [Char]
"DESC" ([Char]
"description for closing transaction (default: "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
defclosingdesc[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
")")
  ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-desc"]    (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"open-desc"  [Char]
s RawOpts
opts) [Char]
"DESC" ([Char]
"description for opening transaction (default: "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
defopeningdesc[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
")")
  ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-acct"]   (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"close-acct" [Char]
s RawOpts
opts) [Char]
"ACCT" ([Char]
"account to transfer closing balances to (default: "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
defclosingacct[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
")")
  ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-acct"]    (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"open-acct"  [Char]
s RawOpts
opts) [Char]
"ACCT" ([Char]
"account to transfer opening balances from (default: "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
defopeningacct[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
")")
  ,[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"explicit",[Char]
"x"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"explicit") [Char]
"show all amounts explicitly"
  ,[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"interleaved"]  ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"interleaved") [Char]
"keep equity and non-equity postings adjacent"
  ,[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"show-costs"]   ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"show-costs") [Char]
"keep balances with different costs separate"
  ]
  [([Char], [Flag RawOpts])
generalflagsgroup1]
  ([Flag RawOpts]
hiddenflags [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. [a] -> [a] -> [a]
++
    -- old close flags for compatibility, hidden
    [[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"closing"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"close") [Char]
"old spelling of --close"
    ,[[Char]] -> (RawOpts -> RawOpts) -> [Char] -> Flag RawOpts
forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"opening"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"open") [Char]
"old spelling of --open"
    ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-to"]  (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"close-acct" [Char]
s RawOpts
opts) [Char]
"ACCT" ([Char]
"old spelling of --close-acct")
    ,[[Char]] -> Update RawOpts -> [Char] -> [Char] -> Flag RawOpts
forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-from"] (\[Char]
s RawOpts
opts -> RawOpts -> Either [Char] RawOpts
forall a b. b -> Either a b
Right (RawOpts -> Either [Char] RawOpts)
-> RawOpts -> Either [Char] RawOpts
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> RawOpts -> RawOpts
setopt [Char]
"open-acct" [Char]
s RawOpts
opts) [Char]
"ACCT" ([Char]
"old spelling of --open-acct")
    ])
  ([], 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
$ [Char] -> Arg RawOpts
argsFlag [Char]
"[QUERY]")

-- debugger, beware: close is incredibly devious. simple rules combine to make a horrid maze.
-- tests are in hledger/test/close.test.
close :: CliOpts -> Journal -> IO ()
close CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts, reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec
rspec} Journal
j = do
  Day
today <- IO Day
getCurrentDay
  let
    -- show opening entry, closing entry, or (default) both ?
    (Bool
opening, Bool
closing) =
      case ([Char] -> RawOpts -> Bool
boolopt [Char]
"open" RawOpts
rawopts, [Char] -> RawOpts -> Bool
boolopt [Char]
"close" RawOpts
rawopts) of
        (Bool
False, Bool
False) -> (Bool
True, Bool
True)
        (Bool
o, Bool
c)         -> (Bool
o, Bool
c)

    -- descriptions to use for the closing/opening transactions
    closingdesc :: Text
closingdesc = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> Text
T.pack [Char]
defclosingdesc) (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> Maybe [Char] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> RawOpts -> Maybe [Char]
maybestringopt [Char]
"close-desc" RawOpts
rawopts
    openingdesc :: Text
openingdesc = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> Text
T.pack [Char]
defopeningdesc) (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> Maybe [Char] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> RawOpts -> Maybe [Char]
maybestringopt [Char]
"open-desc" RawOpts
rawopts

    -- accounts to close to and open from
    -- if only one is specified, it is used for both
    (Text
closingacct, Text
openingacct) =
      let (Maybe Text
mc, Maybe Text
mo) =
            ([Char] -> Text
T.pack ([Char] -> Text) -> Maybe [Char] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> RawOpts -> Maybe [Char]
maybestringopt [Char]
"close-acct" RawOpts
rawopts, [Char] -> Text
T.pack ([Char] -> Text) -> Maybe [Char] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> RawOpts -> Maybe [Char]
maybestringopt [Char]
"open-acct" RawOpts
rawopts)
      in case (Maybe Text
mc, Maybe Text
mo) of
        (Just Text
c, Just Text
o)   -> (Text
c, Text
o)
        (Just Text
c, Maybe Text
Nothing)  -> (Text
c, Text
c)
        (Maybe Text
Nothing, Just Text
o)  -> (Text
o, Text
o)
        (Maybe Text
Nothing, Maybe Text
Nothing) -> ([Char] -> Text
T.pack [Char]
defclosingacct, [Char] -> Text
T.pack [Char]
defopeningacct)

    -- dates of the closing and opening transactions
    rspec_ :: ReportSpec
rspec_ = ReportSpec
rspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
ropts}
    ropts :: ReportOpts
ropts = (ReportSpec -> ReportOpts
rsOpts ReportSpec
rspec){balancetype_ :: BalanceType
balancetype_=BalanceType
HistoricalBalance, accountlistmode_ :: AccountListMode
accountlistmode_=AccountListMode
ALFlat}
    q :: Query
q = ReportSpec -> Query
rsQuery ReportSpec
rspec
    openingdate :: Day
openingdate = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe Day
today (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ Bool -> Query -> Maybe Day
queryEndDate Bool
False Query
q
    closingdate :: Day
closingdate = Integer -> Day -> Day
addDays (-Integer
1) Day
openingdate

    -- should we show the amount(s) on the equity posting(s) ?
    explicit :: Bool
explicit = [Char] -> RawOpts -> Bool
boolopt [Char]
"explicit" RawOpts
rawopts

    -- should we preserve cost information ?
    normalise :: MixedAmount -> MixedAmount
normalise = case [Char] -> RawOpts -> Bool
boolopt [Char]
"show-costs" RawOpts
rawopts of
                  Bool
True  -> MixedAmount -> MixedAmount
normaliseMixedAmount
                  Bool
False -> MixedAmount -> MixedAmount
normaliseMixedAmount (MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> MixedAmount
mixedAmountStripPrices

    -- the balances to close
    ([BalanceReportItem]
acctbals,MixedAmount
_) = ReportSpec -> Journal -> ([BalanceReportItem], MixedAmount)
balanceReport ReportSpec
rspec_ Journal
j
    totalamt :: MixedAmount
totalamt = [MixedAmount] -> MixedAmount
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([MixedAmount] -> MixedAmount) -> [MixedAmount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (BalanceReportItem -> MixedAmount)
-> [BalanceReportItem] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
_,Text
_,Int
_,MixedAmount
b) -> MixedAmount -> MixedAmount
normalise MixedAmount
b) [BalanceReportItem]
acctbals

    -- since balance assertion amounts are required to be exact, the
    -- amounts in opening/closing transactions should be too (#941, #1137)
    precise :: Amount -> Amount
precise = Amount -> Amount
setFullPrecision

    -- interleave equity postings next to the corresponding closing posting, or put them all at the end ?
    interleaved :: Bool
interleaved = [Char] -> RawOpts -> Bool
boolopt [Char]
"interleaved" RawOpts
rawopts

    -- the closing transaction
    closingtxn :: Transaction
closingtxn = Transaction
nulltransaction{tdate :: Day
tdate=Day
closingdate, tdescription :: Text
tdescription=Text
closingdesc, tpostings :: [Posting]
tpostings=[Posting]
closingps}
    closingps :: [Posting]
closingps =
      [[Posting]] -> [Posting]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
        [Posting
posting{paccount :: Text
paccount          = Text
a
                ,pamount :: MixedAmount
pamount           = [Amount] -> MixedAmount
mixed [Amount -> Amount
precise (Amount -> Amount) -> Amount -> Amount
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
forall a. Num a => a -> a
negate Amount
b]
                -- after each commodity's last posting, assert 0 balance (#1035)
                -- balance assertion amounts are unpriced (#824)
                ,pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion =
                    if Bool
islast
                    then BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just BalanceAssertion
nullassertion{baamount :: Amount
baamount=Amount -> Amount
precise Amount
b{aquantity :: Quantity
aquantity=Quantity
0, aprice :: Maybe AmountPrice
aprice=Maybe AmountPrice
forall a. Maybe a
Nothing}}
                    else Maybe BalanceAssertion
forall a. Maybe a
Nothing
                }
        ]
        -- maybe an interleaved posting transferring this balance to equity
        [Posting] -> [Posting] -> [Posting]
forall a. [a] -> [a] -> [a]
++ [Posting
posting{paccount :: Text
paccount=Text
closingacct, pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [Amount -> Amount
precise Amount
b]} | Bool
interleaved]

        | -- get the balances for each commodity and transaction price
          (Text
a,Text
_,Int
_,MixedAmount
mb) <- [BalanceReportItem]
acctbals
        , let bs :: [Amount]
bs = MixedAmount -> [Amount]
amounts (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
normalise MixedAmount
mb
          -- mark the last balance in each commodity with True
        , let bs' :: [(Amount, Bool)]
bs' = [[(Amount, Bool)]] -> [(Amount, Bool)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[(Amount, Bool)] -> [(Amount, Bool)]
forall a. [a] -> [a]
reverse ([(Amount, Bool)] -> [(Amount, Bool)])
-> [(Amount, Bool)] -> [(Amount, Bool)]
forall a b. (a -> b) -> a -> b
$ [Amount] -> [Bool] -> [(Amount, Bool)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([Amount] -> [Amount]
forall a. [a] -> [a]
reverse [Amount]
bs) (Bool
True Bool -> [Bool] -> [Bool]
forall a. a -> [a] -> [a]
: Bool -> [Bool]
forall a. a -> [a]
repeat Bool
False)
                           | [Amount]
bs <- (Amount -> Amount -> Bool) -> [Amount] -> [[Amount]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Text -> Text -> Bool)
-> (Amount -> Text) -> Amount -> Amount -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Amount -> Text
acommodity) [Amount]
bs]
        , (Amount
b, Bool
islast) <- [(Amount, Bool)]
bs'
        ]
      
      -- or a final multicommodity posting transferring all balances to equity
      -- (print will show this as multiple single-commodity postings)
      [Posting] -> [Posting] -> [Posting]
forall a. [a] -> [a] -> [a]
++ [Posting
posting{paccount :: Text
paccount=Text
closingacct, pamount :: MixedAmount
pamount=if Bool
explicit then (Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount Amount -> Amount
precise MixedAmount
totalamt else MixedAmount
missingmixedamt} | Bool -> Bool
not Bool
interleaved]

    -- the opening transaction
    openingtxn :: Transaction
openingtxn = Transaction
nulltransaction{tdate :: Day
tdate=Day
openingdate, tdescription :: Text
tdescription=Text
openingdesc, tpostings :: [Posting]
tpostings=[Posting]
openingps}
    openingps :: [Posting]
openingps =
      [[Posting]] -> [Posting]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
        [Posting
posting{paccount :: Text
paccount          = Text
a
                ,pamount :: MixedAmount
pamount           = [Amount] -> MixedAmount
mixed [Amount -> Amount
precise Amount
b]
                ,pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion =
                    case Maybe Amount
mcommoditysum of
                      Just Amount
s  -> BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just BalanceAssertion
nullassertion{baamount :: Amount
baamount=Amount -> Amount
precise Amount
s{aprice :: Maybe AmountPrice
aprice=Maybe AmountPrice
forall a. Maybe a
Nothing}}
                      Maybe Amount
Nothing -> Maybe BalanceAssertion
forall a. Maybe a
Nothing
                }
        ]
        [Posting] -> [Posting] -> [Posting]
forall a. [a] -> [a] -> [a]
++ [Posting
posting{paccount :: Text
paccount=Text
openingacct, pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [Amount -> Amount
precise (Amount -> Amount) -> Amount -> Amount
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
forall a. Num a => a -> a
negate Amount
b]} | Bool
interleaved]

        | (Text
a,Text
_,Int
_,MixedAmount
mb) <- [BalanceReportItem]
acctbals
        , let bs :: [Amount]
bs = MixedAmount -> [Amount]
amounts (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
normalise MixedAmount
mb
          -- mark the last balance in each commodity with the unpriced sum in that commodity (for a balance assertion)
        , let bs' :: [(Amount, Maybe Amount)]
bs' = [[(Amount, Maybe Amount)]] -> [(Amount, Maybe Amount)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[(Amount, Maybe Amount)] -> [(Amount, Maybe Amount)]
forall a. [a] -> [a]
reverse ([(Amount, Maybe Amount)] -> [(Amount, Maybe Amount)])
-> [(Amount, Maybe Amount)] -> [(Amount, Maybe Amount)]
forall a b. (a -> b) -> a -> b
$ [Amount] -> [Maybe Amount] -> [(Amount, Maybe Amount)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([Amount] -> [Amount]
forall a. [a] -> [a]
reverse [Amount]
bs) (Amount -> Maybe Amount
forall a. a -> Maybe a
Just Amount
commoditysum Maybe Amount -> [Maybe Amount] -> [Maybe Amount]
forall a. a -> [a] -> [a]
: Maybe Amount -> [Maybe Amount]
forall a. a -> [a]
repeat Maybe Amount
forall a. Maybe a
Nothing)
                           | [Amount]
bs <- (Amount -> Amount -> Bool) -> [Amount] -> [[Amount]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Text -> Text -> Bool)
-> (Amount -> Text) -> Amount -> Amount -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Amount -> Text
acommodity) [Amount]
bs
                           , let commoditysum :: Amount
commoditysum = ([Amount] -> Amount
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Amount]
bs)]
        , (Amount
b, Maybe Amount
mcommoditysum) <- [(Amount, Maybe Amount)]
bs'
        ]
      [Posting] -> [Posting] -> [Posting]
forall a. [a] -> [a] -> [a]
++ [Posting
posting{paccount :: Text
paccount=Text
openingacct, pamount :: MixedAmount
pamount=if Bool
explicit then (Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount Amount -> Amount
precise (MixedAmount -> MixedAmount
forall a. Num a => a -> a
negate MixedAmount
totalamt) else MixedAmount
missingmixedamt} | Bool -> Bool
not Bool
interleaved]

  -- print them
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
closing (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
putStr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ Transaction -> [Char]
showTransaction Transaction
closingtxn
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
opening (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
putStr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ Transaction -> [Char]
showTransaction Transaction
openingtxn