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

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
  Tree AccountName        -- all accounts named by the journal's transactions, as a hierarchy
  Map AccountName Account -- the postings, and resulting balances, in each account

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

Evolution of transaction/entry/posting terminology:

  • ledger 2: entries contain transactions
  • hledger 0.4: Entrys contain RawTransactions (which are flattened to Transactions)
  • ledger 3: transactions contain postings
  • hledger 0.5: LedgerTransactions contain Postings (which are flattened to Transactions)
  • hledger 0.8: Transactions contain Postings (referencing Transactions..)

Synopsis

Documentation

data Side Source

Constructors

L 
R 

Instances

data Commodity Source

Constructors

Commodity 

Fields

symbol :: String

the commodity's symbol display preferences for amounts of this commodity

side :: Side

should the symbol appear on the left or the right

spaced :: Bool

should there be a space between symbol and quantity

precision :: Int

number of decimal places to display XXX these three might be better belonging to Journal

decimalpoint :: Char

character to use as decimal point

separator :: Char

character to use for separating digit groups (eg thousands)

separatorpositions :: [Int]

positions of separators, counting leftward from decimal point

data Price Source

An amount's price in another commodity may be written as @ unit price or @@ total price. Note although a MixedAmount is used, it should be in a single commodity, also the amount should be positive; these are not enforced currently.

Instances

data Amount Source

Constructors

Amount 

Fields

commodity :: Commodity
 
quantity :: Double
 
price :: Maybe Price

the price for this amount at posting time

data Posting Source

Constructors

Posting 

Fields

pstatus :: Bool
 
paccount :: AccountName
 
pamount :: MixedAmount
 
pcomment :: String
 
ptype :: PostingType
 
pmetadata :: [(String, String)]
 
ptransaction :: Maybe Transaction

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

Instances

data Transaction Source

Constructors

Transaction 

Fields

tdate :: Day
 
teffectivedate :: Maybe Day
 
tstatus :: Bool
 
tcode :: String
 
tdescription :: String
 
tcomment :: String
 
tmetadata :: [(String, String)]
 
tpostings :: [Posting]

this transaction's postings (co-recursive types).

tpreceding_comment_lines :: String
 

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

ctxCommodity :: !(Maybe Commodity)

the default commodity 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.

filereadtime :: ClockTime

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

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.

data Reader Source

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

data Account Source

Constructors

Account 

Fields

aname :: AccountName
 
apostings :: [Posting]

postings in this account

abalance :: MixedAmount

sum of postings in this account and subaccounts

Instances

data FilterSpec Source

A generic, pure specification of how to filter (or search) transactions and postings.

Constructors

FilterSpec 

Fields

datespan :: DateSpan

only include if in this date span

cleared :: Maybe Bool

only include if cleared/uncleared/don't care

real :: Bool

only include if real/don't care

empty :: Bool

include if empty (ie amount is zero)

acctpats :: [String]

only include if matching these account patterns

descpats :: [String]

only include if matching these description patterns

depth :: Maybe Int
 

Instances