hledger-lib-1.17.1: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Data.Types

Contents

Description

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

Journal                  -- a journal is read from one or more data files. It contains..
 [Transaction]           -- journal transactions (aka entries), which have date, cleared status, code, description and..
  [Posting]              -- multiple account postings, which have account name and amount
 [MarketPrice]           -- historical market prices for commodities

Ledger                   -- a ledger is derived from a journal, by applying a filter specification and doing some further processing. It contains..
 Journal                 -- a filtered copy of the original journal, containing only the transactions and postings we are interested in
 [Account]               -- all accounts, in tree order beginning with a "root" account", with their balances and sub/parent accounts

For more detailed documentation on each type, see the corresponding modules.

Synopsis

Documentation

type SmartDate = (String, String, String) Source #

A possibly incomplete date, whose missing parts will be filled from a reference date. A numeric year, month, and day of month, or the empty string for any of these. See the smartdate parser.

data WhichDate Source #

Constructors

PrimaryDate 
SecondaryDate 
Instances
Eq WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

Show WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

data DateSpan Source #

Constructors

DateSpan (Maybe Day) (Maybe Day) 
Instances
Eq DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Data DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateSpan -> c DateSpan #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateSpan #

toConstr :: DateSpan -> Constr #

dataTypeOf :: DateSpan -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DateSpan) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateSpan) #

gmapT :: (forall b. Data b => b -> b) -> DateSpan -> DateSpan #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateSpan -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateSpan -> r #

gmapQ :: (forall d. Data d => d -> u) -> DateSpan -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DateSpan -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

Ord DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Show DateSpan Source # 
Instance details

Defined in Hledger.Data.Dates

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 #

ToJSON DateSpan Source # 
Instance details

Defined in Hledger.Data.Json

Default DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: DateSpan #

NFData DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: DateSpan -> () #

type Rep DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DateSpan = D1 (MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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))))

type Month = Int Source #

data Period Source #

Instances
Eq Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Data Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Period -> c Period #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Period #

toConstr :: Period -> Constr #

dataTypeOf :: Period -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Period) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period) #

gmapT :: (forall b. Data b => b -> b) -> Period -> Period #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r #

gmapQ :: (forall d. Data d => d -> u) -> Period -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Period -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Period -> m Period #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period #

Ord Period Source # 
Instance details

Defined in Hledger.Data.Types

Show Period Source # 
Instance details

Defined in Hledger.Data.Types

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 #

Default Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Period #

type Rep Period Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 (MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 Interval Source #

Instances
Eq Interval Source # 
Instance details

Defined in Hledger.Data.Types

Data Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Interval -> c Interval #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Interval #

toConstr :: Interval -> Constr #

dataTypeOf :: Interval -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Interval) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Interval) #

gmapT :: (forall b. Data b => b -> b) -> Interval -> Interval #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r #

gmapQ :: (forall d. Data d => d -> u) -> Interval -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Interval -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

Ord Interval Source # 
Instance details

Defined in Hledger.Data.Types

Show Interval Source # 
Instance details

Defined in Hledger.Data.Types

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 #

ToJSON Interval Source # 
Instance details

Defined in Hledger.Data.Json

Default Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Interval #

NFData Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Interval -> () #

type Rep Interval Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 (MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 "DayOfWeek" 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 AccountType Source #

Instances
Eq AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Data AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountType -> c AccountType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountType #

toConstr :: AccountType -> Constr #

dataTypeOf :: AccountType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountType) #

gmapT :: (forall b. Data b => b -> b) -> AccountType -> AccountType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountType -> m AccountType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountType -> m AccountType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountType -> m AccountType #

Ord AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Show AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Generic AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountType :: Type -> Type #

ToJSON AccountType Source # 
Instance details

Defined in Hledger.Data.Json

ToJSONKey AccountType Source # 
Instance details

Defined in Hledger.Data.Json

NFData AccountType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AccountType -> () #

type Rep AccountType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType = D1 (MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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))))

data AccountAlias Source #

Instances
Eq AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Data AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountAlias -> c AccountAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountAlias #

toConstr :: AccountAlias -> Constr #

dataTypeOf :: AccountAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountAlias) #

