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

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

Documentation

type Year = Integer #

Year of Common Era.

data Ledger Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

Generic Ledger Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Ledger

type Rep Ledger Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 NormalSign Source #

Whether an account's balance is normally a positive number (in accounting terms, a debit balance) or a negative number (credit balance). Assets and expenses are normally positive (debit), while liabilities, equity and income are normally negative (credit). https://en.wikipedia.org/wiki/Normal_balance

Instances

Instances details
Show NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

Eq NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

data Account Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Account Source # 
Instance details

Defined in Hledger.Data.Json

Generic Account Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Account

Eq Account Source # 
Instance details

Defined in Hledger.Data.Account

Methods

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

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

type Rep Account Source # 
Instance details

Defined in Hledger.Data.Types

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

Instances details
FromJSON AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Json

Generic AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountDeclarationInfo :: Type -> Type #

Show AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Eq AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo = D1 ('MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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))))

data PayeeDeclarationInfo Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

Generic PayeeDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PayeeDeclarationInfo :: Type -> Type #

Show PayeeDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Eq PayeeDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

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

type StorageFormat = String Source #

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

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 Journal Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

Semigroup Journal Source # 
Instance details

Defined in Hledger.Data.Journal

Generic Journal Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Journal

Default Journal Source # 
Instance details

Defined in Hledger.Data.Journal

Methods

def :: Journal #

Eq Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

type Rep Journal Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 ('MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 "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 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

Instances details
FromJSON MarketPrice Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON MarketPrice Source # 
Instance details

Defined in Hledger.Data.Json

Generic MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MarketPrice :: Type -> Type #

Show MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Eq MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Ord MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

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.

Instances

Instances details
ToJSON PriceDirective Source # 
Instance details

Defined in Hledger.Data.Json

Generic PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PriceDirective :: Type -> Type #

Show PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Eq PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Ord PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective = D1 ('MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 TimeclockEntry Source #

Instances

Instances details
ToJSON TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Json

Generic TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockEntry :: Type -> Type #

Show TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Timeclock

Eq TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry = D1 ('MetaData "TimeclockEntry" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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)))))

data TimeclockCode Source #

Instances

Instances details
ToJSON TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Json

Generic TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockCode :: Type -> Type #

Read TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Timeclock

Show TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Timeclock

Eq TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode = D1 ('MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 PeriodicTransaction Source #

A periodic transaction rule, describing a transaction that recurs.

Constructors

PeriodicTransaction 

Fields

Instances

Instances details
ToJSON PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Json

Generic PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PeriodicTransaction :: Type -> Type #

Show PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.PeriodicTransaction

Eq PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

data TMPostingRule Source #

A transaction modifier transformation, which adds an extra posting to the matched posting's transaction. Can be like a regular posting, or can have the tmprIsMultiplier flag set, indicating that it's a multiplier for the matched posting's amount.

Instances

Instances details
ToJSON TMPostingRule Source # 
Instance details

Defined in Hledger.Data.Json

Generic TMPostingRule Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TMPostingRule :: Type -> Type #

Show TMPostingRule Source # 
Instance details

Defined in Hledger.Data.Types

Eq TMPostingRule Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule = D1 ('MetaData "TMPostingRule" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 TransactionModifier Source #

A transaction modifier rule. This has a query which matches postings in the journal, and a list of transformations to apply to those postings or their transactions. Currently there is one kind of transformation: the TMPostingRule, which adds a posting ("auto posting") to the transaction, optionally setting its amount to the matched posting's amount multiplied by a constant.

Instances

Instances details
ToJSON TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Json

Generic TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TransactionModifier :: Type -> Type #

Show TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Eq TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

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

data Transaction Source #

Constructors

Transaction 

Fields

Instances

Instances details
FromJSON Transaction Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Transaction Source # 
Instance details

Defined in Hledger.Data.Json

Generic Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Transaction :: Type -> Type #

Show Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Eq Transaction Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Transaction Source # 
Instance details

Defined in Hledger.Data.Types

data Posting Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Posting Source # 
Instance details

Defined in Hledger.Data.Json

Generic Posting Source # 
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 Source #

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

Instance details

Defined in Hledger.Data.Types

Eq Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

type Rep Posting Source # 
Instance details

Defined in Hledger.Data.Types

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

Instances details
FromJSON BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Json

Generic BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep BalanceAssertion :: Type -> Type #

Show BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Eq BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion = D1 ('MetaData "BalanceAssertion" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 Status Source #

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 Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Status Source # 
Instance details

Defined in Hledger.Data.Json

Bounded Status Source # 
Instance details

Defined in Hledger.Data.Types

Enum Status Source # 
Instance details

Defined in Hledger.Data.Types

Generic Status Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Types

Eq Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Status Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Status Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 Tag Source #

Arguments

 = (TagName, TagValue)

A tag name and (possibly empty) value.

data PostingType Source #

Instances

Instances details
FromJSON PostingType Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON PostingType Source # 
Instance details

Defined in Hledger.Data.Json

Generic PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PostingType :: Type -> Type #

Show PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Eq PostingType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType Source # 
Instance details

Defined in Hledger.Data.Types

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

data MixedAmount Source #

Instances

Instances details
FromJSON MixedAmount Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON MixedAmount Source # 
Instance details

Defined in Hledger.Data.Json

Monoid MixedAmount Source # 
Instance details

Defined in Hledger.Data.Amount

Semigroup MixedAmount Source # 
Instance details

Defined in Hledger.Data.Amount

Generic MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmount :: Type -> Type #

Num MixedAmount Source # 
Instance details

Defined in Hledger.Data.Amount

Show MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Eq MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Ord MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

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

data Amount Source #

Constructors

Amount 

Fields

Instances

Instances details
FromJSON Amount Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Amount Source # 
Instance details

Defined in Hledger.Data.Json

Generic Amount Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Amount

Show Amount Source # 
Instance details

Defined in Hledger.Data.Types

Eq Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Amount Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Amount Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 Commodity Source #

Instances

Instances details
ToJSON Commodity Source # 
Instance details

Defined in Hledger.Data.Json

Generic Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Commodity :: Type -> Type #

Show Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Eq Commodity Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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))))

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

Instances details
FromJSON DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Json

Generic DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DigitGroupStyle :: Type -> Type #

Read DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Eq DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Ord DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 ('MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 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. This can be from 0 to 255 digits (the maximum supported by the Decimal library), or NaturalPrecision meaning "show all significant decimal digits".

Instances

Instances details
FromJSON AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Json

Generic AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrecision :: Type -> Type #

Read AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

Show AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

Eq AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

Ord AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision = D1 ('MetaData "AmountPrecision" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 style for an amount.

Constructors

AmountStyle 

Fields

Instances

Instances details
FromJSON AmountStyle Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountStyle Source # 
Instance details

Defined in Hledger.Data.Json

Generic AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountStyle :: Type -> Type #

Read AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Eq AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Ord AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle = D1 ('MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 "asprecision") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountPrecision) :*: (S1 ('MetaSel ('Just "asdecimalpoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Char)) :*: S1 ('MetaSel ('Just "asdigitgroups") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DigitGroupStyle))))))

data AmountPrice Source #

An amount's per-unit or total cost/selling price in another commodity, as recorded in the journal entry eg with or @. Docs call this "transaction price". The amount is always positive.

Instances

Instances details
FromJSON AmountPrice Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON AmountPrice Source # 
Instance details

Defined in Hledger.Data.Json

Generic AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrice :: Type -> Type #

Show AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Eq AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Ord AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrice = D1 ('MetaData "AmountPrice" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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)))

type Quantity = Decimal Source #

The basic numeric type used in amounts.

type DecimalMark = Char Source #

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

data Side Source #

Constructors

L 
R 

Instances

Instances details
FromJSON Side Source # 
Instance details

Defined in Hledger.Data.Json

ToJSON Side Source # 
Instance details

Defined in Hledger.Data.Json

Generic Side Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Types

Show Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Eq Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Side Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Types

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

data AccountAlias Source #

Instances

Instances details
ToJSON AccountAlias Source # 
Instance details

Defined in Hledger.Data.Json

Generic AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountAlias :: Type -> Type #

Read AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Show AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Eq AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Ord AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

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 in which to generate conversion postings for transaction prices

Instances

Instances details
ToJSON AccountType Source # 
Instance details

Defined in Hledger.Data.Json

ToJSONKey AccountType Source # 
Instance details

Defined in Hledger.Data.Json

Generic AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountType :: Type -> Type #

Show AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Eq AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Ord AccountType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType = D1 ('MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 Interval Source #

Instances

Instances details
ToJSON Interval Source # 
Instance details

Defined in Hledger.Data.Json

Generic Interval Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Types

Default Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Interval #

Eq Interval Source # 
Instance details

Defined in Hledger.Data.Types

Ord Interval Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Interval Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 ('MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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))))))

data Period Source #

Instances

Instances details
ToJSON Period Source # 
Instance details

Defined in Hledger.Data.Json

Generic Period Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Types

Default Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Period #

Eq Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Period Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Period Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 ('MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" '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 DateSpan Source #

Constructors

DateSpan (Maybe Day) (Maybe Day) 

Instances

Instances details
ToJSON DateSpan Source # 
Instance details

Defined in Hledger.Data.Json

Generic DateSpan Source # 
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 Source # 
Instance details

Defined in Hledger.Data.Dates

Default DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: DateSpan #

Eq DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Ord DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DateSpan = D1 ('MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.28-1sYuTIz9MN21SCq5RkjAmv" 'False) (C1 ('MetaCons "DateSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))))

data WhichDate Source #

Constructors

PrimaryDate 
SecondaryDate 

Instances

Instances details
Show WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

Eq WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

data SmartInterval Source #

Constructors

Day 
Week 
Month 
Quarter 
Year 

Instances

Instances details
Show SmartInterval Source # 
Instance details

Defined in Hledger.Data.Types

data SmartDate Source #

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 Source # 
Instance details

Defined in Hledger.Data.Types

type Month = Int Source #

isAccountSubtypeOf :: AccountType -> AccountType -> Bool Source #

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

maCompare :: MixedAmount -> MixedAmount -> Ordering Source #

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