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

Safe HaskellNone

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.

unBalance :: Balance -> Map Commodity BottomLineSource

Returns a map where the keys are the commodities in the balance and the values are the balance for each commodity. If there is no balance at all, this map can be 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 -> BalanceSource

Removes zero balances from a Balance.

data Column Source

Constructors

Column DrCr Qty 

Instances

Bits

Accounts

newtype Account Source

Constructors

Account 

Fields

unAccount :: [SubAccount]
 

Amounts

Commodities

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.

data Hours Source

Instances

intToHours :: Int -> Maybe HoursSource

succeeds if 0 <= x < 24

intToMinutes :: Int -> Maybe MinutesSource

succeeds if 0 <= x < 60

intToSeconds :: Int -> Maybe SecondsSource

succeeds if 0 <= x < 61 (to allow for leap seconds)

data DateTime Source

A DateTime is a a local date and time, along with a time zone offset. The Eq and Ord instances are derived; therefore, two DateTime instances will not be equivalent if the time zone offsets are different, even if they are the same instant. To compare one DateTime to another, you probably want to use toUTC and compare those. To see if two DateTime are the same instant, use sameInstant.

Constructors

DateTime 

sameInstant :: DateTime -> DateTime -> BoolSource

Are these DateTimes the same instant in time, after adjusting for local timezones?

showDateTime :: DateTime -> StringSource

Shows a DateTime in a pretty way.

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 :: Text
 

Memos

newtype Memo Source

There is one item in the list for each line of the memo. Do not include newlines in the texts themselves. However there is nothing to enforce this convention.

Constructors

Memo 

Fields

unMemo :: [Text]
 

Number

newtype Number Source

Constructors

Number 

Fields

unNumber :: Text
 

Payee

newtype Payee Source

Constructors

Payee 

Fields

unPayee :: Text
 

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.

The Eq instance is derived. Therefore q1 == q2 only if q1 and q2 have both the same mantissa and the same exponent. You may instead want equivalent.

Instances

Eq Qty 
Ord Qty 
Show Qty

Shows a quantity, nicely formatted after accounting for both the mantissa and decimal places, e.g. 0.232 or 232.12 or whatever.

data NumberStr Source

Constructors

Whole String

A whole number only. No radix point.

WholeRad String

A whole number and a radix point, but nothing after the radix point.

WholeRadFrac String String

A whole number and something after the radix point.

RadFrac String

A radix point and a fractional value after it, but nothing before the radix point.

Instances

toQty :: NumberStr -> Maybe QtySource

Converts strings to Qty. Fails if any of the strings have non-digits, or if any are negative, or if the result is not greater than zero, or if the strings are empty.

add :: Qty -> Qty -> QtySource

difference :: Qty -> Qty -> DifferenceSource

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

equivalent :: Qty -> Qty -> BoolSource

Compares Qty after equalizing their exponents.

allocateSource

Arguments

:: Qty

The result will add up to this Qty.

-> NonEmpty Qty

Allocate using this list of Qty.

-> NonEmpty Qty

The length of this list will be equal to the length of the list of allocations. Each item will correspond to the original allocation.

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.

Tags

newtype Tag Source

Constructors

Tag 

Fields

unTag :: Text
 

Instances

newtype Tags Source

Constructors

Tags 

Fields

unTags :: [Tag]
 

Builders

account :: Text -> AccountSource

Create an Account. You supply a single Text, 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.

filterChildren :: (a -> Bool) -> Family p a -> Maybe (Family p a)Source