gmapT :: (forall b. Data b => b -> b) -> AccountAlias -> AccountAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountAlias -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

Ord AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Read AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Show AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Generic AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountAlias :: Type -> Type #

ToJSON AccountAlias Source # 
Instance details

Defined in Hledger.Data.Json

NFData AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AccountAlias -> () #

type Rep AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

data Side Source #

Constructors

L 
R 
Instances
Eq Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Data Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Side -> c Side #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Side #

toConstr :: Side -> Constr #

dataTypeOf :: Side -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Side) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Side) #

gmapT :: (forall b. Data b => b -> b) -> Side -> Side #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Side -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Side -> r #

gmapQ :: (forall d. Data d => d -> u) -> Side -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Side -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Side -> m Side #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Side -> m Side #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Side -> m Side #

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 #

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 #

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 #

ToJSON Side Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Side Source # 
Instance details

Defined in Hledger.Data.Json

NFData Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Side -> () #

type Rep Side Source # 
Instance details

Defined in Hledger.Data.Types

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

type Quantity = Decimal Source #

The basic numeric type used in amounts.

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

Defined in Hledger.Data.Types

Data AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmountPrice -> c AmountPrice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AmountPrice #

toConstr :: AmountPrice -> Constr #

dataTypeOf :: AmountPrice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AmountPrice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AmountPrice) #

gmapT :: (forall b. Data b => b -> b) -> AmountPrice -> AmountPrice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmountPrice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmountPrice -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmountPrice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmountPrice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmountPrice -> m AmountPrice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountPrice -> m AmountPrice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountPrice -> m AmountPrice #

Ord AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Show AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Generic AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrice :: Type -> Type #

ToJSON AmountPrice Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON AmountPrice Source # 
Instance details

Defined in Hledger.Data.Json

NFData AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AmountPrice -> () #

type Rep AmountPrice Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrice = D1 (MetaData "AmountPrice" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" False) (C1 (MetaCons "UnitPrice" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Amount)) :+: C1 (MetaCons "TotalPrice" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Amount)))

data AmountStyle Source #

Display style for an amount.

Constructors

AmountStyle 

Fields

Instances
Eq AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Data AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmountStyle -> c AmountStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AmountStyle #

toConstr :: AmountStyle -> Constr #

dataTypeOf :: AmountStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AmountStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AmountStyle) #

gmapT :: (forall b. Data b => b -> b) -> AmountStyle -> AmountStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmountStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmountStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmountStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmountStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

Ord AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Read AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Generic AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountStyle :: Type -> Type #

ToJSON AmountStyle Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON AmountStyle Source # 
Instance details

Defined in Hledger.Data.Json

NFData AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AmountStyle -> () #

type Rep AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle = D1 (MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" False) (C1 (MetaCons "AmountStyle" PrefixI True) ((S1 (MetaSel (Just "ascommodityside") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side) :*: S1 (MetaSel (Just "ascommodityspaced") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "asprecision") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "asdecimalpoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Char)) :*: S1 (MetaSel (Just "asdigitgroups") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DigitGroupStyle))))))

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 [Int] 
Instances
Eq DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Data DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DigitGroupStyle -> c DigitGroupStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DigitGroupStyle #

toConstr :: DigitGroupStyle -> Constr #

dataTypeOf :: DigitGroupStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DigitGroupStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DigitGroupStyle) #

gmapT :: (forall b. Data b => b -> b) -> DigitGroupStyle -> DigitGroupStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DigitGroupStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DigitGroupStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> DigitGroupStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DigitGroupStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

Ord DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Read DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Generic DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DigitGroupStyle :: Type -> Type #

ToJSON DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Json

NFData DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: DigitGroupStyle -> () #

type Rep DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 (MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" False) (C1 (MetaCons "DigitGroups" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])))

data Commodity Source #

Instances
Eq Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Data Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Commodity -> c Commodity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Commodity #

toConstr :: Commodity -> Constr #

dataTypeOf :: Commodity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Commodity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Commodity) #

gmapT :: (forall b. Data b => b -> b) -> Commodity -> Commodity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Commodity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Commodity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Commodity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Commodity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

Show Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Generic Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Commodity :: Type -> Type #

ToJSON Commodity Source # 
Instance details

