Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- type Tag = (TagName, TagValue)
- data Status
- type YearDay = Int
- type Month = Int
- type MonthDay = Int
- type Quarter = Int
- data MixedAmountKey
- data Account = Account {}
- type AccountName = Text
- data Amount = Amount {
- acommodity :: !CommoditySymbol
- aquantity :: !Quantity
- astyle :: !AmountStyle
- acost :: !(Maybe AmountCost)
- data Journal = Journal {
- jparsedefaultyear :: Maybe Year
- jparsedefaultcommodity :: Maybe (CommoditySymbol, AmountStyle)
- jparsedecimalmark :: Maybe DecimalMark
- jparseparentaccounts :: [AccountName]
- jparsealiases :: [AccountAlias]
- jparsetimeclockentries :: [TimeclockEntry]
- jincludefilestack :: [FilePath]
- jdeclaredpayees :: [(Payee, PayeeDeclarationInfo)]
- jdeclaredtags :: [(TagName, TagDeclarationInfo)]
- jdeclaredaccounts :: [(AccountName, AccountDeclarationInfo)]
- jdeclaredaccounttags :: Map AccountName [Tag]
- jdeclaredaccounttypes :: Map AccountType [AccountName]
- jaccounttypes :: Map AccountName AccountType
- jdeclaredcommodities :: Map CommoditySymbol Commodity
- jinferredcommoditystyles :: Map CommoditySymbol AmountStyle
- jglobalcommoditystyles :: Map CommoditySymbol AmountStyle
- jpricedirectives :: [PriceDirective]
- jinferredmarketprices :: [MarketPrice]
- jtxnmodifiers :: [TransactionModifier]
- jperiodictxns :: [PeriodicTransaction]
- jtxns :: [Transaction]
- jfinalcommentlines :: Text
- jfiles :: [(FilePath, Text)]
- jlastreadtime :: POSIXTime
- data Ledger = Ledger {}
- data Period
- data PeriodicTransaction = PeriodicTransaction {
- ptperiodexpr :: Text
- ptinterval :: Interval
- ptspan :: DateSpan
- ptsourcepos :: (SourcePos, SourcePos)
- ptstatus :: Status
- ptcode :: Text
- ptdescription :: Text
- ptcomment :: Text
- pttags :: [Tag]
- ptpostings :: [Posting]
- 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 Transaction = Transaction {}
- data TransactionModifier = TransactionModifier {}
- type CommoditySymbol = Text
- data AmountPrecision
- newtype MixedAmount = Mixed (Map MixedAmountKey Amount)
- type YearWeek = Int
- type MonthWeek = Int
- type WeekDay = Int
- data SmartDate
- data SmartInterval
- data WhichDate
- data EFDay
- data DateSpan = DateSpan (Maybe EFDay) (Maybe EFDay)
- data Interval
- type Payee = Text
- data DepthSpec = DepthSpec {
- dsFlatDepth :: Maybe Int
- dsRegexpDepths :: [(Regexp, Int)]
- data AccountType
- data AccountAlias
- data Side
- type DecimalMark = Char
- type Quantity = Decimal
- data AmountCost
- data AmountStyle = AmountStyle {
- ascommodityside :: !Side
- ascommodityspaced :: !Bool
- asdigitgroups :: !(Maybe DigitGroupStyle)
- asdecimalmark :: !(Maybe Char)
- asprecision :: !AmountPrecision
- asrounding :: !Rounding
- data DigitGroupStyle = DigitGroups !Char ![Word8]
- data Rounding
- data Commodity = Commodity {}
- class HasAmounts a where
- styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a
- data PostingType
- type TagName = Text
- type TagValue = Text
- type HiddenTag = Tag
- type DateTag = (TagName, Day)
- data BalanceAssertion = BalanceAssertion {
- baamount :: Amount
- batotal :: Bool
- bainclusive :: Bool
- baposition :: SourcePos
- data TMPostingRule = TMPostingRule {}
- data TimeclockCode
- = SetBalance
- | SetRequiredHours
- | In
- | Out
- | FinalOut
- data TimeclockEntry = TimeclockEntry {
- tlsourcepos :: SourcePos
- tlcode :: TimeclockCode
- tldatetime :: LocalTime
- tlaccount :: AccountName
- tldescription :: Text
- tlcomment :: Text
- tltags :: [Tag]
- data PriceDirective = PriceDirective {}
- data MarketPrice = MarketPrice {
- mpdate :: Day
- mpfrom :: CommoditySymbol
- mpto :: CommoditySymbol
- mprate :: Quantity
- data PayeeDeclarationInfo = PayeeDeclarationInfo {
- pdicomment :: Text
- pditags :: [Tag]
- newtype TagDeclarationInfo = TagDeclarationInfo {
- tdicomment :: Text
- data AccountDeclarationInfo = AccountDeclarationInfo {
- adicomment :: Text
- aditags :: [Tag]
- adideclarationorder :: Int
- adisourcepos :: SourcePos
- type ParsedJournal = Journal
- data SepFormat
- data StorageFormat
- data NormalSign
- fromEFDay :: EFDay -> Day
- modifyEFDay :: (Day -> Day) -> EFDay -> EFDay
- isBalanceSheetAccountType :: AccountType -> Bool
- isIncomeStatementAccountType :: AccountType -> Bool
- isAccountSubtypeOf :: AccountType -> AccountType -> Bool
- isDecimalMark :: Char -> Bool
- maCompare :: MixedAmount -> MixedAmount -> Ordering
- toHiddenTag :: Tag -> HiddenTag
- toHiddenTagName :: TagName -> TagName
- toVisibleTag :: HiddenTag -> Tag
- toVisibleTagName :: TagName -> TagName
- isHiddenTagName :: TagName -> Bool
- nullsourcepos :: SourcePos
- nullsourcepospair :: (SourcePos, SourcePos)
- nulltransactionmodifier :: TransactionModifier
- nullperiodictransaction :: PeriodicTransaction
- showMarketPrice :: MarketPrice -> String
- showMarketPrices :: [MarketPrice] -> [Char]
- nullpayeedeclarationinfo :: PayeeDeclarationInfo
- nulltagdeclarationinfo :: TagDeclarationInfo
- nullaccountdeclarationinfo :: AccountDeclarationInfo
- type Year = Integer
Documentation
The status of a transaction or posting, recorded with a status mark (nothing, !, or *). What these mean is ultimately user defined.
Instances
FromJSON Status Source # | |
Defined in Hledger.Data.Json | |
ToJSON Status Source # | |
Bounded Status Source # | |
Enum Status Source # | |
Defined in Hledger.Data.Types | |
Generic Status Source # | |
Show Status Source # | |
Eq Status Source # | |
Ord Status Source # | |
type Rep Status Source # | |
Defined in Hledger.Data.Types type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" '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 MixedAmountKey Source #
Stores the CommoditySymbol of the Amount, along with the CommoditySymbol of the cost, and its unit cost if being used.
MixedAmountKeyNoCost !CommoditySymbol | |
MixedAmountKeyTotalCost !CommoditySymbol !CommoditySymbol | |
MixedAmountKeyUnitCost !CommoditySymbol !CommoditySymbol !Quantity |
Instances
An account, with its balances, parent/subaccount relationships, etc. Only the name is required; the other fields are added when needed.
Account | |
|
Instances
type AccountName = Text Source #
Amount | |
|
Instances
FromJSON Amount Source # | |
Defined in Hledger.Data.Json | |
ToJSON Amount Source # | |
Generic Amount Source # | |
Num Amount Source # | |
Show Amount Source # | |
Eq Amount Source # | |
Ord Amount Source # | |
HasAmounts Amount Source # | |
Defined in Hledger.Data.Amount styleAmounts :: Map CommoditySymbol AmountStyle -> Amount -> Amount Source # | |
type Rep Amount Source # | |
Defined in Hledger.Data.Types type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" 'False) (C1 ('MetaCons "Amount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "acommodity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "aquantity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Quantity)) :*: (S1 ('MetaSel ('Just "astyle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountStyle) :*: S1 ('MetaSel ('Just "acost") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe AmountCost))))) |
A journal, containing general ledger transactions; also directives and various other things. This is hledger's main data model.
During parsing, it is used as the type alias ParsedJournal. The jparse* fields are mainly used during parsing and included here for convenience. The list fields described as "in parse order" are usually reversed for efficiency during parsing. After parsing, "journalFinalise" converts ParsedJournal to a finalised Journal, which has all lists correctly ordered, and much data inference and validation applied.
Journal | |
|
Instances
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
ToJSON Ledger Source # | |
Generic Ledger Source # | |
Show Ledger Source # | |
type Rep Ledger Source # | |
Defined in Hledger.Data.Types type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account]))) |
DayPeriod Day | |
WeekPeriod Day | |
MonthPeriod Year Month | |
QuarterPeriod Year Quarter | |
YearPeriod Year | |
PeriodBetween Day Day | |
PeriodFrom Day | |
PeriodTo Day | |
PeriodAll |
Instances
data PeriodicTransaction Source #
A periodic transaction rule, describing a transaction that recurs.
PeriodicTransaction | |
|
Instances
Posting | |
|
Instances
data Transaction Source #
Transaction | |
|
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.
Instances
type CommoditySymbol = Text Source #
data AmountPrecision Source #
The "display precision" for a hledger amount, by which we mean the number of decimal digits to display to the right of the decimal mark.
Precision !Word8 | show this many decimal digits (0..255) |
NaturalPrecision | show all significant decimal digits stored internally |
Instances
newtype MixedAmount Source #
Instances
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 SmartInterval Source #
Instances
Show SmartInterval Source # | |
Defined in Hledger.Data.Types showsPrec :: Int -> SmartInterval -> ShowS # show :: SmartInterval -> String # showList :: [SmartInterval] -> ShowS # |
Instances
A date which is either exact or flexible. Flexible dates are allowed to be adjusted in certain situations.
Instances
ToJSON EFDay Source # | |
Generic EFDay Source # | |
Show EFDay Source # | |
Eq EFDay Source # | |
Ord EFDay Source # | |
type Rep EFDay Source # | |
Defined in Hledger.Data.Types type Rep EFDay = D1 ('MetaData "EFDay" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" 'False) (C1 ('MetaCons "Exact" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "Flex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day))) |
A possibly open-ended span of time, from an optional inclusive start date to an optional exclusive end date. Each date can be either exact or flexible. An "exact date span" is a Datepan with exact start and end dates.
Instances
ToJSON DateSpan Source # | |
Generic DateSpan Source # | |
Show DateSpan Source # | |
Default DateSpan Source # | |
Defined in Hledger.Data.Types | |
Eq DateSpan Source # | |
Ord 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.41-KmCZ9CfrRKB8FRJeJbvQfv" 'False) (C1 ('MetaCons "DateSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EFDay)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EFDay)))) |
NoInterval | |
Days Int | |
Weeks Int | |
Months Int | |
Quarters Int | |
Years Int | |
NthWeekdayOfMonth Int Int | |
MonthDay Int | |
MonthAndDay Int Int | |
DaysOfWeek [Int] |
Instances
DepthSpec | |
|
data AccountType Source #
Asset | |
Liability | |
Equity | |
Revenue | |
Expense | |
Cash | a subtype of Asset - liquid assets to show in cashflow report |
Conversion | a subtype of Equity - account with which to balance commodity conversions |
Instances
data AccountAlias Source #
Instances
type DecimalMark = Char Source #
One of the decimal marks we support: either period or comma.
data AmountCost Source #
An amount's per-unit or total cost/selling price in another
commodity, as recorded in the journal entry eg with or
@.
Cost, formerly AKA "transaction price". The amount is always positive.
Instances
data AmountStyle Source #
Display styles for amounts - things which can be detected during parsing, such as commodity side and spacing, digit group marks, decimal mark, number of decimal digits etc. Every Amount has an AmountStyle. After amounts are parsed from the input, for each Commodity a standard style is inferred and then used when displaying amounts in that commodity. Related to AmountFormat but higher level.
See also: - hledger manual > Commodity styles - hledger manual > Amounts - hledger manual > Commodity display style
AmountStyle | |
|
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].
DigitGroups !Char ![Word8] |
Instances
"Rounding strategy" - how to apply an AmountStyle's display precision to a posting amount (and its cost, if any). Mainly used to customise print's output, with --round=none|soft|hard|all.
NoRounding | keep display precisions unchanged in amt and cost |
SoftRounding | do soft rounding of amt and cost amounts (show more or fewer decimal zeros to approximate the target precision, but don't hide significant digits) |
HardRounding | do hard rounding of amt (use the exact target precision, possibly hiding significant digits), and soft rounding of cost |
AllRounding | do hard rounding of amt and cost |
Instances
FromJSON Rounding Source # | |
Defined in Hledger.Data.Json | |
ToJSON Rounding Source # | |
Generic Rounding Source # | |
Read Rounding Source # | |
Show Rounding Source # | |
Eq Rounding Source # | |
Ord Rounding Source # | |
Defined in Hledger.Data.Types | |
type Rep Rounding Source # | |
Defined in Hledger.Data.Types type Rep Rounding = D1 ('MetaData "Rounding" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" 'False) ((C1 ('MetaCons "NoRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SoftRounding" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HardRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllRounding" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
ToJSON Commodity Source # | |
Generic Commodity Source # | |
Show Commodity Source # | |
Eq Commodity Source # | |
type Rep Commodity Source # | |
Defined in Hledger.Data.Types type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.41-KmCZ9CfrRKB8FRJeJbvQfv" '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)))) |
class HasAmounts a where Source #
Types with this class have one or more amounts, which can have display styles applied to them.
styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a Source #
Instances
data PostingType Source #
Instances
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.
A balance assignments is an instruction to hledger to adjust an account's balance to a certain amount at a certain point.
The BalanceAssertion
type is used for representing both of these.
hledger supports multiple kinds of balance assertions/assignments, which differ in whether they refer to a single commodity or all commodities, and the (subaccount-)inclusive or exclusive account balance.
BalanceAssertion | |
|
Instances
data TMPostingRule Source #
A transaction modifier transformation, which adds an extra posting to the matched posting's transaction. Can be like a regular posting, or can have the tmprIsMultiplier flag set, indicating that it's a multiplier for the matched posting's amount.
Instances
data TimeclockCode Source #
Instances
data TimeclockEntry Source #
TimeclockEntry | |
|
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.
PriceDirective | |
|
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.
MarketPrice | |
|
Instances
data PayeeDeclarationInfo Source #
Extra information found in a payee directive.
PayeeDeclarationInfo | |
|
Instances
newtype TagDeclarationInfo Source #
Extra information found in a tag directive.
TagDeclarationInfo | |
|
Instances
data AccountDeclarationInfo Source #
Extra information about an account that can be derived from its account directive (and the other account directives).
AccountDeclarationInfo | |
|
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.
One of the standard *-separated value file types known by hledger,
Instances
data StorageFormat Source #
The id of a data format understood by hledger, eg journal
or csv
.
The --output-format option selects one of these for output.
Instances
Show StorageFormat Source # | |
Defined in Hledger.Data.Types showsPrec :: Int -> StorageFormat -> ShowS # show :: StorageFormat -> String # showList :: [StorageFormat] -> ShowS # | |
Eq StorageFormat Source # | |
Defined in Hledger.Data.Types (==) :: StorageFormat -> StorageFormat -> Bool # (/=) :: StorageFormat -> StorageFormat -> Bool # |
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
Instances
Show NormalSign Source # | |
Defined in Hledger.Data.Types showsPrec :: Int -> NormalSign -> ShowS # show :: NormalSign -> String # showList :: [NormalSign] -> ShowS # | |
Eq NormalSign Source # | |
Defined in Hledger.Data.Types (==) :: NormalSign -> NormalSign -> Bool # (/=) :: NormalSign -> NormalSign -> Bool # |
isAccountSubtypeOf :: AccountType -> AccountType -> Bool Source #
Check whether the first argument is a subtype of the second: either equal or one of the defined subtypes.
isDecimalMark :: Char -> Bool Source #
maCompare :: MixedAmount -> MixedAmount -> Ordering Source #
Compare two MixedAmounts, substituting 0 for the quantity of any missing commodities in either.
toHiddenTag :: Tag -> HiddenTag Source #
Add the _ prefix to a normal visible tag's name, making it a hidden tag.
toHiddenTagName :: TagName -> TagName Source #
Add the _ prefix to a normal visible tag's name, making it a hidden tag.
toVisibleTag :: HiddenTag -> Tag Source #
Drop the _ prefix from a hidden tag's name, making it a normal visible tag.
toVisibleTagName :: TagName -> TagName Source #
Drop the _ prefix from a hidden tag's name, making it a normal visible tag.
isHiddenTagName :: TagName -> Bool Source #
Does this tag name begin with the hidden tag prefix (_) ?
showMarketPrice :: MarketPrice -> String Source #
showMarketPrices :: [MarketPrice] -> [Char] Source #
Orphan instances
ToMarkup Quantity Source # | |
Generic (DecimalRaw a) Source # | |
type Rep (DecimalRaw a) :: Type -> Type # from :: DecimalRaw a -> Rep (DecimalRaw a) x # to :: Rep (DecimalRaw a) x -> DecimalRaw a # |