hledger-lib-1.5: 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

data DateSpan Source #

Constructors

DateSpan (Maybe Day) (Maybe Day) 

Instances

Eq DateSpan Source # 
Data DateSpan Source # 

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

Associated Types

type Rep DateSpan :: * -> * #

Methods

from :: DateSpan -> Rep DateSpan x #

to :: Rep DateSpan x -> DateSpan #

Default DateSpan Source # 

Methods

def :: DateSpan #

NFData DateSpan Source # 

Methods

rnf :: DateSpan -> () #

type Rep DateSpan Source # 
type Rep DateSpan = D1 * (MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "DateSpan" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Day))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Day)))))

type Month = Int Source #

data Period Source #

Instances

Eq Period Source # 

Methods

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

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

Data Period Source # 

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

Associated Types

type Rep Period :: * -> * #

Methods

from :: Period -> Rep Period x #

to :: Rep Period x -> Period #

Default Period Source # 

Methods

def :: Period #

type Rep Period Source # 
type Rep Period = D1 * (MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DayPeriod" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day))) (C1 * (MetaCons "WeekPeriod" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day)))) ((:+:) * (C1 * (MetaCons "MonthPeriod" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Year)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Month)))) (C1 * (MetaCons "QuarterPeriod" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Year)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Quarter)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "YearPeriod" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Year))) (C1 * (MetaCons "PeriodBetween" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day))))) ((:+:) * (C1 * (MetaCons "PeriodFrom" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day))) ((:+:) * (C1 * (MetaCons "PeriodTo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day))) (C1 * (MetaCons "PeriodAll" PrefixI False) (U1 *))))))

data Interval Source #

Instances

Eq Interval Source # 
Data Interval Source # 

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

Associated Types

type Rep Interval :: * -> * #

Methods

from :: Interval -> Rep Interval x #

to :: Rep Interval x -> Interval #

Default Interval Source # 

Methods

def :: Interval #

NFData Interval Source # 

Methods

rnf :: Interval -> () #

type Rep Interval Source # 
type Rep Interval = D1 * (MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NoInterval" PrefixI False) (U1 *)) (C1 * (MetaCons "Days" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "Weeks" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "Months" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "Quarters" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Years" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "DayOfMonth" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "WeekdayOfMonth" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "DayOfWeek" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "DayOfYear" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))))

data AccountAlias Source #

Instances

Eq AccountAlias Source # 
Data AccountAlias Source # 

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 # 
Read AccountAlias Source # 
Show AccountAlias Source # 
Generic AccountAlias Source # 

Associated Types

type Rep AccountAlias :: * -> * #

NFData AccountAlias Source # 

Methods

rnf :: AccountAlias -> () #

type Rep AccountAlias Source # 

data Side Source #

Constructors

L 
R 

Instances

Eq Side Source # 

Methods

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

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

Data Side Source # 

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 # 

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

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 

Associated Types

type Rep Side :: * -> * #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

NFData Side Source # 

Methods

rnf :: Side -> () #

type Rep Side Source # 
type Rep Side = D1 * (MetaData "Side" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * (C1 * (MetaCons "L" PrefixI False) (U1 *)) (C1 * (MetaCons "R" PrefixI False) (U1 *)))

type Quantity = Decimal Source #

The basic numeric type used in amounts.

data Price Source #

An amount's price (none, per unit, or total) in another commodity. Note the price should be a positive number, although this is not enforced.

Instances

Eq Price Source # 

Methods

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

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

Data Price Source # 

Methods

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

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

toConstr :: Price -> Constr #

dataTypeOf :: Price -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Price Source # 

Methods

compare :: Price -> Price -> Ordering #

(<) :: Price -> Price -> Bool #

(<=) :: Price -> Price -> Bool #

(>) :: Price -> Price -> Bool #

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

max :: Price -> Price -> Price #

min :: Price -> Price -> Price #

Generic Price Source # 

Associated Types

type Rep Price :: * -> * #

Methods

from :: Price -> Rep Price x #

to :: Rep Price x -> Price #

NFData Price Source # 

Methods

rnf :: Price -> () #

