hledger-lib-0.23.3: Core data types, parsers and utilities for the hledger accounting tool.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Data.Types

Description

Most data types are defined here to avoid import cycles. Here is an overview of the hledger data model:

Journal                  -- a journal is read from one or more data files. It contains..
 [Transaction]           -- journal transactions (aka entries), which have date, status, code, description and..
  [Posting]              -- multiple account postings, which have account name and amount
 [HistoricalPrice]       -- historical commodity prices

Ledger                   -- a ledger is derived from a journal, by applying a filter specification and doing some further processing. It contains..
 Journal                 -- a filtered copy of the original journal, containing only the transactions and postings we are interested in
 [Account]               -- all accounts, in tree order beginning with a "root" account", with their balances and sub/parent accounts

For more detailed documentation on each type, see the corresponding modules.

Synopsis

Documentation

data Side Source

Constructors

L 
R 

data Price Source

An amount's price (none, per unit, or total) in another commodity. Note the price should be a positive number, although this is not enforced.

data AmountStyle Source

Display style for an amount.

Constructors

AmountStyle 

Fields

ascommodityside :: Side

does the symbol appear on the left or the right ?

ascommodityspaced :: Bool

space between symbol and quantity ?

asprecision :: Int

number of digits displayed after the decimal point

asdecimalpoint :: Char

character used as decimal point

asseparator :: Char

character used for separating digit groups (eg thousands)

asseparatorpositions :: [Int]

positions of digit group separators, counting leftward from decimal point

data Amount Source

Constructors

Amount 

Fields

acommodity :: Commodity
 
aquantity :: Quantity
 
aprice :: Price

the (fixed) price for this amount, if any

astyle :: AmountStyle
 

type Tag Source

Arguments

 = (String, String)

A tag name and (possibly empty) value.

data Posting Source

Constructors

Posting 

Fields

pdate :: Maybe Day

this posting's date, if different from the transaction's

pdate2 :: Maybe Day

this posting's secondary date, if different from the transaction's

pstatus :: Bool
 
paccount :: AccountName
 
pamount :: MixedAmount
 
pcomment :: String

this posting's comment lines, as a single non-indented multi-line string

ptype :: PostingType
 
ptags :: [Tag]

tag names and values, extracted from the comment

pbalanceassertion :: Maybe MixedAmount

optional: the expected balance in the account after this posting

ptransaction :: Maybe Transaction

this posting's parent transaction (co-recursive types). Tying this knot gets tedious, Maybe makes it easier/optional.

data Transaction Source

Constructors

Transaction 

Fields

tdate :: Day
 
tdate2 :: Maybe Day
 
tstatus :: Bool
 
tcode :: String
 
tdescription :: String
 
tcomment :: String

this transaction's comment lines, as a single non-indented multi-line string

ttags :: [Tag]

tag names and values, extracted from the comment

tpostings :: [Posting]

this transaction's postings

tpreceding_comment_lines :: String

any comment lines immediately preceding this transaction

data JournalContext Source

A journal "context" is some data which can change in the course of parsing a journal. An example is the default year, which changes when a Y directive is encountered. At the end of parsing, the final context is saved for later use by eg the add command.

Constructors

Ctx 

Fields

ctxYear :: !(Maybe Year)

the default year most recently specified with Y

ctxCommodityAndStyle :: !(Maybe (Commodity, AmountStyle))

the default commodity and amount style most recently specified with D

ctxAccount :: ![AccountName]

the current stack of parent accounts/account name components specified with "account" directive(s). Concatenated, these are the account prefix prepended to parsed account names.

ctxAliases :: ![(AccountName, AccountName)]

the current list of account name aliases in effect

data Journal Source

Constructors

Journal 

Fields

jmodifiertxns :: [ModifierTransaction]
 
jperiodictxns :: [PeriodicTransaction]
 
jtxns :: [Transaction]
 
open_timelog_entries :: [TimeLogEntry]
 
historical_prices :: [HistoricalPrice]
 
final_comment_lines :: String

any trailing comments from the journal file

jContext :: JournalContext

the context (parse state) at the end of parsing

files :: [(FilePath, String)]

the file path and raw text of the main and any included journal files. The main file is first followed by any included files in the order encountered (XXX reversed, cf journalAddFile).

filereadtime :: ClockTime

when this journal was last read from its file(s)

jcommoditystyles :: Map Commodity AmountStyle

how to display amounts in each commodity

type JournalUpdate = ErrorT String IO (Journal -> Journal) Source

A JournalUpdate is some transformation of a Journal. It can do I/O or raise an error.

type StorageFormat = String Source

The id of a data format understood by hledger, eg journal or csv.

data Reader Source

A hledger journal reader is a triple of format name, format-detecting predicate, and a parser to Journal.

Instances

data Account Source

An account, with name, balances and links to parent/subaccounts which let you walk up or down the account tree.

Constructors

Account 

Fields

aname :: AccountName

this account's full name

aebalance :: MixedAmount

this account's balance, excluding subaccounts

asubs :: [Account]

sub-accounts

anumpostings :: Int

number of postings to this account derived from the above:

aibalance :: MixedAmount

this account's balance, including subaccounts

aparent :: Maybe Account

parent account

aboring :: Bool

used in the accounts report to label elidable parents

Instances

data Ledger Source

A Ledger has the journal it derives from, and the accounts derived from that. Accounts are accessible both list-wise and tree-wise, since each one knows its parent and subs; the first account is the root of the tree and always exists.

Constructors

Ledger 

Instances