{-# 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 (fromMaybe)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Time.Calendar (addDays)
import Lens.Micro ((^.))
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")
  [forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"close"]        ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"close") [Char]
"show just closing transaction"
  ,forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"open"]         ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"open") [Char]
"show just opening transaction"
  ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-desc"]   (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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: "forall a. [a] -> [a] -> [a]
++[Char]
defclosingdescforall a. [a] -> [a] -> [a]
++[Char]
")")
  ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-desc"]    (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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: "forall a. [a] -> [a] -> [a]
++[Char]
defopeningdescforall a. [a] -> [a] -> [a]
++[Char]
")")
  ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-acct"]   (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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: "forall a. [a] -> [a] -> [a]
++[Char]
defclosingacctforall a. [a] -> [a] -> [a]
++[Char]
")")
  ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-acct"]    (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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: "forall a. [a] -> [a] -> [a]
++[Char]
defopeningacctforall a. [a] -> [a] -> [a]
++[Char]
")")
  ,forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"explicit",[Char]
"x"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"explicit") [Char]
"show all amounts explicitly"
  ,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"
  ,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 forall a. [a] -> [a] -> [a]
++
    -- old close flags for compatibility, hidden
    [forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"closing"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"close") [Char]
"old spelling of --close"
    ,forall a. [[Char]] -> (a -> a) -> [Char] -> Flag a
flagNone [[Char]
"opening"] ([Char] -> RawOpts -> RawOpts
setboolopt [Char]
"open") [Char]
"old spelling of --open"
    ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"close-to"]  (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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")
    ,forall a. [[Char]] -> Update a -> [Char] -> [Char] -> Flag a
flagReq  [[Char]
"open-from"] (\[Char]
s RawOpts
opts -> forall a b. b -> Either a b
Right 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")
    ])
  ([], forall a. a -> Maybe a
Just 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 copts :: CliOpts
copts@CliOpts{rawopts_ :: CliOpts -> RawOpts
rawopts_=RawOpts
rawopts, reportspec_ :: CliOpts -> ReportSpec
reportspec_=ReportSpec
rspec'} Journal
j = do
  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 = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Text
T.pack [Char]
defclosingdesc) [Char] -> Text
T.pack forall a b. (a -> b) -> a -> b
$ [Char] -> RawOpts -> Maybe [Char]
maybestringopt [Char]
"close-desc" RawOpts
rawopts
    openingdesc :: Text
openingdesc = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Text
T.pack [Char]
defopeningdesc) [Char] -> Text
T.pack forall a b. (a -> b) -> a -> 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 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 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)

    ropts :: ReportOpts
ropts = (ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec'){balanceaccum_ :: BalanceAccumulation
balanceaccum_=BalanceAccumulation
Historical, accountlistmode_ :: AccountListMode
accountlistmode_=AccountListMode
ALFlat}
    rspec :: ReportSpec
