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

The @incomestatement@ command prints a simple income statement (profit & loss report).

-}

module Hledger.Cli.Commands.Incomestatement (
  incomestatementmode
 ,incomestatement
) where

import System.Console.CmdArgs.Explicit

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

incomestatementSpec :: CompoundBalanceCommandSpec
incomestatementSpec = CompoundBalanceCommandSpec {
  cbcdoc :: CommandDoc
cbcdoc      = $(embedFileRelative "Hledger/Cli/Commands/Incomestatement.txt"),
  cbctitle :: CommandDoc
cbctitle    = CommandDoc
"Income Statement",
  cbcqueries :: [CBCSubreportSpec DisplayName]
cbcqueries  = [
     CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Revenues"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Revenue]
     ,cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreportoptions=(\ReportOpts
ropts -> ReportOpts
ropts{normalbalance_=Just NormallyNegative})
     ,cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
cbcsubreporttransform=(MixedAmount -> MixedAmount)
-> PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
forall a b.
(a -> b)
-> PeriodicReport DisplayName a -> PeriodicReport DisplayName b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> MixedAmount
maNegate
     ,cbcsubreportincreasestotal :: Bool
cbcsubreportincreasestotal=Bool
True
     }
    ,CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Expenses"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Expense]
     ,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
False
     }
    ],
  cbcaccum :: BalanceAccumulation
cbcaccum     = BalanceAccumulation
PerPeriod
}

incomestatementmode :: Mode RawOpts
incomestatementmode :: Mode RawOpts
incomestatementmode = CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode CompoundBalanceCommandSpec
incomestatementSpec

incomestatement :: CliOpts -> Journal -> IO ()
incomestatement :: CliOpts -> Journal -> IO ()
incomestatement = CompoundBalanceCommandSpec -> CliOpts -> Journal -> IO ()
compoundBalanceCommand CompoundBalanceCommandSpec
incomestatementSpec
{- 
Summary of code flow, 2021-11:

incomestatement
 compoundBalanceCommand
  compoundBalanceReport
   compoundBalanceReportWith
    colps = getPostingsByColumn
    startps = startingPostings
    generateSubreport
     startbals = startingBalances (startps restricted to this subreport)
     generateMultiBalanceReport startbals (colps restricted to this subreport)
      matrix = calculateReportMatrix startbals colps
      displaynames = displayedAccounts
      buildReportRows displaynames matrix
 -}