penny-0.32.0.4: Extensible double-entry accounting system

Safe HaskellNone

Penny

Contents

Description

Penny - extensible double-entry accounting system

Synopsis

Building a custom Penny binary

Everything you need to create a custom Penny program is available by importing only this module.

data Version

A Version represents the version of a software entity.

An instance of Eq is provided, which implements exact equality modulo reordering of the tags in the versionTags field.

An instance of Ord is also provided, which gives lexicographic ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.). This is expected to be sufficient for many uses, but note that you may need to use a more specific ordering for your versioning scheme. For example, some versioning schemes may include pre-releases which have tags "pre1", "pre2", and so on, and these would need to be taken into account when determining ordering. In some cases, date ordering may be more appropriate, so the application would have to look for date tags in the versionTags field and compare those. The bottom line is, don't always assume that compare and other Ord operations are the right thing for every Version.

Similarly, concrete representations of versions may differ. One possible concrete representation is provided (see showVersion and parseVersion), but depending on the application a different concrete representation may be more appropriate.

Constructors

Version 

Fields

versionBranch :: [Int]

The numeric branch for this version. This reflects the fact that most software versions are tree-structured; there is a main trunk which is tagged with versions at various points (1,2,3...), and the first branch off the trunk after version 3 is 3.1, the second branch off the trunk after version 3 is 3.2, and so on. The tree can be branched arbitrarily, just by adding more digits.

We represent the branch as a list of Int, so version 3.2.1 becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of Ord for [Int]) gives the natural ordering of branches.

versionTags :: [String]

A version can be tagged with an arbitrary list of strings. The interpretation of the list of tags is entirely dependent on the entity that this version applies to.

data Defaults Source

This type contains settings for all the reports, as well as default settings for the global options. Some of these can be overridden on the command line.

Constructors

Defaults 

Fields

caseSensitive :: Bool

Whether the matcher is case sensitive by default

matcher :: Matcher

Which matcher to use

colorToFile :: Bool

Use colors when standard output is not a terminal?

expressionType :: ExprDesc

Use RPN or infix expressions? This affects both the posting filter and the filter for the Postings report.

defaultScheme :: Maybe Scheme

Default color scheme. If Nothing, there is no default color scheme. If there is no default color scheme and the user does not pick one on the command line, no colors will be used.

additionalSchemes :: [Scheme]

Additional color schemes the user can pick from on the command line.

sorter :: [(SortField, SortOrder)]

Postings are sorted in this order by default. For example, if the first pair is (Date, Ascending), then postings are first sorted by date in ascending order. If the second pair is (Payee, Ascending), then postings with the same date are then sorted by payee.

If this list is empty, then by default postings are left in the same order as they appear in the ledger files.

formatQty :: FormatQty

How to format quantities. This affects only quantities that are not parsed from the ledger. Examples include calculated totals and inferred quantities. Affects all reports.

balanceShowZeroBalances :: Bool

Show zero balances in the balance report? If True, show them; if False, hide them.

balanceOrder :: SortOrder

Whether to sort the accounts in ascending or descending order by account name in the balance report.

convertShowZeroBalances :: Bool

Show zero balances in the convert report? If True, show them; if False, hide them.

convertTarget :: Target

The commodity to which to convert the commodities in the convert report.

convertOrder :: SortOrder

Sort the convert report in ascending or descending order.

convertSortBy :: SortBy

Sort by account or by quantity in the convert report.

postingsFields :: Fields Bool

Fields to show by default in the postings report.

postingsWidth :: Int

The postings report is roughly this wide by default. Typically this will be as wide as your terminal.

postingsShowZeroBalances :: Bool

Show zero balances in the postings report? If True, show them; if False, hide them.

postingsDateFormat :: (PostMeta, Posting) -> Text

How to format dates in the postings report.

postingsSubAccountLength :: Int

Account names in the postings report are shortened if necessary in order to help the report fit within the allotted width (see postingsWidth). Account names are only shortened as much as is necessary for them to fit; however, each sub-account name will not be shortened any more than the amount given here.

