hledger-lib-1.31: A reusable library providing the core functionality of hledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Data.Types

Description

Most data types are defined here to avoid import cycles. Here is an overview of the hledger data model:

Journal                  -- a journal is read from one or more data files. It contains..
 [Transaction]           -- journal transactions (aka entries), which have date, 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

Documentation

type Tag #

Arguments

 = (TagName, TagValue)

A tag name and (possibly empty) value.

data Status #

The status of a transaction or posting, recorded with a status mark (nothing, !, or *). What these mean is ultimately user defined.

Constructors

Unmarked 
Pending 
Cleared 

Instances

Instances details
FromJSON Status # 
Instance details

Defined in Hledger.Data.Json

ToJSON Status # 
Instance details

Defined in Hledger.Data.Json

Bounded Status # 
Instance details

Defined in Hledger.Data.Types

Enum Status # 
Instance details

Defined in Hledger.Data.Types

Generic Status # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Status :: Type -> Type

Methods

from :: Status -> Rep Status x

to :: Rep Status x -> Status

Show Status # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Status -> ShowS

show :: Status -> String

showList :: [Status] -> ShowS

Eq Status # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Status -> Status -> Bool

(/=) :: Status -> Status -> Bool

Ord Status # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Status -> Status -> Ordering #

(<) :: Status -> Status -> Bool

(<=) :: Status -> Status -> Bool

(>) :: Status -> Status -> Bool

(>=) :: Status -> Status -> Bool

max :: Status -> Status -> Status

min :: Status -> Status -> Status

type Rep Status # 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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)))

type MonthDay = Int #

type Month = Int #

type Quarter = Int #

type YearDay = Int #

data MixedAmountKey #

Stores the CommoditySymbol of the Amount, along with the CommoditySymbol of the price, and its unit price if being used.

Instances

Instances details
Generic MixedAmountKey # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmountKey :: Type -> Type

Show MixedAmountKey # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> MixedAmountKey -> ShowS

show :: MixedAmountKey -> String

showList :: [MixedAmountKey] -> ShowS

Eq MixedAmountKey # 
Instance details

Defined in Hledger.Data.Types

Ord MixedAmountKey #

We don't auto-derive the Ord instance because it would give an undesired ordering. We want the keys to be sorted lexicographically: (1) By the primary commodity of the amount. (2) By the commodity of the price, with no price being first. (3) By the unit price, from most negative to most positive, with total prices before unit prices. For example, we would like the ordering to give MixedAmountKeyNoPrice X < MixedAmountKeyTotalPrice X Z < MixedAmountKeyNoPrice Y

Instance details

Defined in Hledger.Data.Types

type Rep MixedAmountKey # 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmountKey = D1 ('MetaData "MixedAmountKey" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "MixedAmountKeyNoPrice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol)) :+: (C1 ('MetaCons "MixedAmountKeyTotalPrice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol)) :+: C1 ('MetaCons "MixedAmountKeyUnitPrice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Quantity)))))

data Account #

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

Instances details
FromJSON Account # 
Instance details

Defined in Hledger.Data.Json

ToJSON Account # 
Instance details

Defined in Hledger.Data.Json

Generic Account # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Account :: Type -> Type

Methods

from :: Account -> Rep Account x

to :: Rep Account x -> Account

Show Account 
Instance details

Defined in Hledger.Data.Account

Methods

showsPrec :: Int -> Account -> ShowS

show :: Account -> String

showList :: [Account] -> ShowS

Eq Account 
Instance details

Defined in Hledger.Data.Account

Methods

(==) :: Account -> Account -> Bool

(/=) :: Account -> Account -> Bool

type Rep Account # 
Instance details

Defined in Hledger.Data.Types

type Rep Account = D1 ('MetaData "Account" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (((S1 ('MetaSel ('Just "aname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "adeclarationinfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AccountDeclarationInfo))) :*: (S1 ('MetaSel ('Just "asubs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account]) :*: S1 ('MetaSel ('Just "aparent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Account)))) :*: ((S1 ('MetaSel ('Just "aboring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "anumpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "aebalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount) :*: S1 ('MetaSel ('Just "aibalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))))

type AccountName = Text #

data Amount #

Constructors

Amount 

Fields

Instances

Instances details
FromJSON Amount # 
Instance details

Defined in Hledger.Data.Json

ToJSON Amount # 
Instance details

Defined in Hledger.Data.Json

Generic Amount # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Amount :: Type -> Type

Methods

from :: Amount -> Rep Amount x

to :: Rep Amount x -> Amount

Num Amount 
Instance details

Defined in Hledger.Data.Amount

Show Amount # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Amount -> ShowS

show :: Amount -> String

showList :: [Amount] -> ShowS

Eq Amount # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Amount -> Amount -> Bool

(/=) :: Amount -> Amount -> Bool

Ord Amount # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Amount -> Amount -> Ordering #

(<) :: Amount -> Amount -> Bool

(<=) :: Amount -> Amount -> Bool

(>) :: Amount -> Amount -> Bool

(>=) :: Amount -> Amount -> Bool

max :: Amount -> Amount -> Amount

min :: Amount -> Amount -> Amount

HasAmounts Amount # 
Instance details

Defined in Hledger.Data.Amount

type Rep Amount # 
Instance details

Defined in Hledger.Data.Types

type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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 "aprice") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe AmountPrice)))))

