Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hledger.Data
Description
The Hledger.Data library allows parsing and querying of C++ ledger-style journal files. It generally provides a compatible subset of C++ ledger's functionality. This package re-exports all the Hledger.Data.* modules (except UTF8, which requires an explicit import.)
Synopsis
- module Hledger.Data.Account
- module Hledger.Data.AccountName
- module Hledger.Data.Amount
- module Hledger.Data.Balancing
- module Hledger.Data.Currency
- module Hledger.Data.Dates
- module Hledger.Data.Errors
- module Hledger.Data.Journal
- module Hledger.Data.JournalChecks
- module Hledger.Data.Json
- module Hledger.Data.Ledger
- module Hledger.Data.Period
- module Hledger.Data.PeriodicTransaction
- module Hledger.Data.Posting
- module Hledger.Data.RawOptions
- module Hledger.Data.StringFormat
- module Hledger.Data.Timeclock
- module Hledger.Data.Transaction
- module Hledger.Data.TransactionModifier
- data Side
- data TimeclockCode
- = SetBalance
- | SetRequiredHours
- | In
- | Out
- | FinalOut
- type Tag = (TagName, TagValue)
- data AccountType
- data SepFormat
- data Status
- type Year = Integer
- data SmartInterval
- data Period
- type YearDay = Int
- type Month = Int
- type MonthDay = Int
- data Interval
- type Quarter = Int
- 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 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 StorageFormat
- data Transaction = Transaction {}
- data TransactionModifier = TransactionModifier {}
- fromEFDay :: EFDay -> Day
- modifyEFDay :: (Day -> Day) -> EFDay -> EFDay
- type CommoditySymbol = Text
- data AmountPrecision
- data AmountStyle = AmountStyle {
- ascommodityside :: !Side
- ascommodityspaced :: !Bool
- asdigitgroups :: !(Maybe DigitGroupStyle)
- asdecimalmark :: !(Maybe Char)
- asprecision :: !AmountPrecision
- asrounding :: !Rounding
- data MixedAmount
- type YearWeek = Int
- type MonthWeek = Int
- type WeekDay = Int
- data SmartDate
- data WhichDate
- data EFDay
- data DateSpan = DateSpan (Maybe EFDay) (Maybe EFDay)
- type Payee = Text
- data DepthSpec = DepthSpec {
- dsFlatDepth :: Maybe Int
- dsRegexpDepths :: [(Regexp, Int)]
- isBalanceSheetAccountType :: AccountType -> Bool
- isIncomeStatementAccountType :: AccountType -> Bool
- isAccountSubtypeOf :: AccountType -> AccountType -> Bool
- data AccountAlias
- type DecimalMark = Char
- isDecimalMark :: Char -> Bool
- type Quantity = Decimal
- data AmountCost
- data DigitGroupStyle = DigitGroups !Char ![Word8]
- data Rounding
- data Commodity = Commodity {}
- class HasAmounts a where
- styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a
- maCompare :: MixedAmount -> MixedAmount -> Ordering
- pattern MixedAmountKeyNoCost :: !CommoditySymbol -> MixedAmountKey
- pattern MixedAmountKeyTotalCost :: !CommoditySymbol -> !CommoditySymbol -> MixedAmountKey
- pattern MixedAmountKeyUnitCost :: !CommoditySymbol -> !CommoditySymbol -> !Quantity -> MixedAmountKey
- data PostingType
- type TagName = Text
- type TagValue = Text
- type HiddenTag = Tag
- type DateTag = (TagName, Day)
- toHiddenTag :: Tag -> HiddenTag
- toHiddenTagName :: TagName -> TagName
- toVisibleTag :: HiddenTag -> Tag
- toVisibleTagName :: TagName -> TagName
- isHiddenTagName :: TagName -> Bool
- nullsourcepos :: SourcePos
- nullsourcepospair :: (SourcePos, SourcePos)
- data BalanceAssertion = BalanceAssertion {
- baamount :: Amount
- batotal :: Bool
- bainclusive :: Bool
- baposition :: SourcePos
- data TMPostingRule = TMPostingRule {}
- nulltransactionmodifier :: TransactionModifier
- nullperiodictransaction :: PeriodicTransaction
- 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
- showMarketPrice :: MarketPrice -> String
- showMarketPrices :: [MarketPrice] -> [Char]
- 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
- nullpayeedeclarationinfo :: PayeeDeclarationInfo
- nulltagdeclarationinfo :: TagDeclarationInfo
- nullaccountdeclarationinfo :: AccountDeclarationInfo
- data NormalSign
- module Hledger.Data.Valuation
- tests_Data :: TestTree
Documentation
module Hledger.Data.Account
module Hledger.Data.AccountName
module Hledger.Data.Amount
module Hledger.Data.Balancing
module Hledger.Data.Currency
module Hledger.Data.Dates
module Hledger.Data.Errors
module Hledger.Data.Journal
module Hledger.Data.JournalChecks
module Hledger.Data.Json
module Hledger.Data.Ledger
module Hledger.Data.Period
module Hledger.Data.Posting
module Hledger.Data.RawOptions
module Hledger.Data.StringFormat
module Hledger.Data.Timeclock
module Hledger.Data.Transaction
Instances
FromJSON Side Source # | |
Defined in Hledger.Data.Json | |
ToJSON Side Source # | |
Generic Side Source # | |
Defined in Hledger.Data.Types | |
Read Side Source # | |
Show Side Source # | |
NFData Side Source # | |
Defined in Hledger.Data.Types | |
Eq Side Source # | |
Ord Side Source # | |
type Rep Side Source # | |
data TimeclockCode Source #
Constructors
SetBalance | |
SetRequiredHours | |
In | |
Out | |
FinalOut |
Instances
data AccountType Source #
Constructors
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
ToJSON AccountType Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AccountType -> Value # toEncoding :: AccountType -> Encoding # toJSONList :: [AccountType] -> Value # toEncodingList :: [AccountType] -> Encoding # omitField :: AccountType -> Bool # | |||||
ToJSONKey AccountType Source # | |||||
Defined in Hledger.Data.Json Methods | |||||
Generic AccountType Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show AccountType Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountType -> ShowS # show :: AccountType -> String # showList :: [AccountType] -> ShowS # | |||||
NFData AccountType Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AccountType -> () # | |||||
Eq AccountType Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord AccountType Source # | |||||
Defined in Hledger.Data.Types Methods compare :: AccountType -> AccountType -> Ordering # (<) :: AccountType -> AccountType -> Bool # (<=) :: AccountType -> AccountType -> Bool # (>) :: AccountType -> AccountType -> Bool # (>=) :: AccountType -> AccountType -> Bool # max :: AccountType -> AccountType -> AccountType # min :: AccountType -> AccountType -> AccountType # | |||||
type Rep AccountType Source # | |||||
Defined in Hledger.Data.Types type Rep AccountType = D1 ('MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) ((C1 ('MetaCons "Asset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Liability" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Equity" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Revenue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Expense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Conversion" 'PrefixI 'False) (U1 :: Type -> Type)))) |
One of the standard *-separated value file types known by hledger,
Instances
Show SepFormat Source # | |
Eq SepFormat Source # | |
Ord SepFormat Source # | |
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 # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Status Source # | |||||
NFData Status Source # | |||||
Defined in Hledger.Data.Types | |||||
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.43.2-AWkFvE9IqZD4pwx38wuEvt" '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 SmartInterval Source #
Instances
Show SmartInterval Source # | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> SmartInterval -> ShowS # show :: SmartInterval -> String # showList :: [SmartInterval] -> ShowS # |
Constructors
DayPeriod Day | |
WeekPeriod Day | |
MonthPeriod Year Month | |
QuarterPeriod Year Quarter | |
YearPeriod Year | |
PeriodBetween Day Day | |
PeriodFrom Day | |
PeriodTo Day | |
PeriodAll |
Instances
ToJSON Period Source # | |||||
Generic Period Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Period Source # | |||||
Default Period Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Period Source # | |||||
Ord Period Source # | |||||
HasAmounts PostingsReportItem Source # | |||||
Defined in Hledger.Reports.PostingsReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PostingsReportItem -> PostingsReportItem Source # | |||||
type Rep Period Source # | |||||
Defined in Hledger.Data.Types type Rep Period = D1 ('MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (((C1 ('MetaCons "DayPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day)) :+: C1 ('MetaCons "WeekPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day))) :+: (C1 ('MetaCons "MonthPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Year) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Month)) :+: C1 ('MetaCons "QuarterPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Year) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Quarter)))) :+: ((C1 ('MetaCons "YearPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Year)) :+: C1 ('MetaCons "PeriodBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day))) :+: (C1 ('MetaCons "PeriodFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day)) :+: (C1 ('MetaCons "PeriodTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day)) :+: C1 ('MetaCons "PeriodAll" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Constructors
NoInterval | |
Days Int | |
Weeks Int | |
Months Int | |
Quarters Int | |
Years Int | |
NthWeekdayOfMonth Int Int | |
MonthDay Int | |
MonthAndDay Int Int | |
DaysOfWeek [Int] |
Instances
ToJSON Interval Source # | |||||
Generic Interval Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Interval Source # | |||||
Default Interval Source # | |||||
Defined in Hledger.Data.Types | |||||
NFData Interval Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Interval Source # | |||||
Ord Interval Source # | |||||
Defined in Hledger.Data.Types | |||||
type Rep Interval Source # | |||||
Defined in Hledger.Data.Types type Rep Interval = D1 ('MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (((C1 ('MetaCons "NoInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Days" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "Weeks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "Months" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Quarters" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))) :+: ((C1 ('MetaCons "Years" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "NthWeekdayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "MonthDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "MonthAndDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "DaysOfWeek" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Int])))))) |
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
FromJSON Account Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON Account Source # | |||||
Generic Account Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Account Source # | |||||
Eq Account Source # | |||||
HasAmounts Account Source # | |||||
Defined in Hledger.Data.Amount Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Account -> Account Source # | |||||
type Rep Account Source # | |||||
Defined in Hledger.Data.Types type Rep Account = D1 ('MetaData "Account" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (((S1 ('MetaSel ('Just "aname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "adeclarationinfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe AccountDeclarationInfo))) :*: (S1 ('MetaSel ('Just "asubs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Account]) :*: S1 ('MetaSel ('Just "aparent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Account)))) :*: ((S1 ('MetaSel ('Just "aboring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "anumpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "aebalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MixedAmount) :*: S1 ('MetaSel ('Just "aibalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MixedAmount))))) |
type AccountName = Text Source #
Constructors
Amount | |
Fields
|
Instances
FromJSON Amount Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON Amount Source # | |||||
Generic Amount Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Num Amount Source # | |||||
Show Amount Source # | |||||
NFData Amount Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Amount Source # | |||||
Ord Amount Source # | |||||
HasAmounts Amount Source # | |||||
Defined in Hledger.Data.Amount Methods 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.43.2-AWkFvE9IqZD4pwx38wuEvt" '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.
Constructors
Journal | |
Fields
|
Instances
ToJSON Journal Source # | |||||
Semigroup Journal Source # | |||||
Generic Journal Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Journal Source # | |||||
Default Journal Source # | |||||
Defined in Hledger.Data.Journal | |||||
NFData Journal Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Journal Source # | |||||
type Rep Journal Source # | |||||
Defined in Hledger.Data.Types type Rep Journal = D1 ('MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Journal" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "jparsedefaultyear") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Year)) :*: (S1 ('MetaSel ('Just "jparsedefaultcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (CommoditySymbol, AmountStyle))) :*: S1 ('MetaSel ('Just "jparsedecimalmark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DecimalMark)))) :*: (S1 ('MetaSel ('Just "jparseparentaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [AccountName]) :*: (S1 ('MetaSel ('Just "jparsealiases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [AccountAlias]) :*: S1 ('MetaSel ('Just "jparsetimeclockentries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TimeclockEntry])))) :*: ((S1 ('MetaSel ('Just "jincludefilestack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jdeclaredpayees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Payee, PayeeDeclarationInfo)]) :*: S1 ('MetaSel ('Just "jdeclaredtags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(TagName, TagDeclarationInfo)]))) :*: (S1 ('MetaSel ('Just "jdeclaredaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(AccountName, AccountDeclarationInfo)]) :*: (S1 ('MetaSel ('Just "jdeclaredaccounttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map AccountName [Tag])) :*: S1 ('MetaSel ('Just "jdeclaredaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map AccountType [AccountName])))))) :*: (((S1 ('MetaSel ('Just "jaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map AccountName AccountType)) :*: (S1 ('MetaSel ('Just "jdeclaredcommodities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map CommoditySymbol Commodity)) :*: S1 ('MetaSel ('Just "jinferredcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map CommoditySymbol AmountStyle)))) :*: (S1 ('MetaSel ('Just "jglobalcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map CommoditySymbol AmountStyle)) :*: (S1 ('MetaSel ('Just "jpricedirectives") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PriceDirective]) :*: S1 ('MetaSel ('Just "jinferredmarketprices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [MarketPrice])))) :*: ((S1 ('MetaSel ('Just "jtxnmodifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TransactionModifier]) :*: (S1 ('MetaSel ('Just "jperiodictxns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PeriodicTransaction]) :*: S1 ('MetaSel ('Just "jtxns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Transaction]))) :*: (S1 ('MetaSel ('Just "jfinalcommentlines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "jfiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(FilePath, Text)]) :*: S1 ('MetaSel ('Just "jlastreadtime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 POSIXTime))))))) |
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 # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Ledger Source # | |||||
type Rep Ledger Source # | |||||
Defined in Hledger.Data.Types type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Account]))) |
data PeriodicTransaction Source #
A periodic transaction rule, describing a transaction that recurs.
Constructors
PeriodicTransaction | |
Fields
|
Instances
ToJSON PeriodicTransaction Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: PeriodicTransaction -> Value # toEncoding :: PeriodicTransaction -> Encoding # toJSONList :: [PeriodicTransaction] -> Value # toEncodingList :: [PeriodicTransaction] -> Encoding # omitField :: PeriodicTransaction -> Bool # | |||||
Generic PeriodicTransaction Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: PeriodicTransaction -> Rep PeriodicTransaction x # to :: Rep PeriodicTransaction x -> PeriodicTransaction # | |||||
Show PeriodicTransaction Source # | |||||
Defined in Hledger.Data.PeriodicTransaction Methods showsPrec :: Int -> PeriodicTransaction -> ShowS # show :: PeriodicTransaction -> String # showList :: [PeriodicTransaction] -> ShowS # | |||||
NFData PeriodicTransaction Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: PeriodicTransaction -> () # | |||||
Eq PeriodicTransaction Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: PeriodicTransaction -> PeriodicTransaction -> Bool # (/=) :: PeriodicTransaction -> PeriodicTransaction -> Bool # | |||||
type Rep PeriodicTransaction Source # | |||||
Defined in Hledger.Data.Types type Rep PeriodicTransaction = D1 ('MetaData "PeriodicTransaction" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "PeriodicTransaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ptperiodexpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptinterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Interval)) :*: (S1 ('MetaSel ('Just "ptspan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DateSpan) :*: (S1 ('MetaSel ('Just "ptsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SourcePos, SourcePos)) :*: S1 ('MetaSel ('Just "ptstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status)))) :*: ((S1 ('MetaSel ('Just "ptcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "ptcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "pttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "ptpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Posting])))))) |
Constructors
Posting | |
Fields
|
Instances
FromJSON Posting Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON Posting Source # | |||||
Generic Posting Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Posting Source # | Posting's show instance elides the parent transaction so as not to recurse forever. | ||||
NFData Posting Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Posting Source # | |||||
HasAmounts Posting Source # | |||||
Defined in Hledger.Data.Posting Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Posting -> Posting Source # | |||||
HasAmounts PostingsReportItem Source # | |||||
Defined in Hledger.Reports.PostingsReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PostingsReportItem -> PostingsReportItem Source # | |||||
type Rep Posting Source # | |||||
Defined in Hledger.Data.Types type Rep Posting = D1 ('MetaData "Posting" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Posting" 'PrefixI 'True) (((S1 ('MetaSel ('Just "pdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Just "pdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Day))) :*: (S1 ('MetaSel ('Just "pstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: (S1 ('MetaSel ('Just "paccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "pamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MixedAmount)))) :*: ((S1 ('MetaSel ('Just "pcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ptype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PostingType) :*: S1 ('MetaSel ('Just "ptags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]))) :*: (S1 ('MetaSel ('Just "pbalanceassertion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe BalanceAssertion)) :*: (S1 ('MetaSel ('Just "ptransaction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Transaction)) :*: S1 ('MetaSel ('Just "poriginal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Posting))))))) |
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 Methods showsPrec :: Int -> StorageFormat -> ShowS # show :: StorageFormat -> String # showList :: [StorageFormat] -> ShowS # | |
Eq StorageFormat Source # | |
Defined in Hledger.Data.Types Methods (==) :: StorageFormat -> StorageFormat -> Bool # (/=) :: StorageFormat -> StorageFormat -> Bool # | |
Ord StorageFormat Source # | |
Defined in Hledger.Data.Types Methods compare :: StorageFormat -> StorageFormat -> Ordering # (<) :: StorageFormat -> StorageFormat -> Bool # (<=) :: StorageFormat -> StorageFormat -> Bool # (>) :: StorageFormat -> StorageFormat -> Bool # (>=) :: StorageFormat -> StorageFormat -> Bool # max :: StorageFormat -> StorageFormat -> StorageFormat # min :: StorageFormat -> StorageFormat -> StorageFormat # |
data Transaction Source #
Constructors
Transaction | |
Fields
|
Instances
FromJSON Transaction Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON Transaction Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: Transaction -> Value # toEncoding :: Transaction -> Encoding # toJSONList :: [Transaction] -> Value # toEncodingList :: [Transaction] -> Encoding # omitField :: Transaction -> Bool # | |||||
Generic Transaction Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Transaction Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> Transaction -> ShowS # show :: Transaction -> String # showList :: [Transaction] -> ShowS # | |||||
NFData Transaction Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: Transaction -> () # | |||||
Eq Transaction Source # | |||||
Defined in Hledger.Data.Types | |||||
HasAmounts Transaction Source # | |||||
Defined in Hledger.Data.Transaction Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Transaction -> Transaction Source # | |||||
HasAmounts AccountTransactionsReportItem Source # | |||||
type Rep Transaction Source # | |||||
Defined in Hledger.Data.Types type Rep Transaction = D1 ('MetaData "Transaction" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Transaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "tprecedingcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SourcePos, SourcePos)) :*: (S1 ('MetaSel ('Just "tdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Just "tdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Day))))) :*: ((S1 ('MetaSel ('Just "tstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: (S1 ('MetaSel ('Just "tcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "tdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "tcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "tpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Posting])))))) |
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
ToJSON TransactionModifier Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: TransactionModifier -> Value # toEncoding :: TransactionModifier -> Encoding # toJSONList :: [TransactionModifier] -> Value # toEncodingList :: [TransactionModifier] -> Encoding # omitField :: TransactionModifier -> Bool # | |||||
Generic TransactionModifier Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: TransactionModifier -> Rep TransactionModifier x # to :: Rep TransactionModifier x -> TransactionModifier # | |||||
Show TransactionModifier Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TransactionModifier -> ShowS # show :: TransactionModifier -> String # showList :: [TransactionModifier] -> ShowS # | |||||
NFData TransactionModifier Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: TransactionModifier -> () # | |||||
Eq TransactionModifier Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: TransactionModifier -> TransactionModifier -> Bool # (/=) :: TransactionModifier -> TransactionModifier -> Bool # | |||||
type Rep TransactionModifier Source # | |||||
Defined in Hledger.Data.Types type Rep TransactionModifier = D1 ('MetaData "TransactionModifier" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "TransactionModifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmquerytxt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "tmpostingrules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TMPostingRule]))) |
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.
Constructors
Precision !Word8 | show this many decimal digits (0..255) |
NaturalPrecision | show all significant decimal digits stored internally |
Instances
FromJSON AmountPrecision Source # | |||||
Defined in Hledger.Data.Json Methods parseJSON :: Value -> Parser AmountPrecision # parseJSONList :: Value -> Parser [AmountPrecision] # | |||||
ToJSON AmountPrecision Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AmountPrecision -> Value # toEncoding :: AmountPrecision -> Encoding # toJSONList :: [AmountPrecision] -> Value # toEncodingList :: [AmountPrecision] -> Encoding # omitField :: AmountPrecision -> Bool # | |||||
Generic AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: AmountPrecision -> Rep AmountPrecision x # to :: Rep AmountPrecision x -> AmountPrecision # | |||||
Read AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AmountPrecision # readList :: ReadS [AmountPrecision] # | |||||
Show AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountPrecision -> ShowS # show :: AmountPrecision -> String # showList :: [AmountPrecision] -> ShowS # | |||||
NFData AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AmountPrecision -> () # | |||||
Eq AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: AmountPrecision -> AmountPrecision -> Bool # (/=) :: AmountPrecision -> AmountPrecision -> Bool # | |||||
Ord AmountPrecision Source # | |||||
Defined in Hledger.Data.Types Methods compare :: AmountPrecision -> AmountPrecision -> Ordering # (<) :: AmountPrecision -> AmountPrecision -> Bool # (<=) :: AmountPrecision -> AmountPrecision -> Bool # (>) :: AmountPrecision -> AmountPrecision -> Bool # (>=) :: AmountPrecision -> AmountPrecision -> Bool # max :: AmountPrecision -> AmountPrecision -> AmountPrecision # min :: AmountPrecision -> AmountPrecision -> AmountPrecision # | |||||
type Rep AmountPrecision Source # | |||||
Defined in Hledger.Data.Types type Rep AmountPrecision = D1 ('MetaData "AmountPrecision" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Precision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8)) :+: C1 ('MetaCons "NaturalPrecision" 'PrefixI 'False) (U1 :: Type -> Type)) |
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
Constructors
AmountStyle | |
Fields
|
Instances
FromJSON AmountStyle Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON AmountStyle Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AmountStyle -> Value # toEncoding :: AmountStyle -> Encoding # toJSONList :: [AmountStyle] -> Value # toEncodingList :: [AmountStyle] -> Encoding # omitField :: AmountStyle -> Bool # | |||||
Generic AmountStyle Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read AmountStyle Source # | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AmountStyle # readList :: ReadS [AmountStyle] # readPrec :: ReadPrec AmountStyle # readListPrec :: ReadPrec [AmountStyle] # | |||||
Show AmountStyle Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountStyle -> ShowS # show :: AmountStyle -> String # showList :: [AmountStyle] -> ShowS # | |||||
NFData AmountStyle Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AmountStyle -> () # | |||||
Eq AmountStyle Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord AmountStyle Source # | |||||
Defined in Hledger.Data.Types Methods compare :: AmountStyle -> AmountStyle -> Ordering # (<) :: AmountStyle -> AmountStyle -> Bool # (<=) :: AmountStyle -> AmountStyle -> Bool # (>) :: AmountStyle -> AmountStyle -> Bool # (>=) :: AmountStyle -> AmountStyle -> Bool # max :: AmountStyle -> AmountStyle -> AmountStyle # min :: AmountStyle -> AmountStyle -> AmountStyle # | |||||
type Rep AmountStyle Source # | |||||
Defined in Hledger.Data.Types type Rep AmountStyle = D1 ('MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "AmountStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ascommodityside") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Side) :*: (S1 ('MetaSel ('Just "ascommodityspaced") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "asdigitgroups") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DigitGroupStyle)))) :*: (S1 ('MetaSel ('Just "asdecimalmark") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Char)) :*: (S1 ('MetaSel ('Just "asprecision") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountPrecision) :*: S1 ('MetaSel ('Just "asrounding") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Rounding))))) |
data MixedAmount Source #
Instances
FromJSON MixedAmount Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON MixedAmount Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: MixedAmount -> Value # toEncoding :: MixedAmount -> Encoding # toJSONList :: [MixedAmount] -> Value # toEncodingList :: [MixedAmount] -> Encoding # omitField :: MixedAmount -> Bool # | |||||
Monoid MixedAmount Source # | |||||
Defined in Hledger.Data.Amount Methods mempty :: MixedAmount # mappend :: MixedAmount -> MixedAmount -> MixedAmount # mconcat :: [MixedAmount] -> MixedAmount # | |||||
Semigroup MixedAmount Source # | |||||
Defined in Hledger.Data.Amount Methods (<>) :: MixedAmount -> MixedAmount -> MixedAmount # sconcat :: NonEmpty MixedAmount -> MixedAmount # stimes :: Integral b => b -> MixedAmount -> MixedAmount # | |||||
Generic MixedAmount Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Num MixedAmount Source # | |||||
Defined in Hledger.Data.Amount Methods (+) :: MixedAmount -> MixedAmount -> MixedAmount # (-) :: MixedAmount -> MixedAmount -> MixedAmount # (*) :: MixedAmount -> MixedAmount -> MixedAmount # negate :: MixedAmount -> MixedAmount # abs :: MixedAmount -> MixedAmount # signum :: MixedAmount -> MixedAmount # fromInteger :: Integer -> MixedAmount # | |||||
Show MixedAmount Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> MixedAmount -> ShowS # show :: MixedAmount -> String # showList :: [MixedAmount] -> ShowS # | |||||
NFData MixedAmount Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: MixedAmount -> () # | |||||
Eq MixedAmount Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord MixedAmount Source # | |||||
Defined in Hledger.Data.Types Methods compare :: MixedAmount -> MixedAmount -> Ordering # (<) :: MixedAmount -> MixedAmount -> Bool # (<=) :: MixedAmount -> MixedAmount -> Bool # (>) :: MixedAmount -> MixedAmount -> Bool # (>=) :: MixedAmount -> MixedAmount -> Bool # max :: MixedAmount -> MixedAmount -> MixedAmount # min :: MixedAmount -> MixedAmount -> MixedAmount # | |||||
HasAmounts MixedAmount Source # | |||||
Defined in Hledger.Data.Amount Methods styleAmounts :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount Source # | |||||
HasAmounts AccountTransactionsReportItem Source # | |||||
HasAmounts BalanceReportItem Source # | |||||
Defined in Hledger.Reports.BalanceReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> BalanceReportItem -> BalanceReportItem Source # | |||||
HasAmounts PostingsReportItem Source # | |||||
Defined in Hledger.Reports.PostingsReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PostingsReportItem -> PostingsReportItem Source # | |||||
type Rep MixedAmount Source # | |||||
Defined in Hledger.Data.Types type Rep MixedAmount = D1 ('MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'True) (C1 ('MetaCons "Mixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map MixedAmountKey Amount)))) |
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.
Constructors
PrimaryDate | |
SecondaryDate |
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 # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show EFDay Source # | |||||
NFData EFDay Source # | |||||
Defined in Hledger.Data.Types | |||||
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.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Exact" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day)) :+: C1 ('MetaCons "Flex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (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 # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show DateSpan Source # | |||||
Default DateSpan Source # | |||||
Defined in Hledger.Data.Types | |||||
NFData 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.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "DateSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe EFDay)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe EFDay)))) |
Constructors
DepthSpec | |
Fields
|
isAccountSubtypeOf :: AccountType -> AccountType -> Bool Source #
Check whether the first argument is a subtype of the second: either equal or one of the defined subtypes.
data AccountAlias Source #
Constructors
BasicAlias AccountName AccountName | |
RegexAlias Regexp Replacement |
Instances
ToJSON AccountAlias Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AccountAlias -> Value # toEncoding :: AccountAlias -> Encoding # toJSONList :: [AccountAlias] -> Value # toEncodingList :: [AccountAlias] -> Encoding # omitField :: AccountAlias -> Bool # | |||||
Generic AccountAlias Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read AccountAlias Source # | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AccountAlias # readList :: ReadS [AccountAlias] # | |||||
Show AccountAlias Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountAlias -> ShowS # show :: AccountAlias -> String # showList :: [AccountAlias] -> ShowS # | |||||
NFData AccountAlias Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AccountAlias -> () # | |||||
Eq AccountAlias Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord AccountAlias Source # | |||||
Defined in Hledger.Data.Types Methods compare :: AccountAlias -> AccountAlias -> Ordering # (<) :: AccountAlias -> AccountAlias -> Bool # (<=) :: AccountAlias -> AccountAlias -> Bool # (>) :: AccountAlias -> AccountAlias -> Bool # (>=) :: AccountAlias -> AccountAlias -> Bool # max :: AccountAlias -> AccountAlias -> AccountAlias # min :: AccountAlias -> AccountAlias -> AccountAlias # | |||||
type Rep AccountAlias Source # | |||||
Defined in Hledger.Data.Types type Rep AccountAlias = D1 ('MetaData "AccountAlias" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "BasicAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccountName)) :+: C1 ('MetaCons "RegexAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Regexp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Replacement))) |
type DecimalMark = Char Source #
One of the decimal marks we support: either period or comma.
isDecimalMark :: Char -> Bool Source #
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
FromJSON AmountCost Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON AmountCost Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AmountCost -> Value # toEncoding :: AmountCost -> Encoding # toJSONList :: [AmountCost] -> Value # toEncodingList :: [AmountCost] -> Encoding # omitField :: AmountCost -> Bool # | |||||
Generic AmountCost Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show AmountCost Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountCost -> ShowS # show :: AmountCost -> String # showList :: [AmountCost] -> ShowS # | |||||
NFData AmountCost Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AmountCost -> () # | |||||
Eq AmountCost Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord AmountCost Source # | |||||
Defined in Hledger.Data.Types Methods compare :: AmountCost -> AmountCost -> Ordering # (<) :: AmountCost -> AmountCost -> Bool # (<=) :: AmountCost -> AmountCost -> Bool # (>) :: AmountCost -> AmountCost -> Bool # (>=) :: AmountCost -> AmountCost -> Bool # max :: AmountCost -> AmountCost -> AmountCost # min :: AmountCost -> AmountCost -> AmountCost # | |||||
type Rep AmountCost Source # | |||||
Defined in Hledger.Data.Types type Rep AmountCost = D1 ('MetaData "AmountCost" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "UnitCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)) :+: C1 ('MetaCons "TotalCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount))) |
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
FromJSON DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Json Methods parseJSON :: Value -> Parser DigitGroupStyle # parseJSONList :: Value -> Parser [DigitGroupStyle] # | |||||
ToJSON DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: DigitGroupStyle -> Value # toEncoding :: DigitGroupStyle -> Encoding # toJSONList :: [DigitGroupStyle] -> Value # toEncodingList :: [DigitGroupStyle] -> Encoding # omitField :: DigitGroupStyle -> Bool # | |||||
Generic DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: DigitGroupStyle -> Rep DigitGroupStyle x # to :: Rep DigitGroupStyle x -> DigitGroupStyle # | |||||
Read DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS DigitGroupStyle # readList :: ReadS [DigitGroupStyle] # | |||||
Show DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> DigitGroupStyle -> ShowS # show :: DigitGroupStyle -> String # showList :: [DigitGroupStyle] -> ShowS # | |||||
NFData DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: DigitGroupStyle -> () # | |||||
Eq DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (/=) :: DigitGroupStyle -> DigitGroupStyle -> Bool # | |||||
Ord DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types Methods compare :: DigitGroupStyle -> DigitGroupStyle -> Ordering # (<) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (<=) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (>) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (>=) :: DigitGroupStyle -> DigitGroupStyle -> Bool # max :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle # min :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle # | |||||
type Rep DigitGroupStyle Source # | |||||
Defined in Hledger.Data.Types type Rep DigitGroupStyle = D1 ('MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "DigitGroups" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word8]))) |
"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.
Constructors
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 # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read Rounding Source # | |||||
Show Rounding Source # | |||||
NFData Rounding Source # | |||||
Defined in Hledger.Data.Types | |||||
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.43.2-AWkFvE9IqZD4pwx38wuEvt" '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))) |
Constructors
Commodity | |
Fields |
Instances
ToJSON Commodity Source # | |||||
Generic Commodity Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Commodity Source # | |||||
NFData Commodity Source # | |||||
Defined in Hledger.Data.Types | |||||
Eq Commodity Source # | |||||
type Rep Commodity Source # | |||||
Defined in Hledger.Data.Types type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "Commodity" 'PrefixI 'True) (S1 ('MetaSel ('Just "csymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "cformat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (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.
Methods
styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a Source #
Instances
HasAmounts Account Source # | |
Defined in Hledger.Data.Amount Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Account -> Account Source # | |
HasAmounts Amount Source # | |
Defined in Hledger.Data.Amount Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Amount -> Amount Source # | |
HasAmounts BalanceAssertion Source # | |
Defined in Hledger.Data.Posting Methods styleAmounts :: Map CommoditySymbol AmountStyle -> BalanceAssertion -> BalanceAssertion Source # | |
HasAmounts MixedAmount Source # | |
Defined in Hledger.Data.Amount Methods styleAmounts :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount Source # | |
HasAmounts Posting Source # | |
Defined in Hledger.Data.Posting Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Posting -> Posting Source # | |
HasAmounts Transaction Source # | |
Defined in Hledger.Data.Transaction Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Transaction -> Transaction Source # | |
HasAmounts AccountTransactionsReportItem Source # | |
HasAmounts BalanceReportItem Source # | |
Defined in Hledger.Reports.BalanceReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> BalanceReportItem -> BalanceReportItem Source # | |
HasAmounts PostingsReportItem Source # | |
Defined in Hledger.Reports.PostingsReport Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PostingsReportItem -> PostingsReportItem Source # | |
HasAmounts a => HasAmounts (Maybe a) Source # | |
Defined in Hledger.Data.Types Methods styleAmounts :: Map CommoditySymbol AmountStyle -> Maybe a -> Maybe a Source # | |
HasAmounts a => HasAmounts [a] Source # | |
Defined in Hledger.Data.Types Methods styleAmounts :: Map CommoditySymbol AmountStyle -> [a] -> [a] Source # | |
HasAmounts b => HasAmounts (CompoundPeriodicReport a b) Source # | |
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> CompoundPeriodicReport a b -> CompoundPeriodicReport a b Source # | |
HasAmounts b => HasAmounts (PeriodicReport a b) Source # | |
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PeriodicReport a b -> PeriodicReport a b Source # | |
HasAmounts b => HasAmounts (PeriodicReportRow a b) Source # | |
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PeriodicReportRow a b -> PeriodicReportRow a b Source # | |
(HasAmounts a, HasAmounts b) => HasAmounts (a, b) Source # | |
Defined in Hledger.Data.Types Methods styleAmounts :: Map CommoditySymbol AmountStyle -> (a, b) -> (a, b) Source # | |
HasAmounts b => HasAmounts (Text, PeriodicReport a b, Bool) Source # | |
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> (Text, PeriodicReport a b, Bool) -> (Text, PeriodicReport a b, Bool) Source # |
maCompare :: MixedAmount -> MixedAmount -> Ordering Source #
Compare two MixedAmounts, substituting 0 for the quantity of any missing commodities in either.
pattern MixedAmountKeyNoCost :: !CommoditySymbol -> MixedAmountKey Source #
pattern MixedAmountKeyTotalCost :: !CommoditySymbol -> !CommoditySymbol -> MixedAmountKey Source #
pattern MixedAmountKeyUnitCost :: !CommoditySymbol -> !CommoditySymbol -> !Quantity -> MixedAmountKey Source #
data PostingType Source #
Constructors
RegularPosting | |
VirtualPosting | |
BalancedVirtualPosting |
Instances
FromJSON PostingType Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON PostingType Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: PostingType -> Value # toEncoding :: PostingType -> Encoding # toJSONList :: [PostingType] -> Value # toEncodingList :: [PostingType] -> Encoding # omitField :: PostingType -> Bool # | |||||
Generic PostingType Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show PostingType Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PostingType -> ShowS # show :: PostingType -> String # showList :: [PostingType] -> ShowS # | |||||
NFData PostingType Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: PostingType -> () # | |||||
Eq PostingType Source # | |||||
Defined in Hledger.Data.Types | |||||
type Rep PostingType Source # | |||||
Defined in Hledger.Data.Types type Rep PostingType = D1 ('MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "RegularPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BalancedVirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type))) |
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 (_) ?
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.
Constructors
BalanceAssertion | |
Fields
|
Instances
FromJSON BalanceAssertion Source # | |||||
Defined in Hledger.Data.Json Methods parseJSON :: Value -> Parser BalanceAssertion # parseJSONList :: Value -> Parser [BalanceAssertion] # | |||||
ToJSON BalanceAssertion Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: BalanceAssertion -> Value # toEncoding :: BalanceAssertion -> Encoding # toJSONList :: [BalanceAssertion] -> Value # toEncodingList :: [BalanceAssertion] -> Encoding # omitField :: BalanceAssertion -> Bool # | |||||
Generic BalanceAssertion Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: BalanceAssertion -> Rep BalanceAssertion x # to :: Rep BalanceAssertion x -> BalanceAssertion # | |||||
Show BalanceAssertion Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> BalanceAssertion -> ShowS # show :: BalanceAssertion -> String # showList :: [BalanceAssertion] -> ShowS # | |||||
NFData BalanceAssertion Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: BalanceAssertion -> () # | |||||
Eq BalanceAssertion Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: BalanceAssertion -> BalanceAssertion -> Bool # (/=) :: BalanceAssertion -> BalanceAssertion -> Bool # | |||||
HasAmounts BalanceAssertion Source # | |||||
Defined in Hledger.Data.Posting Methods styleAmounts :: Map CommoditySymbol AmountStyle -> BalanceAssertion -> BalanceAssertion Source # | |||||
type Rep BalanceAssertion Source # | |||||
Defined in Hledger.Data.Types type Rep BalanceAssertion = D1 ('MetaData "BalanceAssertion" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "BalanceAssertion" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Amount) :*: S1 ('MetaSel ('Just "batotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "bainclusive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "baposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SourcePos)))) |
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.
Constructors
TMPostingRule | |
Fields |
Instances
ToJSON TMPostingRule Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: TMPostingRule -> Value # toEncoding :: TMPostingRule -> Encoding # toJSONList :: [TMPostingRule] -> Value # toEncodingList :: [TMPostingRule] -> Encoding # omitField :: TMPostingRule -> Bool # | |||||
Generic TMPostingRule Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show TMPostingRule Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TMPostingRule -> ShowS # show :: TMPostingRule -> String # showList :: [TMPostingRule] -> ShowS # | |||||
NFData TMPostingRule Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: TMPostingRule -> () # | |||||
Eq TMPostingRule Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: TMPostingRule -> TMPostingRule -> Bool # (/=) :: TMPostingRule -> TMPostingRule -> Bool # | |||||
type Rep TMPostingRule Source # | |||||
Defined in Hledger.Data.Types type Rep TMPostingRule = D1 ('MetaData "TMPostingRule" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "TMPostingRule" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmprPosting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Posting) :*: S1 ('MetaSel ('Just "tmprIsMultiplier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) |
data TimeclockEntry Source #
Constructors
TimeclockEntry | |
Fields
|
Instances
ToJSON TimeclockEntry Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: TimeclockEntry -> Value # toEncoding :: TimeclockEntry -> Encoding # toJSONList :: [TimeclockEntry] -> Value # toEncodingList :: [TimeclockEntry] -> Encoding # omitField :: TimeclockEntry -> Bool # | |||||
Generic TimeclockEntry Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: TimeclockEntry -> Rep TimeclockEntry x # to :: Rep TimeclockEntry x -> TimeclockEntry # | |||||
Show TimeclockEntry Source # | |||||
Defined in Hledger.Data.Timeclock Methods showsPrec :: Int -> TimeclockEntry -> ShowS # show :: TimeclockEntry -> String # showList :: [TimeclockEntry] -> ShowS # | |||||
NFData TimeclockEntry Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: TimeclockEntry -> () # | |||||
Eq TimeclockEntry Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: TimeclockEntry -> TimeclockEntry -> Bool # (/=) :: TimeclockEntry -> TimeclockEntry -> Bool # | |||||
Ord TimeclockEntry Source # | |||||
Defined in Hledger.Data.Types Methods compare :: TimeclockEntry -> TimeclockEntry -> Ordering # (<) :: TimeclockEntry -> TimeclockEntry -> Bool # (<=) :: TimeclockEntry -> TimeclockEntry -> Bool # (>) :: TimeclockEntry -> TimeclockEntry -> Bool # (>=) :: TimeclockEntry -> TimeclockEntry -> Bool # max :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry # min :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry # | |||||
type Rep TimeclockEntry Source # | |||||
Defined in Hledger.Data.Types type Rep TimeclockEntry = D1 ('MetaData "TimeclockEntry" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "TimeclockEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tlsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "tlcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TimeclockCode) :*: S1 ('MetaSel ('Just "tldatetime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocalTime))) :*: ((S1 ('MetaSel ('Just "tlaccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "tldescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tlcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "tltags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]))))) |
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
ToJSON PriceDirective Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: PriceDirective -> Value # toEncoding :: PriceDirective -> Encoding # toJSONList :: [PriceDirective] -> Value # toEncodingList :: [PriceDirective] -> Encoding # omitField :: PriceDirective -> Bool # | |||||
Generic PriceDirective Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: PriceDirective -> Rep PriceDirective x # to :: Rep PriceDirective x -> PriceDirective # | |||||
Show PriceDirective Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PriceDirective -> ShowS # show :: PriceDirective -> String # showList :: [PriceDirective] -> ShowS # | |||||
NFData PriceDirective Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: PriceDirective -> () # | |||||
Eq PriceDirective Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: PriceDirective -> PriceDirective -> Bool # (/=) :: PriceDirective -> PriceDirective -> Bool # | |||||
Ord PriceDirective Source # | |||||
Defined in Hledger.Data.Types Methods compare :: PriceDirective -> PriceDirective -> Ordering # (<) :: PriceDirective -> PriceDirective -> Bool # (<=) :: PriceDirective -> PriceDirective -> Bool # (>) :: PriceDirective -> PriceDirective -> Bool # (>=) :: PriceDirective -> PriceDirective -> Bool # max :: PriceDirective -> PriceDirective -> PriceDirective # min :: PriceDirective -> PriceDirective -> PriceDirective # | |||||
type Rep PriceDirective Source # | |||||
Defined in Hledger.Data.Types type Rep PriceDirective = D1 ('MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "PriceDirective" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pdsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "pddate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day)) :*: (S1 ('MetaSel ('Just "pdcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "pdamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Amount)))) |
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
FromJSON MarketPrice Source # | |||||
Defined in Hledger.Data.Json | |||||
ToJSON MarketPrice Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: MarketPrice -> Value # toEncoding :: MarketPrice -> Encoding # toJSONList :: [MarketPrice] -> Value # toEncodingList :: [MarketPrice] -> Encoding # omitField :: MarketPrice -> Bool # | |||||
Generic MarketPrice Source # | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show MarketPrice Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> MarketPrice -> ShowS # show :: MarketPrice -> String # showList :: [MarketPrice] -> ShowS # | |||||
NFData MarketPrice Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: MarketPrice -> () # | |||||
Eq MarketPrice Source # | |||||
Defined in Hledger.Data.Types | |||||
Ord MarketPrice Source # | |||||
Defined in Hledger.Data.Types Methods compare :: MarketPrice -> MarketPrice -> Ordering # (<) :: MarketPrice -> MarketPrice -> Bool # (<=) :: MarketPrice -> MarketPrice -> Bool # (>) :: MarketPrice -> MarketPrice -> Bool # (>=) :: MarketPrice -> MarketPrice -> Bool # max :: MarketPrice -> MarketPrice -> MarketPrice # min :: MarketPrice -> MarketPrice -> MarketPrice # | |||||
type Rep MarketPrice Source # | |||||
Defined in Hledger.Data.Types type Rep MarketPrice = D1 ('MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "MarketPrice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Just "mpfrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommoditySymbol)) :*: (S1 ('MetaSel ('Just "mpto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "mprate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Quantity)))) |
showMarketPrice :: MarketPrice -> String Source #
showMarketPrices :: [MarketPrice] -> [Char] Source #
data PayeeDeclarationInfo Source #
Extra information found in a payee directive.
Constructors
PayeeDeclarationInfo | |
Fields
|
Instances
ToJSON PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: PayeeDeclarationInfo -> Value # toEncoding :: PayeeDeclarationInfo -> Encoding # toJSONList :: [PayeeDeclarationInfo] -> Value # toEncodingList :: [PayeeDeclarationInfo] -> Encoding # omitField :: PayeeDeclarationInfo -> Bool # | |||||
Generic PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: PayeeDeclarationInfo -> Rep PayeeDeclarationInfo x # to :: Rep PayeeDeclarationInfo x -> PayeeDeclarationInfo # | |||||
Show PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PayeeDeclarationInfo -> ShowS # show :: PayeeDeclarationInfo -> String # showList :: [PayeeDeclarationInfo] -> ShowS # | |||||
NFData PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: PayeeDeclarationInfo -> () # | |||||
Eq PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool # (/=) :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool # | |||||
type Rep PayeeDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types type Rep PayeeDeclarationInfo = D1 ('MetaData "PayeeDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "PayeeDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "pdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "pditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]))) |
newtype TagDeclarationInfo Source #
Extra information found in a tag directive.
Constructors
TagDeclarationInfo | |
Fields
|
Instances
ToJSON TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: TagDeclarationInfo -> Value # toEncoding :: TagDeclarationInfo -> Encoding # toJSONList :: [TagDeclarationInfo] -> Value # toEncodingList :: [TagDeclarationInfo] -> Encoding # omitField :: TagDeclarationInfo -> Bool # | |||||
Generic TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: TagDeclarationInfo -> Rep TagDeclarationInfo x # to :: Rep TagDeclarationInfo x -> TagDeclarationInfo # | |||||
Show TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TagDeclarationInfo -> ShowS # show :: TagDeclarationInfo -> String # showList :: [TagDeclarationInfo] -> ShowS # | |||||
NFData TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: TagDeclarationInfo -> () # | |||||
Eq TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: TagDeclarationInfo -> TagDeclarationInfo -> Bool # (/=) :: TagDeclarationInfo -> TagDeclarationInfo -> Bool # | |||||
type Rep TagDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types type Rep TagDeclarationInfo = D1 ('MetaData "TagDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'True) (C1 ('MetaCons "TagDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "tdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
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
FromJSON AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Json Methods parseJSON :: Value -> Parser AccountDeclarationInfo # parseJSONList :: Value -> Parser [AccountDeclarationInfo] # | |||||
ToJSON AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Json Methods toJSON :: AccountDeclarationInfo -> Value # toEncoding :: AccountDeclarationInfo -> Encoding # toJSONList :: [AccountDeclarationInfo] -> Value # toEncodingList :: [AccountDeclarationInfo] -> Encoding # omitField :: AccountDeclarationInfo -> Bool # | |||||
Generic AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: AccountDeclarationInfo -> Rep AccountDeclarationInfo x # to :: Rep AccountDeclarationInfo x -> AccountDeclarationInfo # | |||||
Show AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountDeclarationInfo -> ShowS # show :: AccountDeclarationInfo -> String # showList :: [AccountDeclarationInfo] -> ShowS # | |||||
NFData AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods rnf :: AccountDeclarationInfo -> () # | |||||
Eq AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types Methods (==) :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool # (/=) :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool # | |||||
type Rep AccountDeclarationInfo Source # | |||||
Defined in Hledger.Data.Types type Rep AccountDeclarationInfo = D1 ('MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.43.2-AWkFvE9IqZD4pwx38wuEvt" 'False) (C1 ('MetaCons "AccountDeclarationInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "adicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "aditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag])) :*: (S1 ('MetaSel ('Just "adideclarationorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "adisourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SourcePos)))) |
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.
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
Show NormalSign Source # | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> NormalSign -> ShowS # show :: NormalSign -> String # showList :: [NormalSign] -> ShowS # | |
Eq NormalSign Source # | |
Defined in Hledger.Data.Types |
module Hledger.Data.Valuation