postingsPayeeAllocation :: Int

postingsPayeeAllocation and postingsAccountAllocation determine how much space is allotted to the payee and account fields in the postings report. These fields are variable width. After space for most other fields is allotted, space is allotted for these two fields. The two fields divide the space proportionally depending on postingsPayeeAllocation and postingsAccountAllocation. For example, if postingsPayeeAllocation is 60 and postingsAccountAllocation is 40, then the payee field gets 60 percent of the leftover space and the account field gets 40 percent of the leftover space.

Both postingsPayeeAllocation and postingsAccountAllocation must be positive integers; if either one is less than 1, your program will crash at runtime.

postingsAccountAllocation :: Int

See postingsPayeeAllocation above for an explanation

postingsSpacers :: Spacers Int

Determines the number of spaces that appears to the right of each named field; for example, sPayee indicates how many spaces will appear to the right of the payee field. Each field of the Spacers should be a non-negative integer (although currently the absolute value of the field is taken.)

data Matcher Source

Constructors

Within 
Exact 
PCRE 

Instances

Color schemes

data Scheme Source

Constructors

Scheme 

Fields

name :: String

The name of this scheme. How it will be identified on the command line.

description :: String

A brief (one-line) description of what this scheme is, such as for dark background terminals

changers :: Changers
 

data Labels a Source

Constructors

Labels 

Fields

debit :: a
 
credit :: a
 
zero :: a
 
other :: a
 

Instances

Show a => Show (Labels a) 

data EvenAndOdd a Source

Constructors

EvenAndOdd 

Fields

eoEven :: a
 
eoOdd :: a
 

Instances

Show a => Show (EvenAndOdd a) 

Sorting

Expression type

data ExprDesc

Is this an infix or RPN expression?

Constructors

Infix 
RPN 

Instances

Convert report options

data Target Source

The commodity to which to convert the commodities in the convert report.

Constructors

AutoTarget

Selects a target commodity automatically, based on which commodity is the most common target commodity in the prices in your ledger files. If there is a tie for most common target commodity, the target that appears later in your ledger files is used.

ManualTarget String

Always uses the commodity named by the string given.

Instances

data SortBy Source

Constructors

SortByQty 
SortByName 

Instances

Postings report options

data Fields a Source

Constructors

Fields 

Fields

fGlobalTransaction :: a
 
fRevGlobalTransaction :: a
 
fGlobalPosting :: a
 
fRevGlobalPosting :: a
 
fFileTransaction :: a
 
fRevFileTransaction :: a
 
fFilePosting :: a
 
fRevFilePosting :: a
 
fFiltered :: a
 
fRevFiltered :: a
 
fSorted :: a
 
fRevSorted :: a
 
fVisible :: a
 
fRevVisible :: a
 
fLineNum :: a
 
fDate :: a
 
fFlag :: a
 
fNumber :: a
 
fPayee :: a
 
fAccount :: a
 
fPostingDrCr :: a
 
fPostingCmdty :: a
 
fPostingQty :: a
 
fTotalDrCr :: a
 
fTotalCmdty :: a
 
fTotalQty :: a
 
fTags :: a
 
fMemo :: a
 
fFilename :: a
 

Instances

Eq a => Eq (Fields a) 
Show a => Show (Fields a) 

data Spacers a Source

Constructors

Spacers 

Instances

Eq a => Eq (Spacers a) 
Show a => Show (Spacers a) 

widthFromRuntime :: Runtime -> IntSource

Gets the current screen width from the runtime. If the COLUMNS environment variable is not set, uses 80.

yearMonthDay :: (PostMeta, Posting) -> TextSource

Shows the date of a posting in YYYY-MM-DD format.

Formatting quantities

data S3 a b c

Constructors

S3a a 
S3b b 
S3c c 

Instances

