Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type SmartDate = (String, String, String)
- data WhichDate
- data DateSpan = DateSpan (Maybe Day) (Maybe Day)
- type Year = Integer
- type Month = Int
- type Quarter = Int
- type YearWeek = Int
- type MonthWeek = Int
- type YearDay = Int
- type MonthDay = Int
- type WeekDay = Int
- data Period
- data Interval
- type AccountName = Text
- data AccountType
- data AccountAlias
- data Side
- type Quantity = Decimal
- data Price
- data AmountStyle = AmountStyle {}
- data DigitGroupStyle = DigitGroups Char [Int]
- type CommoditySymbol = Text
- data Commodity = Commodity {}
- data Amount = Amount {}
- newtype MixedAmount = Mixed [Amount]
- data PostingType
- type TagName = Text
- type TagValue = Text
- type Tag = (TagName, TagValue)
- type DateTag = (TagName, Day)
- data Status
- data BalanceAssertion = BalanceAssertion {}
- data Posting = Posting {
- pdate :: Maybe Day
- pdate2 :: Maybe Day
- pstatus :: Status
- paccount :: AccountName
- pamount :: MixedAmount
- pcomment :: Text
- ptype :: PostingType
- ptags :: [Tag]
- pbalanceassertion :: Maybe BalanceAssertion
- ptransaction :: Maybe Transaction
- porigin :: Maybe Posting
- data GenericSourcePos
- data Transaction = Transaction {}
- data TransactionModifier = TransactionModifier {}
- nulltransactionmodifier :: TransactionModifier
- type TMPostingRule = Posting
- data PeriodicTransaction = PeriodicTransaction {
- ptperiodexpr :: Text
- ptinterval :: Interval
- ptspan :: DateSpan
- ptstatus :: Status
- ptcode :: Text
- ptdescription :: Text
- ptcomment :: Text
- pttags :: [Tag]
- ptpostings :: [Posting]
- nullperiodictransaction :: PeriodicTransaction
- data TimeclockCode
- = SetBalance
- | SetRequiredHours
- | In
- | Out
- | FinalOut
- data TimeclockEntry = TimeclockEntry {}
- data MarketPrice = MarketPrice {}
- data Journal = Journal {
- jparsedefaultyear :: Maybe Year
- jparsedefaultcommodity :: Maybe (CommoditySymbol, AmountStyle)
- jparseparentaccounts :: [AccountName]
- jparsealiases :: [AccountAlias]
- jparsetimeclockentries :: [TimeclockEntry]
- jincludefilestack :: [FilePath]
- jdeclaredaccounts :: [AccountName]
- jdeclaredaccounttypes :: Map AccountType [AccountName]
- jcommodities :: Map CommoditySymbol Commodity
- jinferredcommodities :: Map CommoditySymbol AmountStyle
- jmarketprices :: [MarketPrice]
- jtxnmodifiers :: [TransactionModifier]
- jperiodictxns :: [PeriodicTransaction]
- jtxns :: [Transaction]
- jfinalcommentlines :: Text
- jfiles :: [(FilePath, Text)]
- jlastreadtime :: ClockTime
- type ParsedJournal = Journal
- type StorageFormat = String
- data Account = Account {
- aname :: AccountName
- adeclarationorder :: Maybe Int
- aebalance :: MixedAmount
- asubs :: [Account]
- anumpostings :: Int
- aibalance :: MixedAmount
- aparent :: Maybe Account
- aboring :: Bool
- data NormalSign
- data Ledger = Ledger {}
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.
Constructors
PrimaryDate | |
SecondaryDate |
Instances
Eq DateSpan Source # | |
Data DateSpan Source # | |
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 # | |
Defined in Hledger.Data.Types | |
Show DateSpan Source # | |
Generic DateSpan Source # | |
Default DateSpan Source # | |
Defined in Hledger.Data.Types | |
NFData DateSpan Source # | |
Defined in Hledger.Data.Types | |
type Rep DateSpan Source # | |
Defined in Hledger.Data.Types type Rep DateSpan = D1 (MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.12-C1edeYzPhe89lFaDGGE6bC" 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)))) |
Constructors
DayPeriod Day | |
WeekPeriod Day | |
MonthPeriod Year Month | |
QuarterPeriod Year Quarter | |
YearPeriod Year | |
PeriodBetween Day Day | |
PeriodFrom Day | |
PeriodTo Day | |
PeriodAll |
Instances
Constructors
NoInterval | |
Days Int | |
Weeks Int | |
Months Int | |
Quarters Int | |
Years Int | |
DayOfMonth Int | |
WeekdayOfMonth Int Int | |
DayOfWeek Int | |
DayOfYear Int Int |
Instances
type AccountName = Text Source #
data AccountType Source #
Instances
data AccountAlias Source #
Constructors
BasicAlias AccountName AccountName | |
RegexAlias Regexp Replacement |
Instances
Instances
Eq Side Source # | |
Data Side Source # | |
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 # 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 # | |
Read Side Source # | |
Show Side Source # | |
Generic Side Source # | |
NFData Side Source # | |
Defined in Hledger.Data.Types | |
type Rep Side Source # | |
An amount's price (none, per unit, or total) in another commodity. The price amount should always be positive.
Constructors
NoPrice | |
UnitPrice Amount | |
TotalPrice Amount |
Instances
Eq Price Source # | |
Data Price Source # | |
Defined in Hledger.Data.Types 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 # 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 # | |
Show Price Source # | |
Generic Price Source # | |
NFData Price Source # | |
Defined in Hledger.Data.Types | |
type Rep Price Source # | |
Defined in Hledger.Data.Types type Rep Price = D1 (MetaData "Price" "Hledger.Data.Types" "hledger-lib-1.12-C1edeYzPhe89lFaDGGE6bC" False) (C1 (MetaCons "NoPrice" PrefixI False) (U1 :: Type -> Type) :+: (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
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
type CommoditySymbol = Text Source #
Constructors
Commodity | |
Fields |
Instances
Eq Commodity Source # | |
Data Commodity Source # | |
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 # | |
Generic Commodity Source # | |
NFData Commodity Source # | |
Defined in Hledger.Data.Types | |
type Rep Commodity Source # | |
Defined in Hledger.Data.Types type Rep Commodity = D1 (MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.12-C1edeYzPhe89lFaDGGE6bC" 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)))) |
Constructors
Amount | |
Fields
|
Instances
Eq Amount Source # | |
Data Amount Source # | |
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 # | |
Ord Amount Source # | |
Show Amount Source # | |
Generic Amount Source # | |
NFData Amount Source # | |
Defined in Hledger.Data.Types | |
type Rep Amount Source # | |
Defined in Hledger.Data.Types type Rep Amount = D1 (MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.12-C1edeYzPhe89lFaDGGE6bC" False) (C1 (MetaCons "Amount" PrefixI True) ((S1 (MetaSel (Just "acommodity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CommoditySymbol) :*: S1 (MetaSel (Just "aquantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quantity)) :*: (S1 (MetaSel (Just "aprice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price) :*: (S1 (MetaSel (Just "astyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AmountStyle) :*: S1 (MetaSel (Just "amultiplier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) |
newtype MixedAmount Source #
Instances
data PostingType Source #
Constructors
RegularPosting | |
VirtualPosting | |
BalancedVirtualPosting |
Instances
Eq PostingType Source # | |
Defined in Hledger.Data.Types | |
Data PostingType Source # | |
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 # | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PostingType -> ShowS # show :: PostingType -> String # showList :: [PostingType] -> ShowS # | |
Generic PostingType Source # | |
Defined in Hledger.Data.Types Associated Types type Rep PostingType :: Type -> Type # | |
NFData PostingType Source # | |
Defined in Hledger.Data.Types Methods rnf :: PostingType -> () # | |
type Rep PostingType Source # | |
Defined in Hledger.Data.Types type Rep PostingType = D1 (MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.12-C1edeYzPhe89lFaDGGE6bC" 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))) |
The status of a transaction or posting, recorded with a status mark (nothing, !, or *). What these mean is ultimately user defined.
Instances
Bounded Status Source # | |
Enum Status Source # | |
Defined in Hledger.Data.Types | |
Eq Status Source # | |
Data Status Source # | |
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 # | |
Show Status Source # | |
Generic Status Source # | |
NFData Status Source # | |
Defined in Hledger.Data.Types | |
type Rep Status Source # | |
Defined in Hledger.Data.Types |
data BalanceAssertion Source #
The amount to compare an account's balance to, to verify that the history leading to a given point is correct or to set the account to a known value.
Constructors
BalanceAssertion | |
Fields
|
Instances
Constructors
Posting | |
Fields
|
Instances
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
data Transaction Source #
Constructors
Transaction | |
Fields
|
Instances
data TransactionModifier Source #
A transaction modifier rule. This has a query which matches postings in the journal, and a list of transformations to apply to those postings or their transactions. Currently there is one kind of transformation: the TMPostingRule, which adds a posting ("auto posting") to the transaction, optionally setting its amount to the matched posting's amount multiplied by a constant.
Constructors
TransactionModifier | |
Fields
|
Instances
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 amultiplier 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
data TimeclockCode Source #
Constructors
SetBalance | |
SetRequiredHours | |
In | |
Out | |
FinalOut |
Instances
data TimeclockEntry Source #
Constructors
TimeclockEntry | |
Fields |
Instances
data MarketPrice Source #
Constructors
MarketPrice | |
Fields
|
Instances
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
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.
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 NormalSign Source #
Whether an account's balance is normally a positive number (in accounting terms, a debit balance) or a negative number (credit balance). Assets and expenses are normally positive (debit), while liabilities, equity and income are normally negative (credit). https://en.wikipedia.org/wiki/Normal_balance
Constructors
NormallyPositive | |
NormallyNegative |
Instances
Eq NormalSign Source # | |
Defined in Hledger.Data.Types | |
Data NormalSign Source # | |
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 # | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> NormalSign -> ShowS # show :: NormalSign -> String # showList :: [NormalSign] -> ShowS # |
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.
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 # | |
ToMarkup Quantity Source # | |
NFData ClockTime Source # | |
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) # |