rspec = ConversionOp -> ReportSpec -> ReportSpec
setDefaultConversionOp ConversionOp
NoConversionOp ReportSpec
rspec'{_rsReportOpts :: ReportOpts
_rsReportOpts=ReportOpts
ropts}

    -- dates of the closing and opening transactions
    --
    -- Close.md:
    -- "The default closing date is yesterday, or the journal's end date, whichever is later.
    --
    -- Unless you are running `close` on exactly the first day of the new period, 
    -- you'll want to override the closing date. 
    -- This is done by specifying a [report period](#report-start--end-date), 
    -- where "last day of the report period" will be the closing date.
    -- The opening date is always the following day.
    -- So to close on 2020-12-31 and open on 2021-01-01, any of these work
    --
    -- - `-p 2020`
    -- - `date:2020`
    -- - `-e 2021-01-01`  (remember `-e` specifies an exclusive report end date)
    -- - `-e 2021`"
    --
    q :: Query
q = ReportSpec -> Query
_rsQuery ReportSpec
rspec
    yesterday :: Day
yesterday = Integer -> Day -> Day
addDays (-Integer
1) forall a b. (a -> b) -> a -> b
$ ReportSpec -> Day
_rsDay ReportSpec
rspec
    yesterdayorjournalend :: Day
yesterdayorjournalend = case Bool -> Journal -> Maybe Day
journalLastDay Bool
False Journal
j of
      Just Day
journalend -> forall a. Ord a => a -> a -> a
max Day
yesterday Day
journalend
      Maybe Day
Nothing         -> Day
yesterday
    mreportlastday :: Maybe Day
mreportlastday = Integer -> Day -> Day
addDays (-Integer
1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Query -> Maybe Day
queryEndDate Bool
False Query
q
    closingdate :: Day
closingdate = forall a. a -> Maybe a -> a
fromMaybe Day
yesterdayorjournalend  Maybe Day
mreportlastday
    openingdate :: Day
openingdate = Integer -> Day -> Day
addDays Integer
1 Day
closingdate

    -- should we show the amount(s) on the equity posting(s) ?
    explicit :: Bool
explicit = [Char] -> RawOpts -> Bool
boolopt [Char]
"explicit" RawOpts
rawopts Bool -> Bool -> Bool
|| CliOpts
copts forall s a. s -> Getting a s a -> a
^. forall c. HasInputOpts c => Lens' c Bool
infer_costs

    -- the balances to close
    ([BalanceReportItem]
acctbals',MixedAmount
_) = ReportSpec -> Journal -> ([BalanceReportItem], MixedAmount)
balanceReport ReportSpec
rspec Journal
j
    acctbals :: [(Text, MixedAmount)]
acctbals = forall a b. (a -> b) -> [a] -> [b]
map (\(Text
a,Text
_,Int
_,MixedAmount
b) -> (Text
a, if ReportOpts -> Bool
show_costs_ ReportOpts
ropts then MixedAmount
b else MixedAmount -> MixedAmount
mixedAmountStripPrices MixedAmount
b)) [BalanceReportItem]
acctbals'
    totalamt :: MixedAmount
totalamt = forall (t :: * -> *). Foldable t => t MixedAmount -> MixedAmount
maSum forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Text, MixedAmount)]
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
amountSetFullPrecision

    -- 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 =
      forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
        Posting
posting{paccount :: Text
paccount          = Text
a
               ,pamount :: MixedAmount
pamount           = Amount -> MixedAmount
mixedAmount forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Amount
precise forall a b. (a -> b) -> a -> b
$ 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 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=forall a. Maybe a
Nothing}}
                   else forall a. Maybe a
Nothing
               }

        -- maybe an interleaved posting transferring this balance to equity
        forall a. a -> [a] -> [a]
: [Posting
posting{paccount :: Text
paccount=Text
closingacct, pamount :: MixedAmount
pamount=Amount -> MixedAmount
mixedAmount forall a b. (a -> b) -> a -> b
$ Amount -> Amount
precise Amount
b} | Bool
interleaved]

        | -- get the balances for each commodity and transaction price
          (Text
a,MixedAmount
mb) <- [(Text, MixedAmount)]
acctbals
        , let bs0 :: [Amount]
bs0 = MixedAmount -> [Amount]
amounts MixedAmount
mb
          -- mark the last balance in each commodity with True
        , let bs2 :: [(Amount, Bool)]
bs2 = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip (forall a. [a] -> [a]
reverse [Amount]
bs1) (Bool
True forall a. a -> [a] -> [a]
: forall a. a -> [a]
repeat Bool
False)
                           | [Amount]
bs1 <- forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Amount -> Text
acommodity) [Amount]
bs0]
        , (Amount
b, Bool
islast) <- [(Amount, Bool)]
bs2
        ]

      -- or a final multicommodity posting transferring all balances to equity
      -- (print will show this as multiple single-commodity postings)
      forall a. [a] -> [a] -> [a]
++ [Posting
posting{paccount :: Text
paccount=Text
closingacct, pamount :: MixedAmount
pamount=if Bool
explicit then MixedAmount -> MixedAmount
mixedAmountSetFullPrecision 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 =
      forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
        Posting
posting{paccount :: Text
paccount          = Text
a
               ,pamount :: MixedAmount
pamount           = Amount -> MixedAmount
mixedAmount forall a b. (a -> b) -> a -> b
$ Amount -> Amount
precise Amount
b
               ,pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion =
                   case Maybe Amount
mcommoditysum of
                     Just Amount
s  -> forall a. a -> Maybe a
Just BalanceAssertion
nullassertion{baamount :: Amount
baamount=Amount -> Amount
precise Amount
s{aprice :: Maybe AmountPrice
aprice=forall a. Maybe a
Nothing}}
                     Maybe Amount
Nothing -> forall a. Maybe a
Nothing
               }
        forall a. a -> [a] -> [a]
: [Posting
posting{paccount :: Text
paccount=Text
openingacct, pamount :: MixedAmount
pamount=Amount -> MixedAmount
mixedAmount forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Amount
precise forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
negate Amount
b} | Bool
interleaved]

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

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