| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hledger.Data.Posting
Description
A Posting represents a change (by some MixedAmount) of the balance in
some Account.  Each Transaction contains two or more postings which
should add up to 0. Postings reference their parent transaction, so we can
look up the date or description there.
Synopsis
- nullposting :: Posting
- posting :: Posting
- post :: AccountName -> Amount -> Posting
- vpost :: AccountName -> Amount -> Posting
- post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
- vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
- nullsourcepos :: GenericSourcePos
- nullassertion :: BalanceAssertion
- balassert :: Amount -> Maybe BalanceAssertion
- balassertTot :: Amount -> Maybe BalanceAssertion
- balassertParInc :: Amount -> Maybe BalanceAssertion
- balassertTotInc :: Amount -> Maybe BalanceAssertion
- originalPosting :: Posting -> Posting
- postingStatus :: Posting -> Status
- isReal :: Posting -> Bool
- isVirtual :: Posting -> Bool
- isBalancedVirtual :: Posting -> Bool
- isEmptyPosting :: Posting -> Bool
- hasBalanceAssignment :: Posting -> Bool
- hasAmount :: Posting -> Bool
- postingAllTags :: Posting -> [Tag]
- transactionAllTags :: Transaction -> [Tag]
- relatedPostings :: Posting -> [Posting]
- removePrices :: Posting -> Posting
- postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting
- postingDate :: Posting -> Day
- postingDate2 :: Posting -> Day
- isPostingInDateSpan :: DateSpan -> Posting -> Bool
- isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool
- accountNamesFromPostings :: [Posting] -> [AccountName]
- accountNamePostingType :: AccountName -> PostingType
- accountNameWithoutPostingType :: AccountName -> AccountName
- accountNameWithPostingType :: PostingType -> AccountName -> AccountName
- joinAccountNames :: AccountName -> AccountName -> AccountName
- concatAccountNames :: [AccountName] -> AccountName
- accountNameApplyAliases :: [AccountAlias] -> AccountName -> Either RegexError AccountName
- accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> Either RegexError AccountName
- commentJoin :: Text -> Text -> Text
- commentAddTag :: Text -> Tag -> Text
- commentAddTagNextLine :: Text -> Tag -> Text
- sumPostings :: [Posting] -> MixedAmount
- showPosting :: Posting -> String
- showComment :: Text -> String
- postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting
- postingApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Posting -> ValuationType -> Posting
- postingToCost :: Map CommoditySymbol AmountStyle -> Posting -> Posting
- tests_Posting :: TestTree
Posting
vpost :: AccountName -> Amount -> Posting Source #
Make a virtual (unbalanced) posting to an account.
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting Source #
Make a posting to an account, maybe with a balance assertion.
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting Source #
Make a virtual (unbalanced) posting to an account, maybe with a balance assertion.
balassertTot :: Amount -> Maybe BalanceAssertion Source #
Make a total, exclusive balance assertion.
balassertParInc :: Amount -> Maybe BalanceAssertion Source #
Make a partial, inclusive balance assertion.
balassertTotInc :: Amount -> Maybe BalanceAssertion Source #
Make a total, inclusive balance assertion.
operations
originalPosting :: Posting -> Posting Source #
postingStatus :: Posting -> Status Source #
Get a posting's status. This is cleared or pending if those are explicitly set on the posting, otherwise the status of its parent transaction, or unmarked if there is no parent transaction. (Note the ambiguity, unmarked can mean "posting and transaction are both unmarked" or "posting is unmarked and don't know about the transaction".
isBalancedVirtual :: Posting -> Bool Source #
isEmptyPosting :: Posting -> Bool Source #
hasBalanceAssignment :: Posting -> Bool Source #
postingAllTags :: Posting -> [Tag] Source #
Tags for this posting including any inherited from its parent transaction.
transactionAllTags :: Transaction -> [Tag] Source #
Tags for this transaction including any from its postings.
relatedPostings :: Posting -> [Posting] Source #
removePrices :: Posting -> Posting Source #
Remove all prices of a posting
postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting Source #
Apply some account aliases to the posting's account name, as described by accountNameApplyAliases. This can fail due to a bad replacement pattern in a regular expression alias.
date operations
postingDate :: Posting -> Day Source #
Get a posting's (primary) date - it's own primary date if specified, otherwise the parent transaction's primary date, or the null date if there is no parent transaction.
postingDate2 :: Posting -> Day Source #
Get a posting's secondary (secondary) date, which is the first of: posting's secondary date, transaction's secondary date, posting's primary date, transaction's primary date, or the null date if there is no parent transaction.
isPostingInDateSpan :: DateSpan -> Posting -> Bool Source #
Does this posting fall within the given date span ?
account name operations
accountNamesFromPostings :: [Posting] -> [AccountName] Source #
Sorted unique account names referenced by these postings.
joinAccountNames :: AccountName -> AccountName -> AccountName Source #
Prefix one account name to another, preserving posting type indicators like concatAccountNames.
concatAccountNames :: [AccountName] -> AccountName Source #
Join account names into one. If any of them has () or [] posting type indicators, these (the first type encountered) will also be applied to the resulting account name.
accountNameApplyAliases :: [AccountAlias] -> AccountName -> Either RegexError AccountName Source #
Rewrite an account name using all matching aliases from the given list, in sequence. Each alias sees the result of applying the previous aliases. Or, return any error arising from a bad regular expression in the aliases.
accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> Either RegexError AccountName Source #
Memoising version of accountNameApplyAliases, maybe overkill.
comment/tag operations
commentJoin :: Text -> Text -> Text Source #
Join two parts of a comment, eg a tag and another tag, or a tag and a non-tag, on a single line. Interpolates a comma and space unless one of the parts is empty.
commentAddTag :: Text -> Tag -> Text Source #
Add a tag to a comment, comma-separated from any prior content. A space is inserted following the colon, before the value.
commentAddTagNextLine :: Text -> Tag -> Text Source #
Add a tag on its own line to a comment, preserving any prior content. A space is inserted following the colon, before the value.
arithmetic
sumPostings :: [Posting] -> MixedAmount Source #
rendering
showPosting :: Posting -> String Source #
misc.
showComment :: Text -> String Source #
postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting Source #
Apply a transform function to this posting's amount.
postingApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Posting -> ValuationType -> Posting Source #
Apply a specified valuation to this posting's amount, using the provided price oracle, commodity styles, reference dates, and whether this is for a multiperiod report or not. See amountApplyValuation.
postingToCost :: Map CommoditySymbol AmountStyle -> Posting -> Posting Source #
Convert this posting's amount to cost, and apply the appropriate amount styles.