data Journal #

A Journal, containing transactions and various other things. The basic data model for hledger.

This is used during parsing (as the type alias ParsedJournal), and then finalised/validated for use as a Journal. Some extra parsing-related fields are included for convenience, at least for now. In a ParsedJournal these are updated as parsing proceeds, in a Journal they represent the final state at end of parsing (used eg by the add command).

Constructors

Journal 

Fields

Instances

Instances details
ToJSON Journal # 
Instance details

Defined in Hledger.Data.Json

Semigroup Journal # 
Instance details

Defined in Hledger.Data.Journal

Methods

(<>) :: Journal -> Journal -> Journal #

sconcat :: NonEmpty Journal -> Journal #

stimes :: Integral b => b -> Journal -> Journal #

Generic Journal # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Journal :: Type -> Type

Methods

from :: Journal -> Rep Journal x

to :: Rep Journal x -> Journal

Show Journal 
Instance details

Defined in Hledger.Data.Journal

Methods

showsPrec :: Int -> Journal -> ShowS

show :: Journal -> String

showList :: [Journal] -> ShowS

Default Journal # 
Instance details

Defined in Hledger.Data.Journal

Methods

def :: Journal #

Eq Journal # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Journal -> Journal -> Bool

(/=) :: Journal -> Journal -> Bool

type Rep Journal # 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 ('MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Journal" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "jparsedefaultyear") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Year)) :*: (S1 ('MetaSel ('Just "jparsedefaultcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (CommoditySymbol, AmountStyle))) :*: S1 ('MetaSel ('Just "jparsedecimalmark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DecimalMark)))) :*: (S1 ('MetaSel ('Just "jparseparentaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccountName]) :*: (S1 ('MetaSel ('Just "jparsealiases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AccountAlias]) :*: S1 ('MetaSel ('Just "jparsetimeclockentries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TimeclockEntry])))) :*: ((S1 ('MetaSel ('Just "jincludefilestack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jdeclaredpayees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Payee, PayeeDeclarationInfo)]) :*: S1 ('MetaSel ('Just "jdeclaredtags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(TagName, TagDeclarationInfo)]))) :*: (S1 ('MetaSel ('Just "jdeclaredaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AccountName, AccountDeclarationInfo)]) :*: (S1 ('MetaSel ('Just "jdeclaredaccounttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName [Tag])) :*: S1 ('MetaSel ('Just "jdeclaredaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountType [AccountName])))))) :*: (((S1 ('MetaSel ('Just "jaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName AccountType)) :*: (S1 ('MetaSel ('Just "jglobalcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)) :*: S1 ('MetaSel ('Just "jcommodities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol Commodity)))) :*: (S1 ('MetaSel ('Just "jinferredcommodities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)) :*: (S1 ('MetaSel ('Just "jpricedirectives") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PriceDirective]) :*: S1 ('MetaSel ('Just "jinferredmarketprices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MarketPrice])))) :*: ((S1 ('MetaSel ('Just "jtxnmodifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TransactionModifier]) :*: (S1 ('MetaSel ('Just "jperiodictxns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PeriodicTransaction]) :*: S1 ('MetaSel ('Just "jtxns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Transaction]))) :*: (S1 ('MetaSel ('Just "jfinalcommentlines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "jfiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(FilePath, Text)]) :*: S1 ('MetaSel ('Just "jlastreadtime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))))))

data Ledger #

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.

Constructors

Ledger 

Instances

Instances details
ToJSON Ledger # 
Instance details

Defined in Hledger.Data.Json

Generic Ledger # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Ledger :: Type -> Type

Methods

from :: Ledger -> Rep Ledger x

to :: Rep Ledger x -> Ledger

Show Ledger 
Instance details

Defined in Hledger.Data.Ledger

Methods

showsPrec :: Int -> Ledger -> ShowS

show :: Ledger -> String

showList :: [Ledger] -> ShowS

type Rep Ledger # 
Instance details

Defined in Hledger.Data.Types

type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account])))

data Period #

Instances

Instances details
ToJSON Period # 
Instance details

Defined in Hledger.Data.Json

Generic Period # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Period :: Type -> Type

Methods

from :: Period -> Rep Period x

to :: Rep Period x -> Period

Show Period # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Period -> ShowS

show :: Period -> String

showList :: [Period] -> ShowS

Default Period # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Period #

Eq Period # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Period -> Period -> Bool

(/=) :: Period -> Period -> Bool

Ord Period # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Period -> Period -> Ordering #

(<) :: Period -> Period -> Bool

(<=) :: Period -> Period -> Bool