Filters the children. Fails if there are not at least two children after filtering. Retains the original order of the children (after removing the children you don't want.)

find :: (p -> c -> Bool) -> Family p c -> Maybe cSource

Finds the first child matching a predicate.

mapChildren :: (a -> b) -> Family p a -> Family p bSource

Maps over all children.

mapChildrenA :: Applicative m => (a -> m b) -> Family p a -> m (Family p b)Source

Maps over all children, in order starting with child 1, then child 2, then the children in the list from left to right.

mapParent :: (a -> b) -> Family a c -> Family b cSource

Maps over the parent.

mapParentA :: Applicative m => (a -> m b) -> Family a c -> m (Family b c)Source

Maps over the parent in an Applicative.

HasText

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 and deconstructing transactions

data RTransaction Source

Constructors

RTransaction 

Fields

rtCommodity :: Commodity

All postings will have this same commodity

rtSide :: Maybe Side

All commodities will be on this side of the amount

rtSpaceBetween :: Maybe SpaceBetween

All amounts will have this SpaceBetween

rtDrCr :: DrCr

All postings except the inferred one will have this DrCr

rtTopLine :: TopLine
 
rtPosting :: RPosting

You must have at least one posting whose quantity you specify

rtMorePostings :: [RPosting]

Optionally you can have additional restricted postings.

rtIPosting :: IPosting

And at least one posting whose quantity and DrCr will be inferred

Instances

rTransaction :: RTransaction -> TransactionSource

Creates a restricted transaction; that is, one in which all the entries will have the same commodity, and in which all but one of the postings will all be debits or credits. The last posting will have no quantity specified at all and will be inferred. Creating these transactions never fails, in contrast to the transactions created by transaction, which can fail at runtime.

data Error Source

Errors that can arise when making a Transaction.

Instances

toUnverified :: Transaction -> Family TopLine PostingSource

Deconstruct a Transaction to a family of unverified data.

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

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

postFam :: Transaction -> [PostFam]Source

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

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) 

Changing transactions

changeTransaction :: Family TopLineChangeData PostingChangeData -> Transaction -> TransactionSource

Allows you to change the parts of a transaction that can be chanaged without unbalancing the transaction. You cannot change the DrCr, Qty, or Commodity, as changing these might unbalance the transaction. If there are elements you do not want to change at all, use an emptyTopLineChangeData or an emptyPostingChangeData in the appropriate part of the Family that you pass in. If the Family of change data has more children than the transaction, these extra children are ignored. If the Family in the Transaction has more children than the Family of change data, the extra postings are unchanged. That is, changeTransaction will never delete postings.

Metadata

newtype TopLineLine Source

The line number that the TopLine starts on (excluding the memo accompanying the TopLine).

Constructors

TopLineLine 

Fields

unTopLineLine :: Int
 

newtype TopMemoLine Source

The line number that the memo accompanying the TopLine starts on.

Constructors

TopMemoLine 

Fields

unTopMemoLine :: Int
 

data Side Source

The commodity and and the quantity may appear with the commodity on the left (e.g. USD 2.14) or with the commodity on the right (e.g. 2.14 USD).

Instances

data SpaceBetween Source

There may or may not be a space in between the commodity and the quantity.

newtype Filename Source

The name of the file in which a transaction appears.

Constructors

Filename 

Fields

unFilename :: Text
 

Instances

newtype PriceLine Source

The line number on which a price appears.

Constructors

PriceLine 

Fields

unPriceLine :: Int
 

newtype PostingLine Source

The line number on which a posting appears.

Constructors

PostingLine 

Fields

unPostingLine :: Int
 

newtype GlobalPosting Source

All postings are numbered in order, beginning with the first posting in the first file and ending with the last posting in the last file.

Constructors

GlobalPosting 

newtype FilePosting Source

The postings in each file are numbered in order.

Constructors

FilePosting 

newtype GlobalTransaction Source

All transactions are numbered in order, beginning with the first transaction in the first file and ending with the last transaction in the last file.

newtype FileTransaction Source

The transactions in each file are numbered in order.

Constructors

FileTransaction 

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.

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.

data PriceDbError Source

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

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

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

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

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.

Showing postFam in one line

display :: PostFam -> TextSource

Displays a PostFam in a one line format.

Format:

File LineNo Date Payee Acct DrCr Cmdty Qty