Defined in Hledger.Data.Json

NFData Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Commodity -> () #

type Rep Commodity Source # 
Instance details

Defined in Hledger.Data.Types

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

Constructors

Amount 

Fields

Instances
Eq Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Data Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Amount -> c Amount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Amount #

toConstr :: Amount -> Constr #

dataTypeOf :: Amount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Amount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Amount) #

gmapT :: (forall b. Data b => b -> b) -> Amount -> Amount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQ :: (forall d. Data d => d -> u) -> Amount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Amount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

Num Amount Source # 
Instance details

Defined in Hledger.Data.Amount

Ord Amount Source # 
Instance details

Defined in Hledger.Data.Types

Show Amount Source # 
Instance details

Defined in Hledger.Data.Types

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 #

ToJSON Amount Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Amount Source # 
Instance details

Defined in Hledger.Data.Json

NFData Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Amount -> () #

type Rep Amount Source # 
Instance details

Defined in Hledger.Data.Types

newtype MixedAmount Source #

Constructors

Mixed [Amount] 
Instances
Eq MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Data MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MixedAmount -> c MixedAmount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MixedAmount #

toConstr :: MixedAmount -> Constr #

dataTypeOf :: MixedAmount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MixedAmount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MixedAmount) #

gmapT :: (forall b. Data b => b -> b) -> MixedAmount -> MixedAmount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MixedAmount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MixedAmount -> r #

gmapQ :: (forall d. Data d => d -> u) -> MixedAmount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MixedAmount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

Num MixedAmount Source # 
Instance details

Defined in Hledger.Data.Amount

Ord MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Show MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Generic MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmount :: Type -> Type #

ToJSON MixedAmount Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON MixedAmount Source # 
Instance details

Defined in Hledger.Data.Json

NFData MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: MixedAmount -> () #

type Rep MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount = D1 (MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" True) (C1 (MetaCons "Mixed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Amount])))

data PostingType Source #

Instances
Eq PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Data PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostingType -> c PostingType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostingType #

toConstr :: PostingType -> Constr #

dataTypeOf :: PostingType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PostingType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostingType) #

gmapT :: (forall b. Data b => b -> b) -> PostingType -> PostingType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostingType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostingType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PostingType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PostingType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

Show PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Generic PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PostingType :: Type -> Type #

ToJSON PostingType Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON PostingType Source # 
Instance details

Defined in Hledger.Data.Json

NFData PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: PostingType -> () #

type Rep PostingType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType = D1 (MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 Tag Source #

Arguments

 = (TagName, TagValue)

A tag name and (possibly empty) value.

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

Defined in Hledger.Data.Types

Enum 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 #

Data Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Status -> c Status #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Status #

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Status) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status) #

gmapT :: (forall b. Data b => b -> b) -> Status -> Status #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQ :: (forall d. Data d => d -> u) -> Status -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Status -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

Ord Status Source # 
Instance details

Defined in Hledger.Data.Types

Show 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 #

ToJSON Status Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Status Source # 
Instance details

Defined in Hledger.Data.Json

NFData Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Status -> () #

type Rep Status Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 (MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" False) (C1 (MetaCons "Unmarked" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cleared" PrefixI False) (U1 :: Type -> Type)))

data BalanceAssertion Source #

A balance assertion is a declaration about an account's expected balance at a certain point (posting date and parse order). They provide additional error checking and readability to a journal file.

The BalanceAssertion type is also used to represent balance assignments, which instruct hledger what an account's balance should become at a certain point.

Different kinds of balance assertions are discussed eg on #290. Variables include:

  • which postings are to be summed (realvirtual; unmarkedpendingcleared; this accountthis account including subs)
  • which commodities within the balance are to be checked
  • whether to do a partial or a total check (disallowing other commodities)

I suspect we want:

  1. partial, subaccount-exclusive, Ledger-compatible assertions. Because they're what we've always had, and removing them would break some journals unnecessarily. Implemented with = syntax.
  2. total assertions. Because otherwise assertions are a bit leaky. Implemented with == syntax.
  3. subaccount-inclusive assertions. Because that's something folks need. Not implemented.
  4. flexible assertions allowing custom criteria (perhaps arbitrary queries). Because power users have diverse needs and want to try out different schemes (assert cleared balances, assert balance from real or virtual postings, etc.). Not implemented.
  5. multicommodity assertions, asserting the balance of multiple commodities at once. Not implemented, requires #934.

