hax-0.0.2: Haskell cash-flow and tax simulation

Safe HaskellNone
LanguageHaskell2010

HAX.Common

Contents

Description

This module provides some common functions and reexports basic modules.

Synopsis

Basic Types

Ranges and Arrays

range1 :: Ix a => ((a, b), (a, b)) -> [a] Source #

Get the range of the first dimension of an array

bounds1 :: ((c, b), (c, b)) -> (c, c) Source #

Get the bounds of the first dimension of an array

range2 :: Ix a => ((a1, a), (a1, a)) -> [a] Source #

Get the range of the second dimension of an array

bounds2 :: ((a, c), (a, c)) -> (c, c) Source #

Get the bounds of the second dimension of an array

updateArray :: (MArray a e m, Ix i) => a i e -> i -> (e -> e) -> m () Source #

helper function to update an MArray value

assocArray Source #

Arguments

:: Ix i 
=> [(i, e)]

a list of associations of the form (index, value)

-> Array i e 

generate an array and take the bounds from the input data

Utility functions

when' :: Num a => Bool -> a -> a Source #

Return a value only if the condition holds and zero otherwise.

both :: (b -> c) -> (b, b) -> (c, c) Source #

apply a function to both elements of a pair

conv :: (Real a, Fractional c) => a -> c Source #

Conversion between different fractional types. E.g. between Double and Decimal.

positivePart :: (Ord a, Num a) => a -> a Source #

bound checking array acces with error msg (?!) :: Ix i => Array i e -> (String,i) -> e array ?! (String,index) = if bounds array inRange index then array ! index else error index

take the positive par of a Num

assert :: (MonadTrans t, Monad (t IO)) => (b -> Bool) -> t IO b -> [Char] -> t IO b Source #

assert that the result of an action satisfies a certain condition or print an error message

newtype PList a Source #

Constructors

PList 

Fields

Dates

date :: Int -> Int -> ADate Source #

Construct an ADate value from a month an a year

endOfYear :: Int -> ADate Source #

Create an ADate value that corresponds to the last month of the given year.

month :: Int -> ADate Source #

Create an ADate value that corresponds to the given month in year 0. (Fails if argument is outside of [1..12])

yearMonth Source #

Arguments

:: ADate 
-> (Int, Int)

(year,month)

convert a month to a pair of Ints.

Date spans

data ASpan Source #

represents a time span between accounting dates

Constructors

ASpan 

Fields

months :: Int -> ASpan Source #

Create an ASpan value corresponding to the given number of monhts.

yearMonthSpan Source #

Arguments

:: ASpan 
-> (Int, Int)

(year,month)

convert a span to a pair of Ints.

divides :: ASpan -> ASpan -> Bool Source #

Check if the second span is a multiple of the first.

dateSpan Source #

Arguments

:: ADate

start date

-> ADate

end date

-> ASpan 

Calculate the span between two dates

shift :: ASpan -> ADate -> ADate Source #

Shift a date by a given date span.

Reexported modules

module Data.Array

module Data.List

module Data.Maybe

module Data.Ord

module Data.Ratio

module Data.Tuple

module Text.Show

Orphan instances