penny-lib-0.4.0.0: Extensible double-entry accounting system - library

Safe HaskellSafe-Infered

Penny.Lincoln

Contents

Description

Lincoln - the Penny core

Penny's core types and classes are here. This module re-exports the most useful things. For more details you will want to look at the sub-modules. Also, not all types and functions are re-exported due to naming conflicts. In particular, neither Penny.Lincoln.Predicates nor Penny.Lincoln.Queries is exported from here due to the blizzard of name conflicts that would result.

Synopsis

Balances

data Balance Source

A balance summarizes several entries. You do not create a Balance directly. Instead, use entryToBalance. Balance used to be a monoid, but there is nothing appropriate for mempty. Instead, Balance is really a semigroup, but not a monoid.

unBalance :: Balance -> Map Commodity BottomLineSource

The map returned by unBalance is never empty.

data Balanced Source

Returned by isBalanced.

Instances

isBalanced :: Balance -> BalancedSource

Is this balance balanced?

entryToBalance :: Entry -> BalanceSource

Converts an Entry to a Balance.

addBalances :: Balance -> Balance -> BalanceSource

Add two Balances together. Commodities are never removed from the balance, even if their balance is zero. Instead, they are left in the balance. Sometimes you want to know that a commodity was in the account but its balance is now zero.

removeZeroCommodities :: Balance -> Maybe BalanceSource

Removes zero balances from a Balance. Will not return a Balance with no commodities; instead, returns Nothing if there would be a balance with no commodities.

data Column Source

Constructors

Column DrCr Qty 

Instances

Bits

Accounts

Amounts

data Amount Source

Constructors

Amount 

Fields

qty :: Qty
 
commodity :: Commodity
 

Instances

Commodities

charCommodity :: Char -> CommoditySource

Creates a Commodity whose name is only a single character.

DateTime

data DateTime Source

A DateTime is a UTC time that also remembers the local time from which it was set. The Eq and Ord instances will compare two DateTimes based on their equivalent UTC times.

dateTime :: LocalTime -> TimeZoneOffset -> DateTimeSource

Construct a DateTime.

data TimeZoneOffset Source

The number of minutes that this timezone is offset from UTC. Can be positive, negative, or zero.

minsToOffset :: Int -> Maybe TimeZoneOffsetSource

Convert minutes to a time zone offset. I'm having a hard time deciding whether to be liberal or strict in what to accept here. Currently it is somewhat strict in that it will fail if absolute value is greater than 840 minutes; currently the article at http:en.wikipedia.orgwikiList_of_time_zones_by_UTC_offset says there is no offset greater than 14 hours, or 840 minutes.

Debits and credits

data DrCr Source

Constructors

Debit 
Credit 

Instances

opposite :: DrCr -> DrCrSource

Debit returns Credit; Credit returns Debit

Entries

data Entry Source

Constructors

Entry 

Fields

drCr :: DrCr
 
amount :: Amount
 

Instances

Flag

newtype Flag Source

Constructors

Flag 

Fields

unFlag :: TextNonEmpty
 

Memos

newtype Memo Source

Constructors

Memo 

Fields

unMemo :: [MemoLine]
 

Number

Payee

Prices and price points

newtype From Source

Constructors

From 

Fields

unFrom :: Commodity
 

Instances

newtype To Source

Constructors

To 

Fields

unTo :: Commodity
 

Instances

data Price Source

Instances

newPrice :: From -> To -> CountPerUnit -> Maybe PriceSource

Succeeds only if From and To are different commodities.

Quantities

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?

I can imagine situations where a quantity of zero might be useful; for instance maybe you want to specifically indicate that a particular posting in a transaction did not happen (for instance, that a paycheck deduction did not take place). I think the better way to handle that though would be through an addition to DebitCredit - maybe DebitCredit/Zero. Barring the addition of that, though, the best way to indicate a situation such as this would be through transaction memos.

Instances

unQty :: Qty -> DecimalSource

