hledger-lib-0.14: Reusable types and utilities for the hledger accounting tool and financial apps in general.Source codeContentsIndex
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 derived from one or more data files. It contains..
  [Transaction]           -- journal transactions, which have date, status, code, description and..
   [Posting]              -- multiple account postings (entries), 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                 -- the filtered journal, containing only the transactions and postings we are interested in
  Tree AccountName        -- account names referenced in the journal's transactions, as a tree
  Map AccountName Account -- per-account postings and balances from the journal's transactions, as a  map from account name to account info

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
type SmartDate = (String, String, String)
data WhichDate
= ActualDate
| EffectiveDate
data DateSpan = DateSpan (Maybe Day) (Maybe Day)
data Interval
= NoInterval
| Days Int
| Weeks Int
| Months Int
| Quarters Int
| Years Int
| DayOfMonth Int
| DayOfWeek Int
type AccountName = String
data Side
= L
| R
data Commodity = Commodity {
symbol :: String
side :: Side
spaced :: Bool
precision :: Int
decimalpoint :: Char
separator :: Char
separatorpositions :: [Int]
}
data Price
= UnitPrice MixedAmount
| TotalPrice MixedAmount
data Amount = Amount {
commodity :: Commodity
quantity :: Double
price :: Maybe Price
}
newtype MixedAmount = Mixed [Amount]
data PostingType
= RegularPosting
| VirtualPosting
| BalancedVirtualPosting
data Posting = Posting {
pstatus :: Bool
paccount :: AccountName
pamount :: MixedAmount
pcomment :: String
ptype :: PostingType
pmetadata :: [(String, String)]
ptransaction :: Maybe Transaction
}
data Transaction = Transaction {
tdate :: Day
teffectivedate :: Maybe Day
tstatus :: Bool
tcode :: String
tdescription :: String
tcomment :: String
tmetadata :: [(String, String)]
tpostings :: [Posting]
tpreceding_comment_lines :: String
}
data ModifierTransaction = ModifierTransaction {
mtvalueexpr :: String
mtpostings :: [Posting]
}
data PeriodicTransaction = PeriodicTransaction {
ptperiodicexpr :: String
ptpostings :: [Posting]
}
data TimeLogCode
= SetBalance
| SetRequiredHours
| In
| Out
| FinalOut
data TimeLogEntry = TimeLogEntry {
tlcode :: TimeLogCode
tldatetime :: LocalTime
tlcomment :: String
}
data HistoricalPrice = HistoricalPrice {
hdate :: Day
hsymbol :: String
hamount :: MixedAmount
}
type Year = Integer
data JournalContext = Ctx {
ctxYear :: !(Maybe Year)
ctxCommodity :: !(Maybe Commodity)
ctxAccount :: ![AccountName]
}
data Journal = Journal {
jmodifiertxns :: [ModifierTransaction]
jperiodictxns :: [PeriodicTransaction]
jtxns :: [Transaction]
open_timelog_entries :: [TimeLogEntry]
historical_prices :: [HistoricalPrice]
final_comment_lines :: String
jContext :: JournalContext
files :: [(FilePath, String)]
filereadtime :: ClockTime
}
type JournalUpdate = ErrorT String IO (Journal -> Journal)
data Reader = Reader {
rFormat :: String
rDetector :: FilePath -> String -> Bool
rParser :: FilePath -> String -> ErrorT String IO Journal
}
data Ledger = Ledger {
journal :: Journal
accountnametree :: Tree AccountName
accountmap :: Map AccountName Account
}
data Account = Account {
aname :: AccountName
apostings :: [Posting]
abalance :: MixedAmount
}
data FilterSpec = FilterSpec {
datespan :: DateSpan
cleared :: Maybe Bool
real :: Bool
empty :: Bool
costbasis :: Bool
acctpats :: [String]
descpats :: [String]
whichdate :: WhichDate
depth :: Maybe Int
}
Documentation
type SmartDate = (String, String, String)Source
data WhichDate Source
Constructors
ActualDate
EffectiveDate
show/hide Instances
data DateSpan Source
Constructors
DateSpan (Maybe Day) (Maybe Day)
show/hide Instances
data Interval Source
Constructors
NoInterval
Days Int
Weeks Int
Months Int
Quarters Int
Years Int
DayOfMonth Int
DayOfWeek Int
show/hide Instances
type AccountName = StringSource
data Side Source
Constructors
L
R
show/hide Instances
data Commodity Source
Constructors
Commodity
symbol :: Stringthe commodity's symbol display preferences for amounts of this commodity
side :: Sideshould the symbol appear on the left or the right
spaced :: Boolshould there be a space between symbol and quantity
precision :: Intnumber of decimal places to display XXX these three might be better belonging to Journal
decimalpoint :: Charcharacter to use as decimal point
separator :: Charcharacter to use for separating digit groups (eg thousands)
separatorpositions :: [Int]positions of separators, counting leftward from decimal point
show/hide Instances
data Price Source
An amount's price may be written as @ unit price or @@ total price. Note although Price has a MixedAmount, it should hold only single-commodity amounts, cf costOfAmount.
Constructors
UnitPrice MixedAmount
TotalPrice MixedAmount
show/hide Instances
data Amount Source
Constructors
Amount
commodity :: Commodity
quantity :: Double
price :: Maybe Pricethe price for this amount at posting time
show/hide Instances
newtype MixedAmount Source
Constructors
Mixed [Amount]
show/hide Instances
data PostingType Source
Constructors
RegularPosting
VirtualPosting
BalancedVirtualPosting
show/hide Instances
data Posting Source
Constructors
Posting
pstatus :: Bool
paccount :: AccountName
pamount :: MixedAmount
pcomment :: String
ptype :: PostingType
pmetadata :: [(String, String)]
ptransaction :: Maybe Transactionthis posting's parent transaction (co-recursive types). Tying this knot gets tedious, Maybe makes it easier/optional.
show/hide Instances
data Transaction Source
Constructors
Transaction
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
show/hide Instances
data ModifierTransaction Source
Constructors
ModifierTransaction
mtvalueexpr :: String
mtpostings :: [Posting]
show/hide Instances
data PeriodicTransaction Source
Constructors
PeriodicTransaction
ptperiodicexpr :: String
ptpostings :: [Posting]
show/hide Instances
data TimeLogCode Source
Constructors
SetBalance
SetRequiredHours
In
Out
FinalOut
show/hide Instances
data TimeLogEntry Source
Constructors
TimeLogEntry
tlcode :: TimeLogCode
tldatetime :: LocalTime
tlcomment :: String
show/hide Instances
data HistoricalPrice Source
Constructors
HistoricalPrice
hdate :: Day
hsymbol :: String
hamount :: MixedAmount
show/hide Instances
type Year = IntegerSource
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
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 specified by !account
show/hide Instances
data Journal Source
Constructors
Journal
jmodifiertxns :: [ModifierTransaction]
jperiodictxns :: [PeriodicTransaction]
jtxns :: [Transaction]
open_timelog_entries :: [TimeLogEntry]
historical_prices :: [HistoricalPrice]
final_comment_lines :: Stringany trailing comments from the journal file
jContext :: JournalContextthe 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 :: ClockTimewhen this journal was last read from its file(s)
show/hide Instances
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.
Constructors
Reader
rFormat :: String
rDetector :: FilePath -> String -> Bool
rParser :: FilePath -> String -> ErrorT String IO Journal
data Ledger Source
Constructors
Ledger
journal :: Journal
accountnametree :: Tree AccountName
accountmap :: Map AccountName Account
show/hide Instances
data Account Source
Constructors
Account
aname :: AccountName
apostings :: [Posting]postings in this account
abalance :: MixedAmountsum of postings in this account and subaccounts
show/hide Instances
data FilterSpec Source
A generic, pure specification of how to filter transactions and postings.
Constructors
FilterSpec
datespan :: DateSpanonly include if in this date span
cleared :: Maybe Boolonly include if cleared/uncleared/don't care
real :: Boolonly include if real/don't care
empty :: Boolinclude if empty (ie amount is zero)
costbasis :: Boolconvert all amounts to cost basis
acctpats :: [String]only include if matching these account patterns
descpats :: [String]only include if matching these description patterns
whichdate :: WhichDatewhich dates to use (actual or effective)
depth :: Maybe Int
show/hide Instances
Produced by Haddock version 2.6.1