Calculate Amount Paid in Taxes

🏠 ⬅️ ➡️

You are given a 0-indexed 2D integer array brackets where brackets[i] = [upperi, percenti] means that the ith tax bracket has an upper bound of upperi and is taxed at a rate of percenti. The brackets are sorted by upper bound (i.e. upperi-1 < upperi for 0 < i < brackets.length).

Tax is calculated as follows:

  • The first upper0 dollars earned are taxed at a rate of percent0.
  • The next upper1 - upper0 dollars earned are taxed at a rate of percent1.
  • The next upper2 - upper1 dollars earned are taxed at a rate of percent2.
  • And so on.

You are given an integer income representing the amount of money you earned. Return the amount of money that you have to pay in taxes. Answers within 10-5 of the actual answer will be accepted.

Example 1:

Input: brackets = [[3,50],[7,10],[12,25]], income = 10 Output: 2.65000 Explanation: Based on your income, you have 3 dollars in the 1st tax bracket, 4 dollars in the 2nd tax bracket, and 3 dollars in the 3rd tax bracket. The tax rate for the three tax brackets is 50%, 10%, and 25%, respectively. In total, you pay $3 * 50% + $4 * 10% + $3 * 25% = $2.65 in taxes.

Example 2:

Input: brackets = [[1,0],[4,25],[5,50]], income = 2 Output: 0.25000 Explanation: Based on your income, you have 1 dollar in the 1st tax bracket and 1 dollar in the 2nd tax bracket. The tax rate for the two tax brackets is 0% and 25%, respectively. In total, you pay $1 * 0% + $1 * 25% = $0.25 in taxes.

Example 3:

Input: brackets = [[2,50]], income = 0 Output: 0.00000 Explanation: You have no income to tax, so you have to pay a total of $0 in taxes.

Constraints:

  • 1 <= brackets.length <= 100
  • 1 <= upperi <= 1000
  • 0 <= percenti <= 100
  • 0 <= income <= 1000
  • upperi is sorted in ascending order.
  • All the values of upperi are unique.
  • The upper bound of the last tax bracket is greater than or equal to income.

Note: This problem is from LeetCode.
Compiled
Executed
Correct
program main
    use, intrinsic :: iso_fortran_env, only : error_unit, DP => REAL64
    implicit none
    integer, parameter :: nb_examples = 3
    type(brackets) :: brackets
    real(kind=DP), allocatable :: example(:,:)
    integer :: i, j

    allocate(example(nb_examples, 2))
    example(1, :) = [3, 50]
    example(2, :) = [7, 10]
    example(3, :) = [12, 25]

    do i = 1, nb_examples
        brackets = brackets_type(example(i, 1:2))
        write(*, '(A, F8.4)') 'Example ', i, ': ', &
            calculate_tax(brackets, example(i, 2))
    end do

contains

    function calculate_tax(brackets, income) result(tax)
        class(brackets), intent(in) :: brackets
        real(kind=DP), value :: income
        real(kind=DP) :: tax
        integer :: i

        tax = 0.0_DP
        do i = 1, size(brackets%upper)
            if (income >= brackets%upper(i)) then
                tax = tax + (income - brackets%upper(i-1)) * brackets%percent(i) / 100.0_DP
            else
                exit
            end if
        end do
    end function calculate_tax

end program main

type, abstract :: brackets
    integer, allocatable :: upper(:)
    real(kind=DP), allocatable :: percent(:)
contains
    procedure(calculate_tax_interface), deferred :: calculate_tax
end type brackets

abstract interface
    function calculate_tax_interface(brackets, income) result(tax)
        import :: brackets, DP
        class(brackets), intent(in) :: brackets
        real(kind=DP), value :: income
        real(kind=DP) :: tax
    end function calculate_tax_interface
end interface

type, extends(brackets) :: brackets_type
    contains
        procedure :: calculate_tax => calculate_tax_impl
end type brackets_type

