| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hledger.Data.Types
Contents
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, cleared status, code, description and.. [Posting] -- multiple account postings, which have account name and amount [MarketPrice] -- historical market prices for commodities 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
- data SmartDate
- data SmartSequence
- data SmartInterval
- data WhichDate
- data DateSpan = DateSpan (Maybe Day) (Maybe Day)
- type Year = Integer
- type Month = Int
- type Quarter = Int
- type YearWeek = Int
- type MonthWeek = Int
- type YearDay = Int
- type MonthDay = Int
- type WeekDay = Int
- data Period
- data Interval
- type AccountName = Text
- data AccountType
- data AccountAlias
- data Side
- type DecimalMark = Char
- isDecimalMark :: Char -> Bool
- type Quantity = Decimal
- data AmountPrice
- data AmountStyle = AmountStyle {}
- data AmountPrecision
- data DigitGroupStyle = DigitGroups Char [Word8]
- type CommoditySymbol = Text
- data Commodity = Commodity {}
- data Amount = Amount {}
- newtype MixedAmount = Mixed [Amount]
- data PostingType
- type TagName = Text
- type TagValue = Text
- type Tag = (TagName, TagValue)
- type DateTag = (TagName, Day)
- data Status
- data BalanceAssertion = BalanceAssertion {}
- data Posting = Posting {- pdate :: Maybe Day
- pdate2 :: Maybe Day
- pstatus :: Status
- paccount :: AccountName
- pamount :: MixedAmount
- pcomment :: Text
- ptype :: PostingType
- ptags :: [Tag]
- pbalanceassertion :: Maybe BalanceAssertion
- ptransaction :: Maybe Transaction
- poriginal :: Maybe Posting
 
- data GenericSourcePos
- data Transaction = Transaction {}
- data TransactionModifier = TransactionModifier {}
- nulltransactionmodifier :: TransactionModifier
- type TMPostingRule = Posting
- data PeriodicTransaction = PeriodicTransaction {- ptperiodexpr :: Text
- ptinterval :: Interval
- ptspan :: DateSpan
- ptstatus :: Status
- ptcode :: Text
- ptdescription :: Text
- ptcomment :: Text
- pttags :: [Tag]
- ptpostings :: [Posting]
 
- nullperiodictransaction :: PeriodicTransaction
- data TimeclockCode- = SetBalance
- | SetRequiredHours
- | In
- | Out
- | FinalOut
 
- data TimeclockEntry = TimeclockEntry {}
- data PriceDirective = PriceDirective {}
- data MarketPrice = MarketPrice {- mpdate :: Day
- mpfrom :: CommoditySymbol
- mpto :: CommoditySymbol
- mprate :: Quantity
 
- data Journal = Journal {- jparsedefaultyear :: Maybe Year
- jparsedefaultcommodity :: Maybe (CommoditySymbol, AmountStyle)
- jparsedecimalmark :: Maybe DecimalMark
- jparseparentaccounts :: [AccountName]
- jparsealiases :: [AccountAlias]
- jparsetimeclockentries :: [TimeclockEntry]
- jincludefilestack :: [FilePath]
- jdeclaredaccounts :: [(AccountName, AccountDeclarationInfo)]
- jdeclaredaccounttypes :: Map AccountType [AccountName]
- jglobalcommoditystyles :: Map CommoditySymbol AmountStyle
- jcommodities :: Map CommoditySymbol Commodity
- jinferredcommodities :: Map CommoditySymbol AmountStyle
- jpricedirectives :: [PriceDirective]
- jinferredmarketprices :: [MarketPrice]
- jtxnmodifiers :: [TransactionModifier]
- jperiodictxns :: [PeriodicTransaction]
- jtxns :: [Transaction]
- jfinalcommentlines :: Text
- jfiles :: [(FilePath, Text)]
- jlastreadtime :: ClockTime
 
- type ParsedJournal = Journal
- type StorageFormat = String
- data AccountDeclarationInfo = AccountDeclarationInfo {- adicomment :: Text
- aditags :: [Tag]
- adideclarationorder :: Int
 
- nullaccountdeclarationinfo :: AccountDeclarationInfo
- data Account = Account {}
- data NormalSign
- data Ledger = Ledger {}
Documentation
A possibly incomplete year-month-day date provided by the user, to be
 interpreted as either a date or a date span depending on context. Missing
 parts "on the left" will be filled from the provided reference date, e.g. if
 the year and month are missing, the reference date's year and month are used.
 Missing parts "on the right" are assumed, when interpreting as a date, to be
 1, (e.g. if the year and month are present but the day is missing, it means
 first day of that month); or when interpreting as a date span, to be a
 wildcard (so it would mean all days of that month). See the smartdate
 parser for more examples.
Or, one of the standard periods and an offset relative to the reference date: (last|this|next) (day|week|month|quarter|year), where "this" means the period containing the reference date.
data SmartSequence Source #
Instances
| Show SmartSequence Source # | |
| Defined in Hledger.Data.Types Methods showsPrec :: Int -> SmartSequence -> ShowS # show :: SmartSequence -> String # showList :: [SmartSequence] -> ShowS # | |
data SmartInterval Source #
Instances
| Show SmartInterval Source # | |
| Defined in Hledger.Data.Types Methods showsPrec :: Int -> SmartInterval -> ShowS # show :: SmartInterval -> String # showList :: [SmartInterval] -> ShowS # | |
Constructors
| PrimaryDate | |
| SecondaryDate | 
Instances
| Eq DateSpan Source # | |
| Ord DateSpan Source # | |
| Defined in Hledger.Data.Types | |
| Show DateSpan Source # | |
| Generic DateSpan Source # | |
| ToJSON DateSpan Source # | |
| Defined in Hledger.Data.Json | |
| Default DateSpan Source # | |
| Defined in Hledger.Data.Types | |
| type Rep DateSpan Source # | |
| Defined in Hledger.Data.Types type Rep DateSpan = D1 ('MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.20.1-FsvmUDtrIvW5rHga2fHkko" 'False) (C1 ('MetaCons "DateSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)))) | |
Constructors
| DayPeriod Day | |
| WeekPeriod Day | |
| MonthPeriod Year Month | |
| QuarterPeriod Year Quarter | |
| YearPeriod Year | |
| PeriodBetween Day Day | |
| PeriodFrom Day | |
| PeriodTo Day | |
| PeriodAll | 
Instances
Constructors
| NoInterval | |
| Days Int | |
| Weeks Int | |
| Months Int | |
| Quarters Int | |
| Years Int | |
| DayOfMonth Int | |
| WeekdayOfMonth Int Int | |
| DayOfWeek Int | |
| DayOfYear Int Int | 
Instances
type AccountName = Text Source #
data AccountType Source #
Constructors
| Asset | |
| Liability | |
| Equity | |
| Revenue | |
| Expense | |
| Cash | a subtype of Asset - liquid assets to show in cashflow report | 
Instances
data AccountAlias Source #
Constructors
| BasicAlias AccountName AccountName | |
| RegexAlias Regexp Replacement | 
Instances
type DecimalMark = Char Source #
One of the decimal marks we support: either period or comma.
isDecimalMark :: Char -> Bool Source #
data AmountPrice Source #
An amount's per-unit or total cost/selling price in another
 commodity, as recorded in the journal entry eg with  or @.
 Docs call this "transaction price". The amount is always positive.
Constructors
| UnitPrice Amount | |
| TotalPrice Amount | 
Instances
data AmountStyle Source #
Display style for an amount.
Constructors
| AmountStyle | |
| Fields 
 | |
Instances
data AmountPrecision Source #
Constructors
| Precision !Word8 | |
| NaturalPrecision | 
Instances
data DigitGroupStyle Source #
A style for displaying digit groups in the integer part of a floating point number. It consists of the character used to separate groups (comma or period, whichever is not used as decimal point), and the size of each group, starting with the one nearest the decimal point. The last group size is assumed to repeat. Eg, comma between thousands is DigitGroups ',' [3].
Constructors
| DigitGroups Char [Word8] | 
Instances
type CommoditySymbol = Text Source #
Constructors
| Commodity | |
| Fields | |
Instances
| Eq Commodity Source # | |
| Show Commodity Source # | |
| Generic Commodity Source # | |
| ToJSON Commodity Source # | |
| Defined in Hledger.Data.Json | |
| type Rep Commodity Source # | |
| Defined in Hledger.Data.Types type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.20.1-FsvmUDtrIvW5rHga2fHkko" 'False) (C1 ('MetaCons "Commodity" 'PrefixI 'True) (S1 ('MetaSel ('Just "csymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "cformat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AmountStyle)))) | |
Constructors
| Amount | |
| Fields 
 | |
Instances
| Eq Amount Source # | |
| Num Amount Source # | |
| Ord Amount Source # | |
| Show Amount Source # | |
| Generic Amount Source # | |
| ToJSON Amount Source # | |
| Defined in Hledger.Data.Json | |
| FromJSON Amount Source # | |
| type Rep Amount Source # | |
| Defined in Hledger.Data.Types type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.20.1-FsvmUDtrIvW5rHga2fHkko" 'False) (C1 ('MetaCons "Amount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "acommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "aquantity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity)) :*: (S1 ('MetaSel ('Just "aismultiplier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "astyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AmountStyle) :*: S1 ('MetaSel ('Just "aprice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AmountPrice)))))) | |
newtype MixedAmount Source #
Instances
data PostingType Source #
Constructors
| RegularPosting | |
| VirtualPosting | |
| BalancedVirtualPosting | 
Instances
The status of a transaction or posting, recorded with a status mark (nothing, !, or *). What these mean is ultimately user defined.
Instances
| Bounded Status Source # | |
| Enum Status Source # | |
| Defined in Hledger.Data.Types | |
| Eq Status Source # | |
| Ord Status Source # | |
| Show Status Source # | |
| Generic Status Source # | |
| ToJSON Status Source # | |
| Defined in Hledger.Data.Json | |
| FromJSON Status Source # | |
| type Rep Status Source # | |
| Defined in Hledger.Data.Types type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.20.1-FsvmUDtrIvW5rHga2fHkko" 'False) (C1 ('MetaCons "Unmarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cleared" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data BalanceAssertion Source #
A balance assertion is a declaration about an account's expected balance at a certain point (posting date and parse order). They provide additional error checking and readability to a journal file.
The BalanceAssertion type is also used to represent balance assignments,
 which instruct hledger what an account's balance should become at a certain
 point.
Different kinds of balance assertions are discussed eg on #290. Variables include:
- which postings are to be summed (realvirtual; unmarkedpendingcleared; this accountthis account including subs)
- which commodities within the balance are to be checked
- whether to do a partial or a total check (disallowing other commodities)
I suspect we want:
- partial, subaccount-exclusive, Ledger-compatible assertions. Because they're what we've always had, and removing them would break some journals unnecessarily. Implemented with = syntax.
- total assertions. Because otherwise assertions are a bit leaky. Implemented with == syntax.
- subaccount-inclusive assertions. Because that's something folks need. Not implemented.
- flexible assertions allowing custom criteria (perhaps arbitrary queries). Because power users have diverse needs and want to try out different schemes (assert cleared balances, assert balance from real or virtual postings, etc.). Not implemented.
- multicommodity assertions, asserting the balance of multiple commodities at once. Not implemented, requires #934.
Constructors
| BalanceAssertion | |
| Fields 
 | |
Instances
Constructors
| Posting | |
| Fields 
 | |
Instances
data GenericSourcePos Source #
The position of parse errors (eg), like parsec's SourcePos but generic.
Constructors
| GenericSourcePos FilePath Int Int | file path, 1-based line number and 1-based column number. | 
| JournalSourcePos FilePath (Int, Int) | file path, inclusive range of 1-based line numbers (first, last). | 
Instances
data Transaction Source #
Constructors
| Transaction | |
| Fields 
 | |
Instances
data TransactionModifier Source #
A transaction modifier rule. This has a query which matches postings in the journal, and a list of transformations to apply to those postings or their transactions. Currently there is one kind of transformation: the TMPostingRule, which adds a posting ("auto posting") to the transaction, optionally setting its amount to the matched posting's amount multiplied by a constant.
Constructors
| TransactionModifier | |
| Fields 
 | |
Instances
type TMPostingRule = Posting Source #
A transaction modifier transformation, which adds an extra posting to the matched posting's transaction. Can be like a regular posting, or the amount can have the aismultiplier flag set, indicating that it's a multiplier for the matched posting's amount.
data PeriodicTransaction Source #
A periodic transaction rule, describing a transaction that recurs.
Constructors
| PeriodicTransaction | |
| Fields 
 | |
Instances
data TimeclockCode Source #
Constructors
| SetBalance | |
| SetRequiredHours | |
| In | |
| Out | |
| FinalOut | 
Instances
data TimeclockEntry Source #
Constructors
| TimeclockEntry | |
| Fields | |
Instances
data PriceDirective Source #
A market price declaration made by the journal format's P directive. It declares two things: a historical exchange rate between two commodities, and an amount display style for the second commodity.
Constructors
| PriceDirective | |
| Fields 
 | |
Instances
data MarketPrice Source #
A historical market price (exchange rate) from one commodity to another. A more concise form of a PriceDirective, without the amount display info.
Constructors
| MarketPrice | |
| Fields 
 | |
Instances
A Journal, containing transactions and various other things. The basic data model for hledger.
This is used during parsing (as the type alias ParsedJournal), and then finalised/validated for use as a Journal. Some extra parsing-related fields are included for convenience, at least for now. In a ParsedJournal these are updated as parsing proceeds, in a Journal they represent the final state at end of parsing (used eg by the add command).
Constructors
| Journal | |
| Fields 
 | |
Instances
type ParsedJournal = Journal Source #
A journal in the process of being parsed, not yet finalised. The data is partial, and list fields are in reverse order.
type StorageFormat = String Source #
The id of a data format understood by hledger, eg journal or csv.
 The --output-format option selects one of these for output.
data AccountDeclarationInfo Source #
Extra information about an account that can be derived from its account directive (and the other account directives).
Constructors
| AccountDeclarationInfo | |
| Fields 
 | |
Instances
An account, with its balances, parent/subaccount relationships, etc. Only the name is required; the other fields are added when needed.
Constructors
| Account | |
| Fields 
 | |
Instances
data NormalSign Source #
Whether an account's balance is normally a positive number (in accounting terms, a debit balance) or a negative number (credit balance). Assets and expenses are normally positive (debit), while liabilities, equity and income are normally negative (credit). https://en.wikipedia.org/wiki/Normal_balance
Constructors
| NormallyPositive | |
| NormallyNegative | 
Instances
| Eq NormalSign Source # | |
| Defined in Hledger.Data.Types | |
| Show NormalSign Source # | |
| Defined in Hledger.Data.Types Methods showsPrec :: Int -> NormalSign -> ShowS # show :: NormalSign -> String # showList :: [NormalSign] -> ShowS # | |
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.
Instances
| Show Ledger Source # | |
| Generic Ledger Source # | |
| ToJSON Ledger Source # | |
| Defined in Hledger.Data.Json | |
| type Rep Ledger Source # | |
| Defined in Hledger.Data.Json type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.20.1-FsvmUDtrIvW5rHga2fHkko" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account]))) | |