-- This file is part of hs-tax-ato
-- Copyright (C) 2018  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 2017–18 financial year.
module Data.Tax.ATO.FY.FY2018 (FY, fyProxy, tables) where

import Data.Proxy
import Control.Lens (review)
import Data.Tax
import Data.Tax.ATO.Common
import Data.Tax.ATO.PrivateHealthInsuranceRebate
import qualified Data.Tax.ATO.FY.FY2017 as FY2017

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

help, sfss :: (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
55874, a
0.04)
  , (a
62293, a
0.005), (a
68603, a
0.005), (a
72208, a
0.005),  (a
77619, a
0.005)
  , (a
84063, a
0.005), (a
88487, a
0.005), (a
97378, a
0.005), (a
103766, a
0.005) ]
sfss :: forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
sfss = [(a, a)] -> Tax (Money a) (Money a)
forall a.
(Fractional a, Ord a) =>
[(a, a)] -> Tax (Money a) (Money a)
thresholds' [(a
55874, a
0.02), (a
68603, a
0.01), (a
97378, a
0.01)]

-- | Individual tax rates unchanged from 2017.
--
-- The /temporary budget repair levy/ no longer applies.
--
tables :: (Ord a, Fractional a) => TaxTables FY 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
  Tax (Money a) (Money a)
forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
FY2017.individualIncomeTax
  (Money a -> Tax (Money a) (Money a)
forall a.
(Fractional a, Ord a) =>
Money a -> Tax (Money a) (Money a)
medicareLevy (AReview (Money a) a -> a -> Money a
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview (Money a) a
forall a b (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p a (f b) -> p (Money a) (f (Money b))
money a
21980))
  (TaxTables 2017 a -> Tax (Money a) (Money a)
forall {k} (y :: k) a. TaxTables y a -> Tax (Money a) (Money a)
ttMedicareLevySurcharge TaxTables 2017 a
forall a. (Ord a, Fractional a) => TaxTables 2017 a
FY2017.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)
sfss
  Tax (Money a) (Money a)
forall a. (Fractional a, Ord a) => Tax (Money a) (Money a)
lowIncomeTaxOffset
  PrivateHealthInsuranceRebateRates a
forall a. Fractional a => PrivateHealthInsuranceRebateRates a
privateHealthInsuranceRebateRates

privateHealthInsuranceRebateRates
  :: (Fractional a) => PrivateHealthInsuranceRebateRates a
privateHealthInsuranceRebateRates :: forall a. Fractional a => PrivateHealthInsuranceRebateRates a
privateHealthInsuranceRebateRates =
  [ ( a
90000, (a
0.25934, a
0.25415), (a
0.30256, a
0.29651), (a
0.34579, a
0.33887) )
  , (a
105000, (a
0.17289, a
0.16943), (a
0.21612, a
0.21180), (a
0.25934, a
0.25415) )
  , (a
140000, (a
0.08644, a
0.08471), (a
0.12966, a
0.12707), (a
0.17289, a
0.16943) )
  ]