penny-0.32.0.8: Extensible double-entry accounting system

Safe HaskellSafe-Inferred

Penny.Lincoln.Bits.Qty

Contents

Description

Penny quantities. A quantity is simply a count (possibly fractional) of something. It does not have a commodity or a Debit/Credit.

Quantities are always greater than zero, even if infinitesimally so.

There are two main types in this module: a quantity representation, or QtyRep, and a quantity, or Qty. To understand the difference, consider these numbers:

 1364.25
 1,364.25
 1 364.25
 1.364,25
 1364,25

These are all different ways to represent the same quantity. Each is a different quantity representation, or QtyRep. A QtyRep stores information about each digit, each digit grouping character (which may be a comma, thin space, or period) and the radix point, if present (which may be a period or a comma.)

A QtyRep can be converted to a Qty with toQty. A Qty is a quantity stripped of attributes related to its representation. No floating point types are in a Qty; internally, a Qty consists of an integral significand and an integer representing the number of decimal places. Though each QtyRep is convertible to one and only one Qty, a single Qty can correspond to several QtyRep. For example, each of the quantity representations shown above would return identical Qty after being converted with toQty.

You can only perform arithmetic using Qty, not QtyRep. You can add or multiply Qty, which yields the result you would expect. You cannot perform ordinary subtraction on Qty, as this might yield a result which is less than or equal to zero; remember that Qty and QtyRep are always greater than zero, even if infinitesimally so. Instead, difference will tell you if there is a difference between two Qty and, if so, which is greater and by how much.

Synopsis

Quantity representations

Components of quantity representations

data Digit Source

Constructors

D0 
D1 
D2 
D3 
D4 
D5 
D6 
D7 
D8 
D9 

class Digits a whereSource

Methods

digits :: a -> DigitListSource

class Grouper a whereSource

Converting a type that represents a digit grouping character to the underlying character itself.

Methods

groupChar :: a -> CharSource

data PeriodGrp Source

The digit grouping character when the radix is a period.

Constructors

PGSpace

ASCII space

PGThinSpace

Unicode code point 0x2009

PGComma

Comma

data CommaGrp Source

The digit grouping character when the radix is a comma.

Constructors

CGSpace

ASCII space

CGThinSpace

Unicode code point 0x2009

CGPeriod

Period

data GroupedDigits a Source

All of the digits on a single side of a radix point. Typically this is parameterized on a type that represents the grouping character.

Constructors

GroupedDigits 

Fields

dsFirstPart :: DigitList

The first chunk of digits

dsNextParts :: [(a, DigitList)]

Optional subsequent chunks of digits. Each is a grouping character followed by additional digits.

Instances

data WholeFrac a Source

A quantity representation that has both a whole number and a fractional part. Abstract because there must be a non-zero digit in here somewhere, which wholeFrac checks for. Typically this is parameterized on an instance of the Digits class, such as DigitList or GroupedDigits. This allows separate types for values that cannot be grouped as well as those that can.

Instances

Eq a => Eq (WholeFrac a) 
Ord a => Ord (WholeFrac a) 
Show a => Show (WholeFrac a) 

wholeFracSource

Arguments

:: Digits a 
=> a

Whole part

-> a

Fractional part

-> Maybe (WholeFrac a)

If there is no non-zero digit present, Nothing. Otherwise, returns the appropriate WholeFrac.

wholeOrFracSource

Arguments

:: GroupedDigits a

What's before the radix point

-> Maybe (GroupedDigits a)

What's after the radix point (if anything)

-> Maybe (WholeOrFracResult a) 

data WholeOnly a Source

A quantity representation that has a whole part only. Abstract because there must be a non-zero digit in here somewhere, which wholeOnly checks for. Typically this is parameterized on an instance of the Digits class, such as DigitList or GroupedDigits.

Instances

Eq a => Eq (WholeOnly a) 
Ord a => Ord (WholeOnly a) 
Show a => Show (WholeOnly a) 

newtype WholeOrFrac a Source

Typically this is parameterized on an instance of the Digits class, such as DigitList or GroupedDigits.

Constructors

WholeOrFrac 

Instances

Eq a => Eq (WholeOrFrac a) 
Ord a => Ord (WholeOrFrac a) 
Show a => Show (WholeOrFrac a) 

data Radix Source

Constructors

Period 
Comma 

Converting between quantity representations and quantities

Rendering quantity representations

bestRadGroup :: [QtyRep] -> Maybe (S3 Radix PeriodGrp CommaGrp)Source

Given a list of QtyRep, determine the most common radix and grouping that are used. If a single QtyRep is grouped, then the result is also grouped. The most common grouping character determines which grouping character is used.

If no QtyRep are grouped, then the most common radix point is used and the result is not grouped.

If there is no radix point found, returns Nothing.

Qty

data Qty Source

A quantity is always greater than zero. Various odd questions happen if quantities can be zero. For instance, what if you have a debit whose quantity is zero? Does it require a balancing credit that is also zero? And how can you have a debit of zero anyway?

WARNING - before doing comparisons or equality tests

The Eq instance is derived. Therefore q1 == q2 only if q1 and q2 have both the same significand and the same number of places. You may instead want equivalent. Similarly, the Ord instance is derived. It compares based on the integral value of the significand and of the exponent. You may instead want compareQty, which compares after equalizing the exponents.

class HasQty a whereSource

Methods

toQty :: a -> QtySource

Instances

signif :: Qty -> IntegerSource

The significand.

places :: Qty -> IntegerSource

The number of decimal places. For instance, in 1.500, the significand is 1500 and the number of places is 3.

compareQty :: Qty -> Qty -> OrderingSource

Compares Qty after equalizing their exponents.

 compareQty (newQty 15 1) (newQty 1500 3) == EQ

newQty :: Signif -> Places -> Maybe QtySource

Ensures that the significand is greater than zero and the number of decimal places is at least zero.

Arithmetic

add :: Qty -> Qty -> QtySource

mult :: Qty -> Qty -> QtySource

Multiplication

divide :: Fractional a => Qty -> Qty -> aSource

Division. There can be no division by zero errors, as a Qty is never zero. Converting to a floating-point number destroys precision, so be sure this is what you want. Sometimes it is useful where precision is not needed (e.g. percentages).

difference :: Qty -> Qty -> DifferenceSource

Subtract the second Qty from the first, after equalizing their exponents.

allocate :: Qty -> (Qty, [Qty]) -> (Qty, [Qty])Source

Allocate a Qty proportionally so that the sum of the results adds up to a given Qty. Fails if the allocation cannot be made (e.g. if it is impossible to allocate without overflowing Decimal.) The result will always add up to the given sum.

Integer allocations

largestRemainderMethodSource

Arguments

:: TotSeats

Total number of seats in the legislature. This is the integer that will be allocated. This number must be positive or this function will fail at runtime.

-> [PartyVotes]

The total seats will be allocated proportionally depending on how many votes each party received. The sum of this list must be positive, and each member of the list must be at least zero; otherwise a runtime error will occur.

-> [SeatsWon]

The sum of this list will always be equal to the total number of seats, and its length will always be equal to length of the PartyVotes list.

Allocates integers using the largest remainder method. This is the method used to allocate parliamentary seats in many countries, so the types are named accordingly.

qtyOne :: QtySource

Significand 1, exponent 0