Constructors

BalanceAssertion 

Fields

Instances
Eq BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Data BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BalanceAssertion -> c BalanceAssertion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BalanceAssertion #

toConstr :: BalanceAssertion -> Constr #

dataTypeOf :: BalanceAssertion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BalanceAssertion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BalanceAssertion) #

gmapT :: (forall b. Data b => b -> b) -> BalanceAssertion -> BalanceAssertion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BalanceAssertion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BalanceAssertion -> r #

gmapQ :: (forall d. Data d => d -> u) -> BalanceAssertion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BalanceAssertion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BalanceAssertion -> m BalanceAssertion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceAssertion -> m BalanceAssertion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceAssertion -> m BalanceAssertion #

Show BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Generic BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep BalanceAssertion :: Type -> Type #

ToJSON BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Json

NFData BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: BalanceAssertion -> () #

type Rep BalanceAssertion Source # 
Instance details

Defined in Hledger.Data.Types

data Posting Source #

Constructors

Posting 

Fields

Instances
Eq Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Data Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Posting -> c Posting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Posting #

toConstr :: Posting -> Constr #

dataTypeOf :: Posting -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Posting) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Posting) #

gmapT :: (forall b. Data b => b -> b) -> Posting -> Posting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Posting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Posting -> r #

gmapQ :: (forall d. Data d => d -> u) -> Posting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Posting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Posting -> m Posting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Posting -> m Posting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Posting -> m 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

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 #

ToJSON Posting Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Posting Source # 
Instance details

Defined in Hledger.Data.Json

NFData Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Posting -> () #

type Rep Posting Source # 
Instance details

Defined in Hledger.Data.Types

data GenericSourcePos Source #

The position of parse errors (eg), like parsec's SourcePos but generic.

Constructors

GenericSourcePos FilePath Int Int

file path, 1-based line number and 1-based column number.

JournalSourcePos FilePath (Int, Int)

file path, inclusive range of 1-based line numbers (first, last).

Instances
Eq GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Data GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenericSourcePos -> c GenericSourcePos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenericSourcePos #

toConstr :: GenericSourcePos -> Constr #

dataTypeOf :: GenericSourcePos -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenericSourcePos) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenericSourcePos) #

gmapT :: (forall b. Data b => b -> b) -> GenericSourcePos -> GenericSourcePos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenericSourcePos -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenericSourcePos -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenericSourcePos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenericSourcePos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

Ord GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Read GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Show GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Generic GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep GenericSourcePos :: Type -> Type #

ToJSON GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Json

NFData GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: GenericSourcePos -> () #

type Rep GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

data Transaction Source #

Constructors

Transaction 

Fields

Instances
Eq Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Data Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transaction -> c Transaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transaction #

toConstr :: Transaction -> Constr #

dataTypeOf :: Transaction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Transaction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transaction) #

gmapT :: (forall b. Data b => b -> b) -> Transaction -> Transaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Transaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Transaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

Show Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Generic Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Transaction :: Type -> Type #

ToJSON Transaction Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Transaction Source # 
Instance details

Defined in Hledger.Data.Json

NFData Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Transaction -> () #

type Rep Transaction Source # 
Instance details

Defined in Hledger.Data.Types

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

Defined in Hledger.Data.Types

Data TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransactionModifier -> c TransactionModifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransactionModifier #

toConstr :: TransactionModifier -> Constr #

dataTypeOf :: TransactionModifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TransactionModifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransactionModifier) #

gmapT :: (forall b. Data b => b -> b) -> TransactionModifier -> TransactionModifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransactionModifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransactionModifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransactionModifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransactionModifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransactionModifier -> m TransactionModifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionModifier -> m TransactionModifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionModifier -> m TransactionModifier #

Show TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Generic TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TransactionModifier :: Type -> Type #

ToJSON TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Json

NFData TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: TransactionModifier -> () #