(>) :: Period -> Period -> Bool

(>=) :: Period -> Period -> Bool

max :: Period -> Period -> Period

min :: Period -> Period -> Period

HasAmounts PostingsReportItem # 
Instance details

Defined in Hledger.Reports.PostingsReport

type Rep Period # 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 ('MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (((C1 ('MetaCons "DayPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "WeekPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day))) :+: (C1 ('MetaCons "MonthPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Year) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Month)) :+: C1 ('MetaCons "QuarterPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Year) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quarter)))) :+: ((C1 ('MetaCons "YearPeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Year)) :+: C1 ('MetaCons "PeriodBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day))) :+: (C1 ('MetaCons "PeriodFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: (C1 ('MetaCons "PeriodTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "PeriodAll" 'PrefixI 'False) (U1 :: Type -> Type)))))

data PeriodicTransaction #

A periodic transaction rule, describing a transaction that recurs.

Constructors

PeriodicTransaction 

Fields

Instances

Instances details
ToJSON PeriodicTransaction # 
Instance details

Defined in Hledger.Data.Json

Generic PeriodicTransaction # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PeriodicTransaction :: Type -> Type

Show PeriodicTransaction 
Instance details

Defined in Hledger.Data.PeriodicTransaction

Eq PeriodicTransaction # 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction # 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction = D1 ('MetaData "PeriodicTransaction" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "PeriodicTransaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ptperiodexpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptinterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interval)) :*: (S1 ('MetaSel ('Just "ptspan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DateSpan) :*: (S1 ('MetaSel ('Just "ptsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: S1 ('MetaSel ('Just "ptstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :*: ((S1 ('MetaSel ('Just "ptcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "ptcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "pttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "ptpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))

data Posting #

Constructors

Posting 

Fields

  • pdate :: Maybe Day

    this posting's date, if different from the transaction's

  • pdate2 :: Maybe Day

    this posting's secondary date, if different from the transaction's

  • pstatus :: Status
     
  • paccount :: AccountName
     
  • pamount :: MixedAmount
     
  • pcomment :: Text

    this posting's comment lines, as a single non-indented multi-line string

  • ptype :: PostingType
     
  • ptags :: [Tag]

    tag names and values, extracted from the posting comment and (after finalisation) the posting account's directive if any

  • pbalanceassertion :: Maybe BalanceAssertion

    an expected balance in the account after this posting, in a single commodity, excluding subaccounts.

  • ptransaction :: Maybe Transaction

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

  • poriginal :: Maybe Posting

    When this posting has been transformed in some way (eg its amount or price was inferred, or the account name was changed by a pivot or budget report), this references the original untransformed posting (which will have Nothing in this field).

Instances

Instances details
FromJSON Posting # 
Instance details

Defined in Hledger.Data.Json

ToJSON Posting # 
Instance details

Defined in Hledger.Data.Json

Generic Posting # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Posting :: Type -> Type

Methods

from :: Posting -> Rep Posting x

to :: Rep Posting x -> Posting

Show Posting #

Posting's show instance elides the parent transaction so as not to recurse forever.

Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Posting -> ShowS

show :: Posting -> String

showList :: [Posting] -> ShowS

Eq Posting # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Posting -> Posting -> Bool

(/=) :: Posting -> Posting -> Bool

HasAmounts Posting # 
Instance details

Defined in Hledger.Data.Posting

HasAmounts PostingsReportItem # 
Instance details

Defined in Hledger.Reports.PostingsReport

type Rep Posting # 
Instance details

Defined in Hledger.Data.Types