type Rep Price Source # 
type Rep Price = D1 * (MetaData "Price" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * (C1 * (MetaCons "NoPrice" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UnitPrice" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Amount))) (C1 * (MetaCons "TotalPrice" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Amount)))))

data AmountStyle Source #

Display style for an amount.

Constructors

AmountStyle 

Fields

Instances

Eq AmountStyle Source # 
Data AmountStyle Source # 

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 # 
Read AmountStyle Source # 
Show AmountStyle Source # 
Generic AmountStyle Source # 

Associated Types

type Rep AmountStyle :: * -> * #

NFData AmountStyle Source # 

Methods

rnf :: AmountStyle -> () #

type Rep AmountStyle Source # 

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 # 
Data DigitGroupStyle Source # 

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 # 
Read DigitGroupStyle Source # 
Show DigitGroupStyle Source # 
Generic DigitGroupStyle Source # 
NFData DigitGroupStyle Source # 

Methods

rnf :: DigitGroupStyle -> () #

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

data Commodity Source #

Instances

Eq Commodity Source # 
Data Commodity Source # 

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

Associated Types

type Rep Commodity :: * -> * #

NFData Commodity Source # 

Methods

rnf :: Commodity -> () #

type Rep Commodity Source # 
type Rep Commodity = D1 * (MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "Commodity" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "csymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CommoditySymbol)) (S1 * (MetaSel (Just Symbol "cformat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe AmountStyle)))))

data Amount Source #

Constructors

Amount 

Fields

Instances

Eq Amount Source # 

Methods

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

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

Data Amount Source # 

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 #

Ord Amount Source # 
Generic Amount Source # 

Associated Types

type Rep Amount :: * -> * #

Methods

from :: Amount -> Rep Amount x #

to :: Rep Amount x -> Amount #

NFData Amount Source # 

Methods

rnf :: Amount -> () #

type Rep Amount Source # 

newtype MixedAmount Source #

Constructors

Mixed [Amount] 

Instances

Eq MixedAmount Source # 
Data MixedAmount Source # 

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 #

Ord MixedAmount Source # 
Generic MixedAmount Source # 

Associated Types

type Rep MixedAmount :: * -> * #

NFData MixedAmount Source # 

Methods

rnf :: MixedAmount -> () #

type Rep MixedAmount Source # 
type Rep MixedAmount = D1 * (MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" True) (C1 * (MetaCons "Mixed" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Amount])))

data PostingType Source #

Instances

Eq PostingType Source # 
Data PostingType Source # 

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

Associated Types

type Rep PostingType :: * -> * #

NFData PostingType Source # 

Methods

rnf :: PostingType -> () #

type Rep PostingType Source # 
type Rep PostingType = D1 * (MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * (C1 * (MetaCons "RegularPosting" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "VirtualPosting" PrefixI False) (U1 *)) (C1 * (MetaCons "BalancedVirtualPosting" PrefixI False) (U1 *))))

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 # 
Enum Status Source # 
Eq Status Source # 

Methods

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

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

Data Status Source # 

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

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

NFData Status Source # 

Methods

rnf :: Status -> () #

type Rep Status Source # 
type Rep Status = D1 * (MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * (C1 * (MetaCons "Unmarked" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Pending" PrefixI False) (U1 *)) (C1 * (MetaCons "Cleared" PrefixI False) (U1 *))))

data Posting Source #

Constructors

Posting 

Fields

Instances

Eq Posting Source # 

Methods

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

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

Data Posting Source # 

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 #

Generic Posting Source # 

Associated Types

type Rep Posting :: * -> * #

Methods

from :: Posting -> Rep Posting x #

to :: Rep Posting x -> Posting #

NFData Posting Source # 

Methods

rnf :: Posting -> () #

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

data GenericSourcePos Source #

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

Constructors

GenericSourcePos FilePath Int Int

name, 1-based line number and 1-based column number.

JournalSourcePos FilePath (Int, Int)

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

Instances

Eq GenericSourcePos Source # 
Data GenericSourcePos Source # 

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 # 
Read GenericSourcePos Source # 
Show GenericSourcePos Source # 
Generic GenericSourcePos Source # 
NFData GenericSourcePos Source # 

Methods

rnf :: GenericSourcePos -> () #

type Rep GenericSourcePos Source # 

data Transaction Source #

Constructors

Transaction 

Fields

Instances

Eq Transaction Source # 
Data Transaction Source # 

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 #

Generic Transaction Source # 

Associated Types

type Rep Transaction :: * -> * #

NFData Transaction Source # 

Methods

rnf :: Transaction -> () #

type Rep Transaction Source # 

data ModifierTransaction Source #

Constructors

ModifierTransaction 

Instances

Eq ModifierTransaction Source # 
Data ModifierTransaction Source # 

Methods

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

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

toConstr :: ModifierTransaction -> Constr #

dataTypeOf :: ModifierTransaction -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModifierTransaction Source # 
NFData ModifierTransaction Source # 

Methods

rnf :: ModifierTransaction -> () #

type Rep ModifierTransaction Source # 
type Rep ModifierTransaction = D1 * (MetaData "ModifierTransaction" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "ModifierTransaction" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "mtvalueexpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "mtpostings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Posting]))))

data PeriodicTransaction Source #

Instances

Eq PeriodicTransaction Source # 
Data PeriodicTransaction Source # 

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 #

Generic PeriodicTransaction Source # 
NFData PeriodicTransaction Source # 

