Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.Tax
Contents
Description
This library provides combinators for constructing taxes. It is based on the dollaridoos library.
The most basic tax is a flat rate tax:
businessTax = flat
0.3
To compute the tax, use getTax
:
λ> getTax
businessTax (review money 1000000)
$300000.0
Taxes form a semigroup (sum of tax outputs) and monoid:
λ> getTax (flat 0.1 <> flat 0.2) (review money 10) $3.0 λ> getTax mempty (review money 10) $0
Marginal tax rates can be constructed using the above
combinator,
which taxes the amount above a given threshold at a flat rate.
individualIncomeTax :: (Fractional a, Ord a) => Tax a individualIncomeTax =above
(review money 18200) 0.19 <>above
(review money 37000) (0.325 - 0.19) <>above
(review money 87000) (0.37 - 0.325) <>above
(review money 180000) (0.45 - 0.37)
Taxes can be negative. For exmaple, the lump
, above
and limit
combinators can be used to construct a low-income tax offset that
starts at $445 and reduces at a rate of 1.5c per dollar earned over
$37000:
lowIncomeTaxOffset =limit
mempty (lump
(review money (-445)) <>above
(review money 37000) 0.015)
The threshold
combinator applies a tax to the full input amount,
if it exceeds the threshold. Some taxes have "shade-in" where the
amount above the threshold is taxed at a higher rate to "catch up"
to some lower flat rate. The threshold'
and lesserOf
combinators can be used to construct this tax:
medicareLevy :: (Fractional a, Ord a) => Tax a medicareLevy =threshold'
l (lesserOf
(above
l 0.1) (flat
0.02)) where l = review money 21656
Synopsis
- newtype Tax a = Tax {}
- lump :: Money a -> Tax a
- flat :: Num a => a -> Tax a
- threshold :: (Num a, Ord a) => Money a -> a -> Tax a
- threshold' :: (Num a, Ord a) => Money a -> Tax a -> Tax a
- above :: (Num a, Ord a) => Money a -> a -> Tax a
- above' :: (Num a, Ord a) => Money a -> Tax a -> Tax a
- lesserOf :: Ord a => Tax a -> Tax a -> Tax a
- greaterOf :: Ord a => Tax a -> Tax a -> Tax a
- limit :: Ord a => Money a -> Tax a -> Tax a
- adjust :: Num a => a -> Tax a -> Tax a
- effective :: Fractional a => Money a -> Tax a -> Tax a
- class Semigroup a where
- class Semigroup a => Monoid a where
- module Data.Money
Constructing taxes
A function from gross income to tax payable.
Taxes form a semigroup where the tax payable is the sum of tax payable of consituent taxes.
Taxes form a monoid where the identity is a tax of 0%
lump :: Money a -> Tax a Source #
A lump-sum tax; a fixed amount, not affected by the size of the input
threshold :: (Num a, Ord a) => Money a -> a -> Tax a Source #
Tax full amount at flat rate if input >= threshold
threshold' :: (Num a, Ord a) => Money a -> Tax a -> Tax a Source #
Levy the tax if input >= threshold, otherwise don't
above :: (Num a, Ord a) => Money a -> a -> Tax a Source #
Tax the amount exceeding the threshold at a flat rate.
You can use above
to construct marginal taxes:
marginal = above 18200 0.19 <> above 37000 (0.325 - 0.19) <> above 87000 (0.37 - 0.325) <> above 180000 (0.45 - 0.37)
above' :: (Num a, Ord a) => Money a -> Tax a -> Tax a Source #
Tax the amount exceeding the threshold
limit :: Ord a => Money a -> Tax a -> Tax a Source #
Limit the tax payable to the given amount
This could be used e.g. for limiting a compulsory loan repayment to the balance of the loan, or ensuring a (negative) tax offset does not become a (positive) tax.
effective :: Fractional a => Money a -> Tax a -> Tax a Source #
Given a tax and an amount construct the effective flat tax rate
Miscellanea
The class of semigroups (types with an associative binary operation).
Instances should satisfy the associativity law:
Since: base-4.9.0.0
Minimal complete definition
Methods
(<>) :: a -> a -> a infixr 6 #
An associative operation.
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
stimes :: Integral b => b -> a -> a #
Repeat a value n
times.
Given that this works on a Semigroup
it is allowed to fail if
you request 0 or fewer repetitions, and the default definition
will do so.
By making this a member of the class, idempotent semigroups
and monoids can upgrade this to execute in O(1) by
picking stimes =
or stimesIdempotent
stimes =
respectively.stimesIdempotentMonoid
Instances
Semigroup Ordering | Since: base-4.9.0.0 |
Semigroup () | Since: base-4.9.0.0 |
Semigroup [a] | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (IO a) | Since: base-4.10.0.0 |
Ord a => Semigroup (Min a) | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) | Since: base-4.9.0.0 |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last a) | Since: base-4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m # | |
Semigroup a => Semigroup (Option a) | Since: base-4.9.0.0 |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last a) | Since: base-4.9.0.0 |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
Num a => Semigroup (Money a) | |
Num a => Semigroup (Tax a) # | |
Semigroup b => Semigroup (a -> b) | Since: base-4.9.0.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) | Since: base-4.9.0.0 |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | Since: base-4.9.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | Since: base-4.9.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | Since: base-4.9.0.0 |
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
x
<>
mempty
= xmempty
<>
x = xx
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)mconcat
=foldr
'(<>)'mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Minimal complete definition
Methods
Identity of mappend
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.mappend
= '(<>)'
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Instances
Monoid Ordering | Since: base-2.1 |
Monoid () | Since: base-2.1 |
Monoid [a] | Since: base-2.1 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Semigroup a => Monoid (Option a) | Since: base-4.9.0.0 |
Monoid (First a) | Since: base-2.1 |
Monoid (Last a) | Since: base-2.1 |
Num a => Monoid (Money a) | |
Num a => Monoid (Tax a) # | |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |
module Data.Money