type Rep TransactionModifier Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier = D1 (MetaData "TransactionModifier" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 TMPostingRule = Posting Source #

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

data PeriodicTransaction Source #

A periodic transaction rule, describing a transaction that recurs.

Constructors

PeriodicTransaction 

Fields

Instances
Eq PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Data PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PeriodicTransaction -> c PeriodicTransaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PeriodicTransaction #

toConstr :: PeriodicTransaction -> Constr #

dataTypeOf :: PeriodicTransaction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PeriodicTransaction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PeriodicTransaction) #

gmapT :: (forall b. Data b => b -> b) -> PeriodicTransaction -> PeriodicTransaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PeriodicTransaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PeriodicTransaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> PeriodicTransaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PeriodicTransaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

Show PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.PeriodicTransaction

Generic PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PeriodicTransaction :: Type -> Type #

ToJSON PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Json

NFData PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: PeriodicTransaction -> () #

type Rep PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

data TimeclockCode Source #

Instances
Eq TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Data TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeclockCode -> c TimeclockCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeclockCode #

toConstr :: TimeclockCode -> Constr #

dataTypeOf :: TimeclockCode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeclockCode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeclockCode) #

gmapT :: (forall b. Data b => b -> b) -> TimeclockCode -> TimeclockCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeclockCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeclockCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

Ord TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Read TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Timeclock

Show TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Timeclock

Generic TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockCode :: Type -> Type #

ToJSON TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Json

NFData TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: TimeclockCode -> () #

type Rep TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode = D1 (MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 Source #

Instances
Eq TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Data TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeclockEntry -> c TimeclockEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeclockEntry #

toConstr :: TimeclockEntry -> Constr #

dataTypeOf :: TimeclockEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeclockEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeclockEntry) #

gmapT :: (forall b. Data b => b -> b) -> TimeclockEntry -> TimeclockEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockEntry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeclockEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeclockEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

Ord TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Show TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Timeclock

Generic TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockEntry :: Type -> Type #

ToJSON TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Json

NFData TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: TimeclockEntry -> () #

type Rep TimeclockEntry 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
Eq PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Data PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PriceDirective -> c PriceDirective #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PriceDirective #

toConstr :: PriceDirective -> Constr #

dataTypeOf :: PriceDirective -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PriceDirective) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PriceDirective) #

gmapT :: (forall b. Data b => b -> b) -> PriceDirective -> PriceDirective #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PriceDirective -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PriceDirective -> r #

gmapQ :: (forall d. Data d => d -> u) -> PriceDirective -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PriceDirective -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PriceDirective -> m PriceDirective #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PriceDirective -> m PriceDirective #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PriceDirective -> m PriceDirective #

Ord PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Show PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Generic PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PriceDirective :: Type -> Type #

ToJSON PriceDirective Source # 
Instance details

Defined in Hledger.Data.Json

NFData PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: PriceDirective -> () #

type Rep PriceDirective Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective = D1 (MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 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
Eq MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Data MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MarketPrice -> c MarketPrice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MarketPrice #

toConstr :: MarketPrice -> Constr #

dataTypeOf :: MarketPrice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MarketPrice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MarketPrice) #

gmapT :: (forall b. Data b => b -> b) -> MarketPrice -> MarketPrice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MarketPrice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MarketPrice -> r #

gmapQ :: (forall d. Data d => d -> u) -> MarketPrice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MarketPrice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

Ord MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Show MarketPrice Source # 
Instance details

Defined in Hledger.Data.Amount

Generic MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MarketPrice :: Type -> Type #

ToJSON MarketPrice Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON MarketPrice Source # 
Instance details

Defined in Hledger.Data.Json

NFData MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: MarketPrice -> () #

type Rep MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

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

Defined in Hledger.Data.Types

Methods

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

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

Data Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Journal -> c Journal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Journal #

toConstr :: Journal -> Constr #

dataTypeOf :: Journal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Journal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Journal) #

gmapT :: (forall b. Data b => b -> b) -> Journal -> Journal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Journal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Journal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Journal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Journal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

Show 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 #

Semigroup Journal Source # 
Instance details

Defined in Hledger.Data.Journal

ToJSON Journal Source # 
Instance details

Defined in Hledger.Data.Json

Default Journal Source # 
Instance details

Defined in Hledger.Data.Journal

Methods

def :: Journal #

NFData Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Journal -> () #