Unwrap a Qty to get the underlying Decimal. This Decimal will always be greater than zero.

partialNewQty :: Decimal -> QtySource

Make a new Qty. This function is partial. It will call error if its argument is less than or equal to zero.

newQty :: Decimal -> Maybe QtySource

Make a new Qty. Returns Nothing if its argument is less than zero.

add :: Qty -> Qty -> QtySource

difference :: Qty -> Qty -> DifferenceSource

Subtract the second Qty from the first.

Tags

newtype Tag Source

Constructors

Tag 

Fields

unTag :: TextNonEmpty
 

newtype Tags Source

Constructors

Tags 

Fields

unTags :: [Tag]
 

Builders

crashy :: Show e => Exceptional e a -> aSource

Makes a function partial. Use if you don't want to bother dealing with the Exceptional type.

account :: String -> Exceptional String AccountSource

Create an Account. You supply a single String, with colons to separate the different sub-accounts.

Families

Family types

data Family p c Source

A Family has one parent (ah, the anomie, sorry) and at least two children.

Constructors

Family p c c [c] 

Instances

(Eq p, Eq c) => Eq (Family p c) 
(Show p, Show c) => Show (Family p c) 

data Child p c Source

A Child has at least one sibling and a parent.

Constructors

Child c c [c] p 

Instances

(Show p, Show c) => Show (Child p c) 

data Siblings a Source

Describes the siblings of a family, but tells you nothing about the parent. There are always at least two Siblings.

Constructors

Siblings a a [a] 

Manipulating families

children :: Family p c -> Siblings (Child p c)Source

Gets a family's children. The Child type contains information on the parent, and each Child contains information on the other Siblings.

orphans :: Family p c -> Siblings cSource

Separates the children from their parent.

adopt :: p -> Siblings c -> Family p cSource

Unites a parent and some siblings into one family; the dual of orphans.

marryWith :: (p1 -> p2 -> p3) -> (c1 -> c2 -> c3) -> Family p1 c1 -> Family p2 c2 -> Family p3 c3Source

Marries two families into one. This function is rather cruel: if one family has more children than the other family, then the extra children are discarded. That is, all children must pair one-by-one.

marry :: Family p1 c1 -> Family p2 c2 -> Family (p1, p2) (c1, c2)Source

marryWith a tupling function.

divorceWith :: (p1 -> (p2, p3)) -> (c1 -> (c2, c3)) -> Family p1 c1 -> (Family p2 c2, Family p3 c3)Source

Splits up a family.

divorce :: Family (p1, p2) (c1, c2) -> (Family p1 c1, Family p2 c2)Source

divorceWith an untupling function.

HasText

data Delimited a Source

Applying text to a Delimited type will give you a single Text with the delimiter interspersed between the values of the list.

Constructors

Delimited Text [a] 

Instances

TextNonEmpty

Transactions

Postings and transactions

data Posting Source

Each Transaction consists of at least two Postings.

Instances

data Transaction Source

All the Postings in a Transaction must produce a Total whose debits and credits are equal. That is, the Transaction must be balanced. No Transactions are created that are not balanced.

data PostFam Source

Instances

Making transactions

data Error Source

Errors that can arise when making a Transaction.

Instances

Querying postings

data Inferred Source

Indicates whether the entry for this posting was inferred. That is, if the user did not supply an entry for this posting, then it was inferred.

Constructors

Inferred 
NotInferred 

Instances

changePostingMeta :: (PostingMeta -> PostingMeta) -> Transaction -> TransactionSource

Change the metadata on a posting.

Querying transactions

data TopLine Source

The TopLine holds information that applies to all the postings in a transaction (so named because in a ledger file, this information appears on the top line.)

Instances

changeTransactionMetaSource

Arguments

:: (TopLineMeta -> TopLineMeta)

Function that, when applied to the old top line meta, returns the new meta.

-> Transaction

The old transaction with metadata

-> Transaction

Transaction with new metadata

Change the metadata on a transaction.