function calculate_tax_impl(brackets, income) result(tax)
    class(brackets_type), intent(in) :: brackets
    real(kind=DP), value :: income
    real(kind=DP) :: tax
    integer :: i

    tax = 0.0_DP
    do i = 1, size(brackets%upper)
        if (income >= brackets%upper(i)) then
            tax = tax + (income - brackets%upper(i-1)) * brackets%percent(i) / 100.0_DP
        else
            exit
        end if
    end do
end function calculate_tax_impl

subroutine read_input(brackets, example)
    type(brackets), intent(out) :: brackets
    real(kind=DP), allocatable, intent(out) :: example(:,:)
    integer :: nb_brackets, i

    read(*, *) nb_brackets
    allocate(brackets%upper(nb_brackets))
    allocate(brackets%percent(nb_brackets))
    allocate(example(nb_brackets, 2))
    do i = 1, nb_brackets
        read(*, *) example(i, :)
        brackets%upper(i) = example(i, 1)
        brackets%percent(i) = example(i, 2)
    end do
end subroutine read_input

subroutine print_output(tax)
    real(kind=DP), value :: tax

    write(*, '(F8.4)') tax
end subroutine print_output

end
Compiled
Executed
Correct
module TaxBrackets
    implicit none
    private
    public :: tax
contains
    function tax(brackets, income) result(totalTax)
        integer, intent(in) :: brackets(:, :)
        integer, intent(in) :: income
        real(kind=8) :: totalTax
        integer :: i, upper, percent

        totalTax = 0.0d0
        do i = 1, size(brackets, 1)
            upper = brackets(i, 1)
            percent = brackets(i, 2)
            if (income <= upper) then
                totalTax = totalTax + dble(income) * dble(percent) / 100.0d0
                exit
            else
                totalTax = totalTax + dble(upper) * dble(percent) / 100.0d0
                income = income - upper
            end if
        end do
    end function tax
end module TaxBrackets

program test_tax
    use TaxBrackets
    implicit none
    integer, parameter :: brackets(3, 2) = reshape([3, 50, 7, 10, 12, 25], shape(brackets))
    integer :: income
    real(kind=8) :: totalTax

    income = 10
    totalTax = tax(brackets, income)
    write (*, *) "Income: ", income, " Tax: ", totalTax

    income = 2
    totalTax = tax(brackets, income)
    write (*, *) "Income: ", income, " Tax: ", totalTax

    income = 0
    totalTax = tax(brackets, income)
    write (*, *) "Income: ", income, " Tax: ", totalTax
end program test_tax
🌐 Data from online sources
def tax_amount(brackets, income):
    tax = 0
    prev_upper = 0
    for upper, percent in brackets:
        tax += (min(upper, income) - prev_upper) * (percent / 100)
        prev_upper = upper
        if income <= upper:
            break
    return tax

The algorithm loops through the tax brackets and calculates the tax for each segment. The tax amount for each segment is calculated as (min(upper, income) - prev_upper) * percent. We also need to keep track of the previous upper bound, which is why prev_upper is initialized to 0 and updated in each iteration. If the income is less than or equal to the current upper bound, we can break out of the loop as the remaining tax segments don't matter.

The time complexity of this algorithm is O(n), where n is the number of tax brackets.

🌐 Data from online sources
double taxAmount(vector<vector<int>>& brackets, int income) {
    double tax = 0;
    int prev_upper = 0;
    for (vector<int>& bracket : brackets) {
        int upper = bracket[0];
        double percent = bracket[1] / 100.0;
        tax += (min(upper, income) - prev_upper) * percent;
        prev_upper = upper;
        if (income <= upper) break;
    }
    return tax;
}

The algorithm loops through the tax brackets and calculates the tax for each segment. The tax amount for each segment is calculated as (min(upper, income) - prev_upper) * percent. We also need to keep track of the previous upper bound, which is why prev_upper is initialized to 0 and updated in each iteration. If the income is less than or equal to the current upper bound, we can break out of the loop as the remaining tax segments don't matter.

The time complexity of this algorithm is O(n), where n is the number of tax brackets.