type Rep Journal Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 (MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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 "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 "jdeclaredaccounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(AccountName, AccountDeclarationInfo)]) :*: S1 (MetaSel (Just "jdeclaredaccounttypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map AccountType [AccountName]))))) :*: (((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 "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 ClockTime)))))))

type ParsedJournal = Journal Source #

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

type StorageFormat = String Source #

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

data AccountDeclarationInfo Source #

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

Constructors

AccountDeclarationInfo 

Fields

  • 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..)

Instances
Eq AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Data AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountDeclarationInfo -> c AccountDeclarationInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountDeclarationInfo #

toConstr :: AccountDeclarationInfo -> Constr #

dataTypeOf :: AccountDeclarationInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountDeclarationInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountDeclarationInfo) #

gmapT :: (forall b. Data b => b -> b) -> AccountDeclarationInfo -> AccountDeclarationInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountDeclarationInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountDeclarationInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountDeclarationInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountDeclarationInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountDeclarationInfo -> m AccountDeclarationInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountDeclarationInfo -> m AccountDeclarationInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountDeclarationInfo -> m AccountDeclarationInfo #

Show AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Generic AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountDeclarationInfo :: Type -> Type #

ToJSON AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Json

NFData AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AccountDeclarationInfo -> () #

type Rep AccountDeclarationInfo Source # 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo = D1 (MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.17.1-pHZRVNpmaVHTFDKoAIcwo" 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))))

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

Defined in Hledger.Data.Account

Methods

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

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

Data Account Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Show Account Source # 
Instance details

Defined in Hledger.Data.Account

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 #

ToJSON Account Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON Account Source # 
Instance details

Defined in Hledger.Data.Json

type Rep Account Source # 
Instance details

Defined in Hledger.Data.Types

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

Defined in Hledger.Data.Types

Data NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NormalSign -> c NormalSign #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NormalSign #

toConstr :: NormalSign -> Constr #

dataTypeOf :: NormalSign -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NormalSign) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NormalSign) #

gmapT :: (forall b. Data b => b -> b) -> NormalSign -> NormalSign #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NormalSign -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NormalSign -> r #

gmapQ :: (forall d. Data d => d -> u) -> NormalSign -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NormalSign -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

Show NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

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

Defined in Hledger.Data.Ledger

Generic Ledger Source # 
Instance details

Defined in Hledger.Data.Json

Associated Types

type Rep Ledger :: Type -> Type #

Methods

from :: Ledger -> Rep Ledger x #

to :: Rep Ledger x -> Ledger #

ToJSON Ledger Source # 
Instance details

Defined in Hledger.Data.Json

type Rep Ledger Source # 
Instance details

Defined in Hledger.Data.Json

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

Orphan instances

Data ClockTime Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClockTime -> c ClockTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClockTime #

toConstr :: ClockTime -> Constr #

dataTypeOf :: ClockTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClockTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClockTime) #

gmapT :: (forall b. Data b => b -> b) -> ClockTime -> ClockTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClockTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClockTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClockTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClockTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClockTime -> m ClockTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClockTime -> m ClockTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClockTime -> m ClockTime #

Generic ClockTime Source # 
Instance details

Associated Types

type Rep ClockTime :: Type -> Type #

ToMarkup Quantity Source # 
Instance details

NFData ClockTime Source # 
Instance details

Methods

rnf :: ClockTime -> () #

Data (DecimalRaw Integer) Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecimalRaw Integer -> c (DecimalRaw Integer) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DecimalRaw Integer) #

toConstr :: DecimalRaw Integer -> Constr #

dataTypeOf :: DecimalRaw Integer -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DecimalRaw Integer)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DecimalRaw Integer)) #

gmapT :: (forall b. Data b => b -> b) -> DecimalRaw Integer -> DecimalRaw Integer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecimalRaw Integer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecimalRaw Integer -> r #

gmapQ :: (forall d. Data d => d -> u) -> DecimalRaw Integer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DecimalRaw Integer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecimalRaw Integer -> m (DecimalRaw Integer) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecimalRaw Integer -> m (DecimalRaw Integer) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecimalRaw Integer -> m (DecimalRaw Integer) #