hledger-lib-1.20.4: A reusable library providing the core functionality of hledger
Safe HaskellNone
LanguageHaskell2010

Hledger.Data.Transaction

Description

A Transaction represents a movement of some commodity(ies) between two or more accounts. It consists of multiple account Postings which balance to zero, a date, and optional extras like description, cleared status, and tags.

Synopsis

Transaction

transaction :: Day -> [Posting] -> Transaction Source #

Make a simple transaction with the given date and postings.

txnTieKnot :: Transaction -> Transaction Source #

Ensure a transaction's postings refer back to it, so that eg relatedPostings works right.

txnUntieKnot :: Transaction -> Transaction Source #

Ensure a transaction's postings do not refer back to it, so that eg recursiveSize and GHCI's :sprint work right.

operations

showAccountName :: Maybe Int -> PostingType -> AccountName -> String Source #

Show an account name, clipped to the given width if any, and appropriately bracketed/parenthesised for the given posting type.

isTransactionBalanced :: Maybe (Map CommoditySymbol AmountStyle) -> Transaction -> Bool Source #

Legacy form of transactionCheckBalanced.

balanceTransaction Source #

Arguments

:: Maybe (Map CommoditySymbol AmountStyle)

commodity display styles

-> Transaction 
-> Either String Transaction 

Balance this transaction, ensuring that its postings (and its balanced virtual postings) sum to 0, by inferring a missing amount or conversion price(s) if needed. Or if balancing is not possible, because the amounts don't sum to 0 or because there's more than one missing amount, return an error message.

Transactions with balance assignments can have more than one missing amount; to balance those you should use the more powerful journalBalanceTransactions.

The "sum to 0" test is done using commodity display precisions, if provided, so that the result agrees with the numbers users can see.

balanceTransactionHelper Source #

Arguments

:: Maybe (Map CommoditySymbol AmountStyle)

commodity display styles

-> Transaction 
-> Either String (Transaction, [(AccountName, MixedAmount)]) 

Helper used by balanceTransaction and balanceTransactionWithBalanceAssignmentAndCheckAssertionsB; use one of those instead. It also returns a list of accounts and amounts that were inferred.

transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction Source #

Apply a transform function to this transaction's amounts.

transactionApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Transaction -> ValuationType -> Transaction Source #

Apply a specified valuation to this transaction's amounts, using the provided price oracle, commodity styles, reference dates, and whether this is for a multiperiod report or not. See amountApplyValuation.

transactionToCost :: Map CommoditySymbol AmountStyle -> Transaction -> Transaction Source #

Convert this transaction's amounts to cost, and apply the appropriate amount styles.

transactionApplyAliases :: [AccountAlias] -> Transaction -> Either RegexError Transaction Source #

Apply some account aliases to all posting account names in the transaction, as described by accountNameApplyAliases. This can fail due to a bad replacement pattern in a regular expression alias.

date operations

transaction description parts

rendering

showTransaction :: Transaction -> String Source #

Render a journal transaction as text similar to the style of Ledger's print command.

Adapted from Ledger 2.x and 3.x standard format:

yyyy-mm-dd[ *][ CODE] description.........          [  ; comment...............]
    account name 1.....................  ...$amount1[  ; comment...............]
    account name 2.....................  ..$-amount1[  ; comment...............]

pcodewidth    = no limit -- 10          -- mimicking ledger layout.
pdescwidth    = no limit -- 20          -- I don't remember what these mean,
pacctwidth    = 35 minimum, no maximum  -- they were important at the time.
pamtwidth     = 11
pcommentwidth = no limit -- 22

The output will be parseable journal syntax. To facilitate this, postings with explicit multi-commodity amounts are displayed as multiple similar postings, one per commodity. (Normally does not happen with this function).

showTransactionOneLineAmounts :: Transaction -> String Source #

Like showTransaction, but explicit multi-commodity amounts are shown on one line, comma-separated. In this case the output will not be parseable journal syntax.

showPostingLines :: Posting -> [String] Source #

Render a posting, simply. Used in balance assertion errors. showPostingLine p = lineIndent $ if pstatus p == Cleared then "* " else "" ++ -- XXX show ! showAccountName Nothing (ptype p) (paccount p) ++ " " ++ showMixedAmountOneLine (pamount p) ++ assertion where -- XXX extract, handle == assertion = maybe "" ((" = " ++) . showAmountWithZeroCommodity . baamount) $ pbalanceassertion p

Render a posting, at the appropriate width for aligning with its siblings if any. Used by the rewrite command.

GenericSourcePos

showGenericSourcePos :: GenericSourcePos -> String Source #

Render source position in human-readable form. Keep in sync with Hledger.UI.ErrorScreen.hledgerparseerrorpositionp (temporary). XXX

tests