postFam :: Transaction -> [PostFam]Source

Get the Postings from a Transaction, with information on the sibling Postings.

Adding serials to transactions

Unwrapping Transactions

Transaction boxes

data Box m Source

A box stores a family of transaction data along with metadata. The transaction is stored in child form, indicating a particular posting of interest. The metadata is in addition to the metadata associated with the TopLine and with each posting.

Constructors

Box 

Fields

boxMeta :: m
 
boxPostFam :: PostFam
 

Instances

Functor Box 
Show m => Show (Box m) 

Metadata

newtype TopLineLine Source

Constructors

TopLineLine 

Fields

unTopLineLine :: Int
 

newtype TopMemoLine Source

Constructors

TopMemoLine 

Fields

unTopMemoLine :: Int
 

data Side Source

Instances

data Format Source

Constructors

Format 

Fields

side :: Side
 
between :: SpaceBetween
 

Instances

newtype Filename Source

Constructors

Filename 

Fields

unFilename :: Text
 

Instances

newtype PriceLine Source

Constructors

PriceLine 

Fields

unPriceLine :: Int
 

newtype PostingLine Source

Constructors

PostingLine 

Fields

unPostingLine :: Int
 

newtype FilePosting Source

Constructors

FilePosting 

PriceDb

data PriceDb Source

The PriceDb holds information about prices. Create an empty one using emptyDb then fill it with values using foldl or similar.

emptyDb :: PriceDbSource

An empty PriceDb

addPrice :: PriceDb -> PricePoint -> PriceDbSource

Add a single price to the PriceDb.

getPrice :: PriceDb -> From -> To -> DateTime -> Exceptional PriceDbError CountPerUnitSource

Looks up values from the PriceDb. Throws Error if something fails.

First, tries to find the best possible From match. For example, if From is LUV:2001, first tries to see if there is a From match for LUV:2001. If there is not an exact match for LUV:2001 but there is a match for LUV, then LUV is used. If there is not a match for either LUV:2001 or for LUV, then FromNotFound is thrown.

The To commodity must match exactly. So, if the TO commodity is LUV:2001, only LUV:2001 will do. If the To commodity is not found, ToNotFound is thrown.

The DateTime is the time at which to find a price. If a price exists for that exact DateTime, that price is returned. If no price exists for that exact DateTime, but there is a price for an earlier DateTime, the latest possible price is returned. If there are no earlier prices, CpuNotFound is thrown.

There is no backtracking on earlier decisions. For example, if From is LUV:2001, and there is indeed at least one From price in the PriceDb and CpuNotFound occurs, getPrice does not check to see if the computation would have succeeded had it used LUV rather than LUV:2001.

data PriceDbError Source

Getting prices can fail; if it fails, an Error is returned.

convert :: PriceDb -> DateTime -> To -> Amount -> Exceptional PriceDbError AmountSource

Given an Amount and a Commodity to convert the amount to, converts the Amount to the given commodity. If the Amount given is already in the To commodity, simply returns what was passed in. Can fail and throw PriceDbError. Internally uses getPrice, so read its documentation for details on how price lookup works.

Serials

data Serial Source

A type for serial numbers, used widely for different purposes throughout Penny.

Instances

forward :: Serial -> IntSource

Numbered from first to last, beginning at zero.

backward :: Serial -> IntSource

Numbered from last to first, ending at zero.

serials :: [a] -> [Serial]Source

Applied to a list of items, return a list of Serials usable to identify the list of items.

serialItems :: (Serial -> a -> b) -> [a] -> [b]Source

Label a list of items with serials.

Matchers

type FactorySource

Arguments

 = CaseSensitive

Will this matcher be case sensitive?

-> Text

The pattern to use when testing for a match. For example, this might be a regular expression, or simply the text to be matched.

-> Exceptional Text Matcher

Sometimes producing a matcher might fail; for example, the user might have supplied a bad pattern. If so, an exception is returned. On success, a Matcher is returned.

A function that makes Matchers.