type Rep Posting = D1 ('MetaData "Posting" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Posting" 'PrefixI 'True) (((S1 ('MetaSel ('Just "pdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Just "pdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))) :*: (S1 ('MetaSel ('Just "pstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "paccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "pamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))) :*: ((S1 ('MetaSel ('Just "pcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ptype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PostingType) :*: S1 ('MetaSel ('Just "ptags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]))) :*: (S1 ('MetaSel ('Just "pbalanceassertion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BalanceAssertion)) :*: (S1 ('MetaSel ('Just "ptransaction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Transaction)) :*: S1 ('MetaSel ('Just "poriginal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Posting)))))))

data Transaction #

Constructors

Transaction 

Fields

Instances

Instances details
FromJSON Transaction # 
Instance details

Defined in Hledger.Data.Json

ToJSON Transaction # 
Instance details

Defined in Hledger.Data.Json

Generic Transaction # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Transaction :: Type -> Type

Methods

from :: Transaction -> Rep Transaction x

to :: Rep Transaction x -> Transaction

Show Transaction # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Transaction -> ShowS

show :: Transaction -> String

showList :: [Transaction] -> ShowS

Eq Transaction # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Transaction -> Transaction -> Bool

(/=) :: Transaction -> Transaction -> Bool

HasAmounts Transaction # 
Instance details

Defined in Hledger.Data.Transaction

HasAmounts AccountTransactionsReportItem # 
Instance details

Defined in Hledger.Reports.AccountTransactionsReport

type Rep Transaction # 
Instance details

Defined in Hledger.Data.Types

type Rep Transaction = D1 ('MetaData "Transaction" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Transaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "tprecedingcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: (S1 ('MetaSel ('Just "tdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "tdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))))) :*: ((S1 ('MetaSel ('Just "tstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "tcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "tcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "tpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))

data TransactionModifier #

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 

Instances

Instances details
ToJSON TransactionModifier # 
Instance details

Defined in Hledger.Data.Json

Generic TransactionModifier # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TransactionModifier :: Type -> Type

Show TransactionModifier # 
Instance details

Defined in Hledger.Data.Types

Eq TransactionModifier # 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier # 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier = D1 ('MetaData "TransactionModifier" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "TransactionModifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmquerytxt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tmpostingrules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TMPostingRule])))

type YearWeek = Int #

type MonthWeek = Int #

type WeekDay = Int #

data SmartDate #

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.

Instances

Instances details
Show SmartDate # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> SmartDate -> ShowS

show :: SmartDate -> String

showList :: [SmartDate] -> ShowS

data SmartInterval #

Constructors

Day 
Week 
Month 
Quarter 
Year 

Instances

Instances details
Show SmartInterval # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> SmartInterval -> ShowS

show :: SmartInterval -> String

showList :: [SmartInterval] -> ShowS

data WhichDate #

Constructors

PrimaryDate 
SecondaryDate 

Instances

Instances details
Show WhichDate # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> WhichDate -> ShowS

show :: WhichDate -> String

showList :: [WhichDate] -> ShowS

Eq WhichDate # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: WhichDate -> WhichDate -> Bool

(/=) :: WhichDate -> WhichDate -> Bool

data EFDay #

A date which is either exact or flexible. Flexible dates are allowed to be adjusted in certain situations.

Constructors

Exact Day 
Flex Day 

Instances

Instances details
ToJSON EFDay # 
Instance details

Defined in Hledger.Data.Json

Generic EFDay # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep EFDay :: Type -> Type

Methods

from :: EFDay -> Rep EFDay x

to :: Rep EFDay x -> EFDay

Show EFDay # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> EFDay -> ShowS

show :: EFDay -> String

showList :: [EFDay] -> ShowS

Eq EFDay # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: EFDay -> EFDay -> Bool

(/=) :: EFDay -> EFDay -> Bool

Ord EFDay # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: EFDay -> EFDay -> Ordering #

(<) :: EFDay -> EFDay -> Bool

(<=) :: EFDay -> EFDay -> Bool

(>) :: EFDay -> EFDay -> Bool

(>=) :: EFDay -> EFDay -> Bool

max :: EFDay -> EFDay -> EFDay

min :: EFDay -> EFDay -> EFDay

type Rep EFDay # 
Instance details

Defined in Hledger.Data.Types

type Rep EFDay = D1 ('MetaData "EFDay" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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)))

data DateSpan #

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.

Constructors

DateSpan (Maybe EFDay) (Maybe EFDay) 

Instances

Instances details
ToJSON DateSpan # 
Instance details

Defined in Hledger.Data.Json

Generic DateSpan # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DateSpan :: Type -> Type

Methods

from :: DateSpan -> Rep DateSpan x

to :: Rep DateSpan x -> DateSpan

Show DateSpan 
Instance details

Defined in Hledger.Data.Dates

Methods

showsPrec :: Int -> DateSpan -> ShowS

show :: DateSpan -> String

showList :: [DateSpan] -> ShowS

Default DateSpan # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: DateSpan #

Eq DateSpan # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: DateSpan -> DateSpan -> Bool

(/=) :: DateSpan -> DateSpan -> Bool

Ord DateSpan # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: DateSpan -> DateSpan -> Ordering #

(<) :: DateSpan -> DateSpan -> Bool

(<=) :: DateSpan -> DateSpan -> Bool

(>) :: DateSpan -> DateSpan -> Bool

(>=) :: DateSpan -> DateSpan -> Bool

max :: DateSpan -> DateSpan -> DateSpan

min :: DateSpan -> DateSpan -> DateSpan

type Rep DateSpan # 
Instance details

Defined in Hledger.Data.Types

type Rep DateSpan = D1 ('MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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))))

data Interval #

Constructors

NoInterval 
Days Int 
Weeks Int 
Months Int 
Quarters Int 
Years Int 
DayOfMonth Int 
WeekdayOfMonth Int Int 
DaysOfWeek [Int] 
DayOfYear Int Int 

Instances

Instances details
ToJSON Interval # 
Instance details

Defined in Hledger.Data.Json

Generic Interval # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Interval :: Type -> Type

Methods

from :: Interval -> Rep Interval x

to :: Rep Interval x -> Interval

Show Interval # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Interval -> ShowS

show :: Interval -> String

showList :: [Interval] -> ShowS

Default Interval # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Interval #

Eq Interval # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Interval -> Interval -> Bool

(/=) :: Interval -> Interval -> Bool

Ord Interval # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Interval -> Interval -> Ordering #

(<) :: Interval -> Interval -> Bool

(<=) :: Interval -> Interval -> Bool

(>) :: Interval -> Interval -> Bool

(>=) :: Interval -> Interval -> Bool

max :: Interval -> Interval -> Interval

min :: Interval -> Interval -> Interval

type Rep Interval # 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 ('MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (((C1 ('MetaCons "NoInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Days" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "Weeks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "Months" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Quarters" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "Years" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "DayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "WeekdayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "DaysOfWeek" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])) :+: C1 ('MetaCons "DayOfYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))

type Payee = Text #

data AccountType #

Constructors

Asset 
Liability 
Equity 
Revenue 
Expense 
Cash

a subtype of Asset - liquid assets to show in cashflow report

Conversion

a subtype of Equity - account in which to generate conversion postings for transaction prices

Instances

Instances details
ToJSON AccountType # 
Instance details

Defined in Hledger.Data.Json

ToJSONKey AccountType # 
Instance details

Defined in Hledger.Data.Json

Generic AccountType # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountType :: Type -> Type

Methods

from :: AccountType -> Rep AccountType x

to :: Rep AccountType x -> AccountType

Show AccountType # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AccountType -> ShowS

show :: AccountType -> String

showList :: [AccountType] -> ShowS

Eq AccountType # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AccountType -> AccountType -> Bool

(/=) :: AccountType -> AccountType -> Bool

Ord AccountType # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType = D1 ('MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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))))

data AccountAlias #

Instances

Instances details
ToJSON AccountAlias # 
Instance details

Defined in Hledger.Data.Json

Generic AccountAlias # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountAlias :: Type -> Type

Read AccountAlias # 
Instance details

Defined in Hledger.Data.Types

Show AccountAlias # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AccountAlias -> ShowS

show :: AccountAlias -> String

showList :: [AccountAlias] -> ShowS

Eq AccountAlias # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AccountAlias -> AccountAlias -> Bool

(/=) :: AccountAlias -> AccountAlias -> Bool

Ord AccountAlias # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias = D1 ('MetaData "AccountAlias" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "BasicAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName)) :+: C1 ('MetaCons "RegexAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Regexp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Replacement)))

data Side #

Constructors

L 
R 

Instances

Instances details
FromJSON Side # 
Instance details

Defined in Hledger.Data.Json

ToJSON Side # 
Instance details

Defined in Hledger.Data.Json

Generic Side # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Side :: Type -> Type

Methods

from :: Side -> Rep Side x

to :: Rep Side x -> Side

Read Side # 
Instance details

Defined in Hledger.Data.Types

Methods

readsPrec :: Int -> ReadS Side #

readList :: ReadS [Side] #

readPrec :: ReadPrec Side #

readListPrec :: ReadPrec [Side] #

Show Side # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Side -> ShowS

show :: Side -> String

showList :: [Side] -> ShowS

Eq Side # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Side -> Side -> Bool

(/=) :: Side -> Side -> Bool

Ord Side # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Side -> Side -> Ordering #

(<) :: Side -> Side -> Bool

(<=) :: Side -> Side -> Bool

(>) :: Side -> Side -> Bool

(>=) :: Side -> Side -> Bool

max :: Side -> Side -> Side

min :: Side -> Side -> Side

type Rep Side # 
Instance details

Defined in Hledger.Data.Types

type Rep Side = D1 ('MetaData "Side" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R" 'PrefixI 'False) (U1 :: Type -> Type))

type DecimalMark = Char #

One of the decimal marks we support: either period or comma.

type Quantity = Decimal #

The basic numeric type used in amounts.

data AmountPrice #

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

Instances details
FromJSON AmountPrice # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountPrice # 
Instance details

Defined in Hledger.Data.Json

Generic AmountPrice # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrice :: Type -> Type

Methods

from :: AmountPrice -> Rep AmountPrice x

to :: Rep AmountPrice x -> AmountPrice

Show AmountPrice # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountPrice -> ShowS

show :: AmountPrice -> String

showList :: [AmountPrice] -> ShowS

Eq AmountPrice # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AmountPrice -> AmountPrice -> Bool

(/=) :: AmountPrice -> AmountPrice -> Bool

Ord AmountPrice # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrice # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrice = D1 ('MetaData "AmountPrice" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "UnitPrice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)) :+: C1 ('MetaCons "TotalPrice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)))

data AmountStyle #

The display style for an amount. (See also Amount.AmountDisplayOpts).

Constructors

AmountStyle 

Fields

  • ascommodityside :: !Side

    show the symbol on the left or the right ?

  • ascommodityspaced :: !Bool

    show a space between symbol and quantity ?

  • asdigitgroups :: !(Maybe DigitGroupStyle)

    show the integer part with these digit group marks, or not

  • asdecimalmark :: !(Maybe Char)

    show this character (should be . or ,) as decimal mark, or use the default (.)

  • asprecision :: !(Maybe AmountPrecision)

    show this number of digits after the decimal point, or show as-is (leave precision unchanged) XXX Making asprecision a maybe simplifies code for styling with or without precision, but complicates the semantics (Nothing is useful only when setting style).

Instances

Instances details
FromJSON AmountStyle # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountStyle # 
Instance details

Defined in Hledger.Data.Json

Generic AmountStyle # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountStyle :: Type -> Type

Methods

from :: AmountStyle -> Rep AmountStyle x

to :: Rep AmountStyle x -> AmountStyle

Read AmountStyle # 
Instance details

Defined in Hledger.Data.Types

Show AmountStyle # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountStyle -> ShowS

show :: AmountStyle -> String

showList :: [AmountStyle] -> ShowS

Eq AmountStyle # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AmountStyle -> AmountStyle -> Bool

(/=) :: AmountStyle -> AmountStyle -> Bool

Ord AmountStyle # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle = D1 ('MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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 (Maybe AmountPrecision))))))

data DigitGroupStyle #

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

Instances details
FromJSON DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Json

ToJSON DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Json

Generic DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DigitGroupStyle :: Type -> Type

Read DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

Show DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> DigitGroupStyle -> ShowS

show :: DigitGroupStyle -> String

showList :: [DigitGroupStyle] -> ShowS

Eq DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

Ord DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 ('MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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])))

data AmountPrecision #

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

Instances details
FromJSON AmountPrecision # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountPrecision # 
Instance details

Defined in Hledger.Data.Json

Generic AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrecision :: Type -> Type

Read AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

Show AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountPrecision -> ShowS

show :: AmountPrecision -> String

showList :: [AmountPrecision] -> ShowS

Eq AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

Ord AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision = D1 ('MetaData "AmountPrecision" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "Precision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8)) :+: C1 ('MetaCons "NaturalPrecision" 'PrefixI 'False) (U1 :: Type -> Type))

type CommoditySymbol = Text #

data Commodity #

Constructors

Commodity 

Instances

Instances details
ToJSON Commodity # 
Instance details

Defined in Hledger.Data.Json

Generic Commodity # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Commodity :: Type -> Type

Methods

from :: Commodity -> Rep Commodity x

to :: Rep Commodity x -> Commodity

Show Commodity # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Commodity -> ShowS

show :: Commodity -> String

showList :: [Commodity] -> ShowS

Eq Commodity # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Commodity -> Commodity -> Bool

(/=) :: Commodity -> Commodity -> Bool

type Rep Commodity # 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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 #

Types with this class have one or more amounts, which can have display styles applied to them.

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a #

Instances

Instances details
HasAmounts Amount # 
Instance details

Defined in Hledger.Data.Amount

HasAmounts BalanceAssertion # 
Instance details

Defined in Hledger.Data.Posting

HasAmounts MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

HasAmounts Posting # 
Instance details

Defined in Hledger.Data.Posting

HasAmounts Transaction # 
Instance details

Defined in Hledger.Data.Transaction

HasAmounts AccountTransactionsReportItem # 
Instance details

Defined in Hledger.Reports.AccountTransactionsReport

HasAmounts BalanceReportItem # 
Instance details

Defined in Hledger.Reports.BalanceReport

HasAmounts PostingsReportItem # 
Instance details

Defined in Hledger.Reports.PostingsReport

HasAmounts a => HasAmounts (Maybe a) # 
Instance details

Defined in Hledger.Data.Types

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> Maybe a -> Maybe a #

HasAmounts a => HasAmounts [a] # 
Instance details

Defined in Hledger.Data.Types

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> [a] -> [a] #

HasAmounts b => HasAmounts (CompoundPeriodicReport a b) # 
Instance details

Defined in Hledger.Reports.ReportTypes

HasAmounts b => HasAmounts (PeriodicReport a b) # 
Instance details

Defined in Hledger.Reports.ReportTypes

HasAmounts b => HasAmounts (PeriodicReportRow a b) # 
Instance details

Defined in Hledger.Reports.ReportTypes

(HasAmounts a, HasAmounts b) => HasAmounts (a, b) # 
Instance details

Defined in Hledger.Data.Types

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> (a, b) -> (a, b) #

HasAmounts b => HasAmounts (Text, PeriodicReport a b, Bool) # 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> (Text, PeriodicReport a b, Bool) -> (Text, PeriodicReport a b, Bool) #

newtype MixedAmount #

Constructors

Mixed (Map MixedAmountKey Amount) 

Instances

Instances details
FromJSON MixedAmount # 
Instance details

Defined in Hledger.Data.Json

ToJSON MixedAmount # 
Instance details

Defined in Hledger.Data.Json

Monoid MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

Semigroup MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

Generic MixedAmount # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmount :: Type -> Type

Methods

from :: MixedAmount -> Rep MixedAmount x

to :: Rep MixedAmount x -> MixedAmount

Num MixedAmount 
Instance details

Defined in Hledger.Data.Amount

Show MixedAmount # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> MixedAmount -> ShowS

show :: MixedAmount -> String

showList :: [MixedAmount] -> ShowS

Eq MixedAmount # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: MixedAmount -> MixedAmount -> Bool

(/=) :: MixedAmount -> MixedAmount -> Bool

Ord MixedAmount # 
Instance details

Defined in Hledger.Data.Types

HasAmounts MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

HasAmounts AccountTransactionsReportItem # 
Instance details

Defined in Hledger.Reports.AccountTransactionsReport

HasAmounts BalanceReportItem # 
Instance details

Defined in Hledger.Reports.BalanceReport

HasAmounts PostingsReportItem # 
Instance details

Defined in Hledger.Reports.PostingsReport

type Rep MixedAmount # 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount = D1 ('MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'True) (C1 ('MetaCons "Mixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map MixedAmountKey Amount))))

data PostingType #

Instances

Instances details
FromJSON PostingType # 
Instance details

Defined in Hledger.Data.Json

ToJSON PostingType # 
Instance details

Defined in Hledger.Data.Json

Generic PostingType # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PostingType :: Type -> Type

Methods

from :: PostingType -> Rep PostingType x

to :: Rep PostingType x -> PostingType

Show PostingType # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> PostingType -> ShowS

show :: PostingType -> String

showList :: [PostingType] -> ShowS

Eq PostingType # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: PostingType -> PostingType -> Bool

(/=) :: PostingType -> PostingType -> Bool

type Rep PostingType # 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType = D1 ('MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" '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)))

type TagName = Text #

type TagValue = Text #

type DateTag = (TagName, Day) #

data BalanceAssertion #

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

  • baamount :: Amount

    the expected balance in a particular commodity

  • batotal :: Bool

    disallow additional non-asserted commodities ?

  • bainclusive :: Bool

    include subaccounts when calculating the actual balance ?

  • baposition :: SourcePos

    the assertion's file position, for error reporting

Instances

Instances details
FromJSON BalanceAssertion # 
Instance details

Defined in Hledger.Data.Json

ToJSON BalanceAssertion # 
Instance details

Defined in Hledger.Data.Json

Generic BalanceAssertion # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep BalanceAssertion :: Type -> Type

Show BalanceAssertion # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> BalanceAssertion -> ShowS

show :: BalanceAssertion -> String

showList :: [BalanceAssertion] -> ShowS

Eq BalanceAssertion # 
Instance details

Defined in Hledger.Data.Types

HasAmounts BalanceAssertion # 
Instance details

Defined in Hledger.Data.Posting

type Rep BalanceAssertion # 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion = D1 ('MetaData "BalanceAssertion" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "BalanceAssertion" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Just "batotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "bainclusive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "baposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))

data TMPostingRule #

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 

Instances

Instances details
ToJSON TMPostingRule # 
Instance details

Defined in Hledger.Data.Json

Generic TMPostingRule # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TMPostingRule :: Type -> Type

Show TMPostingRule # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> TMPostingRule -> ShowS

show :: TMPostingRule -> String

showList :: [TMPostingRule] -> ShowS

Eq TMPostingRule # 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule # 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule = D1 ('MetaData "TMPostingRule" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "TMPostingRule" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmprPosting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Posting) :*: S1 ('MetaSel ('Just "tmprIsMultiplier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data TimeclockCode #

Instances

Instances details
ToJSON TimeclockCode # 
Instance details

Defined in Hledger.Data.Json

Generic TimeclockCode # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockCode :: Type -> Type

Read TimeclockCode # 
Instance details

Defined in Hledger.Data.Timeclock

Show TimeclockCode 
Instance details

Defined in Hledger.Data.Timeclock

Methods

showsPrec :: Int -> TimeclockCode -> ShowS

show :: TimeclockCode -> String

showList :: [TimeclockCode] -> ShowS

Eq TimeclockCode # 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockCode # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode = D1 ('MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) ((C1 ('MetaCons "SetBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetRequiredHours" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Out" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FinalOut" 'PrefixI 'False) (U1 :: Type -> Type))))

data TimeclockEntry #

Instances

Instances details
ToJSON TimeclockEntry # 
Instance details

Defined in Hledger.Data.Json

Generic TimeclockEntry # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockEntry :: Type -> Type

Show TimeclockEntry 
Instance details

Defined in Hledger.Data.Timeclock

Methods

showsPrec :: Int -> TimeclockEntry -> ShowS

show :: TimeclockEntry -> String

showList :: [TimeclockEntry] -> ShowS

Eq TimeclockEntry # 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockEntry # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry = D1 ('MetaData "TimeclockEntry" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "TimeclockEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tlsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "tlcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeclockCode) :*: S1 ('MetaSel ('Just "tldatetime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime))) :*: ((S1 ('MetaSel ('Just "tlaccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "tldescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tlcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tltags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))))

data PriceDirective #

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.

Instances

Instances details
ToJSON PriceDirective # 
Instance details

Defined in Hledger.Data.Json

Generic PriceDirective # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PriceDirective :: Type -> Type

Show PriceDirective # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> PriceDirective -> ShowS

show :: PriceDirective -> String

showList :: [PriceDirective] -> ShowS

Eq PriceDirective # 
Instance details

Defined in Hledger.Data.Types

Ord PriceDirective # 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective # 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective = D1 ('MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "PriceDirective" 'PrefixI 'True) (S1 ('MetaSel ('Just "pddate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: (S1 ('MetaSel ('Just "pdcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "pdamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))))

data MarketPrice #

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

Instances details
FromJSON MarketPrice # 
Instance details

Defined in Hledger.Data.Json

ToJSON MarketPrice # 
Instance details

Defined in Hledger.Data.Json

Generic MarketPrice # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MarketPrice :: Type -> Type

Methods

from :: MarketPrice -> Rep MarketPrice x

to :: Rep MarketPrice x -> MarketPrice

Show MarketPrice # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> MarketPrice -> ShowS

show :: MarketPrice -> String

showList :: [MarketPrice] -> ShowS

Eq MarketPrice # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: MarketPrice -> MarketPrice -> Bool

(/=) :: MarketPrice -> MarketPrice -> Bool

Ord MarketPrice # 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice # 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice = D1 ('MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "MarketPrice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "mpfrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol)) :*: (S1 ('MetaSel ('Just "mpto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "mprate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity))))

data PayeeDeclarationInfo #

Extra information found in a payee directive.

Constructors

PayeeDeclarationInfo 

Fields

  • pdicomment :: Text

    any comment lines following the payee directive

  • pditags :: [Tag]

    tags extracted from the comment, if any

Instances

Instances details
ToJSON PayeeDeclarationInfo # 
Instance details

Defined in Hledger.Data.Json

Generic PayeeDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PayeeDeclarationInfo :: Type -> Type

Show PayeeDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Eq PayeeDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo = D1 ('MetaData "PayeeDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "PayeeDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "pdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "pditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))

newtype TagDeclarationInfo #

Extra information found in a tag directive.

Constructors

TagDeclarationInfo 

Fields

  • tdicomment :: Text

    any comment lines following the tag directive. No tags allowed here.

Instances

Instances details
ToJSON TagDeclarationInfo # 
Instance details

Defined in Hledger.Data.Json

Generic TagDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TagDeclarationInfo :: Type -> Type

Show TagDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Eq TagDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep TagDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep TagDeclarationInfo = D1 ('MetaData "TagDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'True) (C1 ('MetaCons "TagDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "tdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data AccountDeclarationInfo #

Extra information about an account that can be derived from its account directive (and the other account directives).

Constructors

AccountDeclarationInfo 

Fields

  • adicomment :: Text

    any comment lines following an account directive for this account

  • aditags :: [Tag]

    tags extracted from the account comment, if any

  • adideclarationorder :: Int

    the order in which this account was declared, relative to other account declarations, during parsing (1..)

  • adisourcepos :: SourcePos

    source file and position

Instances

Instances details
FromJSON AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Json

ToJSON AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Json

Generic AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountDeclarationInfo :: Type -> Type

Show AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

Eq AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo = D1 ('MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.31-10Abz9vlABn64B0DmcMPJI" 'False) (C1 ('MetaCons "AccountDeclarationInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "adicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "aditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])) :*: (S1 ('MetaSel ('Just "adideclarationorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "adisourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))

type ParsedJournal = Journal #

A journal in the process of being parsed, not yet finalised. The data is partial, and list fields are in reverse order.

type StorageFormat = String #

The id of a data format understood by hledger, eg journal or csv. The --output-format option selects one of these for output.

data NormalSign #

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

Instances details
Show NormalSign # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> NormalSign -> ShowS

show :: NormalSign -> String

showList :: [NormalSign] -> ShowS

Eq NormalSign # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: NormalSign -> NormalSign -> Bool

(/=) :: NormalSign -> NormalSign -> Bool

modifyEFDay :: (Day -> Day) -> EFDay -> EFDay #

isAccountSubtypeOf :: AccountType -> AccountType -> Bool #

Check whether the first argument is a subtype of the second: either equal or one of the defined subtypes.

isDecimalMark :: Char -> Bool #

maCompare :: MixedAmount -> MixedAmount -> Ordering #

Compare two MixedAmounts, substituting 0 for the quantity of any missing commodities in either.

type Year = Integer #

Orphan instances

ToMarkup Quantity # 
Instance details

Generic (DecimalRaw a) # 
Instance details

Associated Types

type Rep (DecimalRaw a) :: Type -> Type

Methods

from :: DecimalRaw a -> Rep (DecimalRaw a) x

to :: Rep (DecimalRaw a) x -> DecimalRaw a