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

The @balancesheetequity@ command prints a simple balance sheet.

-}

module Hledger.Cli.Commands.Balancesheetequity (
  balancesheetequitymode
 ,balancesheetequity
) where

import System.Console.CmdArgs.Explicit

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

balancesheetequitySpec :: CompoundBalanceCommandSpec
balancesheetequitySpec = CompoundBalanceCommandSpec {
  cbcdoc :: CommandDoc
cbcdoc      = $(embedFileRelative "Hledger/Cli/Commands/Balancesheetequity.txt"),
  cbctitle :: CommandDoc
cbctitle    = CommandDoc
"Balance Sheet With Equity",
  cbcqueries :: [CBCSubreportSpec DisplayName]
cbcqueries  = [
     CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Assets"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Asset]
     ,cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreportoptions=(\ReportOpts
ropts -> ReportOpts
ropts{normalbalance_ :: Maybe NormalSign
normalbalance_=forall a. a -> Maybe a
Just NormalSign
NormallyPositive})
     ,cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
cbcsubreporttransform=forall a. a -> a
id
     ,cbcsubreportincreasestotal :: Bool
cbcsubreportincreasestotal=Bool
True
     }
    ,CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Liabilities"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Liability]
     ,cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreportoptions=(\ReportOpts
ropts -> ReportOpts
ropts{normalbalance_ :: Maybe NormalSign
normalbalance_=forall a. a -> Maybe a
Just NormalSign
NormallyNegative})
     ,cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
cbcsubreporttransform=forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> MixedAmount
maNegate
     ,cbcsubreportincreasestotal :: Bool
cbcsubreportincreasestotal=Bool
False
     }
    ,CBCSubreportSpec{
      cbcsubreporttitle :: Text
cbcsubreporttitle=Text
"Equity"
     ,cbcsubreportquery :: Query
cbcsubreportquery=[AccountType] -> Query
Type [AccountType
Equity]
     ,cbcsubreportoptions :: ReportOpts -> ReportOpts
cbcsubreportoptions=(\ReportOpts
ropts -> ReportOpts
ropts{normalbalance_ :: Maybe NormalSign
normalbalance_=forall a. a -> Maybe a
Just NormalSign
NormallyNegative})
     ,cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount
-> PeriodicReport DisplayName MixedAmount
cbcsubreporttransform=forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MixedAmount -> MixedAmount
maNegate
     ,cbcsubreportincreasestotal :: Bool
cbcsubreportincreasestotal=Bool
False
     }
    ],
  cbcaccum :: BalanceAccumulation
cbcaccum     = BalanceAccumulation
Historical
}

balancesheetequitymode :: Mode RawOpts
balancesheetequitymode :: Mode RawOpts
balancesheetequitymode = CompoundBalanceCommandSpec -> Mode RawOpts
compoundBalanceCommandMode CompoundBalanceCommandSpec
balancesheetequitySpec

balancesheetequity :: CliOpts -> Journal -> IO ()
balancesheetequity :: CliOpts -> Journal -> IO ()
balancesheetequity = CompoundBalanceCommandSpec -> CliOpts -> Journal -> IO ()
compoundBalanceCommand CompoundBalanceCommandSpec
balancesheetequitySpec