{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE TemplateHaskell   #-}
{-|

The @cashflow@ command prints a simplified cashflow statement.  It just
shows the change in all "cash" accounts for the period (without the
traditional segmentation into operating, investing, and financing
cash flows.)

-}

module Hledger.Cli.Commands.Cashflow (
  cashflowmode
 ,cashflow
) where

import System.Console.CmdArgs.Explicit

import Hledger
import Hledger.Cli.CliOptions
import Hledger.Cli.CompoundBalanceCommand

cashflowSpec :: CompoundBalanceCommandSpec
cashflowSpec = CompoundBalanceCommandSpec {
  cbcdoc :: CommandDoc
cbcdoc      = $(embedFileRelative "Hledger/Cli/Commands/Cashflow.txt"),
  cbctitle :: CommandDoc
cbctitle    = CommandDoc
"Cashflow Statement",
  cbcqueries :: [CBCSubreportSpec DisplayName]
cbcqueries  = [
     CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Cash flows"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Cash]
     ,cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreportoptions=(\ReportOpts
ropts -> ReportOpts
ropts{normalbalance_= Just NormallyPositive})
     ,cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
cbcsubreporttransform=PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a. a -> a
id
     ,cbcsubreportincreasestotal :: Bool
cbcsubreportincreasestotal=Bool
True
     }
    ],
  cbcaccum :: BalanceAccumulation
cbcaccum     = BalanceAccumulation
PerPeriod
}

cashflowmode :: Mode RawOpts
cashflowmode :: Mode RawOpts
cashflowmode = CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode CompoundBalanceCommandSpec
cashflowSpec

cashflow :: CliOpts -> Journal -> IO ()
cashflow :: CliOpts -> Journal -> IO ()
cashflow = CompoundBalanceCommandSpec -> CliOpts -> Journal -> IO ()
compoundBalanceCommand CompoundBalanceCommandSpec
cashflowSpec