Typeable3 S3 
(Eq a, Eq b, Eq c) => Eq (S3 a b c) 
(Ord a, Ord b, Ord c) => Ord (S3 a b c) 
(Read a, Read b, Read c) => Read (S3 a b c) 
(Show a, Show b, Show c) => Show (S3 a b c) 
(Typeable a, Show a, Typeable b, Show b, Typeable c, Show c) => Exception (S3 a b c) 

type FormatQtySource

Arguments

 = [LedgerItem]

All parsed items

-> Amount Qty 
-> Text 

A function used to format quantities.

qtyFormatterSource

Arguments

:: S3 Radix PeriodGrp CommaGrp

What to do if no radix or grouping information can be determined from the ledger. Pass Radix if you want to use a radix point but no grouping; a PeriodGrp if you want to use a period for a radix point and the given grouping character, or a CommaGrp if you want to use a comma for a radix point and the given grouping character.

-> FormatQty 

Provides a function to use in the formatQty field. This formats quantities that were not parsed in the ledger. It first consults a list of all items that were parsed from the ledger. It examines these items to determine if another item with the same commodity already exists in the ledger.

If other items with the same commodity exist in the ledger, the radix point most frequently occurring amongst those items is used. If at least one of these items (with this radix point) also has grouped digits, then the quantity will be formatted with grouped digits; otherwise, no digit grouping is performed. If digit grouping is performed, it is done according to the following rules:

  • only digits to the left of the radix point are grouped
  • grouping is performed only if the number has at least five digits. Therefore, 1234 is not grouped, but 1,234.5 is grouped, as is 12,345
  • the character most frequently appearing as a grouping character (for this particular commodity and radix point) is used to perform grouping
  • digits are grouped into groups of 3 digits

If a radix point cannot be determined from the quantities for a given commodity, then the radix point appearing most frequently for all commodities is used. If it's impossible to determine a radix point from all commodities, then the given default radix point and digit grouping (if desired) is used.

This function builds a map internally which holds all the formatting information; it might be expensive to build, so the function is written to be partially applied.

getQtyFormatSource

Arguments

:: S3 Radix PeriodGrp CommaGrp

What to do if no radix or grouping information can be determined from the ledger. Pass Radix if you want to use a radix point but no grouping; a PeriodGrp if you want to use a period for a radix point and the given grouping character, or a CommaGrp if you want to use a comma for a radix point and the given grouping character.

-> [LedgerItem] 
-> Amount Qty 
-> S3 Radix PeriodGrp CommaGrp 

Obtains radix and grouping information for a particular commodity and quantity, but does not actually perform the formatting.

data Radix Source

Constructors

Period 
Comma 

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

Runtime

data Runtime Source

Information about the runtime environment.

Text

data Text

A space efficient, packed, unboxed Unicode text type.

pack :: String -> Text

O(n) Convert a String into a Text. Subject to fusion. Performs replacement on invalid scalar values.

Main function

runPennySource

Arguments

:: Version

Version of the executable

-> (Runtime -> Defaults)

runPenny will apply this function to the Runtime. This way the defaults you use can vary depending on environment variables, the terminal type, the date, etc.

-> IO () 

Creates an IO action that you can use for the main function.

Developer overview

Penny is organized into a tree of modules, each with a name. Check out the links for details on each component of Penny.

Penny.Brenner - Penny financial institution transaction handling. Depends on Lincoln and Copper.

Penny.Cabin - Penny reports. Depends on Lincoln and Liberty.

Penny.Copper - the Penny parser. Depends on Lincoln.

Penny.Liberty - Penny command line parser helpers. Depends on Lincoln and Copper.

Penny.Lincoln - the Penny core. Depends on no other Penny components.

Penny.Shield - the Penny runtime environment. Depends on Lincoln.

Penny.Steel - independent utilities. Depends on no other Penny components.

Penny.Wheat - helping you build your own programs to check your ledger. Depends on Steel, Lincoln, and Copper.

Penny.Zinc - the Penny command-line interface. Depends on Cabin, Copper, Liberty, and Lincoln.

The dependencies are represented as a dot file in doc/dependencies.dot in the Penny git repository.