-- This file is part of hs-tax-ato
-- Copyright (C) 2023  Fraser Tweedale
--
-- hs-tax-ato is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

{-# LANGUAGE DataKinds #-}

-- | Tax tables for 2022–23 financial year.
module Data.Tax.ATO.FY.FY2023 (FY, fyProxy, tables) where

import Data.Proxy
import Data.Tax
import Data.Tax.ATO.Common
import qualified Data.Tax.ATO.FY.FY2022 as FY2022

type FY = 2023
fyProxy :: Proxy FY
fyProxy :: Proxy FY
fyProxy = Proxy FY
forall {k} (t :: k). Proxy t
Proxy

help :: (Fractional a, Ord a) => Tax (Money a) (Money a)
help :: forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
help = [(a, a)] -> Tax (Money a) (Money a)
forall a.
(Fractional a, Ord a) =>
[(a, a)] -> Tax (Money a) (Money a)
thresholds'
  [ (a
48361, a
0.01)
  , (a
55837, a
0.01)
  , (a
59187, a
0.005)
  , (a
62739, a
0.005)
  , (a
66503, a
0.005)
  , (a
70493, a
0.005)
  , (a
74723, a
0.005)
  , (a
79207, a
0.005)
  , (a
83959, a
0.005)
  , (a
88997, a
0.005)
  , (a
94337, a
0.005)
  , (a
99997, a
0.005)
  , (a
105997, a
0.005)
  , (a
112356, a
0.005)
  , (a
119098, a
0.005)
  , (a
126244, a
0.005)
  , (a
133819, a
0.005)
  , (a
141848, a
0.005)
  ]

tables :: (Ord a, Fractional a) => TaxTables 2023 a
tables :: forall a. (Ord a, Fractional a) => TaxTables FY a
tables = Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> PrivateHealthInsuranceRebateRates a
-> TaxTables FY a
forall {k} (y :: k) a.
Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> Tax (Money a) (Money a)
-> PrivateHealthInsuranceRebateRates a
-> TaxTables y a
TaxTables
  (TaxTables FY a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttIndividualIncomeTax TaxTables FY a
forall a. (Ord a, Fractional a) => TaxTables FY a
FY2022.tables)

  (Money a -> Tax (Money a) (Money a)
forall a.
(Fractional a, Ord a) =>
Money a -> Tax (Money a) (Money a)
medicareLevy (a -> Money a
forall num. num -> Money num
Money a
24276))
  (TaxTables FY a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttMedicareLevySurcharge TaxTables FY a
forall a. (Ord a, Fractional a) => TaxTables FY a
FY2022.tables)

  Tax (Money a) (Money a)
forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
help
  Tax (Money a) (Money a)
forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
help

  Tax (Money a) (Money a)
forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
lowIncomeTaxOffset2021 -- LMITO ceased

  -- https://www.health.gov.au/news/phi-circulars/phi-1023-private-health-insurance-rebate-adjustment-factor-effective-1-april-2023
  (TaxTables FY a -> PrivateHealthInsuranceRebateRates a
forall {k} (y :: k) a.
TaxTables y a -> PrivateHealthInsuranceRebateRates a
ttPHIRebateRates TaxTables FY a
forall a. (Ord a, Fractional a) => TaxTables FY a
FY2022.tables)