{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Data.Tax.ATO
(
TaxReturnInfo
, newTaxReturnInfo
, newTaxReturnInfoForTables
, taxableIncome
, PaymentSummary(..)
, paymentSummaries
, ABN
, interest
, Dividend(..)
, dividends
, dividendFromGross
, dividendFromNet
, dividendFromNetFranked
, dividendFromNetFranked30
, HasCapitalLossCarryForward(..)
, cgtEvents
, ESSStatement
, newESSStatement
, ess
, essTaxedUpfrontReduction
, essTaxedUpfrontNoReduction
, essDeferral
, essPre2009
, essTFNAmounts
, essForeignSourceDiscounts
, foreignIncome
, mlsExemption
, privateHealthInsurancePolicyDetails
, helpBalance
, sfssBalance
, SpouseDetails
, spouseDetails
, newSpouseDetails
, spouseTaxableIncome
, IncomeTests
, incomeTests
, newIncomeTests
, taxFreeGovernmentPensionsOrBenefits
, targetForeignIncome
, childSupportPaid
, dependentChildren
, Deductions
, deductions
, totalDeductions
, workRelatedCarExpenses
, workRelatedTravelExpenses
, workRelatedClothingLaundryAndDryCleaningExpenses
, workRelatedSelfEducationExpenses
, otherWorkRelatedExpenses
, lowValuePoolDeduction
, interestDeductions
, dividendDeductions
, giftsOrDonations
, costOfManagingTaxAffairs
, deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity
, personalSuperannuationContributions
, deductionForProjectPool
, forestryManagedInvestmentSchemeDeduction
, otherDeductions
, foreignIncomeDeductions
, Offsets
, offsets
, spouseContributionOffset
, foreignTaxOffset
, paygInstalments
, TaxAssessment
, assessTax
, taxBalance
, taxDue
, medicareLevyDue
, studyAndTrainingLoanRepayment
, taxCreditsAndOffsets
, paygInstalmentsCredit
, taxCGTAssessment
, privateHealthInsuranceRebateAdjustment
, corporateTax
, GrossAndWithheld(..)
, HasTaxWithheld(..)
, Proportion
, getProportion
, proportion
, module Data.Tax
, module Data.Tax.ATO.PrivateHealthInsuranceRebate
, module Data.Tax.ATO.Rounding
) where
import Control.Lens (Getter, Lens', (&), foldOf, lens, set, to, view, views)
import Data.Time (Day)
import Data.Tax
import Data.Tax.ATO.CGT
import Data.Tax.ATO.Common
import Data.Tax.ATO.FY
import Data.Tax.ATO.PrivateHealthInsuranceRebate
import Data.Tax.ATO.Rounding
class HasTaxWithheld a b c where
taxWithheld :: Getter (a b) (Money c)
instance (Foldable t, HasTaxWithheld x a a, Num a)
=> HasTaxWithheld t (x a) a where
taxWithheld :: Getter (t (x a)) (Money a)
taxWithheld = (t (x a) -> Money a)
-> (Money a -> f (Money a)) -> t (x a) -> f (t (x a))
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((x a -> Money a) -> t (x a) -> Money a
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Getting (Money a) (x a) (Money a) -> x a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (x a) (Money a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter (x a) (Money a)
taxWithheld))
newtype SpouseDetails a = SpouseDetails
{ forall a. SpouseDetails a -> Money a
_spouseTaxableIncome :: Money a
}
newSpouseDetails :: (Num a) => SpouseDetails a
newSpouseDetails :: forall a. Num a => SpouseDetails a
newSpouseDetails = Money a -> SpouseDetails a
forall a. Money a -> SpouseDetails a
SpouseDetails Money a
forall a. Monoid a => a
mempty
spouseTaxableIncome :: Lens' (SpouseDetails a) (Money a)
spouseTaxableIncome :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> SpouseDetails a -> f (SpouseDetails a)
spouseTaxableIncome =
(SpouseDetails a -> Money a)
-> (SpouseDetails a -> Money a -> SpouseDetails a)
-> Lens (SpouseDetails a) (SpouseDetails a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens SpouseDetails a -> Money a
forall a. SpouseDetails a -> Money a
_spouseTaxableIncome (\SpouseDetails a
s Money a
b -> SpouseDetails a
s { _spouseTaxableIncome = b })
data IncomeTests a = IncomeTests
{ forall a. IncomeTests a -> Money a
_govBenefit :: Money a
, forall a. IncomeTests a -> Money a
_targetForeignIncome :: Money a
, forall a. IncomeTests a -> Money a
_childSupportPaid :: Money a
, forall a. IncomeTests a -> Integer
_dependents :: Integer
}
newIncomeTests :: (Num a) => IncomeTests a
newIncomeTests :: forall a. Num a => IncomeTests a
newIncomeTests = Money a -> Money a -> Money a -> Integer -> IncomeTests a
forall a. Money a -> Money a -> Money a -> Integer -> IncomeTests a
IncomeTests Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Integer
0
taxFreeGovernmentPensionsOrBenefits :: Lens' (IncomeTests a) (Money a)
taxFreeGovernmentPensionsOrBenefits :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> IncomeTests a -> f (IncomeTests a)
taxFreeGovernmentPensionsOrBenefits =
(IncomeTests a -> Money a)
-> (IncomeTests a -> Money a -> IncomeTests a)
-> Lens (IncomeTests a) (IncomeTests a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IncomeTests a -> Money a
forall a. IncomeTests a -> Money a
_govBenefit (\IncomeTests a
s Money a
b -> IncomeTests a
s { _govBenefit = b })
targetForeignIncome :: Lens' (IncomeTests a) (Money a)
targetForeignIncome :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> IncomeTests a -> f (IncomeTests a)
targetForeignIncome =
(IncomeTests a -> Money a)
-> (IncomeTests a -> Money a -> IncomeTests a)
-> Lens (IncomeTests a) (IncomeTests a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IncomeTests a -> Money a
forall a. IncomeTests a -> Money a
_targetForeignIncome (\IncomeTests a
s Money a
b -> IncomeTests a
s { _targetForeignIncome = b })
childSupportPaid :: Lens' (IncomeTests a) (Money a)
childSupportPaid :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> IncomeTests a -> f (IncomeTests a)
childSupportPaid =
(IncomeTests a -> Money a)
-> (IncomeTests a -> Money a -> IncomeTests a)
-> Lens (IncomeTests a) (IncomeTests a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IncomeTests a -> Money a
forall a. IncomeTests a -> Money a
_childSupportPaid (\IncomeTests a
s Money a
b -> IncomeTests a
s { _childSupportPaid = b })
dependentChildren :: Lens' (IncomeTests a) Integer
dependentChildren :: forall a (f :: * -> *).
Functor f =>
(Integer -> f Integer) -> IncomeTests a -> f (IncomeTests a)
dependentChildren =
(IncomeTests a -> Integer)
-> (IncomeTests a -> Integer -> IncomeTests a)
-> Lens (IncomeTests a) (IncomeTests a) Integer Integer
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IncomeTests a -> Integer
forall a. IncomeTests a -> Integer
_dependents (\IncomeTests a
s Integer
b -> IncomeTests a
s { _dependents = b })
data TaxReturnInfo y a = TaxReturnInfo
{ forall (y :: Nat) a. TaxReturnInfo y a -> Days y
_mlsExemption :: Days y
, forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_helpBalance :: Money a
, forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_sfssBalance :: Money a
, forall (y :: Nat) a. TaxReturnInfo y a -> [PaymentSummary a]
_paymentSummaries :: [PaymentSummary a]
, forall (y :: Nat) a. TaxReturnInfo y a -> GrossAndWithheld a
_interest :: GrossAndWithheld a
, forall (y :: Nat) a. TaxReturnInfo y a -> [Dividend a]
_dividends :: [Dividend a]
, forall (y :: Nat) a. TaxReturnInfo y a -> ESSStatement a
_ess :: ESSStatement a
, forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_foreignIncome :: Money a
, forall (y :: Nat) a. TaxReturnInfo y a -> [CGTEvent a]
_cgtEvents :: [CGTEvent a]
, forall (y :: Nat) a. TaxReturnInfo y a -> Deductions a
_deductions :: Deductions a
, forall (y :: Nat) a. TaxReturnInfo y a -> Offsets a
_offsets :: Offsets a
, forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_triCapitalLossCarryForward :: Money a
, forall (y :: Nat) a.
TaxReturnInfo y a -> [PrivateHealthInsurancePolicyDetail a]
_phi :: [PrivateHealthInsurancePolicyDetail a]
, forall (y :: Nat) a. TaxReturnInfo y a -> Maybe (SpouseDetails a)
_spouseDetails :: Maybe (SpouseDetails a)
, forall (y :: Nat) a. TaxReturnInfo y a -> IncomeTests a
_incomeTests :: IncomeTests a
}
newTaxReturnInfo
:: (FinancialYear y, Num a)
=> TaxReturnInfo y a
newTaxReturnInfo :: forall (y :: Nat) a. (FinancialYear y, Num a) => TaxReturnInfo y a
newTaxReturnInfo = Days y
-> Money a
-> Money a
-> [PaymentSummary a]
-> GrossAndWithheld a
-> [Dividend a]
-> ESSStatement a
-> Money a
-> [CGTEvent a]
-> Deductions a
-> Offsets a
-> Money a
-> [PrivateHealthInsurancePolicyDetail a]
-> Maybe (SpouseDetails a)
-> IncomeTests a
-> TaxReturnInfo y a
forall (y :: Nat) a.
Days y
-> Money a
-> Money a
-> [PaymentSummary a]
-> GrossAndWithheld a
-> [Dividend a]
-> ESSStatement a
-> Money a
-> [CGTEvent a]
-> Deductions a
-> Offsets a
-> Money a
-> [PrivateHealthInsurancePolicyDetail a]
-> Maybe (SpouseDetails a)
-> IncomeTests a
-> TaxReturnInfo y a
TaxReturnInfo
Days y
forall (a :: Nat). FinancialYear a => Days a
daysAll
Money a
forall a. Monoid a => a
mempty
Money a
forall a. Monoid a => a
mempty
[PaymentSummary a]
forall a. Monoid a => a
mempty
GrossAndWithheld a
forall a. Monoid a => a
mempty
[Dividend a]
forall a. Monoid a => a
mempty
ESSStatement a
forall a. Monoid a => a
mempty
Money a
forall a. Monoid a => a
mempty
[CGTEvent a]
forall a. Monoid a => a
mempty
Deductions a
forall a. Monoid a => a
mempty
Offsets a
forall a. Monoid a => a
mempty
Money a
forall a. Monoid a => a
mempty
[PrivateHealthInsurancePolicyDetail a]
forall a. Monoid a => a
mempty
Maybe (SpouseDetails a)
forall a. Maybe a
Nothing
IncomeTests a
forall a. Num a => IncomeTests a
newIncomeTests
newTaxReturnInfoForTables
:: (FinancialYear y, Num a)
=> TaxTables y a -> TaxReturnInfo y a
newTaxReturnInfoForTables :: forall (y :: Nat) a.
(FinancialYear y, Num a) =>
TaxTables y a -> TaxReturnInfo y a
newTaxReturnInfoForTables TaxTables y a
_ = TaxReturnInfo y a
forall (y :: Nat) a. (FinancialYear y, Num a) => TaxReturnInfo y a
newTaxReturnInfo
instance HasCapitalLossCarryForward (TaxReturnInfo y) a where
capitalLossCarryForward :: Lens' (TaxReturnInfo y a) (Money a)
capitalLossCarryForward = (TaxReturnInfo y a -> Money a)
-> (TaxReturnInfo y a -> Money a -> TaxReturnInfo y a)
-> Lens' (TaxReturnInfo y a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Money a
forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_triCapitalLossCarryForward
(\TaxReturnInfo y a
s Money a
b -> TaxReturnInfo y a
s { _triCapitalLossCarryForward = b })
helpBalance :: Lens' (TaxReturnInfo y a) (Money a)
helpBalance :: forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
helpBalance = (TaxReturnInfo y a -> Money a)
-> (TaxReturnInfo y a -> Money a -> TaxReturnInfo y a)
-> Lens (TaxReturnInfo y a) (TaxReturnInfo y a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Money a
forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_helpBalance (\TaxReturnInfo y a
s Money a
b -> TaxReturnInfo y a
s { _helpBalance = b })
sfssBalance :: Lens' (TaxReturnInfo y a) (Money a)
sfssBalance :: forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
sfssBalance = (TaxReturnInfo y a -> Money a)
-> (TaxReturnInfo y a -> Money a -> TaxReturnInfo y a)
-> Lens (TaxReturnInfo y a) (TaxReturnInfo y a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Money a
forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_sfssBalance (\TaxReturnInfo y a
s Money a
b -> TaxReturnInfo y a
s { _sfssBalance = b })
mlsExemption :: Lens' (TaxReturnInfo y a) (Days y)
mlsExemption :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Days y -> f (Days y))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
mlsExemption = (TaxReturnInfo y a -> Days y)
-> (TaxReturnInfo y a -> Days y -> TaxReturnInfo y a)
-> Lens (TaxReturnInfo y a) (TaxReturnInfo y a) (Days y) (Days y)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Days y
forall (y :: Nat) a. TaxReturnInfo y a -> Days y
_mlsExemption (\TaxReturnInfo y a
s Days y
b -> TaxReturnInfo y a
s { _mlsExemption = b })
paymentSummaries :: Lens' (TaxReturnInfo y a) [PaymentSummary a]
paymentSummaries :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PaymentSummary a] -> f [PaymentSummary a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
paymentSummaries = (TaxReturnInfo y a -> [PaymentSummary a])
-> (TaxReturnInfo y a -> [PaymentSummary a] -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
[PaymentSummary a]
[PaymentSummary a]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> [PaymentSummary a]
forall (y :: Nat) a. TaxReturnInfo y a -> [PaymentSummary a]
_paymentSummaries (\TaxReturnInfo y a
s [PaymentSummary a]
b -> TaxReturnInfo y a
s { _paymentSummaries = b })
interest :: Lens' (TaxReturnInfo y a) (GrossAndWithheld a)
interest :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(GrossAndWithheld a -> f (GrossAndWithheld a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
interest = (TaxReturnInfo y a -> GrossAndWithheld a)
-> (TaxReturnInfo y a -> GrossAndWithheld a -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
(GrossAndWithheld a)
(GrossAndWithheld a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> GrossAndWithheld a
forall (y :: Nat) a. TaxReturnInfo y a -> GrossAndWithheld a
_interest (\TaxReturnInfo y a
s GrossAndWithheld a
b -> TaxReturnInfo y a
s { _interest = b })
dividends :: Lens' (TaxReturnInfo y a) [Dividend a]
dividends :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
([Dividend a] -> f [Dividend a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
dividends = (TaxReturnInfo y a -> [Dividend a])
-> (TaxReturnInfo y a -> [Dividend a] -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a) (TaxReturnInfo y a) [Dividend a] [Dividend a]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> [Dividend a]
forall (y :: Nat) a. TaxReturnInfo y a -> [Dividend a]
_dividends (\TaxReturnInfo y a
s [Dividend a]
b -> TaxReturnInfo y a
s { _dividends = b })
ess :: Lens' (TaxReturnInfo y a) (ESSStatement a)
ess :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(ESSStatement a -> f (ESSStatement a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
ess = (TaxReturnInfo y a -> ESSStatement a)
-> (TaxReturnInfo y a -> ESSStatement a -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
(ESSStatement a)
(ESSStatement a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> ESSStatement a
forall (y :: Nat) a. TaxReturnInfo y a -> ESSStatement a
_ess (\TaxReturnInfo y a
s ESSStatement a
b -> TaxReturnInfo y a
s { _ess = b })
foreignIncome :: Lens' (TaxReturnInfo y a) (Money a)
foreignIncome :: forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
foreignIncome = (TaxReturnInfo y a -> Money a)
-> (TaxReturnInfo y a -> Money a -> TaxReturnInfo y a)
-> Lens (TaxReturnInfo y a) (TaxReturnInfo y a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Money a
forall (y :: Nat) a. TaxReturnInfo y a -> Money a
_foreignIncome (\TaxReturnInfo y a
s Money a
b -> TaxReturnInfo y a
s { _foreignIncome = b })
cgtEvents :: Lens' (TaxReturnInfo y a) [CGTEvent a]
cgtEvents :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
([CGTEvent a] -> f [CGTEvent a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
cgtEvents = (TaxReturnInfo y a -> [CGTEvent a])
-> (TaxReturnInfo y a -> [CGTEvent a] -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a) (TaxReturnInfo y a) [CGTEvent a] [CGTEvent a]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> [CGTEvent a]
forall (y :: Nat) a. TaxReturnInfo y a -> [CGTEvent a]
_cgtEvents (\TaxReturnInfo y a
s [CGTEvent a]
b -> TaxReturnInfo y a
s { _cgtEvents = b })
deductions :: Lens' (TaxReturnInfo y a) (Deductions a)
deductions :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Deductions a -> f (Deductions a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
deductions = (TaxReturnInfo y a -> Deductions a)
-> (TaxReturnInfo y a -> Deductions a -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
(Deductions a)
(Deductions a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Deductions a
forall (y :: Nat) a. TaxReturnInfo y a -> Deductions a
_deductions (\TaxReturnInfo y a
s Deductions a
b -> TaxReturnInfo y a
s { _deductions = b })
offsets :: Lens' (TaxReturnInfo y a) (Offsets a)
offsets :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Offsets a -> f (Offsets a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
offsets = (TaxReturnInfo y a -> Offsets a)
-> (TaxReturnInfo y a -> Offsets a -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a) (TaxReturnInfo y a) (Offsets a) (Offsets a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Offsets a
forall (y :: Nat) a. TaxReturnInfo y a -> Offsets a
_offsets (\TaxReturnInfo y a
s Offsets a
b -> TaxReturnInfo y a
s { _offsets = b })
privateHealthInsurancePolicyDetails
:: Lens' (TaxReturnInfo y a) [PrivateHealthInsurancePolicyDetail a]
privateHealthInsurancePolicyDetails :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PrivateHealthInsurancePolicyDetail a]
-> f [PrivateHealthInsurancePolicyDetail a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
privateHealthInsurancePolicyDetails = (TaxReturnInfo y a -> [PrivateHealthInsurancePolicyDetail a])
-> (TaxReturnInfo y a
-> [PrivateHealthInsurancePolicyDetail a] -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
[PrivateHealthInsurancePolicyDetail a]
[PrivateHealthInsurancePolicyDetail a]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> [PrivateHealthInsurancePolicyDetail a]
forall (y :: Nat) a.
TaxReturnInfo y a -> [PrivateHealthInsurancePolicyDetail a]
_phi (\TaxReturnInfo y a
s [PrivateHealthInsurancePolicyDetail a]
b -> TaxReturnInfo y a
s { _phi = b })
spouseDetails :: Lens' (TaxReturnInfo y a) (Maybe (SpouseDetails a))
spouseDetails :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Maybe (SpouseDetails a) -> f (Maybe (SpouseDetails a)))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
spouseDetails = (TaxReturnInfo y a -> Maybe (SpouseDetails a))
-> (TaxReturnInfo y a
-> Maybe (SpouseDetails a) -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
(Maybe (SpouseDetails a))
(Maybe (SpouseDetails a))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> Maybe (SpouseDetails a)
forall (y :: Nat) a. TaxReturnInfo y a -> Maybe (SpouseDetails a)
_spouseDetails (\TaxReturnInfo y a
s Maybe (SpouseDetails a)
b -> TaxReturnInfo y a
s { _spouseDetails = b })
incomeTests :: Lens' (TaxReturnInfo y a) (IncomeTests a)
incomeTests :: forall (y :: Nat) a (f :: * -> *).
Functor f =>
(IncomeTests a -> f (IncomeTests a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
incomeTests = (TaxReturnInfo y a -> IncomeTests a)
-> (TaxReturnInfo y a -> IncomeTests a -> TaxReturnInfo y a)
-> Lens
(TaxReturnInfo y a)
(TaxReturnInfo y a)
(IncomeTests a)
(IncomeTests a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxReturnInfo y a -> IncomeTests a
forall (y :: Nat) a. TaxReturnInfo y a -> IncomeTests a
_incomeTests (\TaxReturnInfo y a
s IncomeTests a
b -> TaxReturnInfo y a
s { _incomeTests = b })
data TaxAssessment a = TaxAssessment
{ forall a. TaxAssessment a -> Money a
_taxableIncome :: Money a
, forall a. TaxAssessment a -> Money a
_taxDue :: Money a
, forall a. TaxAssessment a -> Money a
_medicareLevyDue :: Money a
, forall a. TaxAssessment a -> Money a
_taxWithheld :: Money a
, forall a. TaxAssessment a -> Money a
_taxCreditsAndOffsets :: Money a
, forall a. TaxAssessment a -> CGTAssessment a
_taCGTAssessment :: CGTAssessment a
, forall a. TaxAssessment a -> Money a
_phiAdj :: Money a
, forall a. TaxAssessment a -> Money a
_studyAndTrainingLoanRepayment :: Money a
, forall a. TaxAssessment a -> Money a
_paygInstalmentsCredit :: Money a
}
instance HasTaxableIncome TaxAssessment a a where
taxableIncome :: Getter (TaxAssessment a) (Money a)
taxableIncome = (TaxAssessment a -> Money a)
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_taxableIncome
instance HasTaxWithheld TaxAssessment a a where
taxWithheld :: Getter (TaxAssessment a) (Money a)
taxWithheld = (TaxAssessment a -> Money a)
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_taxWithheld
taxDue :: Getter (TaxAssessment a) (Money a)
taxDue :: forall a. Getter (TaxAssessment a) (Money a)
taxDue = (TaxAssessment a -> Money a)
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_taxDue
medicareLevyDue :: Getter (TaxAssessment a) (Money a)
medicareLevyDue :: forall a. Getter (TaxAssessment a) (Money a)
medicareLevyDue = (TaxAssessment a -> Money a)
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_medicareLevyDue
taxCreditsAndOffsets :: Getter (TaxAssessment a) (Money a)
taxCreditsAndOffsets :: forall a. Getter (TaxAssessment a) (Money a)
taxCreditsAndOffsets = (TaxAssessment a -> Money a)
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_taxCreditsAndOffsets
taxCGTAssessment :: Lens' (TaxAssessment a) (CGTAssessment a)
taxCGTAssessment :: forall a (f :: * -> *).
Functor f =>
(CGTAssessment a -> f (CGTAssessment a))
-> TaxAssessment a -> f (TaxAssessment a)
taxCGTAssessment = (TaxAssessment a -> CGTAssessment a)
-> (TaxAssessment a -> CGTAssessment a -> TaxAssessment a)
-> Lens
(TaxAssessment a)
(TaxAssessment a)
(CGTAssessment a)
(CGTAssessment a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxAssessment a -> CGTAssessment a
forall a. TaxAssessment a -> CGTAssessment a
_taCGTAssessment (\TaxAssessment a
s CGTAssessment a
b -> TaxAssessment a
s { _taCGTAssessment = b })
studyAndTrainingLoanRepayment :: Lens' (TaxAssessment a) (Money a)
studyAndTrainingLoanRepayment :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
studyAndTrainingLoanRepayment =
(TaxAssessment a -> Money a)
-> (TaxAssessment a -> Money a -> TaxAssessment a)
-> Lens (TaxAssessment a) (TaxAssessment a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_studyAndTrainingLoanRepayment (\TaxAssessment a
s Money a
b -> TaxAssessment a
s { _studyAndTrainingLoanRepayment = b })
privateHealthInsuranceRebateAdjustment :: Lens' (TaxAssessment a) (Money a)
privateHealthInsuranceRebateAdjustment :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
privateHealthInsuranceRebateAdjustment = (TaxAssessment a -> Money a)
-> (TaxAssessment a -> Money a -> TaxAssessment a)
-> Lens (TaxAssessment a) (TaxAssessment a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_phiAdj (\TaxAssessment a
s Money a
b -> TaxAssessment a
s { _phiAdj = b })
paygInstalmentsCredit :: Lens' (TaxAssessment a) (Money a)
paygInstalmentsCredit :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
paygInstalmentsCredit =
(TaxAssessment a -> Money a)
-> (TaxAssessment a -> Money a -> TaxAssessment a)
-> Lens (TaxAssessment a) (TaxAssessment a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TaxAssessment a -> Money a
forall a. TaxAssessment a -> Money a
_paygInstalmentsCredit (\TaxAssessment a
s Money a
b -> TaxAssessment a
s { _paygInstalmentsCredit = b })
taxBalance :: Num a => Getter (TaxAssessment a) (Money a)
taxBalance :: forall a. Num a => Getter (TaxAssessment a) (Money a)
taxBalance = (TaxAssessment a -> Money a)
-> Optic' (->) f (TaxAssessment a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((TaxAssessment a -> Money a)
-> Optic' (->) f (TaxAssessment a) (Money a))
-> (TaxAssessment a -> Money a)
-> Optic' (->) f (TaxAssessment a) (Money a)
forall a b. (a -> b) -> a -> b
$ \TaxAssessment a
a ->
Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter (TaxAssessment a) (Money a)
taxWithheld TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a. Getter (TaxAssessment a) (Money a)
taxDue TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a. Getter (TaxAssessment a) (Money a)
medicareLevyDue TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
studyAndTrainingLoanRepayment TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
privateHealthInsuranceRebateAdjustment TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$+$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a. Getter (TaxAssessment a) (Money a)
taxCreditsAndOffsets TaxAssessment a
a
Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$+$ Getting (Money a) (TaxAssessment a) (Money a)
-> TaxAssessment a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxAssessment a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> TaxAssessment a -> f (TaxAssessment a)
paygInstalmentsCredit TaxAssessment a
a
instance (Num a, Eq a) => HasCapitalLossCarryForward TaxAssessment a where
capitalLossCarryForward :: Lens' (TaxAssessment a) (Money a)
capitalLossCarryForward = (CGTAssessment a -> f (CGTAssessment a))
-> TaxAssessment a -> f (TaxAssessment a)
forall a (f :: * -> *).
Functor f =>
(CGTAssessment a -> f (CGTAssessment a))
-> TaxAssessment a -> f (TaxAssessment a)
taxCGTAssessment ((CGTAssessment a -> f (CGTAssessment a))
-> TaxAssessment a -> f (TaxAssessment a))
-> ((Money a -> f (Money a))
-> CGTAssessment a -> f (CGTAssessment a))
-> (Money a -> f (Money a))
-> TaxAssessment a
-> f (TaxAssessment a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> f (Money a)) -> CGTAssessment a -> f (CGTAssessment a)
Lens' (CGTAssessment a) (Money a)
forall (a :: * -> *) b.
HasCapitalLossCarryForward a b =>
Lens' (a b) (Money b)
capitalLossCarryForward
individualTax
:: (Fractional a, Ord a)
=> TaxTables y a
-> Tax (Money a) (Money a)
individualTax :: forall {k} a (y :: k).
(Fractional a, Ord a) =>
TaxTables y a -> Tax (Money a) (Money a)
individualTax TaxTables y a
table =
Tax (Money a) (Money a)
-> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a b. Ord a => Tax b a -> Tax b a -> Tax b a
greaterOf Tax (Money a) (Money a)
forall a. Monoid a => a
mempty (TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttIndividualIncomeTax TaxTables y a
table Tax (Money a) (Money a)
-> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a. Semigroup a => a -> a -> a
<> TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttAdditional TaxTables y a
table)
studyAndTrainingLoanRepaymentTax
:: (Fractional a, Ord a)
=> TaxTables y a
-> TaxReturnInfo y a
-> Tax (Money a) (Money a)
studyAndTrainingLoanRepaymentTax :: forall a (y :: Nat).
(Fractional a, Ord a) =>
TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
studyAndTrainingLoanRepaymentTax TaxTables y a
table TaxReturnInfo y a
info =
Money a -> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a b. Ord a => a -> Tax b a -> Tax b a
limit (Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
helpBalance TaxReturnInfo y a
info) (TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttHelp TaxTables y a
table)
Tax (Money a) (Money a)
-> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a. Semigroup a => a -> a -> a
<> Money a -> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a b. Ord a => a -> Tax b a -> Tax b a
limit (Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
sfssBalance TaxReturnInfo y a
info) (TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttSfss TaxTables y a
table)
medicareLevyTax
:: (FinancialYear y, Fractional a)
=> TaxTables y a
-> TaxReturnInfo y a
-> Tax (Money a) (Money a)
medicareLevyTax :: forall (y :: Nat) a.
(FinancialYear y, Fractional a) =>
TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
medicareLevyTax TaxTables y a
table TaxReturnInfo y a
info =
let
ml :: Tax (Money a) (Money a)
ml = TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttMedicareLevy TaxTables y a
table
mls :: Tax (Money a) (Money a)
mls = TaxTables y a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttMedicareLevySurcharge TaxTables y a
table
mlsFrac :: a
mlsFrac = a
1 a -> a -> a
forall a. Num a => a -> a -> a
- Days y -> a
forall (a :: Nat) frac.
(FinancialYear a, Fractional frac) =>
Days a -> frac
getFraction (Getting (Days y) (TaxReturnInfo y a) (Days y)
-> TaxReturnInfo y a -> Days y
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Days y) (TaxReturnInfo y a) (Days y)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Days y -> f (Days y))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
mlsExemption TaxReturnInfo y a
info)
in
Tax (Money a) (Money a)
ml
Tax (Money a) (Money a)
-> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a. Semigroup a => a -> a -> a
<> (Money a -> Money a)
-> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
forall a b. (a -> b) -> Tax (Money a) a -> Tax (Money a) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Money a -> a -> Money a
forall a. Num a => Money a -> a -> Money a
$* a
mlsFrac) Tax (Money a) (Money a)
mls
instance (RealFrac a) => HasTaxableIncome (TaxReturnInfo y) a a where
taxableIncome :: Getter (TaxReturnInfo y a) (Money a)
taxableIncome = (TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a))
-> (TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a)
forall a b. (a -> b) -> a -> b
$ \TaxReturnInfo y a
info ->
let
cf :: Money a
cf = Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
Lens' (TaxReturnInfo y a) (Money a)
forall (a :: * -> *) b.
HasCapitalLossCarryForward a b =>
Lens' (a b) (Money b)
capitalLossCarryForward TaxReturnInfo y a
info
gross :: Money a
gross = (Money a -> Money a) -> [Money a] -> Money a
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Money a -> Money a
forall a. RealFrac a => Money a -> Money a
wholeDollars
[ Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PaymentSummary a] -> f [PaymentSummary a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
paymentSummaries (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a]
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter [PaymentSummary a] (Money a)
taxableIncome) TaxReturnInfo y a
info
, Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(GrossAndWithheld a -> f (GrossAndWithheld a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
interest ((GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter (GrossAndWithheld a) (Money a)
taxableIncome) TaxReturnInfo y a
info
, Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (([Dividend a] -> Const (Money a) [Dividend a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([Dividend a] -> f [Dividend a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
dividends (([Dividend a] -> Const (Money a) [Dividend a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [Dividend a] -> Const (Money a) [Dividend a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> [Dividend a] -> Const (Money a) [Dividend a]
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter [Dividend a] (Money a)
taxableIncome) TaxReturnInfo y a
info
, Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((ESSStatement a -> Const (Money a) (ESSStatement a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(ESSStatement a -> f (ESSStatement a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
ess ((ESSStatement a -> Const (Money a) (ESSStatement a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> ESSStatement a -> Const (Money a) (ESSStatement a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> ESSStatement a -> Const (Money a) (ESSStatement a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter (ESSStatement a) (Money a)
taxableIncome) TaxReturnInfo y a
info
, Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (([CGTEvent a] -> Const (Money a) [CGTEvent a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([CGTEvent a] -> f [CGTEvent a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
cgtEvents (([CGTEvent a] -> Const (Money a) [CGTEvent a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [CGTEvent a] -> Const (Money a) [CGTEvent a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([CGTEvent a] -> CGTAssessment a)
-> (CGTAssessment a -> Const (Money a) (CGTAssessment a))
-> [CGTEvent a]
-> Const (Money a) [CGTEvent a]
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (Money a -> [CGTEvent a] -> CGTAssessment a
forall a (t :: * -> *).
(Fractional a, Ord a, Foldable t) =>
Money a -> t (CGTEvent a) -> CGTAssessment a
assessCGTEvents Money a
cf) ((CGTAssessment a -> Const (Money a) (CGTAssessment a))
-> [CGTEvent a] -> Const (Money a) [CGTEvent a])
-> ((Money a -> Const (Money a) (Money a))
-> CGTAssessment a -> Const (Money a) (CGTAssessment a))
-> (Money a -> Const (Money a) (Money a))
-> [CGTEvent a]
-> Const (Money a) [CGTEvent a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> CGTAssessment a -> Const (Money a) (CGTAssessment a)
forall a. Num a => Getter (CGTAssessment a) (Money a)
Getter (CGTAssessment a) (Money a)
cgtNetGain) TaxReturnInfo y a
info
, Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
foreignIncome TaxReturnInfo y a
info
]
in
Money a -> Money a
forall a. RealFrac a => Money a -> Money a
wholeDollars (Money a
gross Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ LensLike' (Const (Money a)) (TaxReturnInfo y a) (Deductions a)
-> (Deductions a -> Money a) -> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) r a.
MonadReader s m =>
LensLike' (Const r) s a -> (a -> r) -> m r
views LensLike' (Const (Money a)) (TaxReturnInfo y a) (Deductions a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Deductions a -> f (Deductions a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
deductions Deductions a -> Money a
forall a. (Num a, Ord a) => Deductions a -> Money a
totalDeductions TaxReturnInfo y a
info)
instance (Num a) => HasTaxWithheld (TaxReturnInfo y) a a where
taxWithheld :: Getter (TaxReturnInfo y a) (Money a)
taxWithheld = (TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a))
-> (TaxReturnInfo y a -> Money a)
-> Optic' (->) f (TaxReturnInfo y a) (Money a)
forall a b. (a -> b) -> a -> b
$ \TaxReturnInfo y a
info ->
Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PaymentSummary a] -> f [PaymentSummary a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
paymentSummaries (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a]
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter [PaymentSummary a] (Money a)
taxWithheld) TaxReturnInfo y a
info
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(GrossAndWithheld a -> f (GrossAndWithheld a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
interest ((GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> GrossAndWithheld a -> Const (Money a) (GrossAndWithheld a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter (GrossAndWithheld a) (Money a)
taxWithheld) TaxReturnInfo y a
info
assessTax
:: (FinancialYear y, RealFrac a)
=> TaxTables y a -> TaxReturnInfo y a -> TaxAssessment a
assessTax :: forall (y :: Nat) a.
(FinancialYear y, RealFrac a) =>
TaxTables y a -> TaxReturnInfo y a -> TaxAssessment a
assessTax TaxTables y a
tables TaxReturnInfo y a
info =
let
cg :: CGTAssessment a
cg = Money a -> [CGTEvent a] -> CGTAssessment a
forall a (t :: * -> *).
(Fractional a, Ord a, Foldable t) =>
Money a -> t (CGTEvent a) -> CGTAssessment a
assessCGTEvents
(Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
Lens' (TaxReturnInfo y a) (Money a)
forall (a :: * -> *) b.
HasCapitalLossCarryForward a b =>
Lens' (a b) (Money b)
capitalLossCarryForward TaxReturnInfo y a
info) (Getting [CGTEvent a] (TaxReturnInfo y a) [CGTEvent a]
-> TaxReturnInfo y a -> [CGTEvent a]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting [CGTEvent a] (TaxReturnInfo y a) [CGTEvent a]
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([CGTEvent a] -> f [CGTEvent a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
cgtEvents TaxReturnInfo y a
info)
taxable :: Money a
taxable = Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter (TaxReturnInfo y a) (Money a)
taxableIncome TaxReturnInfo y a
info
due :: Money a
due = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax (TaxTables y a -> Tax (Money a) (Money a)
forall {k} a (y :: k).
(Fractional a, Ord a) =>
TaxTables y a -> Tax (Money a) (Money a)
individualTax TaxTables y a
tables) Money a
taxable
studyRepayment :: Money a
studyRepayment = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax (TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
forall a (y :: Nat).
(Fractional a, Ord a) =>
TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
studyAndTrainingLoanRepaymentTax TaxTables y a
tables TaxReturnInfo y a
info) Money a
taxable
mlAndMLS :: Money a
mlAndMLS = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax (TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
forall (y :: Nat) a.
(FinancialYear y, Fractional a) =>
TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
medicareLevyTax TaxTables y a
tables TaxReturnInfo y a
info) Money a
taxable
incomeForSurchargePurposes :: Money a
incomeForSurchargePurposes =
Money a
taxable
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall a s. Getting a s a -> s -> a
foldOf (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PaymentSummary a] -> f [PaymentSummary a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
paymentSummaries (([PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PaymentSummary a -> Const (Money a) (PaymentSummary a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((PaymentSummary a -> Const (Money a) (PaymentSummary a))
-> [PaymentSummary a] -> Const (Money a) [PaymentSummary a])
-> ((Money a -> Const (Money a) (Money a))
-> PaymentSummary a -> Const (Money a) (PaymentSummary a))
-> (Money a -> Const (Money a) (Money a))
-> [PaymentSummary a]
-> Const (Money a) [PaymentSummary a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PaymentSummary a -> Money a)
-> (Money a -> Const (Money a) (Money a))
-> PaymentSummary a
-> Const (Money a) (PaymentSummary a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to PaymentSummary a -> Money a
forall a. PaymentSummary a -> Money a
reportableEmployerSuperannuationContributions) TaxReturnInfo y a
info
spouseIncomeForSurchargePurposes :: Maybe (Money a)
spouseIncomeForSurchargePurposes =
(SpouseDetails a -> Money a)
-> Maybe (SpouseDetails a) -> Maybe (Money a)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting (Money a) (SpouseDetails a) (Money a)
-> SpouseDetails a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (SpouseDetails a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> SpouseDetails a -> f (SpouseDetails a)
spouseTaxableIncome) (Getting
(Maybe (SpouseDetails a))
(TaxReturnInfo y a)
(Maybe (SpouseDetails a))
-> TaxReturnInfo y a -> Maybe (SpouseDetails a)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(Maybe (SpouseDetails a))
(TaxReturnInfo y a)
(Maybe (SpouseDetails a))
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Maybe (SpouseDetails a) -> f (Maybe (SpouseDetails a)))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
spouseDetails TaxReturnInfo y a
info)
phiAdj :: Money a
phiAdj = Money a
-> Maybe (Money a)
-> Integer
-> PrivateHealthInsuranceRebateRates a
-> [PrivateHealthInsurancePolicyDetail a]
-> Money a
forall a.
RealFrac a =>
Money a
-> Maybe (Money a)
-> Integer
-> PrivateHealthInsuranceRebateRates a
-> [PrivateHealthInsurancePolicyDetail a]
-> Money a
assessExcessPrivateHealthRebate
Money a
incomeForSurchargePurposes
Maybe (Money a)
spouseIncomeForSurchargePurposes
(Getting Integer (TaxReturnInfo y a) Integer
-> TaxReturnInfo y a -> Integer
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((IncomeTests a -> Const Integer (IncomeTests a))
-> TaxReturnInfo y a -> Const Integer (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(IncomeTests a -> f (IncomeTests a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
incomeTests ((IncomeTests a -> Const Integer (IncomeTests a))
-> TaxReturnInfo y a -> Const Integer (TaxReturnInfo y a))
-> ((Integer -> Const Integer Integer)
-> IncomeTests a -> Const Integer (IncomeTests a))
-> Getting Integer (TaxReturnInfo y a) Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Integer -> Const Integer Integer)
-> IncomeTests a -> Const Integer (IncomeTests a)
forall a (f :: * -> *).
Functor f =>
(Integer -> f Integer) -> IncomeTests a -> f (IncomeTests a)
dependentChildren) TaxReturnInfo y a
info)
(TaxTables y a -> PrivateHealthInsuranceRebateRates a
forall {k} (y :: k) a.
TaxTables y a -> PrivateHealthInsuranceRebateRates a
ttPHIRebateRates TaxTables y a
tables)
(Getting
[PrivateHealthInsurancePolicyDetail a]
(TaxReturnInfo y a)
[PrivateHealthInsurancePolicyDetail a]
-> TaxReturnInfo y a -> [PrivateHealthInsurancePolicyDetail a]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
[PrivateHealthInsurancePolicyDetail a]
(TaxReturnInfo y a)
[PrivateHealthInsurancePolicyDetail a]
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([PrivateHealthInsurancePolicyDetail a]
-> f [PrivateHealthInsurancePolicyDetail a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
privateHealthInsurancePolicyDetails TaxReturnInfo y a
info)
foreignIncomeTaxOffsetLimit :: Money a
foreignIncomeTaxOffsetLimit =
let
step1 :: Money a
step1 = Money a
due Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
mlAndMLS
step2 :: Money a
step2 =
let
info' :: TaxReturnInfo y a
info' = TaxReturnInfo y a
info TaxReturnInfo y a
-> (TaxReturnInfo y a -> TaxReturnInfo y a) -> TaxReturnInfo y a
forall a b. a -> (a -> b) -> b
& ASetter (TaxReturnInfo y a) (TaxReturnInfo y a) (Money a) (Money a)
-> Money a -> TaxReturnInfo y a -> TaxReturnInfo y a
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter (TaxReturnInfo y a) (TaxReturnInfo y a) (Money a) (Money a)
forall (y :: Nat) a. Lens' (TaxReturnInfo y a) (Money a)
foreignIncome Money a
forall a. Monoid a => a
mempty
taxable' :: Money a
taxable' =
Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter (TaxReturnInfo y a) (Money a)
taxableIncome TaxReturnInfo y a
info'
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((Deductions a -> Const (Money a) (Deductions a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Deductions a -> f (Deductions a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
deductions ((Deductions a -> Const (Money a) (Deductions a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> Deductions a -> Const (Money a) (Deductions a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> Deductions a -> Const (Money a) (Deductions a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
foreignIncomeDeductions) TaxReturnInfo y a
info'
due' :: Money a
due' = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax (TaxTables y a -> Tax (Money a) (Money a)
forall {k} a (y :: k).
(Fractional a, Ord a) =>
TaxTables y a -> Tax (Money a) (Money a)
individualTax TaxTables y a
tables) Money a
taxable'
mlAndMLS' :: Money a
mlAndMLS' = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax (TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
forall (y :: Nat) a.
(FinancialYear y, Fractional a) =>
TaxTables y a -> TaxReturnInfo y a -> Tax (Money a) (Money a)
medicareLevyTax TaxTables y a
tables TaxReturnInfo y a
info') Money a
taxable'
in
Money a
due' Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
mlAndMLS'
step3 :: Money a
step3 = Money a
step1 Money a -> Money a -> Money a
forall a. Num a => Money a -> Money a -> Money a
$-$ Money a
step2
in
Money a -> Money a -> Money a
forall a. Ord a => a -> a -> a
max (a -> Money a
forall num. num -> Money num
Money a
1000) Money a
step3
frankingCredit :: Money a
frankingCredit = Money a -> Money a
forall a. RealFrac a => Money a -> Money a
wholeDollars (Money a -> Money a) -> Money a -> Money a
forall a b. (a -> b) -> a -> b
$ Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (([Dividend a] -> Const (Money a) [Dividend a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
([Dividend a] -> f [Dividend a])
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
dividends (([Dividend a] -> Const (Money a) [Dividend a])
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> [Dividend a] -> Const (Money a) [Dividend a])
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> [Dividend a] -> Const (Money a) [Dividend a]
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter [Dividend a] (Money a)
taxWithheld) TaxReturnInfo y a
info
off :: Money a
off =
Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Offsets a -> f (Offsets a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
offsets ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
spouseContributionOffset) TaxReturnInfo y a
info
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a -> Money a -> Money a
forall a. Ord a => a -> a -> a
min (Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Offsets a -> f (Offsets a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
offsets ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
foreignTaxOffset) TaxReturnInfo y a
info) Money a
foreignIncomeTaxOffsetLimit
in
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> CGTAssessment a
-> Money a
-> Money a
-> Money a
-> TaxAssessment a
forall a.
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> CGTAssessment a
-> Money a
-> Money a
-> Money a
-> TaxAssessment a
TaxAssessment
Money a
taxable
Money a
due
Money a
mlAndMLS
(Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (TaxReturnInfo y a) (Money a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter (TaxReturnInfo y a) (Money a)
taxWithheld TaxReturnInfo y a
info)
(Money a
frankingCredit Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
off)
CGTAssessment a
cg
Money a
phiAdj
Money a
studyRepayment
(Getting (Money a) (TaxReturnInfo y a) (Money a)
-> TaxReturnInfo y a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a)
forall (y :: Nat) a (f :: * -> *).
Functor f =>
(Offsets a -> f (Offsets a))
-> TaxReturnInfo y a -> f (TaxReturnInfo y a)
offsets ((Offsets a -> Const (Money a) (Offsets a))
-> TaxReturnInfo y a -> Const (Money a) (TaxReturnInfo y a))
-> ((Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a))
-> Getting (Money a) (TaxReturnInfo y a) (Money a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Const (Money a) (Money a))
-> Offsets a -> Const (Money a) (Offsets a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
paygInstalments) TaxReturnInfo y a
info)
type ABN = String
data PaymentSummary a = PaymentSummary
{ forall a. PaymentSummary a -> ABN
summaryABN :: ABN
, forall a. PaymentSummary a -> Money a
summaryGross :: Money a
, forall a. PaymentSummary a -> Money a
summaryWithheld :: Money a
, forall a. PaymentSummary a -> Money a
reportableEmployerSuperannuationContributions :: Money a
}
instance HasTaxableIncome PaymentSummary a a where
taxableIncome :: Getter (PaymentSummary a) (Money a)
taxableIncome = (PaymentSummary a -> Money a)
-> (Money a -> f (Money a))
-> PaymentSummary a
-> f (PaymentSummary a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to PaymentSummary a -> Money a
forall a. PaymentSummary a -> Money a
summaryGross
instance HasTaxWithheld PaymentSummary a a where
taxWithheld :: Getter (PaymentSummary a) (Money a)
taxWithheld = (PaymentSummary a -> Money a)
-> (Money a -> f (Money a))
-> PaymentSummary a
-> f (PaymentSummary a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to PaymentSummary a -> Money a
forall a. PaymentSummary a -> Money a
summaryWithheld
newtype Proportion a = Proportion
{ forall a. Proportion a -> a
getProportion :: a
}
deriving (Int -> Proportion a -> ShowS
[Proportion a] -> ShowS
Proportion a -> ABN
(Int -> Proportion a -> ShowS)
-> (Proportion a -> ABN)
-> ([Proportion a] -> ShowS)
-> Show (Proportion a)
forall a. Show a => Int -> Proportion a -> ShowS
forall a. Show a => [Proportion a] -> ShowS
forall a. Show a => Proportion a -> ABN
forall a.
(Int -> a -> ShowS) -> (a -> ABN) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Proportion a -> ShowS
showsPrec :: Int -> Proportion a -> ShowS
$cshow :: forall a. Show a => Proportion a -> ABN
show :: Proportion a -> ABN
$cshowList :: forall a. Show a => [Proportion a] -> ShowS
showList :: [Proportion a] -> ShowS
Show, Proportion a -> Proportion a -> Bool
(Proportion a -> Proportion a -> Bool)
-> (Proportion a -> Proportion a -> Bool) -> Eq (Proportion a)
forall a. Eq a => Proportion a -> Proportion a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Proportion a -> Proportion a -> Bool
== :: Proportion a -> Proportion a -> Bool
$c/= :: forall a. Eq a => Proportion a -> Proportion a -> Bool
/= :: Proportion a -> Proportion a -> Bool
Eq, Eq (Proportion a)
Eq (Proportion a) =>
(Proportion a -> Proportion a -> Ordering)
-> (Proportion a -> Proportion a -> Bool)
-> (Proportion a -> Proportion a -> Bool)
-> (Proportion a -> Proportion a -> Bool)
-> (Proportion a -> Proportion a -> Bool)
-> (Proportion a -> Proportion a -> Proportion a)
-> (Proportion a -> Proportion a -> Proportion a)
-> Ord (Proportion a)
Proportion a -> Proportion a -> Bool
Proportion a -> Proportion a -> Ordering
Proportion a -> Proportion a -> Proportion a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Proportion a)
forall a. Ord a => Proportion a -> Proportion a -> Bool
forall a. Ord a => Proportion a -> Proportion a -> Ordering
forall a. Ord a => Proportion a -> Proportion a -> Proportion a
$ccompare :: forall a. Ord a => Proportion a -> Proportion a -> Ordering
compare :: Proportion a -> Proportion a -> Ordering
$c< :: forall a. Ord a => Proportion a -> Proportion a -> Bool
< :: Proportion a -> Proportion a -> Bool
$c<= :: forall a. Ord a => Proportion a -> Proportion a -> Bool
<= :: Proportion a -> Proportion a -> Bool
$c> :: forall a. Ord a => Proportion a -> Proportion a -> Bool
> :: Proportion a -> Proportion a -> Bool
$c>= :: forall a. Ord a => Proportion a -> Proportion a -> Bool
>= :: Proportion a -> Proportion a -> Bool
$cmax :: forall a. Ord a => Proportion a -> Proportion a -> Proportion a
max :: Proportion a -> Proportion a -> Proportion a
$cmin :: forall a. Ord a => Proportion a -> Proportion a -> Proportion a
min :: Proportion a -> Proportion a -> Proportion a
Ord)
proportion :: (Ord a, Num a) => a -> Proportion a
proportion :: forall a. (Ord a, Num a) => a -> Proportion a
proportion = a -> Proportion a
forall a. a -> Proportion a
Proportion (a -> Proportion a) -> (a -> a) -> a -> Proportion a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
forall a. Ord a => a -> a -> a
max a
0 (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
forall a. Ord a => a -> a -> a
min a
1
data Dividend a = Dividend
{ forall a. Dividend a -> ABN
dividendSource :: String
, forall a. Dividend a -> Day
dividendDate :: Day
, forall a. Dividend a -> GrossAndWithheld a
dividendGrossAndWithheld :: GrossAndWithheld a
}
instance (RealFrac a) => HasTaxWithheld Dividend a a where
taxWithheld :: Getter (Dividend a) (Money a)
taxWithheld = (Dividend a -> GrossAndWithheld a)
-> (GrossAndWithheld a -> f (GrossAndWithheld a))
-> Dividend a
-> f (Dividend a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Dividend a -> GrossAndWithheld a
forall a. Dividend a -> GrossAndWithheld a
dividendGrossAndWithheld ((GrossAndWithheld a -> f (GrossAndWithheld a))
-> Dividend a -> f (Dividend a))
-> ((Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a))
-> (Money a -> f (Money a))
-> Dividend a
-> f (Dividend a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxWithheld a b c =>
Getter (a b) (Money c)
Getter (GrossAndWithheld a) (Money a)
taxWithheld ((Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a))
-> ((Money a -> f (Money a)) -> Money a -> f (Money a))
-> (Money a -> f (Money a))
-> GrossAndWithheld a
-> f (GrossAndWithheld a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Money a)
-> (Money a -> f (Money a)) -> Money a -> f (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Money a -> Money a
forall a. RealFrac a => Money a -> Money a
roundCents
instance (RealFrac a) => HasTaxableIncome Dividend a a where
taxableIncome :: Getter (Dividend a) (Money a)
taxableIncome = (Dividend a -> GrossAndWithheld a)
-> (GrossAndWithheld a -> f (GrossAndWithheld a))
-> Dividend a
-> f (Dividend a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Dividend a -> GrossAndWithheld a
forall a. Dividend a -> GrossAndWithheld a
dividendGrossAndWithheld ((GrossAndWithheld a -> f (GrossAndWithheld a))
-> Dividend a -> f (Dividend a))
-> ((Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a))
-> (Money a -> f (Money a))
-> Dividend a
-> f (Dividend a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a)
forall {k} (a :: k -> *) (b :: k) c.
HasTaxableIncome a b c =>
Getter (a b) (Money c)
Getter (GrossAndWithheld a) (Money a)
taxableIncome ((Money a -> f (Money a))
-> GrossAndWithheld a -> f (GrossAndWithheld a))
-> ((Money a -> f (Money a)) -> Money a -> f (Money a))
-> (Money a -> f (Money a))
-> GrossAndWithheld a
-> f (GrossAndWithheld a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Money a -> Money a)
-> (Money a -> f (Money a)) -> Money a -> f (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Money a -> Money a
forall a. RealFrac a => Money a -> Money a
roundCents
dividendFromNetFranked
:: (Fractional a)
=> String
-> Day
-> Money a
-> Proportion a
-> Tax (Money a) (Money a)
-> Dividend a
dividendFromNetFranked :: forall a.
Fractional a =>
ABN
-> Day
-> Money a
-> Proportion a
-> Tax (Money a) (Money a)
-> Dividend a
dividendFromNetFranked ABN
src Day
date Money a
net Proportion a
franked Tax (Money a) (Money a)
rate =
ABN -> Day -> Money a -> Money a -> Dividend a
forall a. ABN -> Day -> Money a -> Money a -> Dividend a
dividendFromGross ABN
src Day
date Money a
gross Money a
withheld
where
Money a
r = Tax (Money a) (Money a) -> Money a -> Money a
forall a b. Tax a b -> a -> b
getTax Tax (Money a) (Money a)
rate (a -> Money a
forall num. num -> Money num
Money a
1)
withheld :: Money a
withheld = Money a
net Money a -> a -> Money a
forall a. Num a => Money a -> a -> Money a
$* ( Proportion a -> a
forall a. Proportion a -> a
getProportion Proportion a
franked a -> a -> a
forall a. Num a => a -> a -> a
* a
r a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
r) )
gross :: Money a
gross = Money a
net Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
withheld
dividendFromNetFranked30
:: (Fractional a)
=> String
-> Day
-> Money a
-> Proportion a
-> Dividend a
dividendFromNetFranked30 :: forall a.
Fractional a =>
ABN -> Day -> Money a -> Proportion a -> Dividend a
dividendFromNetFranked30 ABN
src Day
date Money a
net Proportion a
franked =
ABN
-> Day
-> Money a
-> Proportion a
-> Tax (Money a) (Money a)
-> Dividend a
forall a.
Fractional a =>
ABN
-> Day
-> Money a
-> Proportion a
-> Tax (Money a) (Money a)
-> Dividend a
dividendFromNetFranked ABN
src Day
date Money a
net Proportion a
franked Tax (Money a) (Money a)
forall a. Fractional a => Tax (Money a) (Money a)
corporateTax
dividendFromNet
:: (Num a)
=> String
-> Day
-> Money a
-> Money a
-> Dividend a
dividendFromNet :: forall a. Num a => ABN -> Day -> Money a -> Money a -> Dividend a
dividendFromNet ABN
src Day
date Money a
net Money a
withheld =
ABN -> Day -> Money a -> Money a -> Dividend a
forall a. ABN -> Day -> Money a -> Money a -> Dividend a
dividendFromGross ABN
src Day
date (Money a
net Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
withheld) Money a
withheld
dividendFromGross
:: String
-> Day
-> Money a
-> Money a
-> Dividend a
dividendFromGross :: forall a. ABN -> Day -> Money a -> Money a -> Dividend a
dividendFromGross ABN
src Day
date Money a
gross Money a
withheld =
ABN -> Day -> GrossAndWithheld a -> Dividend a
forall a. ABN -> Day -> GrossAndWithheld a -> Dividend a
Dividend ABN
src Day
date (Money a -> Money a -> GrossAndWithheld a
forall a. Money a -> Money a -> GrossAndWithheld a
GrossAndWithheld Money a
gross Money a
withheld)
data Offsets a = Offsets
{ forall a. Offsets a -> Money a
_spouseOffset :: Money a
, forall a. Offsets a -> Money a
_foreignTaxOffset :: Money a
, forall a. Offsets a -> Money a
_paygInstalments :: Money a
}
instance Num a => Semigroup (Offsets a) where
Offsets Money a
a Money a
b Money a
c <> :: Offsets a -> Offsets a -> Offsets a
<> Offsets Money a
a' Money a
b' Money a
c' = Money a -> Money a -> Money a -> Offsets a
forall a. Money a -> Money a -> Money a -> Offsets a
Offsets (Money a
a Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
a') (Money a
b Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
b') (Money a
c Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
c')
instance Num a => Monoid (Offsets a) where
mempty :: Offsets a
mempty = Money a -> Money a -> Money a -> Offsets a
forall a. Money a -> Money a -> Money a -> Offsets a
Offsets Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty
mappend :: Offsets a -> Offsets a -> Offsets a
mappend = Offsets a -> Offsets a -> Offsets a
forall a. Semigroup a => a -> a -> a
(<>)
spouseContributionOffset :: Lens' (Offsets a) (Money a)
spouseContributionOffset :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
spouseContributionOffset = (Offsets a -> Money a)
-> (Offsets a -> Money a -> Offsets a)
-> Lens (Offsets a) (Offsets a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Offsets a -> Money a
forall a. Offsets a -> Money a
_spouseOffset (\Offsets a
s Money a
b -> Offsets a
s { _spouseOffset = b })
foreignTaxOffset :: Lens' (Offsets a) (Money a)
foreignTaxOffset :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
foreignTaxOffset = (Offsets a -> Money a)
-> (Offsets a -> Money a -> Offsets a)
-> Lens (Offsets a) (Offsets a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Offsets a -> Money a
forall a. Offsets a -> Money a
_foreignTaxOffset (\Offsets a
s Money a
b -> Offsets a
s { _foreignTaxOffset = b })
paygInstalments :: Lens' (Offsets a) (Money a)
paygInstalments :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Offsets a -> f (Offsets a)
paygInstalments = (Offsets a -> Money a)
-> (Offsets a -> Money a -> Offsets a)
-> Lens (Offsets a) (Offsets a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Offsets a -> Money a
forall a. Offsets a -> Money a
_paygInstalments (\Offsets a
s Money a
b -> Offsets a
s { _paygInstalments = b })
data Deductions a = Deductions
{ forall a. Deductions a -> Money a
_workRelatedCarExpenses :: Money a
, forall a. Deductions a -> Money a
_workRelatedTravelExpenses :: Money a
, forall a. Deductions a -> Money a
_workRelatedClothingLaundryAndDryCleaningExpenses :: Money a
, forall a. Deductions a -> Money a
_workRelatedSelfEducationExpenses :: Money a
, forall a. Deductions a -> Money a
_otherWorkRelatedExpenses :: Money a
, forall a. Deductions a -> Money a
_lowValuePoolDeduction :: Money a
, forall a. Deductions a -> Money a
_interestDeductions :: Money a
, forall a. Deductions a -> Money a
_dividendDeductions :: Money a
, forall a. Deductions a -> Money a
_giftsOrDonations :: Money a
, forall a. Deductions a -> Money a
_costOfManagingTaxAffairs :: Money a
, forall a. Deductions a -> Money a
_deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity :: Money a
, forall a. Deductions a -> Money a
_personalSuperannuationContributions :: Money a
, forall a. Deductions a -> Money a
_deductionForProjectPool :: Money a
, forall a. Deductions a -> Money a
_forestryManagedInvestmentSchemeDeduction :: Money a
, forall a. Deductions a -> Money a
_otherDeductions :: Money a
, forall a. Deductions a -> Money a
_foreignIncomeDeductions :: Money a
}
instance Num a => Semigroup (Deductions a) where
Deductions Money a
a Money a
b Money a
c Money a
d Money a
e Money a
f Money a
g Money a
h Money a
i Money a
j Money a
k Money a
l Money a
m Money a
n Money a
o Money a
p
<> :: Deductions a -> Deductions a -> Deductions a
<> Deductions Money a
a' Money a
b' Money a
c' Money a
d' Money a
e' Money a
f' Money a
g' Money a
h' Money a
i' Money a
j' Money a
k' Money a
l' Money a
m' Money a
n' Money a
o' Money a
p'
= Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Deductions a
forall a.
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Deductions a
Deductions (Money a
a Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
a') (Money a
b Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
b') (Money a
c Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
c') (Money a
d Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
d') (Money a
e Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
e') (Money a
f Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
f') (Money a
g Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
g') (Money a
h Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
h')
(Money a
i Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
i') (Money a
j Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
j') (Money a
k Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
k') (Money a
l Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
l') (Money a
m Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
m') (Money a
n Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
n') (Money a
o Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
o') (Money a
p Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
p')
instance Num a => Monoid (Deductions a) where
mempty :: Deductions a
mempty = Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Deductions a
forall a.
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Deductions a
Deductions Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty
Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty
totalDeductions :: (Num a, Ord a) => Deductions a -> Money a
totalDeductions :: forall a. (Num a, Ord a) => Deductions a -> Money a
totalDeductions Deductions a
a =
(Money a -> Money a) -> [Money a] -> Money a
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Money a -> Money a -> Money a
forall a. Ord a => a -> a -> a
max Money a
forall a. Monoid a => a
mempty)
[ Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedCarExpenses Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedTravelExpenses Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedClothingLaundryAndDryCleaningExpenses Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedSelfEducationExpenses Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
otherWorkRelatedExpenses Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
lowValuePoolDeduction Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
interestDeductions Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
dividendDeductions Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
giftsOrDonations Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
costOfManagingTaxAffairs Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
personalSuperannuationContributions Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
deductionForProjectPool Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
forestryManagedInvestmentSchemeDeduction Deductions a
a
, Getting (Money a) (Deductions a) (Money a)
-> Deductions a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (Deductions a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
otherDeductions Deductions a
a
]
workRelatedCarExpenses :: Lens' (Deductions a) (Money a)
workRelatedCarExpenses :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedCarExpenses =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_workRelatedCarExpenses (\Deductions a
s Money a
b -> Deductions a
s { _workRelatedCarExpenses = b })
workRelatedTravelExpenses :: Lens' (Deductions a) (Money a)
workRelatedTravelExpenses :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedTravelExpenses =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_workRelatedTravelExpenses (\Deductions a
s Money a
b -> Deductions a
s { _workRelatedTravelExpenses = b })
workRelatedClothingLaundryAndDryCleaningExpenses :: Lens' (Deductions a) (Money a)
workRelatedClothingLaundryAndDryCleaningExpenses :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedClothingLaundryAndDryCleaningExpenses =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Deductions a -> Money a
forall a. Deductions a -> Money a
_workRelatedClothingLaundryAndDryCleaningExpenses
(\Deductions a
s Money a
b -> Deductions a
s { _workRelatedClothingLaundryAndDryCleaningExpenses = b })
workRelatedSelfEducationExpenses :: Lens' (Deductions a) (Money a)
workRelatedSelfEducationExpenses :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
workRelatedSelfEducationExpenses =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_workRelatedSelfEducationExpenses (\Deductions a
s Money a
b -> Deductions a
s { _workRelatedSelfEducationExpenses = b })
otherWorkRelatedExpenses :: Lens' (Deductions a) (Money a)
otherWorkRelatedExpenses :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
otherWorkRelatedExpenses =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_otherWorkRelatedExpenses (\Deductions a
s Money a
b -> Deductions a
s { _otherWorkRelatedExpenses = b })
lowValuePoolDeduction :: Lens' (Deductions a) (Money a)
lowValuePoolDeduction :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
lowValuePoolDeduction =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_lowValuePoolDeduction (\Deductions a
s Money a
b -> Deductions a
s { _lowValuePoolDeduction = b })
interestDeductions :: Lens' (Deductions a) (Money a)
interestDeductions :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
interestDeductions =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_interestDeductions (\Deductions a
s Money a
b -> Deductions a
s { _interestDeductions = b })
dividendDeductions :: Lens' (Deductions a) (Money a)
dividendDeductions :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
dividendDeductions =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_dividendDeductions (\Deductions a
s Money a
b -> Deductions a
s { _dividendDeductions = b })
giftsOrDonations :: Lens' (Deductions a) (Money a)
giftsOrDonations :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
giftsOrDonations =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_giftsOrDonations (\Deductions a
s Money a
b -> Deductions a
s { _giftsOrDonations = b })
costOfManagingTaxAffairs :: Lens' (Deductions a) (Money a)
costOfManagingTaxAffairs :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
costOfManagingTaxAffairs =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_costOfManagingTaxAffairs (\Deductions a
s Money a
b -> Deductions a
s { _costOfManagingTaxAffairs = b })
deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity :: Lens' (Deductions a) (Money a)
deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Deductions a -> Money a
forall a. Deductions a -> Money a
_deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity
(\Deductions a
s Money a
b -> Deductions a
s { _deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity = b })
personalSuperannuationContributions :: Lens' (Deductions a) (Money a)
personalSuperannuationContributions :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
personalSuperannuationContributions =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_personalSuperannuationContributions (\Deductions a
s Money a
b -> Deductions a
s { _personalSuperannuationContributions = b })
deductionForProjectPool :: Lens' (Deductions a) (Money a)
deductionForProjectPool :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
deductionForProjectPool =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_deductionForProjectPool (\Deductions a
s Money a
b -> Deductions a
s { _deductionForProjectPool = b })
forestryManagedInvestmentSchemeDeduction :: Lens' (Deductions a) (Money a)
forestryManagedInvestmentSchemeDeduction :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
forestryManagedInvestmentSchemeDeduction =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
Deductions a -> Money a
forall a. Deductions a -> Money a
_forestryManagedInvestmentSchemeDeduction
(\Deductions a
s Money a
b -> Deductions a
s { _forestryManagedInvestmentSchemeDeduction = b })
otherDeductions :: Lens' (Deductions a) (Money a)
otherDeductions :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
otherDeductions =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_otherDeductions (\Deductions a
s Money a
b -> Deductions a
s { _otherDeductions = b })
foreignIncomeDeductions :: Lens' (Deductions a) (Money a)
foreignIncomeDeductions :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> Deductions a -> f (Deductions a)
foreignIncomeDeductions =
(Deductions a -> Money a)
-> (Deductions a -> Money a -> Deductions a)
-> Lens (Deductions a) (Deductions a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Deductions a -> Money a
forall a. Deductions a -> Money a
_foreignIncomeDeductions (\Deductions a
s Money a
b -> Deductions a
s { _foreignIncomeDeductions = b })
data GrossAndWithheld a = GrossAndWithheld (Money a) (Money a)
instance (Num a) => Semigroup (GrossAndWithheld a) where
GrossAndWithheld Money a
a Money a
b <> :: GrossAndWithheld a -> GrossAndWithheld a -> GrossAndWithheld a
<> GrossAndWithheld Money a
a' Money a
b' =
Money a -> Money a -> GrossAndWithheld a
forall a. Money a -> Money a -> GrossAndWithheld a
GrossAndWithheld (Money a
a Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
a') (Money a
b Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
b')
instance (Num a) => Monoid (GrossAndWithheld a) where
mempty :: GrossAndWithheld a
mempty = Money a -> Money a -> GrossAndWithheld a
forall a. Money a -> Money a -> GrossAndWithheld a
GrossAndWithheld Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty
mappend :: GrossAndWithheld a -> GrossAndWithheld a -> GrossAndWithheld a
mappend = GrossAndWithheld a -> GrossAndWithheld a -> GrossAndWithheld a
forall a. Semigroup a => a -> a -> a
(<>)
instance HasTaxableIncome GrossAndWithheld a a where
taxableIncome :: Getter (GrossAndWithheld a) (Money a)
taxableIncome = (GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a))
-> (GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a)
forall a b. (a -> b) -> a -> b
$ \(GrossAndWithheld Money a
a Money a
_) -> Money a
a
instance HasTaxWithheld GrossAndWithheld a a where
taxWithheld :: Getter (GrossAndWithheld a) (Money a)
taxWithheld = (GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a))
-> (GrossAndWithheld a -> Money a)
-> Optic' (->) f (GrossAndWithheld a) (Money a)
forall a b. (a -> b) -> a -> b
$ \(GrossAndWithheld Money a
_ Money a
a) -> Money a
a
data ESSStatement a = ESSStatement
{ forall a. ESSStatement a -> Money a
_taxedUpfrontReduction :: Money a
, forall a. ESSStatement a -> Money a
_taxedUpfrontNoReduction :: Money a
, forall a. ESSStatement a -> Money a
_deferral :: Money a
, forall a. ESSStatement a -> Money a
_pre2009 :: Money a
, forall a. ESSStatement a -> Money a
_tfnAmounts :: Money a
, forall a. ESSStatement a -> Money a
_foreignSourceDiscounts :: Money a
}
newESSStatement :: Num a => ESSStatement a
newESSStatement :: forall a. Num a => ESSStatement a
newESSStatement = Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> ESSStatement a
forall a.
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> ESSStatement a
ESSStatement Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty Money a
forall a. Monoid a => a
mempty
essTaxedUpfrontReduction :: Lens' (ESSStatement a) (Money a)
essTaxedUpfrontReduction :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essTaxedUpfrontReduction =
(ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_taxedUpfrontReduction (\ESSStatement a
s Money a
b -> ESSStatement a
s { _taxedUpfrontReduction = b })
essTaxedUpfrontNoReduction :: Lens' (ESSStatement a) (Money a)
essTaxedUpfrontNoReduction :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essTaxedUpfrontNoReduction =
(ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_taxedUpfrontNoReduction (\ESSStatement a
s Money a
b -> ESSStatement a
s { _taxedUpfrontNoReduction = b })
essDeferral :: Lens' (ESSStatement a) (Money a)
essDeferral :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essDeferral = (ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_deferral (\ESSStatement a
s Money a
b -> ESSStatement a
s { _deferral = b })
essPre2009 :: Lens' (ESSStatement a) (Money a)
essPre2009 :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essPre2009 = (ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_pre2009 (\ESSStatement a
s Money a
b -> ESSStatement a
s { _pre2009 = b })
essTFNAmounts :: Lens' (ESSStatement a) (Money a)
essTFNAmounts :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essTFNAmounts = (ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_tfnAmounts (\ESSStatement a
s Money a
b -> ESSStatement a
s { _tfnAmounts = b })
essForeignSourceDiscounts :: Lens' (ESSStatement a) (Money a)
essForeignSourceDiscounts :: forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essForeignSourceDiscounts =
(ESSStatement a -> Money a)
-> (ESSStatement a -> Money a -> ESSStatement a)
-> Lens (ESSStatement a) (ESSStatement a) (Money a) (Money a)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ESSStatement a -> Money a
forall a. ESSStatement a -> Money a
_foreignSourceDiscounts (\ESSStatement a
s Money a
b -> ESSStatement a
s { _foreignSourceDiscounts = b })
instance (Num a) => HasTaxableIncome ESSStatement a a where
taxableIncome :: Getter (ESSStatement a) (Money a)
taxableIncome = (ESSStatement a -> Money a)
-> Optic' (->) f (ESSStatement a) (Money a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((ESSStatement a -> Money a)
-> Optic' (->) f (ESSStatement a) (Money a))
-> (ESSStatement a -> Money a)
-> Optic' (->) f (ESSStatement a) (Money a)
forall a b. (a -> b) -> a -> b
$ \ESSStatement a
s ->
Getting (Money a) (ESSStatement a) (Money a)
-> ESSStatement a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (ESSStatement a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essTaxedUpfrontReduction ESSStatement a
s
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (ESSStatement a) (Money a)
-> ESSStatement a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (ESSStatement a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essTaxedUpfrontNoReduction ESSStatement a
s
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (ESSStatement a) (Money a)
-> ESSStatement a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (ESSStatement a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essDeferral ESSStatement a
s
Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Getting (Money a) (ESSStatement a) (Money a)
-> ESSStatement a -> Money a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Money a) (ESSStatement a) (Money a)
forall a (f :: * -> *).
Functor f =>
(Money a -> f (Money a)) -> ESSStatement a -> f (ESSStatement a)
essPre2009 ESSStatement a
s
instance (Num a) => Semigroup (ESSStatement a) where
ESSStatement Money a
a Money a
b Money a
c Money a
d Money a
e Money a
f <> :: ESSStatement a -> ESSStatement a -> ESSStatement a
<> ESSStatement Money a
a' Money a
b' Money a
c' Money a
d' Money a
e' Money a
f' =
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> ESSStatement a
forall a.
Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> Money a
-> ESSStatement a
ESSStatement (Money a
a Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
a') (Money a
b Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
b') (Money a
c Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
c') (Money a
d Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
d') (Money a
e Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
e') (Money a
f Money a -> Money a -> Money a
forall a. Semigroup a => a -> a -> a
<> Money a
f')
instance (Num a) => Monoid (ESSStatement a) where
mempty :: ESSStatement a
mempty = ESSStatement a
forall a. Num a => ESSStatement a
newESSStatement
mappend :: ESSStatement a -> ESSStatement a -> ESSStatement a
mappend = ESSStatement a -> ESSStatement a -> ESSStatement a
forall a. Semigroup a => a -> a -> a
(<>)