Methods

rnf :: PeriodicTransaction -> () #

type Rep PeriodicTransaction Source # 
type Rep PeriodicTransaction = D1 * (MetaData "PeriodicTransaction" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "PeriodicTransaction" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ptperiodicexpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "ptpostings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Posting]))))

data TimeclockCode Source #

Instances

Eq TimeclockCode Source # 
Data TimeclockCode Source # 

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

Associated Types

type Rep TimeclockCode :: * -> * #

NFData TimeclockCode Source # 

Methods

rnf :: TimeclockCode -> () #

type Rep TimeclockCode Source # 
type Rep TimeclockCode = D1 * (MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SetBalance" PrefixI False) (U1 *)) (C1 * (MetaCons "SetRequiredHours" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "In" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Out" PrefixI False) (U1 *)) (C1 * (MetaCons "FinalOut" PrefixI False) (U1 *)))))

data TimeclockEntry Source #

Instances

Eq TimeclockEntry Source # 
Data TimeclockEntry Source # 

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

Associated Types

type Rep TimeclockEntry :: * -> * #

NFData TimeclockEntry Source # 

Methods

rnf :: TimeclockEntry -> () #

type Rep TimeclockEntry Source # 

data MarketPrice Source #

Instances

Eq MarketPrice Source # 
Data MarketPrice Source # 

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

Associated Types

type Rep MarketPrice :: * -> * #

NFData MarketPrice Source # 

Methods

rnf :: MarketPrice -> () #

type Rep MarketPrice Source # 
type Rep MarketPrice = D1 * (MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "MarketPrice" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "mpdate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Day)) ((:*:) * (S1 * (MetaSel (Just Symbol "mpcommodity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CommoditySymbol)) (S1 * (MetaSel (Just Symbol "mpamount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Amount)))))

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 # 

Methods

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

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

Data Journal Source # 

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 #

Generic Journal Source # 

Associated Types

type Rep Journal :: * -> * #

Methods

from :: Journal -> Rep Journal x #

to :: Rep Journal x -> Journal #

NFData Journal Source # 

Methods

rnf :: Journal -> () #

type Rep Journal Source # 
type Rep Journal = D1 * (MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.5-3Yp7rto1AaFI5WWC7fkex8" False) (C1 * (MetaCons "Journal" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "jparsedefaultyear") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Year))) ((:*:) * (S1 * (MetaSel (Just Symbol "jparsedefaultcommodity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (CommoditySymbol, AmountStyle)))) (S1 * (MetaSel (Just Symbol "jparseparentaccounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [AccountName])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "jparsealiases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [AccountAlias])) (S1 * (MetaSel (Just Symbol "jparsetimeclockentries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TimeclockEntry]))) ((:*:) * (S1 * (MetaSel (Just Symbol "jaccounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [AccountName])) (S1 * (MetaSel (Just Symbol "jcommodities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map CommoditySymbol Commodity)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "jinferredcommodities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map CommoditySymbol AmountStyle))) (S1 * (MetaSel (Just Symbol "jmarketprices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [MarketPrice]))) ((:*:) * (S1 * (MetaSel (Just Symbol "jmodifiertxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ModifierTransaction])) (S1 * (MetaSel (Just Symbol "jperiodictxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [PeriodicTransaction])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "jtxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Transaction])) (S1 * (MetaSel (Just Symbol "jfinalcommentlines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "jfiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(FilePath, Text)])) (S1 * (MetaSel (Just Symbol "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 Reader Source #

A hledger journal reader is a triple of storage format name, a detector of that format, and a parser from that format to Journal.

Instances

data Account Source #

An account, with name, balances and links to parent/subaccounts which let you walk up or down the account tree.

Constructors

Account 

Fields

Instances

Data Account Source # 

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 #

Generic Account Source # 

Associated Types

type Rep Account :: * -> * #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

type Rep Account Source # 

data NormalBalance Source #

Whether an account's balance is normally a positive number (in accounting terms, normally a debit balance), as for asset and expense accounts, or a negative number (in accounting terms, normally a credit balance), as for liability, equity and income accounts. Cf https://en.wikipedia.org/wiki/Normal_balance .

Constructors

NormalPositive

normally debit - assets, expenses...

NormalNegative

normally credit - liabilities, equity, income...

Instances

Eq NormalBalance Source # 
Data NormalBalance Source # 

Methods

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

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

toConstr :: NormalBalance -> Constr #

dataTypeOf :: NormalBalance -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NormalBalance Source # 

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 

Orphan instances

Data ClockTime Source # 

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 # 

Associated Types

type Rep ClockTime :: * -> * #

ToMarkup Quantity Source # 
NFData ClockTime Source # 

Methods

rnf :: ClockTime -> () #

Data (DecimalRaw Integer) Source # 

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