tax-ato-2023.2: Tax types and computations for Australia
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Tax.ATO

Description

Types and computations for taxes in Australia.

No guarantee that computations are correct, complete or current.

Lots of things are not implemented, including (but not limited to): ETPs, income from partnerships and trusts, superannuation income streams and lump payments, tax losses from previous years, Medicare levy reduction/exemption, adjustments, and variations based on family income and dependents.

Synopsis

Individual tax returns

data TaxReturnInfo y a Source #

Individual tax return information.

Use newTaxReturnInfo to construct. Alternatively, newTaxReturnInfoForTables can be used to coerce the type parameters to be the same as some TaxTables.

The following lenses are available:

mlsExemptionMedicare levy exemption
helpBalanceHELP account balance
sfssBalanceSFSS account balance
paymentSummariesPAYG payment summaries
interestInterest data
dividendsDividend data
essEmployee Share Scheme statement
foreignIncomeForeign income
cgtEventsCapital gains and losses
deductionsDeductions
offsetsTax offsets
privateHealthInsurancePolicyDetails Private health insurance policy details
spouseDetailsSpouse Details (or Nothing)
incomeTestsIncome Tests

Instances

Instances details
Num a => HasTaxWithheld (TaxReturnInfo y :: Type -> Type) (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

RealFrac a => HasIncome (TaxReturnInfo y :: Type -> Type) (a :: Type) a Source #

Taxable income

Instance details

Defined in Data.Tax.ATO

Methods

income :: Getter (TaxReturnInfo y a) (Money a) Source #

HasCapitalLossCarryForward (TaxReturnInfo y) a Source # 
Instance details

Defined in Data.Tax.ATO

newTaxReturnInfo :: (DaysInYear y, Num a) => TaxReturnInfo y a Source #

Construct a new TaxReturnInfo.

All monetary fields and lists are initially empty.

The Medicare levy surcharge exemption field is initially set to the number of days in the year (i.e. the taxpayer is fully exempt).

newTaxReturnInfoForTables :: (DaysInYear y, Num a) => TaxTables y a -> TaxReturnInfo y a Source #

Construct a TaxReturnInfo per newTaxReturnInfo, coercing the type parameters to match the TaxTables argument (which is ignored).

income :: HasIncome a b c => Getter (a b) (Money c) Source #

Income

PAYG Payment Summaries

data PaymentSummary a Source #

PAYG payment summary - individual non-business

Instances

Instances details
HasTaxWithheld PaymentSummary (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

HasIncome PaymentSummary (a :: Type) a Source #

Gross income

Instance details

Defined in Data.Tax.ATO

type ABN = String Source #

Australian Business Number

Interest

Dividends and franking credits

data Dividend a Source #

Dividend payment. Records net income, franked portion and amount of tax withheld.

Instances

Instances details
RealFrac a => HasTaxWithheld Dividend (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

RealFrac a => HasIncome Dividend (a :: Type) a Source #

Attributable income

Instance details

Defined in Data.Tax.ATO

Methods

income :: Getter (Dividend a) (Money a) Source #

Show a => Show (Dividend a) Source # 
Instance details

Defined in Data.Tax.ATO

Methods

showsPrec :: Int -> Dividend a -> ShowS #

show :: Dividend a -> String #

showList :: [Dividend a] -> ShowS #

dividendFrankingCredit :: RealFrac a => Dividend a -> Money a Source #

Calculate the franking credit for a dividend

Capital gains tax (CGT)

class HasCapitalLossCarryForward a b where Source #

Types that have a carry-forward capital loss (either as an input or an output).

Employee share schemes

data ESSStatement a Source #

Employee share scheme statement. Use newESSStatement to construct.

Instances

Instances details
Num a => HasIncome ESSStatement (a :: Type) a Source #

Note: does not implement the reduction of taxed up front amounts eligible for reduction.

Instance details

Defined in Data.Tax.ATO

Num a => Monoid (ESSStatement a) Source # 
Instance details

Defined in Data.Tax.ATO

Num a => Semigroup (ESSStatement a) Source # 
Instance details

Defined in Data.Tax.ATO

newESSStatement :: Num a => ESSStatement a Source #

Construct an ESSStatement with all amounts at zero.

essTaxedUpfrontReduction :: Lens' (ESSStatement a) (Money a) Source #

Discount from taxed up front schemes—eligible for reduction. Item D in Employee share schemes section.

essTaxedUpfrontNoReduction :: Lens' (ESSStatement a) (Money a) Source #

Discount from taxed up front schemes—not eligible for reduction Item E in Employee share schemes section.

essDeferral :: Lens' (ESSStatement a) (Money a) Source #

Discount from taxed deferral schemes. Item F in Employee share schemes section.

essPre2009 :: Lens' (ESSStatement a) (Money a) Source #

discounts on ESS interests acquired pre 1 July 2009 and "cessation time" occurred during the finanical year. Item G in Employee share schemes section.

essTFNAmounts :: Lens' (ESSStatement a) (Money a) Source #

TFN amounts withheld from discounts. Item C in Employee share schemes section.

essForeignSourceDiscounts :: Lens' (ESSStatement a) (Money a) Source #

ESS foreign source discounts Item A in Employee share schemes section.

Foreign income

Medicare Levy Surcharge and Private Health Insurance

Student loan balances

Spouse details

Income Tests

Deductions

data Deductions a Source #

Deductions that individuals can claim.

The only "special case" field is foreignIncomeDeductions, which is the aggregate amount of other deductions that pertains to foreign income. It is used only for calculating the Foreign Income Tax Offset Limit.

Instances

Instances details
Num a => Monoid (Deductions a) Source # 
Instance details

Defined in Data.Tax.ATO

Num a => Semigroup (Deductions a) Source # 
Instance details

Defined in Data.Tax.ATO

totalDeductions :: (Num a, Ord a) => Deductions a -> Money a Source #

Sum the deductions. Negative components are ignored.

workRelatedCarExpenses :: Lens' (Deductions a) (Money a) Source #

D1 Work-related car expenses

workRelatedTravelExpenses :: Lens' (Deductions a) (Money a) Source #

D2 Work-related travel expenses

workRelatedClothingLaundryAndDryCleaningExpenses :: Lens' (Deductions a) (Money a) Source #

D3 Work-related clothing, laundry and dry-cleaning expenses

workRelatedSelfEducationExpenses :: Lens' (Deductions a) (Money a) Source #

D4 Work-related self-education expenses

otherWorkRelatedExpenses :: Lens' (Deductions a) (Money a) Source #

D5 Other work-related expenses

lowValuePoolDeduction :: Lens' (Deductions a) (Money a) Source #

D6 Low-value pool deduction

interestDeductions :: Lens' (Deductions a) (Money a) Source #

D7 Interest deductions

dividendDeductions :: Lens' (Deductions a) (Money a) Source #

D8 Dividend deductions

giftsOrDonations :: Lens' (Deductions a) (Money a) Source #

D9 Gifts or donations

costOfManagingTaxAffairs :: Lens' (Deductions a) (Money a) Source #

D10 Cost of managing tax affairs

deductibleAmountOfUndeductedPurchasePriceOfAForeignPensionOrAnnuity :: Lens' (Deductions a) (Money a) Source #

D11 Deductible amount of undeducted purchase price of a foreign pension or annuity

personalSuperannuationContributions :: Lens' (Deductions a) (Money a) Source #

D12 Personal superannuation contributions

deductionForProjectPool :: Lens' (Deductions a) (Money a) Source #

D13 Deduction for project pool

forestryManagedInvestmentSchemeDeduction :: Lens' (Deductions a) (Money a) Source #

D14 Forestry managed investment scheme deduction

otherDeductions :: Lens' (Deductions a) (Money a) Source #

D15 Other deductions — not claimable at D1 to D14 or elsewhere in your tax return

foreignIncomeDeductions :: Lens' (Deductions a) (Money a) Source #

Aggregate of deductions related to foreign income, including:

  • Deductions that are reasonably related to amounts on which foreign income tax has been paid
  • Debt deductions attributable to your overseas permanent establishment
  • Amount of the foreign loss component of one or more tax losses deducted in the income year.

The components making up this amount must be included in other fields. This field is only used in calculating the Foreign Income Tax Offset Limit.

Tax offsets

data Offsets a Source #

Tax offsets that individuals can claim

The following lenses are available:

spouseContributionOffsetSpouse super contribution
foreignTaxOffsetForeign income tax offset
paygInstalmentsPAYG Instalments

Instances

Instances details
Num a => Monoid (Offsets a) Source # 
Instance details

Defined in Data.Tax.ATO

Methods

mempty :: Offsets a #

mappend :: Offsets a -> Offsets a -> Offsets a #

mconcat :: [Offsets a] -> Offsets a #

Num a => Semigroup (Offsets a) Source # 
Instance details

Defined in Data.Tax.ATO

Methods

(<>) :: Offsets a -> Offsets a -> Offsets a #

sconcat :: NonEmpty (Offsets a) -> Offsets a #

stimes :: Integral b => b -> Offsets a -> Offsets a #

spouseContributionOffset :: Lens' (Offsets a) (Money a) Source #

Spouse contribution offset. Maximum of $540 (not enforced).

foreignTaxOffset :: Lens' (Offsets a) (Money a) Source #

Offset for tax paid on foreign income.

Assessing tax

data TaxAssessment a Source #

A tax assessment. Use assessTax to compute a TaxAssessment.

Instances

Instances details
(Num a, Eq a) => HasCapitalLossCarryForward TaxAssessment a Source # 
Instance details

Defined in Data.Tax.ATO

HasTaxWithheld TaxAssessment (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

HasIncome TaxAssessment (a :: Type) a Source #

Taxable income

Instance details

Defined in Data.Tax.ATO

assessTax :: (DaysInYear y, RealFrac a) => TaxTables y a -> TaxReturnInfo y a -> TaxAssessment a Source #

Assess a tax return, given tax tables and tax return info.

taxBalance :: Num a => Getter (TaxAssessment a) (Money a) Source #

What is the balance of the assessment? Positive means a refund (tax withheld exceeds obligation), negative means a bill.

Corporate tax

corporateTax :: Fractional a => Tax (Money a) (Money a) Source #

The corporate tax rate of 30%. In the future, different rates may be levied depending on business turnover/income.

Miscellaneous

data GrossAndWithheld a Source #

A gross income (first argument) and amount of tax withheld (second argument)

Constructors

GrossAndWithheld (Money a) (Money a) 

class HasTaxWithheld a b c where Source #

Data that can have an amount of tax withheld

Methods

taxWithheld :: Getter (a b) (Money c) Source #

Instances

Instances details
RealFrac a => HasTaxWithheld Dividend (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

HasTaxWithheld GrossAndWithheld (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

HasTaxWithheld PaymentSummary (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

HasTaxWithheld TaxAssessment (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

Num a => HasTaxWithheld (TaxReturnInfo y :: Type -> Type) (a :: Type) a Source # 
Instance details

Defined in Data.Tax.ATO

(Foldable t, HasTaxWithheld x a a, Num a) => HasTaxWithheld (t :: TYPE LiftedRep -> Type) (x a :: TYPE LiftedRep) a Source # 
Instance details

Defined in Data.Tax.ATO

Methods

taxWithheld :: Getter (t (x a)) (Money a) Source #

data Proportion a Source #

A proportion is a non-negative number in interval [0,1]. Use proportion to construct.

Instances

Instances details
Show a => Show (Proportion a) Source # 
Instance details

Defined in Data.Tax.ATO

Eq a => Eq (Proportion a) Source # 
Instance details

Defined in Data.Tax.ATO

Methods

(==) :: Proportion a -> Proportion a -> Bool #

(/=) :: Proportion a -> Proportion a -> Bool #

Ord a => Ord (Proportion a) Source # 
Instance details

Defined in Data.Tax.ATO

getProportion :: Proportion a -> a Source #

Return underlying figure, which is in interval [0,1]

proportion :: (Ord a, Num a) => a -> Proportion a Source #

Construct a proportion. Out of range numbers are clamped to 0 or 1 (no runtime errors).

module Data.Tax