| Safe Haskell | None |
|---|---|
| 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 =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 =limitmempty (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 =threshold'l (lesserOf(abovel 0.1) (flat0.02)) where l = review money 21656
Although some of the combinators deal directory with Money, a
Tax can be defined for other types. For example, you can tax a
person a certain number of days labour, based on their age.
data Sex = M | F newtype Years = Years Int newtype Days = Days Int data Person = Person Years Sex corvée :: Tax Person Days corvée = Tax f where f (Person (Years age) sex) = Days $ if age >= 18 && age <= maxAge sex then 10 else 0 maxAge sex = case sex of M -> 45 ; F -> 35
Synopsis
- newtype Tax a b = Tax {
- getTax :: a -> b
- type MoneyTax a = Tax (Money a) (Money a)
- lump :: a -> Tax b a
- flat :: Num a => a -> Tax (Money a) (Money a)
- threshold :: (Num a, Ord a) => Money a -> a -> Tax (Money a) (Money a)
- threshold' :: (Ord b, Monoid a) => b -> Tax b a -> Tax b a
- thresholds :: (Fractional a, Ord a) => [(Money a, a)] -> Tax (Money a) (Money a)
- above :: (Num a, Ord a) => Money a -> a -> Tax (Money a) (Money a)
- above' :: (Num b, Ord b) => Money b -> Tax (Money b) a -> Tax (Money b) a
- marginal :: (Fractional a, Ord a) => [(Money a, a)] -> Tax (Money a) (Money a)
- lesserOf :: Ord a => Tax b a -> Tax b a -> Tax b a
- greaterOf :: Ord a => Tax b a -> Tax b a -> Tax b a
- limit :: Ord a => a -> Tax b a -> Tax b a
- effective :: Fractional a => Money a -> Tax (Money a) (Money a) -> Tax (Money a) (Money a)
- class Semigroup a where
- class Semigroup a => Monoid a where
- class Profunctor (p :: * -> * -> *) 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%
Taxes are a profunctor, making it trivial to perform simple transformations of the input and/or output (e.g. rounding down to whole dollars).
threshold :: (Num a, Ord a) => Money a -> a -> Tax (Money a) (Money a) Source #
Tax full amount at flat rate if input >= threshold
threshold' :: (Ord b, Monoid a) => b -> Tax b a -> Tax b a Source #
Levy the tax if input >= threshold, otherwise don't
thresholds :: (Fractional a, Ord a) => [(Money a, a)] -> Tax (Money a) (Money a) Source #
Convert a [(threshold, rate)] into a flat tax whose rate is
the sum of the rates that apply for a given input. The rates
are cumulative. For example, if you want to tax people earning
>$30,000 20%, and people earning >$50,000 30%, you only tax an
extra 10% at 50000:
tax = thresholds [(30000, .2), (50000, .1)]
above :: (Num a, Ord a) => Money a -> a -> Tax (Money a) (Money a) Source #
Tax the amount exceeding the threshold at a flat rate.
above' :: (Num b, Ord b) => Money b -> Tax (Money b) a -> Tax (Money b) a Source #
Tax the amount exceeding the threshold
marginal :: (Fractional a, Ord a) => [(Money a, a)] -> Tax (Money a) (Money a) Source #
Convert a [(threshold, rate)] into a marginal tax.
The rates are cumulative, i.e. the top marginal rate is the
sum of the rates that apply for a given input.
limit :: Ord a => a -> Tax b a -> Tax b 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 (Money a) (Money a) -> Tax (Money a) (Money 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 stimesIdempotentstimes =
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) | |
| 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 b => Semigroup (Tax a b) # | |
| (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)<>zSemigrouplaw)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 newtypes 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) | |
| Monoid b => Monoid (a -> b) | Since: base-2.1 |
| (Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
| Monoid b => Monoid (Tax a b) # | |
| (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 |
class Profunctor (p :: * -> * -> *) where #
Formally, the class Profunctor represents a profunctor
from Hask -> Hask.
Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.
You can define a Profunctor by either defining dimap or by defining both
lmap and rmap.
If you supply dimap, you should ensure that:
dimapidid≡id
If you supply lmap and rmap, ensure:
lmapid≡idrmapid≡id
If you supply both, you should also ensure:
dimapf g ≡lmapf.rmapg
These ensure by parametricity:
dimap(f.g) (h.i) ≡dimapg h.dimapf ilmap(f.g) ≡lmapg.lmapfrmap(f.g) ≡rmapf.rmapg
Instances
| Profunctor Tax # | |
| Monad m => Profunctor (Kleisli m) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d # lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c # rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c # (#.) :: Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c # (.#) :: Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c # | |
| Profunctor (Tagged :: * -> * -> *) | |
Defined in Data.Profunctor.Unsafe | |
| Profunctor ((->) :: * -> * -> *) | |
| Functor w => Profunctor (Cokleisli w) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d # lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c # rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c # (#.) :: Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c # (.#) :: Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c # | |
| Functor f => Profunctor (Joker f :: * -> * -> *) | |
Defined in Data.Profunctor.Unsafe | |
| Contravariant f => Profunctor (Clown f :: * -> * -> *) | |
Defined in Data.Profunctor.Unsafe | |
| (Profunctor p, Profunctor q) => Profunctor (Sum p q) | |
Defined in Data.Profunctor.Unsafe | |
| (Profunctor p, Profunctor q) => Profunctor (Product p q) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d # lmap :: (a -> b) -> Product p q b c -> Product p q a c # rmap :: (b -> c) -> Product p q a b -> Product p q a c # (#.) :: Coercible c b => q0 b c -> Product p q a b -> Product p q a c # (.#) :: Coercible b a => Product p q b c -> q0 a b -> Product p q a c # | |
| (Functor f, Profunctor p) => Profunctor (Tannen f p) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d # lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c # rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c # (#.) :: Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c # (.#) :: Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c # | |
| (Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d # lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c # rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c # (#.) :: Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c # (.#) :: Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c # | |
module Data.Money