diff options
author | SimonMichael <> | 2021-03-10 19:12:00 (GMT) |
---|---|---|
committer | hdiff <hdiff@hdiff.luite.com> | 2021-03-10 19:12:00 (GMT) |
commit | 5b34b68fbdf471bc48f0a41b7847032ef09b0fbf (patch) | |
tree | 6ce41aae3c8b76ea68d8ad7677539f696e3cae52 | |
parent | 0912525ccb4b819678b842ffbeaab6af043fef18 (diff) |
50 files changed, 1867 insertions, 11680 deletions
@@ -1,6 +1,97 @@ Internal/api/developer-ish changes in the hledger-lib (and hledger) packages. For user-visible changes, see the hledger package changelog. +# 1.21 2021-03-10 + +- Building Hledger.Data.Journal no longer fails if the monad-extras + package is installed. + +- Many parts of the hledger-lib and hledger APIs have become more + Text-ified, expecting or returning Text instead of String, reducing + hledger's time and resident memory requirements by roughly 10%. + Some functions now use WideBuilder (a text "builder" which keeps track + of width), to concatenate text more efficiently. There are some + helpers for converting to and from WideBuilder (wbUnpack, wbToText..) + showAmountB/showMixedAmountB are new amount-displaying functions + taking an AmountDisplayOpts. These will probably replace the old + show(Mixed)Amount* functions. (#1427, Stephen Morgan) + +- AtThen valuation is now implemented for all report types. + amountApplyValuation now takes the posting date as an argument. + (transaction/posting)ApplyValuation's valuation type and + transaction/posting arguments have been reordered like + amountApplyValuation's. (Stephen Morgan) + +- Amount, AmountPrice, AmountStyle, DigitGroupStyle fields are now + strict. (Stephen Morgan) + +- Amount prices are now stored with their sign, so negative prices can + be represented. (They seem to have always worked, but now the + internal representation is more accurate.) (Stephen Morgan) + +- normaliseMixedAmount now combines Amounts with TotalPrices in the + same commodity. (Stephen Morgan) + +- normaliseMixedAmount now uses a strict Map for combining amounts + internally, closing a big space leak. (Stephen Morgan) + +- (multiply|divide)(Mixed)?Amount now also multiply or divide the + TotalPrice if it is present, and the old + (multiply|divide)(Mixed)?AmountAndPrice functions are removed. (Stephen Morgan) + +- (amount|mixedAmount)(Looks|Is)Zero functions now check whether both + the quantity and the cost are zero. This is usually what you want, + but if you do only want to check whether the quantity is zero, you + can run mixedAmountStripPrices (or similar) before this. (Stephen Morgan) + +- commodityStylesFromAmounts now consumes the list immediately, + reducing the maximum heap size per thread from ~850K to ~430K in a + real-world register report. (Stephen Morgan) + +- *ApplyValuation functions take two less arguments, and + *ApplyCostValuation functions have been added, performing both + costing and valuation. (Stephen Morgan) + +- traceAtWith now has a level argument and works properly. + +- API changes include: + ``` + Hledger.Data.Amount: + setAmountPrecision -> amountSetPrecision + setFullPrecision -> amountSetFullPrecision + setMixedAmountPrecision -> mixedAmountSetPrecision + showMixed -> showMixedAmountB + showMixedLines -> showMixedAmountLinesB + -mixedAmountSetFullPrecision + + Hledger.Data.Journal: + mapJournalTransactions -> journalMapTransactions + mapJournalPostings -> journalMapPostings + -mapTransactionPostings + +journalPayeesUsed + +journalPayeesDeclaredOrUsed + + Hledger.Data.Transaction: + +transactionFile + +transactionMapPostings + + Hledger.Data.Valuation: + -valuationTypeIsCost + -valuationTypeIsDefaultValue + -ValuationType's AtDefault constructor + + Hledger.Query: + +matchesDescription + +matchesPayeeWIP + + Hledger.Utils.Text: + +textConcatBottomPadded + +wbToText + +wbUnpack + + Text.Tabular.AsciiWide: + alignCell -> textCell + ``` # 1.20.4 2021-01-29 - See hledger. diff --git a/Hledger/Data/Account.hs b/Hledger/Data/Account.hs index 43a29bd..97dd736 100644 --- a/Hledger/Data/Account.hs +++ b/Hledger/Data/Account.hs @@ -30,8 +30,8 @@ instance Show Account where aname (if aboring then "y" else "n" :: String) anumpostings - (showMixedAmount aebalance) - (showMixedAmount aibalance) + (wbUnpack $ showMixedAmountB noColour aebalance) + (wbUnpack $ showMixedAmountB noColour aibalance) instance Eq Account where (==) a b = aname a == aname b -- quick equality test for speed @@ -265,6 +265,6 @@ showAccountsBoringFlag = unlines . map (show . aboring) . flattenAccounts showAccountDebug a = printf "%-25s %4s %4s %s" (aname a) - (showMixedAmount $ aebalance a) - (showMixedAmount $ aibalance a) + (wbUnpack . showMixedAmountB noColour $ aebalance a) + (wbUnpack . showMixedAmountB noColour $ aibalance a) (if aboring a then "b" else " " :: String) diff --git a/Hledger/Data/AccountName.hs b/Hledger/Data/AccountName.hs index b666189..32003f5 100644 --- a/Hledger/Data/AccountName.hs +++ b/Hledger/Data/AccountName.hs @@ -208,31 +208,31 @@ clipOrEllipsifyAccountName (Just 0) = const "..." clipOrEllipsifyAccountName n = clipAccountName n -- | Escape an AccountName for use within a regular expression. --- >>> putStr $ escapeName "First?!#$*?$(*) !@^#*? %)*!@#" +-- >>> putStr . T.unpack $ escapeName "First?!#$*?$(*) !@^#*? %)*!@#" -- First\?!#\$\*\?\$\(\*\) !@\^#\*\? %\)\*!@# -escapeName :: AccountName -> String -escapeName = T.unpack . T.concatMap escapeChar +escapeName :: AccountName -> Text +escapeName = T.concatMap escapeChar where escapeChar c = if c `elem` escapedChars then T.snoc "\\" c else T.singleton c escapedChars = ['[', '?', '+', '|', '(', ')', '*', '$', '^', '\\'] -- | Convert an account name to a regular expression matching it and its subaccounts. accountNameToAccountRegex :: AccountName -> Regexp -accountNameToAccountRegex a = toRegex' $ '^' : escapeName a ++ "(:|$)" -- PARTIAL: Is this safe after escapeName? +accountNameToAccountRegex a = toRegex' $ "^" <> escapeName a <> "(:|$)" -- PARTIAL: Is this safe after escapeName? -- | Convert an account name to a regular expression matching it and its subaccounts, -- case insensitively. accountNameToAccountRegexCI :: AccountName -> Regexp -accountNameToAccountRegexCI a = toRegexCI' $ '^' : escapeName a ++ "(:|$)" -- PARTIAL: Is this safe after escapeName? +accountNameToAccountRegexCI a = toRegexCI' $ "^" <> escapeName a <> "(:|$)" -- PARTIAL: Is this safe after escapeName? -- | Convert an account name to a regular expression matching it but not its subaccounts. accountNameToAccountOnlyRegex :: AccountName -> Regexp -accountNameToAccountOnlyRegex a = toRegex' $ '^' : escapeName a ++ "$" -- PARTIAL: Is this safe after escapeName? +accountNameToAccountOnlyRegex a = toRegex' $ "^" <> escapeName a <> "$" -- PARTIAL: Is this safe after escapeName? -- | Convert an account name to a regular expression matching it but not its subaccounts, -- case insensitively. accountNameToAccountOnlyRegexCI :: AccountName -> Regexp -accountNameToAccountOnlyRegexCI a = toRegexCI' $ '^' : escapeName a ++ "$" -- PARTIAL: Is this safe after escapeName? +accountNameToAccountOnlyRegexCI a = toRegexCI' $ "^" <> escapeName a <> "$" -- PARTIAL: Is this safe after escapeName? -- -- | Does this string look like an exact account-matching regular expression ? --isAccountRegex :: String -> Bool diff --git a/Hledger/Data/Amount.hs b/Hledger/Data/Amount.hs index e77cb55..b62f2c6 100644 --- a/Hledger/Data/Amount.hs +++ b/Hledger/Data/Amount.hs @@ -40,7 +40,11 @@ exchange rates. -} -{-# LANGUAGE StandaloneDeriving, RecordWildCards, OverloadedStrings #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE StandaloneDeriving #-} module Hledger.Data.Amount ( -- * Amount @@ -62,22 +66,25 @@ module Hledger.Data.Amount ( amountLooksZero, divideAmount, multiplyAmount, - divideAmountAndPrice, - multiplyAmountAndPrice, amountTotalPriceToUnitPrice, -- ** rendering + AmountDisplayOpts(..), + noColour, + noPrice, + oneLine, amountstyle, styleAmount, styleAmountExceptPrecision, amountUnstyled, + showAmountB, showAmount, cshowAmount, showAmountWithZeroCommodity, showAmountDebug, showAmountWithoutPrice, - setAmountPrecision, + amountSetPrecision, withPrecision, - setFullPrecision, + amountSetFullPrecision, setAmountInternalPrecision, withInternalPrecision, setAmountDecimalPoint, @@ -99,8 +106,6 @@ module Hledger.Data.Amount ( mixedAmountCost, divideMixedAmount, multiplyMixedAmount, - divideMixedAmountAndPrice, - multiplyMixedAmountAndPrice, averageMixedAmounts, isNegativeAmount, isNegativeMixedAmount, @@ -117,12 +122,12 @@ module Hledger.Data.Amount ( showMixedAmountOneLineWithoutPrice, showMixedAmountElided, showMixedAmountWithZeroCommodity, - showMixedAmountWithPrecision, - showMixed, - showMixedUnnormalised, - showMixedOneLine, - showMixedOneLineUnnormalised, - setMixedAmountPrecision, + showMixedAmountB, + showMixedAmountLinesB, + wbToText, + wbUnpack, + mixedAmountSetPrecision, + mixedAmountSetFullPrecision, canonicaliseMixedAmount, -- * misc. ltraceamount, @@ -130,17 +135,20 @@ module Hledger.Data.Amount ( ) where import Control.Monad (foldM) -import Data.Char (isDigit) -import Data.Decimal (decimalPlaces, normalizeDecimal, roundTo) -import Data.Function (on) -import Data.List (genericSplitAt, groupBy, intercalate, mapAccumL, - partition, sortBy) -import qualified Data.Map as M -import Data.Map (findWithDefault) +import Data.Decimal (DecimalRaw(..), decimalPlaces, normalizeDecimal, roundTo) +import Data.Default (Default(..)) +import Data.Foldable (toList) +import Data.List (intercalate, intersperse, mapAccumL, partition) +import Data.List.NonEmpty (NonEmpty(..), nonEmpty) +import qualified Data.Map.Strict as M import Data.Maybe (fromMaybe) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif import qualified Data.Text as T +import qualified Data.Text.Lazy.Builder as TB import Data.Word (Word8) -import Safe (lastDef, lastMay) +import Safe (headDef, lastDef, lastMay) import Text.Printf (printf) import Hledger.Data.Types @@ -150,13 +158,45 @@ import Hledger.Utils deriving instance Show MarketPrice +-- | Options for the display of Amount and MixedAmount. +data AmountDisplayOpts = AmountDisplayOpts + { displayPrice :: Bool -- ^ Whether to display the Price of an Amount. + , displayZeroCommodity :: Bool -- ^ If the Amount rounds to 0, whether to display its commodity string. + , displayColour :: Bool -- ^ Whether to colourise negative Amounts. + , displayNormalised :: Bool -- ^ Whether to normalise MixedAmounts before displaying. + , displayOneLine :: Bool -- ^ Whether to display on one line. + , displayMinWidth :: Maybe Int -- ^ Minimum width to pad to + , displayMaxWidth :: Maybe Int -- ^ Maximum width to clip to + } deriving (Show) + +-- | Display Amount and MixedAmount with no colour. +instance Default AmountDisplayOpts where def = noColour + +-- | Display Amount and MixedAmount with no colour. +noColour :: AmountDisplayOpts +noColour = AmountDisplayOpts { displayPrice = True + , displayColour = False + , displayZeroCommodity = False + , displayNormalised = True + , displayOneLine = False + , displayMinWidth = Nothing + , displayMaxWidth = Nothing + } + +-- | Display Amount and MixedAmount with no prices. +noPrice :: AmountDisplayOpts +noPrice = def{displayPrice=False} + +-- | Display Amount and MixedAmount on one line with no prices. +oneLine :: AmountDisplayOpts +oneLine = def{displayOneLine=True, displayPrice=False} + ------------------------------------------------------------------------------- -- Amount styles -- | Default amount style amountstyle = AmountStyle L False (Precision 0) (Just '.') Nothing - ------------------------------------------------------------------------------- -- Amount @@ -164,7 +204,7 @@ instance Num Amount where abs a@Amount{aquantity=q} = a{aquantity=abs q} signum a@Amount{aquantity=q} = a{aquantity=signum q} fromInteger i = nullamt{aquantity=fromInteger i} - negate a@Amount{aquantity=q} = a{aquantity= -q} + negate a = transformAmount negate a (+) = similarAmountsOp (+) (-) = similarAmountsOp (-) (*) = similarAmountsOp (*) @@ -197,8 +237,8 @@ amt @@ priceamt = amt{aprice=Just $ TotalPrice priceamt} -- Prices are ignored and discarded. -- Remember: the caller is responsible for ensuring both amounts have the same commodity. similarAmountsOp :: (Quantity -> Quantity -> Quantity) -> Amount -> Amount -> Amount -similarAmountsOp op Amount{acommodity=_, aquantity=q1, astyle=AmountStyle{asprecision=p1}} - Amount{acommodity=c2, aquantity=q2, astyle=s2@AmountStyle{asprecision=p2}} = +similarAmountsOp op !Amount{acommodity=_, aquantity=q1, astyle=AmountStyle{asprecision=p1}} + !Amount{acommodity=c2, aquantity=q2, astyle=s2@AmountStyle{asprecision=p2}} = -- trace ("a1:"++showAmountDebug a1) $ trace ("a2:"++showAmountDebug a2) $ traceWith (("= :"++).showAmountDebug) amount{acommodity=c2, aquantity=q1 `op` q2, astyle=s2{asprecision=max p1 p2}} -- c1==c2 || q1==0 || q2==0 = @@ -215,14 +255,14 @@ amountWithCommodity c a = a{acommodity=c, aprice=Nothing} -- - price amounts must be MixedAmounts with exactly one component Amount -- (or there will be a runtime error XXX) -- --- - price amounts should be positive +-- - price amounts should be positive in the Journal -- (though this is currently not enforced) amountCost :: Amount -> Amount amountCost a@Amount{aquantity=q, aprice=mp} = case mp of Nothing -> a Just (UnitPrice p@Amount{aquantity=pq}) -> p{aquantity=pq * q} - Just (TotalPrice p@Amount{aquantity=pq}) -> p{aquantity=pq * signum q} + Just (TotalPrice p@Amount{aquantity=pq}) -> p{aquantity=pq} -- | Replace an amount's TotalPrice, if it has one, with an equivalent UnitPrice. -- Has no effect on amounts without one. @@ -240,29 +280,20 @@ amountTotalPriceToUnitPrice Precision p -> Precision $ if p == maxBound then maxBound else p + 1 amountTotalPriceToUnitPrice a = a --- | Divide an amount's quantity by a constant. -divideAmount :: Quantity -> Amount -> Amount -divideAmount n a@Amount{aquantity=q} = a{aquantity=q/n} - --- | Multiply an amount's quantity by a constant. -multiplyAmount :: Quantity -> Amount -> Amount -multiplyAmount n a@Amount{aquantity=q} = a{aquantity=q*n} +-- | Apply a function to an amount's quantity (and its total price, if it has one). +transformAmount :: (Quantity -> Quantity) -> Amount -> Amount +transformAmount f a@Amount{aquantity=q,aprice=p} = a{aquantity=f q, aprice=f' <$> p} + where + f' (TotalPrice a@Amount{aquantity=pq}) = TotalPrice a{aquantity = f pq} + f' p = p -- | Divide an amount's quantity (and its total price, if it has one) by a constant. --- The total price will be kept positive regardless of the multiplier's sign. -divideAmountAndPrice :: Quantity -> Amount -> Amount -divideAmountAndPrice n a@Amount{aquantity=q,aprice=p} = a{aquantity=q/n, aprice=f <$> p} - where - f (TotalPrice a) = TotalPrice $ abs $ n `divideAmount` a - f p = p +divideAmount :: Quantity -> Amount -> Amount +divideAmount n = transformAmount (/n) -- | Multiply an amount's quantity (and its total price, if it has one) by a constant. --- The total price will be kept positive regardless of the multiplier's sign. -multiplyAmountAndPrice :: Quantity -> Amount -> Amount -multiplyAmountAndPrice n a@Amount{aquantity=q,aprice=p} = a{aquantity=q*n, aprice=f <$> p} - where - f (TotalPrice a) = TotalPrice $ abs $ n `multiplyAmount` a - f p = p +multiplyAmount :: Quantity -> Amount -> Amount +multiplyAmount n = transformAmount (*n) -- | Is this amount negative ? The price is ignored. isNegativeAmount :: Amount -> Bool @@ -275,28 +306,34 @@ amountRoundedQuantity Amount{aquantity=q, astyle=AmountStyle{asprecision=p}} = c NaturalPrecision -> q Precision p' -> roundTo p' q --- | Does mixed amount appear to be zero when rendered with its +-- | Apply a test to both an Amount and its total price, if it has one. +testAmountAndTotalPrice :: (Amount -> Bool) -> Amount -> Bool +testAmountAndTotalPrice f amt = case aprice amt of + Just (TotalPrice price) -> f amt && f price + _ -> f amt + +-- | Do this Amount and (and its total price, if it has one) appear to be zero when rendered with its -- display precision ? amountLooksZero :: Amount -> Bool -amountLooksZero = (0==) . amountRoundedQuantity +amountLooksZero = testAmountAndTotalPrice ((0==) . amountRoundedQuantity) --- | Is this amount exactly zero, ignoring its display precision ? +-- | Is this Amount (and its total price, if it has one) exactly zero, ignoring its display precision ? amountIsZero :: Amount -> Bool -amountIsZero Amount{aquantity=q} = q == 0 +amountIsZero = testAmountAndTotalPrice ((0==) . aquantity) -- | Set an amount's display precision, flipped. withPrecision :: Amount -> AmountPrecision -> Amount -withPrecision = flip setAmountPrecision +withPrecision = flip amountSetPrecision -- | Set an amount's display precision. -setAmountPrecision :: AmountPrecision -> Amount -> Amount -setAmountPrecision p a@Amount{astyle=s} = a{astyle=s{asprecision=p}} +amountSetPrecision :: AmountPrecision -> Amount -> Amount +amountSetPrecision p a@Amount{astyle=s} = a{astyle=s{asprecision=p}} -- | Increase an amount's display precision, if needed, to enough decimal places -- to show it exactly (showing all significant decimal digits, excluding trailing -- zeros). -setFullPrecision :: Amount -> Amount -setFullPrecision a = setAmountPrecision p a +amountSetFullPrecision :: Amount -> Amount +amountSetFullPrecision a = amountSetPrecision p a where p = max displayprecision naturalprecision displayprecision = asprecision $ astyle a @@ -327,10 +364,12 @@ setAmountDecimalPoint mc a@Amount{ astyle=s } = a{ astyle=s{asdecimalpoint=mc} } withDecimalPoint :: Amount -> Maybe Char -> Amount withDecimalPoint = flip setAmountDecimalPoint -showAmountPrice :: Maybe AmountPrice -> String -showAmountPrice Nothing = "" -showAmountPrice (Just (UnitPrice pa)) = " @ " ++ showAmount pa -showAmountPrice (Just (TotalPrice pa)) = " @@ " ++ showAmount pa +showAmountPrice :: Amount -> WideBuilder +showAmountPrice amt = case aprice amt of + Nothing -> mempty + Just (UnitPrice pa) -> WideBuilder (TB.fromString " @ ") 3 <> showAmountB noColour pa + Just (TotalPrice pa) -> WideBuilder (TB.fromString " @@ ") 4 <> showAmountB noColour (sign pa) + where sign = if aquantity amt < 0 then negate else id showAmountPriceDebug :: Maybe AmountPrice -> String showAmountPriceDebug Nothing = "" @@ -361,40 +400,49 @@ amountUnstyled a = a{astyle=amountstyle} -- commodity's display settings. String representations equivalent to -- zero are converted to just \"0\". The special "missing" amount is -- displayed as the empty string. +-- +-- > showAmount = wbUnpack . showAmountB noColour showAmount :: Amount -> String -showAmount = showAmountHelper False +showAmount = wbUnpack . showAmountB noColour + +-- | General function to generate a WideBuilder for an Amount, according the +-- supplied AmountDisplayOpts. The special "missing" amount is displayed as +-- the empty string. This is the main function to use for showing +-- Amounts, constructing a builder; it can then be converted to a Text with +-- wbToText, or to a String with wbUnpack. +showAmountB :: AmountDisplayOpts -> Amount -> WideBuilder +showAmountB _ Amount{acommodity="AUTO"} = mempty +showAmountB opts a@Amount{astyle=style} = + color $ case ascommodityside style of + L -> c' <> space <> quantity' <> price + R -> quantity' <> space <> c' <> price + where + quantity = showamountquantity a + (quantity',c) | amountLooksZero a && not (displayZeroCommodity opts) = (WideBuilder (TB.singleton '0') 1,"") + | otherwise = (quantity, quoteCommoditySymbolIfNeeded $ acommodity a) + space = if not (T.null c) && ascommodityspaced style then WideBuilder (TB.singleton ' ') 1 else mempty + c' = WideBuilder (TB.fromText c) (textWidth c) + price = if displayPrice opts then showAmountPrice a else mempty + color = if displayColour opts && isNegativeAmount a then colorB Dull Red else id -- | Colour version. For a negative amount, adds ANSI codes to change the colour, -- currently to hard-coded red. +-- +-- > cshowAmount = wbUnpack . showAmountB def{displayColour=True} cshowAmount :: Amount -> String -cshowAmount a = (if isNegativeAmount a then color Dull Red else id) $ - showAmountHelper False a +cshowAmount = wbUnpack . showAmountB def{displayColour=True} -- | Get the string representation of an amount, without any \@ price. +-- +-- > showAmountWithoutPrice = wbUnpack . showAmountB noPrice showAmountWithoutPrice :: Amount -> String -showAmountWithoutPrice a = showAmount a{aprice=Nothing} - --- | Get the string representation of an amount, based on its commodity's --- display settings except using the specified precision. -showAmountWithPrecision :: AmountPrecision -> Amount -> String -showAmountWithPrecision p = showAmount . setAmountPrecision p - -showAmountHelper :: Bool -> Amount -> String -showAmountHelper _ Amount{acommodity="AUTO"} = "" -showAmountHelper showzerocommodity a@Amount{acommodity=c, aprice=mp, astyle=AmountStyle{..}} = - case ascommodityside of - L -> printf "%s%s%s%s" (T.unpack c') space quantity' price - R -> printf "%s%s%s%s" quantity' space (T.unpack c') price - where - quantity = showamountquantity a - (quantity',c') | amountLooksZero a && not showzerocommodity = ("0","") - | otherwise = (quantity, quoteCommoditySymbolIfNeeded c) - space = if not (T.null c') && ascommodityspaced then " " else "" :: String - price = showAmountPrice mp +showAmountWithoutPrice = wbUnpack . showAmountB noPrice -- | Like showAmount, but show a zero amount's commodity if it has one. +-- +-- > showAmountWithZeroCommodity = wbUnpack . showAmountB noColour{displayZeryCommodity=True} showAmountWithZeroCommodity :: Amount -> String -showAmountWithZeroCommodity = showAmountHelper True +showAmountWithZeroCommodity = wbUnpack . showAmountB noColour{displayZeroCommodity=True} -- | Get a string representation of an amount for debugging, -- appropriate to the current debug level. 9 shows maximum detail. @@ -402,42 +450,46 @@ showAmountDebug :: Amount -> String showAmountDebug Amount{acommodity="AUTO"} = "(missing)" showAmountDebug Amount{..} = printf "Amount {acommodity=%s, aquantity=%s, aprice=%s, astyle=%s}" (show acommodity) (show aquantity) (showAmountPriceDebug aprice) (show astyle) --- | Get the string representation of the number part of of an amount, --- using the display settings from its commodity. -showamountquantity :: Amount -> String +-- | Get a Text Builder for the string representation of the number part of of an amount, +-- using the display settings from its commodity. Also returns the width of the +-- number. +showamountquantity :: Amount -> WideBuilder showamountquantity amt@Amount{astyle=AmountStyle{asdecimalpoint=mdec, asdigitgroups=mgrps}} = - punctuatenumber (fromMaybe '.' mdec) mgrps . show $ amountRoundedQuantity amt - --- | Replace a number string's decimal mark with the specified --- character, and add the specified digit group marks. The last digit --- group will be repeated as needed. -punctuatenumber :: Char -> Maybe DigitGroupStyle -> String -> String -punctuatenumber dec mgrps s = sign ++ reverse (applyDigitGroupStyle mgrps (reverse int)) ++ frac'' - where - (sign,num) = break isDigit s - (int,frac) = break (=='.') num - frac' = dropWhile (=='.') frac - frac'' | null frac' = "" - | otherwise = dec:frac' - -applyDigitGroupStyle :: Maybe DigitGroupStyle -> String -> String -applyDigitGroupStyle Nothing s = s -applyDigitGroupStyle (Just (DigitGroups c gs)) s = addseps (repeatLast gs) s + signB <> intB <> fracB where - addseps [] s = s - addseps (g:gs) s - | toInteger (length s) <= toInteger g = s - | otherwise = let (part,rest) = genericSplitAt g s - in part ++ c : addseps gs rest - repeatLast [] = [] - repeatLast gs = init gs ++ repeat (last gs) + Decimal e n = amountRoundedQuantity amt + + strN = T.pack . show $ abs n + len = T.length strN + intLen = max 1 $ len - fromIntegral e + dec = fromMaybe '.' mdec + padded = T.replicate (fromIntegral e + 1 - len) "0" <> strN + (intPart, fracPart) = T.splitAt intLen padded + + intB = applyDigitGroupStyle mgrps intLen $ if e == 0 then strN else intPart + signB = if n < 0 then WideBuilder (TB.singleton '-') 1 else mempty + fracB = if e > 0 then WideBuilder (TB.singleton dec <> TB.fromText fracPart) (fromIntegral e + 1) else mempty + +-- | Split a string representation into chunks according to DigitGroupStyle, +-- returning a Text builder and the number of separators used. +applyDigitGroupStyle :: Maybe DigitGroupStyle -> Int -> T.Text -> WideBuilder +applyDigitGroupStyle Nothing l s = WideBuilder (TB.fromText s) l +applyDigitGroupStyle (Just (DigitGroups _ [])) l s = WideBuilder (TB.fromText s) l +applyDigitGroupStyle (Just (DigitGroups c (g:gs))) l s = addseps (g:|gs) (toInteger l) s + where + addseps (g:|gs) l s + | l' > 0 = addseps gs' l' rest <> WideBuilder (TB.singleton c <> TB.fromText part) (fromIntegral g + 1) + | otherwise = WideBuilder (TB.fromText s) (fromInteger l) + where + (rest, part) = T.splitAt (fromInteger l') s + gs' = fromMaybe (g:|[]) $ nonEmpty gs + l' = l - toInteger g -- like journalCanonicaliseAmounts -- | Canonicalise an amount's display style using the provided commodity style map. canonicaliseAmount :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount canonicaliseAmount styles a@Amount{acommodity=c, astyle=s} = a{astyle=s'} - where - s' = findWithDefault s c styles + where s' = M.findWithDefault s c styles ------------------------------------------------------------------------------- -- MixedAmount @@ -479,24 +531,18 @@ normaliseMixedAmount = normaliseHelper False normaliseHelper :: Bool -> MixedAmount -> MixedAmount normaliseHelper squashprices (Mixed as) - | missingamt `elem` as = missingmixedamt -- missingamt should always be alone, but detect it even if not - | null nonzeros = Mixed [newzero] - | otherwise = Mixed nonzeros + | missingkey `M.member` amtMap = missingmixedamt -- missingamt should always be alone, but detect it even if not + | M.null nonzeros= Mixed [newzero] + | otherwise = Mixed $ toList nonzeros where - newzero = lastDef nullamt $ filter (not . T.null . acommodity) zeros - (zeros, nonzeros) = partition amountIsZero $ - map sumSimilarAmountsUsingFirstPrice $ - groupBy groupfn $ - sortBy sortfn - as - sortfn | squashprices = compare `on` acommodity - | otherwise = compare `on` \a -> (acommodity a, aprice a) - groupfn | squashprices = (==) `on` acommodity - | otherwise = \a1 a2 -> acommodity a1 == acommodity a2 && combinableprices a1 a2 - - combinableprices Amount{aprice=Nothing} Amount{aprice=Nothing} = True - combinableprices Amount{aprice=Just (UnitPrice p1)} Amount{aprice=Just (UnitPrice p2)} = p1 == p2 - combinableprices _ _ = False + newzero = maybe nullamt snd . M.lookupMin $ M.filter (not . T.null . acommodity) zeros + (zeros, nonzeros) = M.partition amountIsZero amtMap + amtMap = foldr (\a -> M.insertWith sumSimilarAmountsUsingFirstPrice (key a) a) mempty as + key Amount{acommodity=c,aprice=p} = (c, if squashprices then Nothing else priceKey <$> p) + where + priceKey (UnitPrice x) = (acommodity x, Just $ aquantity x) + priceKey (TotalPrice x) = (acommodity x, Nothing) + missingkey = key missingamt -- | Like normaliseMixedAmount, but combine each commodity's amounts -- into just one by throwing away all prices except the first. This is @@ -520,9 +566,13 @@ unifyMixedAmount = foldM combine 0 . amounts -- | Sum same-commodity amounts in a lossy way, applying the first -- price to the result and discarding any other prices. Only used as a -- rendering helper. -sumSimilarAmountsUsingFirstPrice :: [Amount] -> Amount -sumSimilarAmountsUsingFirstPrice [] = nullamt -sumSimilarAmountsUsingFirstPrice as = (sumStrict as){aprice=aprice $ head as} +sumSimilarAmountsUsingFirstPrice :: Amount -> Amount -> Amount +sumSimilarAmountsUsingFirstPrice a b = (a + b){aprice=p} + where + p = case (aprice a, aprice b) of + (Just (TotalPrice ap), Just (TotalPrice bp)) + -> Just . TotalPrice $ ap{aquantity = aquantity ap + aquantity bp } + _ -> aprice a -- -- | Sum same-commodity amounts. If there were different prices, set -- -- the price to a special marker indicating "various". Only used as a @@ -557,26 +607,16 @@ mapMixedAmount f (Mixed as) = Mixed $ map f as -- | Convert all component amounts to cost/selling price where -- possible (see amountCost). mixedAmountCost :: MixedAmount -> MixedAmount -mixedAmountCost (Mixed as) = Mixed $ map amountCost as +mixedAmountCost = mapMixedAmount amountCost --- | Divide a mixed amount's quantities by a constant. +-- | Divide a mixed amount's quantities (and total prices, if any) by a constant. divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount divideMixedAmount n = mapMixedAmount (divideAmount n) --- | Multiply a mixed amount's quantities by a constant. +-- | Multiply a mixed amount's quantities (and total prices, if any) by a constant. multiplyMixedAmount :: Quantity -> MixedAmount -> MixedAmount multiplyMixedAmount n = mapMixedAmount (multiplyAmount n) --- | Divide a mixed amount's quantities (and total prices, if any) by a constant. --- The total prices will be kept positive regardless of the multiplier's sign. -divideMixedAmountAndPrice :: Quantity -> MixedAmount -> MixedAmount -divideMixedAmountAndPrice n = mapMixedAmount (divideAmountAndPrice n) - --- | Multiply a mixed amount's quantities (and total prices, if any) by a constant. --- The total prices will be kept positive regardless of the multiplier's sign. -multiplyMixedAmountAndPrice :: Quantity -> MixedAmount -> MixedAmount -multiplyMixedAmountAndPrice n = mapMixedAmount (multiplyAmountAndPrice n) - -- | Calculate the average of some mixed amounts. averageMixedAmounts :: [MixedAmount] -> MixedAmount averageMixedAmounts [] = 0 @@ -593,12 +633,15 @@ isNegativeMixedAmount m = as | not (any isNegativeAmount as) -> Just False _ -> Nothing -- multiple amounts with different signs --- | Does this mixed amount appear to be zero when rendered with its --- display precision ? +-- | Does this mixed amount appear to be zero when rendered with its display precision? +-- i.e. does it have zero quantity with no price, zero quantity with a total price (which is also zero), +-- and zero quantity for each unit price? mixedAmountLooksZero :: MixedAmount -> Bool mixedAmountLooksZero = all amountLooksZero . amounts . normaliseMixedAmountSquashPricesForDisplay --- | Is this mixed amount exactly zero, ignoring display precisions ? +-- | Is this mixed amount exactly to be zero, ignoring its display precision? +-- i.e. does it have zero quantity with no price, zero quantity with a total price (which is also zero), +-- and zero quantity for each unit price? mixedAmountIsZero :: MixedAmount -> Bool mixedAmountIsZero = all amountIsZero . amounts . normaliseMixedAmountSquashPricesForDisplay @@ -613,7 +656,7 @@ mixedAmountIsZero = all amountIsZero . amounts . normaliseMixedAmountSquashPrice -- | Given a map of standard commodity display styles, apply the -- appropriate one to each individual amount. styleMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount -styleMixedAmount styles (Mixed as) = Mixed $ map (styleAmount styles) as +styleMixedAmount styles = mapMixedAmount (styleAmount styles) -- | Reset each individual amount's display style to the default. mixedAmountUnstyled :: MixedAmount -> MixedAmount @@ -622,40 +665,46 @@ mixedAmountUnstyled = mapMixedAmount amountUnstyled -- | Get the string representation of a mixed amount, after -- normalising it to one amount per commodity. Assumes amounts have -- no or similar prices, otherwise this can show misleading prices. +-- +-- > showMixedAmount = wbUnpack . showMixedAmountB noColour showMixedAmount :: MixedAmount -> String -showMixedAmount = fst . showMixed showAmount Nothing Nothing False +showMixedAmount = wbUnpack . showMixedAmountB noColour -- | Get the one-line string representation of a mixed amount. +-- +-- > showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine showMixedAmountOneLine :: MixedAmount -> String -showMixedAmountOneLine = fst . showMixedOneLine showAmountWithoutPrice Nothing Nothing False +showMixedAmountOneLine = wbUnpack . showMixedAmountB oneLine -- | Like showMixedAmount, but zero amounts are shown with their -- commodity if they have one. +-- +-- > showMixedAmountWithZeroCommodity = wbUnpack . showMixedAmountB noColour{displayZeroCommodity=True} showMixedAmountWithZeroCommodity :: MixedAmount -> String -showMixedAmountWithZeroCommodity = fst . showMixed showAmountWithZeroCommodity Nothing Nothing False - --- | Get the string representation of a mixed amount, showing each of its --- component amounts with the specified precision, ignoring their --- commoditys' display precision settings. -showMixedAmountWithPrecision :: AmountPrecision -> MixedAmount -> String -showMixedAmountWithPrecision p = fst . showMixed (showAmountWithPrecision p) Nothing Nothing False +showMixedAmountWithZeroCommodity = wbUnpack . showMixedAmountB noColour{displayZeroCommodity=True} -- | Get the string representation of a mixed amount, without showing any transaction prices. -- With a True argument, adds ANSI codes to show negative amounts in red. +-- +-- > showMixedAmountWithoutPrice c = wbUnpack . showMixedAmountB noPrice{displayColour=c} showMixedAmountWithoutPrice :: Bool -> MixedAmount -> String -showMixedAmountWithoutPrice c = fst . showMixed showAmountWithoutPrice Nothing Nothing c +showMixedAmountWithoutPrice c = wbUnpack . showMixedAmountB noPrice{displayColour=c} -- | Get the one-line string representation of a mixed amount, but without -- any \@ prices. -- With a True argument, adds ANSI codes to show negative amounts in red. +-- +-- > showMixedAmountOneLineWithoutPrice c = wbUnpack . showMixedAmountB oneLine{displayColour=c} showMixedAmountOneLineWithoutPrice :: Bool -> MixedAmount -> String -showMixedAmountOneLineWithoutPrice c = fst . showMixedOneLine showAmountWithoutPrice Nothing Nothing c +showMixedAmountOneLineWithoutPrice c = wbUnpack . showMixedAmountB oneLine{displayColour=c} -- | Like showMixedAmountOneLineWithoutPrice, but show at most the given width, -- with an elision indicator if there are more. -- With a True argument, adds ANSI codes to show negative amounts in red. +-- +-- > showMixedAmountElided w c = wbUnpack . showMixedAmountB oneLine{displayColour=c, displayMaxWidth=Just w} showMixedAmountElided :: Int -> Bool -> MixedAmount -> String -showMixedAmountElided w c = fst . showMixedOneLine showAmountWithoutPrice Nothing (Just w) c +showMixedAmountElided w c = wbUnpack . showMixedAmountB oneLine{displayColour=c, displayMaxWidth=Just w} -- | Get an unambiguous string representation of a mixed amount for debugging. showMixedAmountDebug :: MixedAmount -> String @@ -663,59 +712,66 @@ showMixedAmountDebug m | m == missingmixedamt = "(missing)" | otherwise = printf "Mixed [%s]" as where as = intercalate "\n " $ map showAmountDebug $ amounts m --- | General function to display a MixedAmount, one Amount on each line. --- It takes a function to display each Amount, an optional minimum width --- to pad to, an optional maximum width to display, and a Bool to determine --- whether to colourise negative numbers. Amounts longer than the maximum --- width (if given) will be elided. The function also returns the actual --- width of the output string. -showMixed :: (Amount -> String) -> Maybe Int -> Maybe Int -> Bool -> MixedAmount -> (String, Int) -showMixed showamt mmin mmax c = - showMixedUnnormalised showamt mmin mmax c . normaliseMixedAmountSquashPricesForDisplay - --- | Like showMixed, but does not normalise the MixedAmount before displaying. -showMixedUnnormalised :: (Amount -> String) -> Maybe Int -> Maybe Int -> Bool -> MixedAmount -> (String, Int) -showMixedUnnormalised showamt mmin mmax c (Mixed as) = - (intercalate "\n" $ map finalise elided, width) +-- | General function to generate a WideBuilder for a MixedAmount, according the +-- supplied AmountDisplayOpts. This is the main function to use for showing +-- MixedAmounts, constructing a builder; it can then be converted to a Text with +-- wbToText, or to a String with wbUnpack. +-- +-- If a maximum width is given then: +-- - If displayed on one line, it will display as many Amounts as can +-- fit in the given width, and further Amounts will be elided. +-- - If displayed on multiple lines, any Amounts longer than the +-- maximum width will be elided. +showMixedAmountB :: AmountDisplayOpts -> MixedAmount -> WideBuilder +showMixedAmountB opts ma + | displayOneLine opts = showMixedAmountOneLineB opts ma' + | otherwise = WideBuilder (wbBuilder . mconcat $ intersperse sep lines) width + where + ma' = if displayPrice opts then ma else mixedAmountStripPrices ma + lines = showMixedAmountLinesB opts ma' + width = headDef 0 $ map wbWidth lines + sep = WideBuilder (TB.singleton '\n') 0 + +-- | Helper for showMixedAmountB to show a MixedAmount on multiple lines. This returns +-- the list of WideBuilders: one for each Amount in the MixedAmount (possibly +-- normalised), and padded/elided to the appropriate width. This does not +-- honour displayOneLine: all amounts will be displayed as if displayOneLine +-- were False. +showMixedAmountLinesB :: AmountDisplayOpts -> MixedAmount -> [WideBuilder] +showMixedAmountLinesB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma = + map (adBuilder . pad) elided where - width = maximum $ fromMaybe 0 mmin : map adLength elided - astrs = amtDisplayList sepwidth showamt as - sepwidth = 0 -- "\n" has width 0 + Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma + + astrs = amtDisplayList (wbWidth sep) (showAmountB opts) amts + sep = WideBuilder (TB.singleton '\n') 0 + width = maximum $ fromMaybe 0 mmin : map (wbWidth . adBuilder) elided - finalise = adString . pad . if c then colourise else id - pad amt = amt{ adString = applyN (width - adLength amt) (' ':) $ adString amt - , adLength = width - } + pad amt = amt{ adBuilder = WideBuilder (TB.fromText $ T.replicate w " ") w <> adBuilder amt } + where w = width - wbWidth (adBuilder amt) elided = maybe id elideTo mmax astrs elideTo m xs = maybeAppend elisionStr short where - elisionStr = elisionDisplay (Just m) sepwidth (length long) $ lastDef nullAmountDisplay short - (short, long) = partition ((m>=) . adLength) xs - --- | General function to display a MixedAmount on a single line. It --- takes a function to display each Amount, an optional minimum width to --- pad to, an optional maximum width to display, and a Bool to determine --- whether to colourise negative numbers. It will display as many Amounts --- as it can in the maximum width (if given), and further Amounts will be --- elided. The function also returns the actual width of the output string. -showMixedOneLine :: (Amount -> String) -> Maybe Int -> Maybe Int -> Bool -> MixedAmount -> (String, Int) -showMixedOneLine showamt mmin mmax c = - showMixedOneLineUnnormalised showamt mmin mmax c . normaliseMixedAmountSquashPricesForDisplay - --- | Like showMixedOneLine, but does not normalise the MixedAmount before --- displaying. -showMixedOneLineUnnormalised :: (Amount -> String) -> Maybe Int -> Maybe Int -> Bool -> MixedAmount -> (String, Int) -showMixedOneLineUnnormalised showamt mmin mmax c (Mixed as) = - (pad . intercalate ", " $ map finalise elided, max width $ fromMaybe 0 mmin) + elisionStr = elisionDisplay (Just m) (wbWidth sep) (length long) $ lastDef nullAmountDisplay short + (short, long) = partition ((m>=) . wbWidth . adBuilder) xs + +-- | Helper for showMixedAmountB to deal with single line displays. This does not +-- honour displayOneLine: all amounts will be displayed as if displayOneLine +-- were True. +showMixedAmountOneLineB :: AmountDisplayOpts -> MixedAmount -> WideBuilder +showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWidth=mmin} ma = + WideBuilder (wbBuilder . pad . mconcat . intersperse sep $ map adBuilder elided) . max width $ fromMaybe 0 mmin where - width = maybe 0 adTotal $ lastMay elided - astrs = amtDisplayList sepwidth showamt as - sepwidth = 2 -- ", " has width 2 - n = length as + Mixed amts = if displayNormalised opts then normaliseMixedAmountSquashPricesForDisplay ma else ma - finalise = adString . if c then colourise else id - pad = applyN (fromMaybe 0 mmin - width) (' ':) + width = maybe 0 adTotal $ lastMay elided + astrs = amtDisplayList (wbWidth sep) (showAmountB opts) amts + sep = WideBuilder (TB.fromString ", ") 2 + n = length amts + + pad = (WideBuilder (TB.fromText $ T.replicate w " ") w <>) + where w = fromMaybe 0 mmin - width elided = maybe id elideTo mmax astrs elideTo m = addElide . takeFitting m . withElided @@ -728,39 +784,36 @@ showMixedOneLineUnnormalised showamt mmin mmax c (Mixed as) = dropWhileRev p = foldr (\x xs -> if null xs && p x then [] else x:xs) [] -- Add the elision strings (if any) to each amount - withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing sepwidth num amt)) [n-1,n-2..0] + withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing (wbWidth sep) num amt)) [n-1,n-2..0] data AmountDisplay = AmountDisplay - { adAmount :: !Amount -- ^ Amount displayed - , adString :: !String -- ^ String representation of the Amount - , adLength :: !Int -- ^ Length of the string representation - , adTotal :: !Int -- ^ Cumulative length of MixedAmount this Amount is part of, - -- including separators - } deriving (Show) + { adBuilder :: !WideBuilder -- ^ String representation of the Amount + , adTotal :: !Int -- ^ Cumulative length of MixedAmount this Amount is part of, + -- including separators + } nullAmountDisplay :: AmountDisplay -nullAmountDisplay = AmountDisplay nullamt "" 0 0 +nullAmountDisplay = AmountDisplay mempty 0 -amtDisplayList :: Int -> (Amount -> String) -> [Amount] -> [AmountDisplay] +amtDisplayList :: Int -> (Amount -> WideBuilder) -> [Amount] -> [AmountDisplay] amtDisplayList sep showamt = snd . mapAccumL display (-sep) where - display tot amt = (tot', AmountDisplay amt str width tot') + display tot amt = (tot', AmountDisplay str tot') where str = showamt amt - width = strWidth str - tot' = tot + width + sep + tot' = tot + (wbWidth str) + sep -- The string "m more", added to the previous running total elisionDisplay :: Maybe Int -> Int -> Int -> AmountDisplay -> Maybe AmountDisplay elisionDisplay mmax sep n lastAmt - | n > 0 = Just $ AmountDisplay 0 str len (adTotal lastAmt + len) + | n > 0 = Just $ AmountDisplay (WideBuilder (TB.fromText str) len) (adTotal lastAmt + len) | otherwise = Nothing where - fullString = show n ++ " more.." + fullString = T.pack $ show n ++ " more.." -- sep from the separator, 7 from " more..", 1 + floor (logBase 10 n) from number fullLength = sep + 8 + floor (logBase 10 $ fromIntegral n) - str | Just m <- mmax, fullLength > m = take (m - 2) fullString ++ ".." + str | Just m <- mmax, fullLength > m = T.take (m - 2) fullString <> ".." | otherwise = fullString len = case mmax of Nothing -> fullLength Just m -> max 2 $ min m fullLength @@ -769,30 +822,31 @@ maybeAppend :: Maybe a -> [a] -> [a] maybeAppend Nothing = id maybeAppend (Just a) = (++[a]) -colourise :: AmountDisplay -> AmountDisplay -colourise amt = amt{adString=markColour $ adString amt} - where markColour = if isNegativeAmount (adAmount amt) then color Dull Red else id - -- | Compact labelled trace of a mixed amount, for debugging. ltraceamount :: String -> MixedAmount -> MixedAmount ltraceamount s = traceWith (((s ++ ": ") ++).showMixedAmount) -- | Set the display precision in the amount's commodities. -setMixedAmountPrecision :: AmountPrecision -> MixedAmount -> MixedAmount -setMixedAmountPrecision p (Mixed as) = Mixed $ map (setAmountPrecision p) as +mixedAmountSetPrecision :: AmountPrecision -> MixedAmount -> MixedAmount +mixedAmountSetPrecision p = mapMixedAmount (amountSetPrecision p) + +-- | In each component amount, increase the display precision sufficiently +-- to render it exactly (showing all significant decimal digits). +mixedAmountSetFullPrecision :: MixedAmount -> MixedAmount +mixedAmountSetFullPrecision = mapMixedAmount amountSetFullPrecision mixedAmountStripPrices :: MixedAmount -> MixedAmount -mixedAmountStripPrices (Mixed as) = Mixed $ map (\a -> a{aprice=Nothing}) as +mixedAmountStripPrices = mapMixedAmount (\a -> a{aprice=Nothing}) -- | Canonicalise a mixed amount's display styles using the provided commodity style map. canonicaliseMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount -canonicaliseMixedAmount styles (Mixed as) = Mixed $ map (canonicaliseAmount styles) as +canonicaliseMixedAmount styles = mapMixedAmount (canonicaliseAmount styles) -- | Replace each component amount's TotalPrice, if it has one, with an equivalent UnitPrice. -- Has no effect on amounts without one. -- Does Decimal division, might be some rounding/irrational number issues. mixedAmountTotalPriceToUnitPrice :: MixedAmount -> MixedAmount -mixedAmountTotalPriceToUnitPrice (Mixed as) = Mixed $ map amountTotalPriceToUnitPrice as +mixedAmountTotalPriceToUnitPrice = mapMixedAmount amountTotalPriceToUnitPrice ------------------------------------------------------------------------------- @@ -805,7 +859,7 @@ tests_Amount = tests "Amount" [ amountCost (eur 1) @?= eur 1 amountCost (eur 2){aprice=Just $ UnitPrice $ usd 2} @?= usd 4 amountCost (eur 1){aprice=Just $ TotalPrice $ usd 2} @?= usd 2 - amountCost (eur (-1)){aprice=Just $ TotalPrice $ usd 2} @?= usd (-2) + amountCost (eur (-1)){aprice=Just $ TotalPrice $ usd (-2)} @?= usd (-2) ,test "amountLooksZero" $ do assertBool "" $ amountLooksZero amount @@ -846,9 +900,7 @@ tests_Amount = tests "Amount" [ [usd 1 @@ eur 1 ,usd (-2) @@ eur 1 ]) - @?= Mixed [usd 1 @@ eur 1 - ,usd (-2) @@ eur 1 - ] + @?= Mixed [usd (-1) @@ eur 2 ] ,test "showMixedAmount" $ do showMixedAmount (Mixed [usd 1]) @?= "$1.00" @@ -871,8 +923,8 @@ tests_Amount = tests "Amount" [ normaliseMixedAmount (Mixed [usd 1 `at` eur 1, usd 1 `at` eur 1]) @?= Mixed [usd 2 `at` eur 1] ,test "amounts with different unit prices are not combined" $ normaliseMixedAmount (Mixed [usd 1 `at` eur 1, usd 1 `at` eur 2]) @?= Mixed [usd 1 `at` eur 1, usd 1 `at` eur 2] - ,test "amounts with total prices are not combined" $ - normaliseMixedAmount (Mixed [usd 1 @@ eur 1, usd 1 @@ eur 1]) @?= Mixed [usd 1 @@ eur 1, usd 1 @@ eur 1] + ,test "amounts with total prices are combined" $ + normaliseMixedAmount (Mixed [usd 1 @@ eur 1, usd 1 @@ eur 1]) @?= Mixed [usd 2 @@ eur 2] ] ,test "normaliseMixedAmountSquashPricesForDisplay" $ do diff --git a/Hledger/Data/Dates.hs b/Hledger/Data/Dates.hs index 3ccdeae..c9c0ca4 100644 --- a/Hledger/Data/Dates.hs +++ b/Hledger/Data/Dates.hs @@ -110,19 +110,19 @@ import Hledger.Utils -- Help ppShow parse and line-wrap DateSpans better in debug output. instance Show DateSpan where - show s = "DateSpan " ++ showDateSpan s + show s = "DateSpan " ++ T.unpack (showDateSpan s) -showDate :: Day -> String -showDate = show +showDate :: Day -> Text +showDate = T.pack . show -- | Render a datespan as a display string, abbreviating into a -- compact form if possible. -showDateSpan :: DateSpan -> String +showDateSpan :: DateSpan -> Text showDateSpan = showPeriod . dateSpanAsPeriod -- | Like showDateSpan, but show month spans as just the abbreviated month name -- in the current locale. -showDateSpanMonthAbbrev :: DateSpan -> String +showDateSpanMonthAbbrev :: DateSpan -> Text showDateSpanMonthAbbrev = showPeriodMonthAbbrev . dateSpanAsPeriod -- | Get the current local date. @@ -388,13 +388,13 @@ spanFromSmartDate refdate sdate = DateSpan (Just b) (Just e) -- | Convert a smart date string to an explicit yyyy\/mm\/dd string using -- the provided reference date, or raise an error. -fixSmartDateStr :: Day -> Text -> String +fixSmartDateStr :: Day -> Text -> Text fixSmartDateStr d s = either (error' . printf "could not parse date %s %s" (show s) . show) id $ -- PARTIAL: - (fixSmartDateStrEither d s :: Either (ParseErrorBundle Text CustomErr) String) + (fixSmartDateStrEither d s :: Either (ParseErrorBundle Text CustomErr) Text) -- | A safe version of fixSmartDateStr. -fixSmartDateStrEither :: Day -> Text -> Either (ParseErrorBundle Text CustomErr) String +fixSmartDateStrEither :: Day -> Text -> Either (ParseErrorBundle Text CustomErr) Text fixSmartDateStrEither d = fmap showDate . fixSmartDateStrEither' d fixSmartDateStrEither' diff --git a/Hledger/Data/Journal.hs b/Hledger/Data/Journal.hs index afe9838..537c4c5 100644 --- a/Hledger/Data/Journal.hs +++ b/Hledger/Data/Journal.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE PackageImports #-} {-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} @@ -37,9 +38,9 @@ module Hledger.Data.Journal ( filterTransactionPostings, filterPostingAmount, -- * Mapping - mapJournalTransactions, - mapJournalPostings, - mapTransactionPostings, + journalMapTransactions, + journalMapPostings, + journalMapPostingAmounts, -- * Querying journalAccountNamesUsed, journalAccountNamesImplied, @@ -52,8 +53,12 @@ module Hledger.Data.Journal ( -- overJournalAmounts, -- traverseJournalAmounts, -- journalCanonicalCommodities, + journalPayeesDeclared, + journalPayeesUsed, + journalPayeesDeclaredOrUsed, journalCommoditiesDeclared, journalDateSpan, + journalDateSpanBothDates, journalStartDate, journalEndDate, journalDescriptions, @@ -63,6 +68,7 @@ module Hledger.Data.Journal ( journalNextTransaction, journalPrevTransaction, journalPostings, + journalTransactionsSimilarTo, -- journalPrices, -- * Standard account types journalBalanceSheetAccountQuery, @@ -86,31 +92,33 @@ module Hledger.Data.Journal ( tests_Journal, ) where -import Control.Monad -import Control.Monad.Except -import Control.Monad.Extra + +import Control.Applicative ((<|>)) +import Control.Monad.Except (ExceptT(..), runExceptT, throwError) +import "extra" Control.Monad.Extra (whenM) import Control.Monad.Reader as R -import Control.Monad.ST -import Data.Array.ST +import Control.Monad.ST (ST, runST) +import Data.Array.ST (STArray, getElems, newListArray, writeArray) +import Data.Char (toUpper, isDigit) import Data.Default (Default(..)) import Data.Function ((&)) import qualified Data.HashTable.Class as H (toList) import qualified Data.HashTable.ST.Cuckoo as H -import Data.List -import Data.List.Extra (groupSort, nubSort) -import qualified Data.Map as M -import Data.Maybe +import Data.List (find, foldl', sortOn) +import Data.List.Extra (nubSort) +import qualified Data.Map.Strict as M +import Data.Maybe (catMaybes, fromJust, fromMaybe, isJust, mapMaybe, maybeToList) #if !(MIN_VERSION_base(4,11,0)) import Data.Semigroup (Semigroup(..)) #endif import qualified Data.Set as S import Data.Text (Text) import qualified Data.Text as T -import Safe (headMay, headDef) -import Data.Time.Calendar -import Data.Tree +import Safe (headMay, headDef, maximumMay, minimumMay) +import Data.Time.Calendar (Day, addDays, fromGregorian) +import Data.Tree (Tree, flatten) import System.Time (ClockTime(TOD)) -import Text.Printf +import Text.Printf (printf) import Hledger.Utils import Hledger.Data.Types @@ -121,6 +129,7 @@ import Hledger.Data.Transaction import Hledger.Data.TransactionModifier import Hledger.Data.Posting import Hledger.Query +import Data.List (sortBy) -- try to make Journal ppShow-compatible @@ -183,6 +192,7 @@ instance Semigroup Journal where -- ,jparsetransactioncount = jparsetransactioncount j1 + jparsetransactioncount j2 ,jparsetimeclockentries = jparsetimeclockentries j1 <> jparsetimeclockentries j2 ,jincludefilestack = jincludefilestack j2 + ,jdeclaredpayees = jdeclaredpayees j1 <> jdeclaredpayees j2 ,jdeclaredaccounts = jdeclaredaccounts j1 <> jdeclaredaccounts j2 ,jdeclaredaccounttypes = jdeclaredaccounttypes j1 <> jdeclaredaccounttypes j2 ,jglobalcommoditystyles = jglobalcommoditystyles j1 <> jglobalcommoditystyles j2 @@ -211,6 +221,7 @@ nulljournal = Journal { -- ,jparsetransactioncount = 0 ,jparsetimeclockentries = [] ,jincludefilestack = [] + ,jdeclaredpayees = [] ,jdeclaredaccounts = [] ,jdeclaredaccounttypes = M.empty ,jglobalcommoditystyles = M.empty @@ -261,10 +272,6 @@ journalNextTransaction j t = journalTransactionAt j (tindex t + 1) journalPrevTransaction :: Journal -> Transaction -> Maybe Transaction journalPrevTransaction j t = journalTransactionAt j (tindex t - 1) --- | Unique transaction descriptions used in this journal. -journalDescriptions :: Journal -> [Text] -journalDescriptions = nubSort . map tdescription . jtxns - -- | All postings from this journal's transactions, in order. journalPostings :: Journal -> [Posting] journalPostings = concatMap tpostings . jtxns @@ -273,6 +280,22 @@ journalPostings = concatMap tpostings . jtxns journalCommoditiesDeclared :: Journal -> [AccountName] journalCommoditiesDeclared = nubSort . M.keys . jcommodities +-- | Unique transaction descriptions used in this journal. +journalDescriptions :: Journal -> [Text] +journalDescriptions = nubSort . map tdescription . jtxns + +-- | Sorted unique payees declared by payee directives in this journal. +journalPayeesDeclared :: Journal -> [Payee] +journalPayeesDeclared = nubSort . map fst . jdeclaredpayees + +-- | Sorted unique payees used by transactions in this journal. +journalPayeesUsed :: Journal -> [Payee] +journalPayeesUsed = nubSort . map transactionPayee . jtxns + +-- | Sorted unique payees used in transactions or declared by payee directives in this journal. +journalPayeesDeclaredOrUsed :: Journal -> [Payee] +journalPayeesDeclaredOrUsed j = nubSort $ journalPayeesDeclared j ++ journalPayeesUsed j + -- | Sorted unique account names posted to by this journal's transactions. journalAccountNamesUsed :: Journal -> [AccountName] journalAccountNamesUsed = accountNamesFromPostings . journalPostings @@ -303,25 +326,133 @@ journalAccountNames = journalAccountNamesDeclaredOrImplied journalAccountNameTree :: Journal -> Tree AccountName journalAccountNameTree = accountNameTreeFrom . journalAccountNames +-- | Find up to N most similar and most recent transactions matching +-- the given transaction description and query. Transactions are +-- listed with their description's similarity score (see +-- compareDescriptions), sorted by highest score and then by date. +-- Only transactions with a similarity score greater than a minimum +-- threshold (currently 0) are returned. +journalTransactionsSimilarTo :: Journal -> Query -> Text -> Int -> [(Double,Transaction)] +journalTransactionsSimilarTo Journal{jtxns} q desc n = + take n $ + sortBy (\(s1,t1) (s2,t2) -> compare (s2,tdate t2) (s1,tdate t1)) $ + filter ((> threshold).fst) + [(compareDescriptions desc $ tdescription t, t) | t <- jtxns, q `matchesTransaction` t] + where + threshold = 0 + +-- | Return a similarity score from 0 to 1.5 for two transaction descriptions. +-- This is based on compareStrings, with the following modifications: +-- +-- - numbers are stripped out before measuring similarity +-- +-- - if the (unstripped) first description appears in its entirety within the second, +-- the score is boosted by 0.5. +-- +compareDescriptions :: Text -> Text -> Double +compareDescriptions a b = + (if a `T.isInfixOf` b then (0.5+) else id) $ + compareStrings (simplify a) (simplify b) + where + simplify = T.unpack . T.filter (not.isDigit) + +-- | Return a similarity score from 0 to 1 for two strings. This +-- was based on Simon White's string similarity algorithm +-- (http://www.catalysoft.com/articles/StrikeAMatch.html), later found +-- to be https://en.wikipedia.org/wiki/S%C3%B8rensen%E2%80%93Dice_coefficient, +-- and modified to handle short strings better. +-- Todo: check out http://nlp.fi.muni.cz/raslan/2008/raslan08.pdf#page=14 . +compareStrings :: String -> String -> Double +compareStrings "" "" = 1 +compareStrings [_] "" = 0 +compareStrings "" [_] = 0 +compareStrings [a] [b] = if toUpper a == toUpper b then 1 else 0 +compareStrings s1 s2 = 2 * commonpairs / totalpairs + where + pairs1 = S.fromList $ wordLetterPairs $ uppercase s1 + pairs2 = S.fromList $ wordLetterPairs $ uppercase s2 + commonpairs = fromIntegral $ S.size $ S.intersection pairs1 pairs2 + totalpairs = fromIntegral $ S.size pairs1 + S.size pairs2 + +wordLetterPairs :: String -> [String] +wordLetterPairs = concatMap letterPairs . words + +letterPairs :: String -> [String] +letterPairs (a:b:rest) = [a,b] : letterPairs (b:rest) +letterPairs _ = [] + -- queries for standard account types +-- | Get a query for accounts of the specified types in this journal. +-- Account types include Asset, Liability, Equity, Revenue, Expense, Cash. +-- For each type, if no accounts were declared with this type, the query +-- will instead match accounts with names matched by the case-insensitive +-- regular expression provided as a fallback. +-- The query will match all accounts which were declared as one of +-- these types (by account directives with the type: tag), plus all their +-- subaccounts which have not been declared as some other type. +journalAccountTypeQuery :: [AccountType] -> Regexp -> Journal -> Query +journalAccountTypeQuery atypes fallbackregex Journal{jdeclaredaccounttypes} = + let + declaredacctsoftype :: [AccountName] = + concat $ mapMaybe (`M.lookup` jdeclaredaccounttypes) atypes + in case declaredacctsoftype of + [] -> Acct fallbackregex + as -> And $ [ Or acctnameRegexes ] + ++ if null differentlyTypedRegexes then [] else [ Not $ Or differentlyTypedRegexes ] + where + -- XXX Query isn't able to match account type since that requires extra info from the journal. + -- So we do a hacky search by name instead. + acctnameRegexes = map (Acct . accountNameToAccountRegex) as + differentlyTypedRegexes = map (Acct . accountNameToAccountRegex) differentlytypedsubs + + differentlytypedsubs = concat + [subs | (t,bs) <- M.toList jdeclaredaccounttypes + , not $ t `elem` atypes + , let subs = [b | b <- bs, any (`isAccountNamePrefixOf` b) as] + ] + -- | A query for accounts in this journal which have been -- declared as Asset (or Cash, a subtype of Asset) by account directives, -- or otherwise for accounts with names matched by the case-insensitive -- regular expression @^assets?(:|$)@. journalAssetAccountQuery :: Journal -> Query -journalAssetAccountQuery = journalAccountTypeQuery [Asset,Cash] (toRegexCI' "^assets?(:|$)") +journalAssetAccountQuery j = + Or [ + journalAccountTypeQuery [Asset] (toRegexCI' "^assets?(:|$)") j + ,journalCashAccountOnlyQuery j + ] --- | A query for "Cash" (liquid asset) accounts in this journal, ie accounts --- declared as Cash by account directives, or otherwise with names matched by the --- case-insensitive regular expression @^assets?(:|$)@. and not including --- the case-insensitive regular expression @(investment|receivable|:A/R|:fixed)@. +-- | A query for accounts in this journal which have been +-- declared as Asset (and not Cash) by account directives, +-- or otherwise for accounts with names matched by the case-insensitive +-- regular expression @^assets?(:|$)@. +journalAssetNonCashAccountQuery :: Journal -> Query +journalAssetNonCashAccountQuery j = + journalAccountTypeQuery [Asset] (toRegexCI' "^assets?(:|$)") j + +-- | A query for Cash (liquid asset) accounts in this journal, ie accounts +-- declared as Cash by account directives, or otherwise Asset accounts whose +-- names do not include the case-insensitive regular expression +-- @(investment|receivable|:A/R|:fixed)@. journalCashAccountQuery :: Journal -> Query journalCashAccountQuery j = case M.lookup Cash (jdeclaredaccounttypes j) of - Nothing -> And [ journalAssetAccountQuery j, Not . Acct $ toRegexCI' "(investment|receivable|:A/R|:fixed)" ] - Just _ -> journalAccountTypeQuery [Cash] notused j - where notused = error' "journalCashAccountQuery: this should not have happened!" -- PARTIAL: + Just _ -> journalCashAccountOnlyQuery j + Nothing -> + -- no Cash accounts are declared; query for Asset accounts and exclude some of them + And [ journalAssetNonCashAccountQuery j, Not . Acct $ toRegexCI' "(investment|receivable|:A/R|:fixed)" ] + +-- | A query for accounts in this journal specifically declared as Cash by +-- account directives, or otherwise the None query. +journalCashAccountOnlyQuery :: Journal -> Query +journalCashAccountOnlyQuery j = + case M.lookup Cash (jdeclaredaccounttypes j) of + Just _ -> + -- Cash accounts are declared; get a query for them (the fallback regex won't be used) + journalAccountTypeQuery [Cash] notused j + where notused = error' "journalCashAccountOnlyQuery: this should not have happened!" -- PARTIAL: + Nothing -> None -- | A query for accounts in this journal which have been -- declared as Liability by account directives, or otherwise for @@ -366,33 +497,6 @@ journalProfitAndLossAccountQuery j = Or [journalRevenueAccountQuery j ,journalExpenseAccountQuery j ] --- | Get a query for accounts of the specified types (Asset, Liability..) in this journal. --- The query will match all accounts which were declared as one of --- these types by account directives, plus all their subaccounts which --- have not been declared as some other type. --- Or if no accounts were declared with these types, the query will --- instead match accounts with names matched by the provided --- case-insensitive regular expression. -journalAccountTypeQuery :: [AccountType] -> Regexp -> Journal -> Query -journalAccountTypeQuery atypes fallbackregex Journal{jdeclaredaccounttypes} = - let - declaredacctsoftype :: [AccountName] = - concat $ mapMaybe (`M.lookup` jdeclaredaccounttypes) atypes - in case declaredacctsoftype of - [] -> Acct fallbackregex - as -> And [ Or acctnameRegexes, Not $ Or differentlyTypedRegexes ] - where - -- XXX Query isn't able to match account type since that requires extra info from the journal. - -- So we do a hacky search by name instead. - acctnameRegexes = map (Acct . accountNameToAccountRegex) as - differentlyTypedRegexes = map (Acct . accountNameToAccountRegex) differentlytypedsubs - - differentlytypedsubs = concat - [subs | (t,bs) <- M.toList jdeclaredaccounttypes - , not $ t `elem` atypes - , let subs = [b | b <- bs, any (`isAccountNamePrefixOf` b) as] - ] - -- Various kinds of filtering on journals. We do it differently depending -- on the command. @@ -426,16 +530,16 @@ filterTransactionPostings :: Query -> Transaction -> Transaction filterTransactionPostings q t@Transaction{tpostings=ps} = t{tpostings=filter (q `matchesPosting`) ps} -- | Apply a transformation to a journal's transactions. -mapJournalTransactions :: (Transaction -> Transaction) -> Journal -> Journal -mapJournalTransactions f j@Journal{jtxns=ts} = j{jtxns=map f ts} +journalMapTransactions :: (Transaction -> Transaction) -> Journal -> Journal +journalMapTransactions f j@Journal{jtxns=ts} = j{jtxns=map f ts} -- | Apply a transformation to a journal's postings. -mapJournalPostings :: (Posting -> Posting) -> Journal -> Journal -mapJournalPostings f j@Journal{jtxns=ts} = j{jtxns=map (mapTransactionPostings f) ts} +journalMapPostings :: (Posting -> Posting) -> Journal -> Journal +journalMapPostings f j@Journal{jtxns=ts} = j{jtxns=map (transactionMapPostings f) ts} --- | Apply a transformation to a transaction's postings. -mapTransactionPostings :: (Posting -> Posting) -> Transaction -> Transaction -mapTransactionPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps} +-- | Apply a transformation to a journal's posting amounts. +journalMapPostingAmounts :: (Amount -> Amount) -> Journal -> Journal +journalMapPostingAmounts f = journalMapPostings (postingTransformAmount (mapMixedAmount f)) {- ------------------------------------------------------------------------------- @@ -888,7 +992,7 @@ checkBalanceAssertionOneCommodityB p@Posting{paccount=assertedacct} assertedamt Nothing -> "?" -- shouldn't happen Just t -> printf "%s\ntransaction:\n%s" (showGenericSourcePos pos) - (chomp $ showTransaction t) + (textChomp $ showTransaction t) :: String where pos = baposition $ fromJust $ pbalanceassertion p @@ -919,11 +1023,11 @@ checkIllegalBalanceAssignmentB p = do checkBalanceAssignmentPostingDateB :: Posting -> Balancing s () checkBalanceAssignmentPostingDateB p = when (hasBalanceAssignment p && isJust (pdate p)) $ - throwError $ unlines $ + throwError . T.unpack $ T.unlines ["postings which are balance assignments may not have a custom date." ,"Please write the posting amount explicitly, or remove the posting date:" ,"" - ,maybe (unlines $ showPostingLines p) showTransaction $ ptransaction p + ,maybe (T.unlines $ showPostingLines p) showTransaction $ ptransaction p ] -- | Throw an error if this posting is trying to do a balance assignment and @@ -933,16 +1037,16 @@ checkBalanceAssignmentUnassignableAccountB :: Posting -> Balancing s () checkBalanceAssignmentUnassignableAccountB p = do unassignable <- R.asks bsUnassignable when (hasBalanceAssignment p && paccount p `S.member` unassignable) $ - throwError $ unlines $ + throwError . T.unpack $ T.unlines ["balance assignments cannot be used with accounts which are" ,"posted to by transaction modifier rules (auto postings)." ,"Please write the posting amount explicitly, or remove the rule." ,"" - ,"account: "++T.unpack (paccount p) + ,"account: " <> paccount p ,"" ,"transaction:" ,"" - ,maybe (unlines $ showPostingLines p) showTransaction $ ptransaction p + ,maybe (T.unlines $ showPostingLines p) showTransaction $ ptransaction p ] -- @@ -963,7 +1067,8 @@ journalApplyCommodityStyles j@Journal{jtxns=ts, jpricedirectives=pds} = fixtransaction t@Transaction{tpostings=ps} = t{tpostings=map fixposting ps} fixposting p = p{pamount=styleMixedAmount styles $ pamount p ,pbalanceassertion=fixbalanceassertion <$> pbalanceassertion p} - fixbalanceassertion ba = ba{baamount=styleAmount styles $ baamount ba} + -- balance assertion amounts are always displayed (by print) at full precision, per docs + fixbalanceassertion ba = ba{baamount=styleAmountExceptPrecision styles $ baamount ba} fixpricedirective pd@PriceDirective{pdamount=a} = pd{pdamount=styleAmountExceptPrecision styles a} -- | Get the canonical amount styles for this journal, whether (in order of precedence): @@ -1006,42 +1111,40 @@ journalInferCommodityStyles j = -- and this function never reports an error. -- commodityStylesFromAmounts :: [Amount] -> Either String (M.Map CommoditySymbol AmountStyle) -commodityStylesFromAmounts amts = - Right $ M.fromList commstyles - where - commamts = groupSort [(acommodity as, as) | as <- amts] - commstyles = [(c, canonicalStyleFrom $ map astyle as) | (c,as) <- commamts] +commodityStylesFromAmounts = + Right . foldr (\a -> M.insertWith canonicalStyle (acommodity a) (astyle a)) mempty --- TODO: should probably detect and report inconsistencies here. --- Though, we don't have the info for a good error message, so maybe elsewhere. -- | Given a list of amount styles (assumed to be from parsed amounts -- in a single commodity), in parse order, choose a canonical style. +canonicalStyleFrom :: [AmountStyle] -> AmountStyle +-- canonicalStyleFrom [] = amountstyle +canonicalStyleFrom ss = foldl' canonicalStyle amountstyle ss + +-- TODO: should probably detect and report inconsistencies here. +-- Though, we don't have the info for a good error message, so maybe elsewhere. +-- | Given a pair of AmountStyles, choose a canonical style. -- This is: --- the general style of the first amount, +-- the general style of the first amount, -- with the first digit group style seen, -- with the maximum precision of all. --- -canonicalStyleFrom :: [AmountStyle] -> AmountStyle -canonicalStyleFrom [] = amountstyle -canonicalStyleFrom ss@(s:_) = - s{asprecision=prec, asdecimalpoint=Just decmark, asdigitgroups=mgrps} +canonicalStyle :: AmountStyle -> AmountStyle -> AmountStyle +canonicalStyle a b = a{asprecision=prec, asdecimalpoint=decmark, asdigitgroups=mgrps} where -- precision is maximum of all precisions - prec = maximumStrict $ map asprecision ss + prec = max (asprecision a) (asprecision b) -- identify the digit group mark (& group sizes) - mgrps = headMay $ mapMaybe asdigitgroups ss + mgrps = asdigitgroups a <|> asdigitgroups b -- if a digit group mark was identified above, we can rely on that; -- make sure the decimal mark is different. If not, default to period. - defdecmark = - case mgrps of + defdecmark = case mgrps of Just (DigitGroups '.' _) -> ',' _ -> '.' -- identify the decimal mark: the first one used, or the above default, -- but never the same character as the digit group mark. -- urgh.. refactor.. decmark = case mgrps of - Just _ -> defdecmark - _ -> headDef defdecmark $ mapMaybe asdecimalpoint ss + Just _ -> Just defdecmark + Nothing -> asdecimalpoint a <|> asdecimalpoint b <|> Just defdecmark -- -- | Apply this journal's historical price records to unpriced amounts where possible. -- journalApplyPriceDirectives :: Journal -> Journal @@ -1185,16 +1288,33 @@ journalStyleInfluencingAmounts j = -- of all this journal's transactions and postings, or DateSpan Nothing Nothing -- if there are none. journalDateSpan :: Bool -> Journal -> DateSpan -journalDateSpan secondary j - | null ts = DateSpan Nothing Nothing - | otherwise = DateSpan (Just earliest) (Just $ addDays 1 latest) - where - earliest = minimumStrict dates - latest = maximumStrict dates - dates = pdates ++ tdates - tdates = map (if secondary then transactionDate2 else tdate) ts - pdates = concatMap (mapMaybe (if secondary then (Just . postingDate2) else pdate) . tpostings) ts - ts = jtxns j +journalDateSpan False = journalDateSpanHelper $ Just PrimaryDate +journalDateSpan True = journalDateSpanHelper $ Just SecondaryDate + +-- | The fully specified date span enclosing the dates (primary and secondary) +-- of all this journal's transactions and postings, or DateSpan Nothing Nothing +-- if there are none. +journalDateSpanBothDates :: Journal -> DateSpan +journalDateSpanBothDates = journalDateSpanHelper Nothing + +-- | A helper for journalDateSpan which takes Maybe WhichDate directly. Nothing +-- uses both primary and secondary dates. +journalDateSpanHelper :: Maybe WhichDate -> Journal -> DateSpan +journalDateSpanHelper whichdate j = + DateSpan (minimumMay dates) (addDays 1 <$> maximumMay dates) + where + dates = pdates ++ tdates + tdates = concatMap gettdate ts + pdates = concatMap getpdate $ concatMap tpostings ts + ts = jtxns j + gettdate t = case whichdate of + Just PrimaryDate -> [tdate t] + Just SecondaryDate -> [fromMaybe (tdate t) $ tdate2 t] + Nothing -> tdate t : maybeToList (tdate2 t) + getpdate p = case whichdate of + Just PrimaryDate -> maybeToList $ pdate p + Just SecondaryDate -> maybeToList $ pdate2 p <|> pdate p + Nothing -> catMaybes [pdate p, pdate2 p] -- | The earliest of this journal's transaction and posting dates, or -- Nothing if there are none. @@ -1241,7 +1361,7 @@ journalApplyAliases aliases j = case mapM (transactionApplyAliases aliases) $ jtxns j of Right ts -> Right j{jtxns = ts} Left err -> Left err - + -- -- | Build a database of market prices in effect on the given date, -- -- from the journal's price directives. -- journalPrices :: Day -> Journal -> Prices @@ -1253,7 +1373,7 @@ journalApplyAliases aliases j = -- [ "P" -- , showDate (pddate pd) -- , T.unpack (pdcommodity pd) --- , (showAmount . setAmountPrecision maxprecision) (pdamount pd +-- , (showAmount . amountSetPrecision maxprecision) (pdamount pd -- ) -- ] diff --git a/Hledger/Data/Json.hs b/Hledger/Data/Json.hs index 925b1fd..b509ad0 100644 --- a/Hledger/Data/Json.hs +++ b/Hledger/Data/Json.hs @@ -44,7 +44,7 @@ import Data.Decimal import Data.Maybe import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.IO as TL -import Data.Text.Lazy.Builder (toLazyText) +import qualified Data.Text.Lazy.Builder as TB import GHC.Generics (Generic) import System.Time (ClockTime) @@ -126,6 +126,7 @@ instance ToJSON AccountAlias instance ToJSON AccountType instance ToJSONKey AccountType instance ToJSON AccountDeclarationInfo +instance ToJSON PayeeDeclarationInfo instance ToJSON Commodity instance ToJSON TimeclockCode instance ToJSON TimeclockEntry @@ -231,7 +232,7 @@ instance FromJSON (DecimalRaw Integer) -- | Show a JSON-convertible haskell value as pretty-printed JSON text. toJsonText :: ToJSON a => a -> TL.Text -toJsonText = (<>"\n") . toLazyText . encodePrettyToTextBuilder +toJsonText = TB.toLazyText . (<> TB.fromText "\n") . encodePrettyToTextBuilder -- | Write a JSON-convertible haskell value to a pretty-printed JSON file. -- Eg: writeJsonFile "a.json" nulltransaction diff --git a/Hledger/Data/Period.hs b/Hledger/Data/Period.hs index 9f7c785..bf26156 100644 --- a/Hledger/Data/Period.hs +++ b/Hledger/Data/Period.hs @@ -5,6 +5,8 @@ a richer abstraction than DateSpan. See also Types and Dates. -} +{-# LANGUAGE OverloadedStrings #-} + module Hledger.Data.Period ( periodAsDateSpan ,dateSpanAsPeriod @@ -30,6 +32,8 @@ module Hledger.Data.Period ( ) where +import Data.Text (Text) +import qualified Data.Text as T import Data.Time.Calendar import Data.Time.Calendar.MonthDay import Data.Time.Calendar.OrdinalDate @@ -155,21 +159,23 @@ isStandardPeriod = isStandardPeriod' . simplifyPeriod -- -- >>> showPeriod (WeekPeriod (fromGregorian 2016 7 25)) -- "2016-07-25W30" -showPeriod (DayPeriod b) = formatTime defaultTimeLocale "%F" b -- DATE -showPeriod (WeekPeriod b) = formatTime defaultTimeLocale "%FW%V" b -- STARTDATEWYEARWEEK -showPeriod (MonthPeriod y m) = printf "%04d-%02d" y m -- YYYY-MM -showPeriod (QuarterPeriod y q) = printf "%04dQ%d" y q -- YYYYQN -showPeriod (YearPeriod y) = printf "%04d" y -- YYYY -showPeriod (PeriodBetween b e) = formatTime defaultTimeLocale "%F" b +showPeriod :: Period -> Text +showPeriod (DayPeriod b) = T.pack $ formatTime defaultTimeLocale "%F" b -- DATE +showPeriod (WeekPeriod b) = T.pack $ formatTime defaultTimeLocale "%FW%V" b -- STARTDATEWYEARWEEK +showPeriod (MonthPeriod y m) = T.pack $ printf "%04d-%02d" y m -- YYYY-MM +showPeriod (QuarterPeriod y q) = T.pack $ printf "%04dQ%d" y q -- YYYYQN +showPeriod (YearPeriod y) = T.pack $ printf "%04d" y -- YYYY +showPeriod (PeriodBetween b e) = T.pack $ formatTime defaultTimeLocale "%F" b ++ formatTime defaultTimeLocale "..%F" (addDays (-1) e) -- STARTDATE..INCLUSIVEENDDATE -showPeriod (PeriodFrom b) = formatTime defaultTimeLocale "%F.." b -- STARTDATE.. -showPeriod (PeriodTo e) = formatTime defaultTimeLocale "..%F" (addDays (-1) e) -- ..INCLUSIVEENDDATE +showPeriod (PeriodFrom b) = T.pack $ formatTime defaultTimeLocale "%F.." b -- STARTDATE.. +showPeriod (PeriodTo e) = T.pack $ formatTime defaultTimeLocale "..%F" (addDays (-1) e) -- ..INCLUSIVEENDDATE showPeriod PeriodAll = ".." -- | Like showPeriod, but if it's a month period show just -- the 3 letter month name abbreviation for the current locale. +showPeriodMonthAbbrev :: Period -> Text showPeriodMonthAbbrev (MonthPeriod _ m) -- Jan - | m > 0 && m <= length monthnames = snd $ monthnames !! (m-1) + | m > 0 && m <= length monthnames = T.pack . snd $ monthnames !! (m-1) where monthnames = months defaultTimeLocale showPeriodMonthAbbrev p = showPeriod p diff --git a/Hledger/Data/PeriodicTransaction.hs b/Hledger/Data/PeriodicTransaction.hs index 57487be..44472f1 100644 --- a/Hledger/Data/PeriodicTransaction.hs +++ b/Hledger/Data/PeriodicTransaction.hs @@ -16,6 +16,7 @@ where import Data.Semigroup ((<>)) #endif import qualified Data.Text as T +import qualified Data.Text.IO as T import Text.Printf import Hledger.Data.Types @@ -40,7 +41,7 @@ _ptgen str = do case checkPeriodicTransactionStartDate i s t of Just e -> error' e -- PARTIAL: Nothing -> - mapM_ (putStr . showTransaction) $ + mapM_ (T.putStr . showTransaction) $ runPeriodicTransaction nullperiodictransaction{ ptperiodexpr=t , ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1] } nulldatespan @@ -52,7 +53,7 @@ _ptgenspan str span = do case checkPeriodicTransactionStartDate i s t of Just e -> error' e -- PARTIAL: Nothing -> - mapM_ (putStr . showTransaction) $ + mapM_ (T.putStr . showTransaction) $ runPeriodicTransaction nullperiodictransaction{ ptperiodexpr=t , ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1] } span diff --git a/Hledger/Data/Posting.hs b/Hledger/Data/Posting.hs index 57a8ce7..7e2679c 100644 --- a/Hledger/Data/Posting.hs +++ b/Hledger/Data/Posting.hs @@ -64,6 +64,7 @@ module Hledger.Data.Posting ( -- * misc. showComment, postingTransformAmount, + postingApplyCostValuation, postingApplyValuation, postingToCost, tests_Posting @@ -161,20 +162,20 @@ originalPosting p = fromMaybe p $ poriginal p -- XXX once rendered user output, but just for debugging now; clean up showPosting :: Posting -> String showPosting p@Posting{paccount=a,pamount=amt,ptype=t} = - unlines $ [concatTopPadded [show (postingDate p) ++ " ", showaccountname a ++ " ", showamount amt, showComment (pcomment p)]] + unlines $ [concatTopPadded [show (postingDate p) ++ " ", showaccountname a ++ " ", showamount amt, T.unpack . showComment $ pcomment p]] where ledger3ishlayout = False acctnamewidth = if ledger3ishlayout then 25 else 22 - showaccountname = fitString (Just acctnamewidth) Nothing False False . bracket . T.unpack . elideAccountName width + showaccountname = T.unpack . fitText (Just acctnamewidth) Nothing False False . bracket . elideAccountName width (bracket,width) = case t of - BalancedVirtualPosting -> (\s -> "["++s++"]", acctnamewidth-2) - VirtualPosting -> (\s -> "("++s++")", acctnamewidth-2) - _ -> (id,acctnamewidth) - showamount = fst . showMixed showAmount (Just 12) Nothing False + BalancedVirtualPosting -> (wrap "[" "]", acctnamewidth-2) + VirtualPosting -> (wrap "(" ")", acctnamewidth-2) + _ -> (id,acctnamewidth) + showamount = wbUnpack . showMixedAmountB noColour{displayMinWidth=Just 12} -showComment :: Text -> String -showComment t = if T.null t then "" else " ;" ++ T.unpack t +showComment :: Text -> Text +showComment t = if T.null t then "" else " ;" <> t isReal :: Posting -> Bool isReal p = ptype p == RegularPosting @@ -274,9 +275,9 @@ accountNameWithoutPostingType a = case accountNamePostingType a of RegularPosting -> a accountNameWithPostingType :: PostingType -> AccountName -> AccountName -accountNameWithPostingType BalancedVirtualPosting a = "["<>accountNameWithoutPostingType a<>"]" -accountNameWithPostingType VirtualPosting a = "("<>accountNameWithoutPostingType a<>")" -accountNameWithPostingType RegularPosting a = accountNameWithoutPostingType a +accountNameWithPostingType BalancedVirtualPosting = wrap "[" "]" . accountNameWithoutPostingType +accountNameWithPostingType VirtualPosting = wrap "(" ")" . accountNameWithoutPostingType +accountNameWithPostingType RegularPosting = accountNameWithoutPostingType -- | Prefix one account name to another, preserving posting type -- indicators like concatAccountNames. @@ -330,33 +331,24 @@ aliasReplace (BasicAlias old new) a aliasReplace (RegexAlias re repl) a = fmap T.pack . regexReplace re repl $ T.unpack a -- XXX +-- | Apply a specified costing and valuation to this posting's amount, +-- using the provided price oracle, commodity styles, and reference dates. +-- Costing is done first if requested, and after that any valuation. +-- See amountApplyValuation and amountCost. +postingApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Posting -> Posting +postingApplyCostValuation priceoracle styles periodlast today cost v p = + postingTransformAmount (mixedAmountApplyCostValuation priceoracle styles periodlast today (postingDate p) cost v) p + -- | 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. -postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Posting -> ValuationType -> Posting -postingApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod p v = - case v of - AtCost Nothing -> postingToCost styles p - AtCost mc -> postingValueAtDate priceoracle styles mc periodlast $ postingToCost styles p - AtThen mc -> postingValueAtDate priceoracle styles mc (postingDate p) p - AtEnd mc -> postingValueAtDate priceoracle styles mc periodlast p - AtNow mc -> postingValueAtDate priceoracle styles mc today p - AtDefault mc | ismultiperiod -> postingValueAtDate priceoracle styles mc periodlast p - AtDefault mc -> postingValueAtDate priceoracle styles mc (fromMaybe today mreportlast) p - AtDate d mc -> postingValueAtDate priceoracle styles mc d p +-- provided price oracle, commodity styles, and reference dates. +-- See amountApplyValuation. +postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting +postingApplyValuation priceoracle styles periodlast today v p = + postingTransformAmount (mixedAmountApplyValuation priceoracle styles periodlast today (postingDate p) v) p -- | Convert this posting's amount to cost, and apply the appropriate amount styles. postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting -postingToCost styles p@Posting{pamount=a} = p{pamount=styleMixedAmount styles $ mixedAmountCost a} - --- | Convert this posting's amount to market value in the given commodity, --- or the default valuation commodity, at the given valuation date, --- using the given market price oracle. --- When market prices available on that date are not sufficient to --- calculate the value, amounts are left unchanged. -postingValueAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> Posting -> Posting -postingValueAtDate priceoracle styles mc d p = postingTransformAmount (mixedAmountValueAtDate priceoracle styles mc d) p +postingToCost styles = postingTransformAmount (styleMixedAmount styles . mixedAmountCost) -- | Apply a transform function to this posting's amount. postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting @@ -385,7 +377,7 @@ commentAddTag c (t,v) -- A space is inserted following the colon, before the value. commentAddTagNextLine :: Text -> Tag -> Text commentAddTagNextLine cmt (t,v) = - cmt <> if "\n" `T.isSuffixOf` cmt then "" else "\n" <> t <> ": " <> v + cmt <> (if "\n" `T.isSuffixOf` cmt then "" else "\n") <> t <> ": " <> v -- tests diff --git a/Hledger/Data/StringFormat.hs b/Hledger/Data/StringFormat.hs index b0f58db..3282bdc 100644 --- a/Hledger/Data/StringFormat.hs +++ b/Hledger/Data/StringFormat.hs @@ -2,7 +2,10 @@ -- hledger's report item fields. The formats are used by -- report-specific renderers like renderBalanceReportItem. -{-# LANGUAGE FlexibleContexts, OverloadedStrings, TypeFamilies, PackageImports #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PackageImports #-} +{-# LANGUAGE TypeFamilies #-} module Hledger.Data.StringFormat ( parseStringFormat @@ -10,7 +13,6 @@ module Hledger.Data.StringFormat ( , StringFormat(..) , StringFormatComponent(..) , ReportItemField(..) - , overlineWidth , defaultBalanceLineFormat , tests_StringFormat ) where @@ -21,22 +23,20 @@ import Numeric (readDec) import Data.Char (isPrint) import Data.Default (Default(..)) import Data.Maybe (isJust) --- import qualified Data.Text as T +import Data.Text (Text) +import qualified Data.Text as T import Text.Megaparsec import Text.Megaparsec.Char (char, digitChar, string) -import Hledger.Utils.Parse (SimpleStringParser) -import Hledger.Utils.String (formatString) +import Hledger.Utils.Parse (SimpleTextParser) +import Hledger.Utils.Text (formatText) import Hledger.Utils.Test -- | A format specification/template to use when rendering a report line item as text. -- --- A format is an optional width, along with a sequence of components; --- each is either a literal string, or a hledger report item field with --- specified width and justification whose value will be interpolated --- at render time. The optional width determines the length of the --- overline to draw above the totals row; if it is Nothing, then the --- maximum width of all lines is used. +-- A format is a sequence of components; each is either a literal +-- string, or a hledger report item field with specified width and +-- justification whose value will be interpolated at render time. -- -- A component's value may be a multi-line string (or a -- multi-commodity amount), in which case the final string will be @@ -47,13 +47,13 @@ import Hledger.Utils.Test -- mode, which provides a limited StringFormat renderer. -- data StringFormat = - OneLine (Maybe Int) [StringFormatComponent] -- ^ multi-line values will be rendered on one line, comma-separated - | TopAligned (Maybe Int) [StringFormatComponent] -- ^ values will be top-aligned (and bottom-padded to the same height) - | BottomAligned (Maybe Int) [StringFormatComponent] -- ^ values will be bottom-aligned (and top-padded) + OneLine [StringFormatComponent] -- ^ multi-line values will be rendered on one line, comma-separated + | TopAligned [StringFormatComponent] -- ^ values will be top-aligned (and bottom-padded to the same height) + | BottomAligned [StringFormatComponent] -- ^ values will be bottom-aligned (and top-padded) deriving (Show, Eq) data StringFormatComponent = - FormatLiteral String -- ^ Literal text to be rendered as-is + FormatLiteral Text -- ^ Literal text to be rendered as-is | FormatField Bool (Maybe Int) (Maybe Int) @@ -81,14 +81,9 @@ data ReportItemField = instance Default StringFormat where def = defaultBalanceLineFormat -overlineWidth :: StringFormat -> Maybe Int -overlineWidth (OneLine w _) = w -overlineWidth (TopAligned w _) = w -overlineWidth (BottomAligned w _) = w - -- | Default line format for balance report: "%20(total) %2(depth_spacer)%-(account)" defaultBalanceLineFormat :: StringFormat -defaultBalanceLineFormat = BottomAligned (Just 20) [ +defaultBalanceLineFormat = BottomAligned [ FormatField False (Just 20) Nothing TotalField , FormatLiteral " " , FormatField True (Just 2) Nothing DepthSpacerField @@ -102,37 +97,37 @@ defaultBalanceLineFormat = BottomAligned (Just 20) [ ---------------------------------------------------------------------- -- | Parse a string format specification, or return a parse error. -parseStringFormat :: String -> Either String StringFormat +parseStringFormat :: Text -> Either String StringFormat parseStringFormat input = case (runParser (stringformatp <* eof) "(unknown)") input of Left y -> Left $ show y Right x -> Right x defaultStringFormatStyle = BottomAligned -stringformatp :: SimpleStringParser StringFormat +stringformatp :: SimpleTextParser StringFormat stringformatp = do alignspec <- optional (try $ char '%' >> oneOf ("^_,"::String)) let constructor = case alignspec of - Just '^' -> TopAligned Nothing - Just '_' -> BottomAligned Nothing - Just ',' -> OneLine Nothing - _ -> defaultStringFormatStyle Nothing + Just '^' -> TopAligned + Just '_' -> BottomAligned + Just ',' -> OneLine + _ -> defaultStringFormatStyle constructor <$> many componentp -componentp :: SimpleStringParser StringFormatComponent +componentp :: SimpleTextParser StringFormatComponent componentp = formatliteralp <|> formatfieldp -formatliteralp :: SimpleStringParser StringFormatComponent +formatliteralp :: SimpleTextParser StringFormatComponent formatliteralp = do - s <- some c + s <- T.pack <$> some c return $ FormatLiteral s where isPrintableButNotPercentage x = isPrint x && x /= '%' c = (satisfy isPrintableButNotPercentage <?> "printable character") <|> try (string "%%" >> return '%') -formatfieldp :: SimpleStringParser StringFormatComponent +formatfieldp :: SimpleTextParser StringFormatComponent formatfieldp = do char '%' leftJustified <- optional (char '-') @@ -147,7 +142,7 @@ formatfieldp = do Just text -> Just m where ((m,_):_) = readDec text _ -> Nothing -fieldp :: SimpleStringParser ReportItemField +fieldp :: SimpleTextParser ReportItemField fieldp = do try (string "account" >> return AccountField) <|> try (string "depth_spacer" >> return DepthSpacerField) @@ -161,8 +156,8 @@ fieldp = do formatStringTester fs value expected = actual @?= expected where actual = case fs of - FormatLiteral l -> formatString False Nothing Nothing l - FormatField leftJustify min max _ -> formatString leftJustify min max value + FormatLiteral l -> formatText False Nothing Nothing l + FormatField leftJustify min max _ -> formatText leftJustify min max value tests_StringFormat = tests "StringFormat" [ @@ -176,25 +171,25 @@ tests_StringFormat = tests "StringFormat" [ formatStringTester (FormatField True (Just 20) (Just 20) DescriptionField) "description" "description " formatStringTester (FormatField True Nothing (Just 3) DescriptionField) "description" "des" - ,let s `gives` expected = test s $ parseStringFormat s @?= Right expected + ,let s `gives` expected = test s $ parseStringFormat (T.pack s) @?= Right expected in tests "parseStringFormat" [ - "" `gives` (defaultStringFormatStyle Nothing []) - , "D" `gives` (defaultStringFormatStyle Nothing [FormatLiteral "D"]) - , "%(date)" `gives` (defaultStringFormatStyle Nothing [FormatField False Nothing Nothing DescriptionField]) - , "%(total)" `gives` (defaultStringFormatStyle Nothing [FormatField False Nothing Nothing TotalField]) + "" `gives` (defaultStringFormatStyle []) + , "D" `gives` (defaultStringFormatStyle [FormatLiteral "D"]) + , "%(date)" `gives` (defaultStringFormatStyle [FormatField False Nothing Nothing DescriptionField]) + , "%(total)" `gives` (defaultStringFormatStyle [FormatField False Nothing Nothing TotalField]) -- TODO -- , "^%(total)" `gives` (TopAligned [FormatField False Nothing Nothing TotalField]) -- , "_%(total)" `gives` (BottomAligned [FormatField False Nothing Nothing TotalField]) -- , ",%(total)" `gives` (OneLine [FormatField False Nothing Nothing TotalField]) - , "Hello %(date)!" `gives` (defaultStringFormatStyle Nothing [FormatLiteral "Hello ", FormatField False Nothing Nothing DescriptionField, FormatLiteral "!"]) - , "%-(date)" `gives` (defaultStringFormatStyle Nothing [FormatField True Nothing Nothing DescriptionField]) - , "%20(date)" `gives` (defaultStringFormatStyle Nothing [FormatField False (Just 20) Nothing DescriptionField]) - , "%.10(date)" `gives` (defaultStringFormatStyle Nothing [FormatField False Nothing (Just 10) DescriptionField]) - , "%20.10(date)" `gives` (defaultStringFormatStyle Nothing [FormatField False (Just 20) (Just 10) DescriptionField]) - , "%20(account) %.10(total)" `gives` (defaultStringFormatStyle Nothing [FormatField False (Just 20) Nothing AccountField - ,FormatLiteral " " - ,FormatField False Nothing (Just 10) TotalField - ]) + , "Hello %(date)!" `gives` (defaultStringFormatStyle [FormatLiteral "Hello ", FormatField False Nothing Nothing DescriptionField, FormatLiteral "!"]) + , "%-(date)" `gives` (defaultStringFormatStyle [FormatField True Nothing Nothing DescriptionField]) + , "%20(date)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) Nothing DescriptionField]) + , "%.10(date)" `gives` (defaultStringFormatStyle [FormatField False Nothing (Just 10) DescriptionField]) + , "%20.10(date)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) (Just 10) DescriptionField]) + , "%20(account) %.10(total)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) Nothing AccountField + ,FormatLiteral " " + ,FormatField False Nothing (Just 10) TotalField + ]) , test "newline not parsed" $ assertLeft $ parseStringFormat "\n" ] ] diff --git a/Hledger/Data/Timeclock.hs b/Hledger/Data/Timeclock.hs index 1cf1643..2d5f1fe 100644 --- a/Hledger/Data/Timeclock.hs +++ b/Hledger/Data/Timeclock.hs @@ -6,6 +6,7 @@ converted to 'Transactions' and queried like a ledger. -} +{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module Hledger.Data.Timeclock ( @@ -14,14 +15,18 @@ module Hledger.Data.Timeclock ( ) where -import Data.Maybe +import Data.Maybe (fromMaybe) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif -- import Data.Text (Text) import qualified Data.Text as T -import Data.Time.Calendar -import Data.Time.Clock -import Data.Time.Format -import Data.Time.LocalTime -import Text.Printf +import Data.Time.Calendar (addDays) +import Data.Time.Clock (addUTCTime, getCurrentTime) +import Data.Time.Format (defaultTimeLocale, formatTime, parseTimeM) +import Data.Time.LocalTime (LocalTime(..), TimeOfDay(..), getCurrentTimeZone, + localTimeToUTC, midnight, utc, utcToLocalTime) +import Text.Printf (printf) import Hledger.Utils import Hledger.Data.Types @@ -90,8 +95,8 @@ errorWithSourceLine line msg = error $ "line " ++ show line ++ ": " ++ msg entryFromTimeclockInOut :: TimeclockEntry -> TimeclockEntry -> Transaction entryFromTimeclockInOut i o | otime >= itime = t - | otherwise = - error' $ "clock-out time less than clock-in time in:\n" ++ showTransaction t -- PARTIAL: + | otherwise = error' . T.unpack $ + "clock-out time less than clock-in time in:\n" <> showTransaction t -- PARTIAL: where t = Transaction { tindex = 0, diff --git a/Hledger/Data/Transaction.hs b/Hledger/Data/Transaction.hs index e0b5b09..e839954 100644 --- a/Hledger/Data/Transaction.hs +++ b/Hledger/Data/Transaction.hs @@ -7,12 +7,14 @@ tags. -} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE Rank2Types #-} -{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE NamedFieldPuns #-} module Hledger.Data.Transaction ( -- * Transaction nulltransaction, @@ -31,9 +33,12 @@ module Hledger.Data.Transaction ( balanceTransaction, balanceTransactionHelper, transactionTransformPostings, + transactionApplyCostValuation, transactionApplyValuation, transactionToCost, transactionApplyAliases, + transactionMapPostings, + transactionMapPostingAmounts, -- nonzerobalanceerror, -- * date operations transactionDate2, @@ -44,8 +49,6 @@ module Hledger.Data.Transaction ( -- * rendering showTransaction, showTransactionOneLineAmounts, - showTransactionUnelided, - showTransactionUnelidedOneLineAmounts, -- showPostingLine, showPostingLines, -- * GenericSourcePos @@ -53,17 +56,24 @@ module Hledger.Data.Transaction ( sourceFirstLine, showGenericSourcePos, annotateErrorWithTransaction, + transactionFile, -- * tests tests_Transaction ) where -import Data.List + +import Data.Default (def) +import Data.List (intercalate, partition) import Data.List.Extra (nubSort) -import Data.Maybe +import Data.Maybe (fromMaybe, mapMaybe) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif import Data.Text (Text) import qualified Data.Text as T -import Data.Time.Calendar -import Text.Printf +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Builder as TB +import Data.Time.Calendar (Day, fromGregorian) import qualified Data.Map as M import Hledger.Utils @@ -72,6 +82,8 @@ import Hledger.Data.Dates import Hledger.Data.Posting import Hledger.Data.Amount import Hledger.Data.Valuation +import Text.Tabular +import Text.Tabular.AsciiWide sourceFilePath :: GenericSourcePos -> FilePath sourceFilePath = \case @@ -148,53 +160,46 @@ 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). -} -showTransaction :: Transaction -> String -showTransaction = showTransactionHelper False - --- | Deprecated alias for 'showTransaction' -showTransactionUnelided :: Transaction -> String -showTransactionUnelided = showTransaction -- TODO: drop it +showTransaction :: Transaction -> Text +showTransaction = TL.toStrict . TB.toLazyText . showTransactionHelper False -- | 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. -showTransactionOneLineAmounts :: Transaction -> String -showTransactionOneLineAmounts = showTransactionHelper True - --- | Deprecated alias for 'showTransactionOneLineAmounts' -showTransactionUnelidedOneLineAmounts :: Transaction -> String -showTransactionUnelidedOneLineAmounts = showTransactionOneLineAmounts -- TODO: drop it +showTransactionOneLineAmounts :: Transaction -> Text +showTransactionOneLineAmounts = TL.toStrict . TB.toLazyText . showTransactionHelper True -- | Helper for showTransaction*. -showTransactionHelper :: Bool -> Transaction -> String +showTransactionHelper :: Bool -> Transaction -> TB.Builder showTransactionHelper onelineamounts t = - unlines $ [descriptionline] - ++ newlinecomments - ++ (postingsAsLines onelineamounts (tpostings t)) - ++ [""] - where - descriptionline = rstrip $ concat [date, status, code, desc, samelinecomment] - date = showDate (tdate t) ++ maybe "" (("="++) . showDate) (tdate2 t) - status | tstatus t == Cleared = " *" - | tstatus t == Pending = " !" - | otherwise = "" - code = if T.length (tcode t) > 0 then printf " (%s)" $ T.unpack $ tcode t else "" - desc = if null d then "" else " " ++ d where d = T.unpack $ tdescription t - (samelinecomment, newlinecomments) = - case renderCommentLines (tcomment t) of [] -> ("",[]) - c:cs -> (c,cs) + TB.fromText descriptionline <> newline + <> foldMap ((<> newline) . TB.fromText) newlinecomments + <> foldMap ((<> newline) . TB.fromText) (postingsAsLines onelineamounts $ tpostings t) + <> newline + where + descriptionline = T.stripEnd $ T.concat [date, status, code, desc, samelinecomment] + date = showDate (tdate t) <> maybe "" (("="<>) . showDate) (tdate2 t) + status | tstatus t == Cleared = " *" + | tstatus t == Pending = " !" + | otherwise = "" + code = if T.null (tcode t) then "" else wrap " (" ")" $ tcode t + desc = if T.null d then "" else " " <> d where d = tdescription t + (samelinecomment, newlinecomments) = + case renderCommentLines (tcomment t) of [] -> ("",[]) + c:cs -> (c,cs) + newline = TB.singleton '\n' -- | Render a transaction or posting's comment as indented, semicolon-prefixed comment lines. -- The first line (unless empty) will have leading space, subsequent lines will have a larger indent. -renderCommentLines :: Text -> [String] +renderCommentLines :: Text -> [Text] renderCommentLines t = - case lines $ T.unpack t of + case T.lines t of [] -> [] - [l] -> [(commentSpace . comment) l] -- single-line comment + [l] -> [commentSpace $ comment l] -- single-line comment ("":ls) -> "" : map (lineIndent . comment) ls -- multi-line comment with empty first line - (l:ls) -> (commentSpace . comment) l : map (lineIndent . comment) ls + (l:ls) -> commentSpace (comment l) : map (lineIndent . comment) ls where - comment = ("; "++) + comment = ("; "<>) -- | Given a transaction and its postings, render the postings, suitable -- for `print` output. Normally this output will be valid journal syntax which @@ -214,7 +219,7 @@ renderCommentLines t = -- Posting amounts will be aligned with each other, starting about 4 columns -- beyond the widest account name (see postingAsLines for details). -- -postingsAsLines :: Bool -> [Posting] -> [String] +postingsAsLines :: Bool -> [Posting] -> [Text] postingsAsLines onelineamounts ps = concatMap (postingAsLines False onelineamounts ps) ps -- | Render one posting, on one or more lines, suitable for `print` output. @@ -236,41 +241,55 @@ postingsAsLines onelineamounts ps = concatMap (postingAsLines False onelineamoun -- increased if needed to match the posting with the longest account name. -- This is used to align the amounts of a transaction's postings. -- -postingAsLines :: Bool -> Bool -> [Posting] -> Posting -> [String] -postingAsLines elideamount onelineamounts pstoalignwith p = concat [ - postingblock - ++ newlinecomments - | postingblock <- postingblocks] +postingAsLines :: Bool -> Bool -> [Posting] -> Posting -> [Text] +postingAsLines elideamount onelineamounts pstoalignwith p = + concatMap (++ newlinecomments) postingblocks where - postingblocks = [map rstrip $ lines $ concatTopPadded [statusandaccount, " ", amt, assertion, samelinecomment] | amt <- shownAmounts] - assertion = maybe "" ((' ':).showBalanceAssertion) $ pbalanceassertion p - statusandaccount = lineIndent $ fitString (Just $ minwidth) Nothing False True $ pstatusandacct p - where - -- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned - minwidth = maximum $ map ((2+) . textWidth . T.pack . pacctstr) pstoalignwith - pstatusandacct p' = pstatusprefix p' ++ pacctstr p' - pstatusprefix p' | null s = "" - | otherwise = s ++ " " - where s = show $ pstatus p' - pacctstr p' = showAccountName Nothing (ptype p') (paccount p') + -- This needs to be converted to strict Text in order to strip trailing + -- spaces. This adds a small amount of inefficiency, and the only difference + -- is whether there are trailing spaces in print (and related) reports. This + -- could be removed and we could just keep everything as a Text Builder, but + -- would require adding trailing spaces to 42 failing tests. + postingblocks = [map T.stripEnd . T.lines . TL.toStrict $ + render [ textCell BottomLeft statusandaccount + , textCell BottomLeft " " + , Cell BottomLeft [amt] + , Cell BottomLeft [assertion] + , textCell BottomLeft samelinecomment + ] + | amt <- shownAmounts] + render = renderRow def{tableBorders=False, borderSpaces=False} . Group NoLine . map Header + assertion = maybe mempty ((WideBuilder (TB.singleton ' ') 1 <>).showBalanceAssertion) $ pbalanceassertion p + statusandaccount = lineIndent . fitText (Just $ minwidth) Nothing False True $ pstatusandacct p + where + -- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned + minwidth = maximum $ map ((2+) . textWidth . pacctstr) pstoalignwith + pstatusandacct p' = pstatusprefix p' <> pacctstr p' + pstatusprefix p' = case pstatus p' of + Unmarked -> "" + s -> T.pack (show s) <> " " + pacctstr p' = showAccountName Nothing (ptype p') (paccount p') -- currently prices are considered part of the amount string when right-aligning amounts shownAmounts - | elideamount = [""] - | onelineamounts = [fst . showMixedOneLineUnnormalised showAmount (Just amtwidth) Nothing False $ pamount p] - | null (amounts $ pamount p) = [""] - | otherwise = lines . fst . showMixedUnnormalised showAmount (Just amtwidth) Nothing False $ pamount p + | elideamount || null (amounts $ pamount p) = [mempty] + | otherwise = showMixedAmountLinesB displayopts $ pamount p where - amtwidth = maximum $ 12 : map (snd . showMixedUnnormalised showAmount Nothing Nothing False . pamount) pstoalignwith -- min. 12 for backwards compatibility + displayopts = noColour{displayOneLine=onelineamounts, displayMinWidth = Just amtwidth, displayNormalised=False} + amtwidth = maximum $ 12 : map (wbWidth . showMixedAmountB displayopts{displayMinWidth=Nothing} . pamount) pstoalignwith -- min. 12 for backwards compatibility (samelinecomment, newlinecomments) = case renderCommentLines (pcomment p) of [] -> ("",[]) c:cs -> (c,cs) -- | Render a balance assertion, as the =[=][*] symbol and expected amount. -showBalanceAssertion :: BalanceAssertion -> [Char] +showBalanceAssertion :: BalanceAssertion -> WideBuilder showBalanceAssertion BalanceAssertion{..} = - "=" ++ ['=' | batotal] ++ ['*' | bainclusive] ++ " " ++ showAmountWithZeroCommodity baamount + singleton '=' <> eq <> ast <> singleton ' ' <> showAmountB def{displayZeroCommodity=True} baamount + where + eq = if batotal then singleton '=' else mempty + ast = if bainclusive then singleton '*' else mempty + singleton c = WideBuilder (TB.singleton c) 1 -- | Render a posting, simply. Used in balance assertion errors. -- showPostingLine p = @@ -286,33 +305,27 @@ showBalanceAssertion BalanceAssertion{..} = -- | Render a posting, at the appropriate width for aligning with -- its siblings if any. Used by the rewrite command. -showPostingLines :: Posting -> [String] +showPostingLines :: Posting -> [Text] showPostingLines p = postingAsLines False False ps p where ps | Just t <- ptransaction p = tpostings t | otherwise = [p] -- | Prepend a suitable indent for a posting (or transaction/posting comment) line. -lineIndent :: String -> String -lineIndent = (" "++) +lineIndent :: Text -> Text +lineIndent = (" "<>) -- | Prepend the space required before a same-line comment. -commentSpace :: String -> String -commentSpace = (" "++) +commentSpace :: Text -> Text +commentSpace = (" "<>) -- | Show an account name, clipped to the given width if any, and -- appropriately bracketed/parenthesised for the given posting type. -showAccountName :: Maybe Int -> PostingType -> AccountName -> String +showAccountName :: Maybe Int -> PostingType -> AccountName -> Text showAccountName w = fmt where - fmt RegularPosting = maybe id take w . T.unpack - fmt VirtualPosting = parenthesise . maybe id (takeEnd . subtract 2) w . T.unpack - fmt BalancedVirtualPosting = bracket . maybe id (takeEnd . subtract 2) w . T.unpack - -parenthesise :: String -> String -parenthesise s = "("++s++")" - -bracket :: String -> String -bracket s = "["++s++"]" + fmt RegularPosting = maybe id T.take w + fmt VirtualPosting = wrap "(" ")" . maybe id (T.takeEnd . subtract 2) w + fmt BalancedVirtualPosting = wrap "[" "]" . maybe id (T.takeEnd . subtract 2) w hasRealPostings :: Transaction -> Bool hasRealPostings = not . null . realPostings @@ -356,7 +369,7 @@ transactionCheckBalanced mstyles t = errs -- check for mixed signs, detecting nonzeros at display precision canonicalise = maybe id canonicaliseMixedAmount mstyles - signsOk ps = + signsOk ps = case filter (not.mixedAmountLooksZero) $ map (canonicalise.mixedAmountCost.pamount) ps of nonzeros | length nonzeros >= 2 -> length (nubSort $ mapMaybe isNegativeMixedAmount nonzeros) > 1 @@ -427,7 +440,9 @@ transactionBalanceError t errs = annotateErrorWithTransaction :: Transaction -> String -> String annotateErrorWithTransaction t s = - unlines [showGenericSourcePos $ tsourcepos t, s, rstrip $ showTransaction t] + unlines [ showGenericSourcePos $ tsourcepos t, s + , T.unpack . T.stripEnd $ showTransaction t + ] -- | Infer up to one missing amount for this transactions's real postings, and -- likewise for its balanced virtual postings, if needed; or return an error @@ -540,8 +555,9 @@ priceInferrerFor t pt = inferprice = p{pamount=Mixed [a{aprice=Just conversionprice}], poriginal=Just $ originalPosting p} where fromcommodity = head $ filter (`elem` sumcommodities) pcommodities -- these heads are ugly but should be safe + totalpricesign = if aquantity a < 0 then negate else id conversionprice - | fromcount==1 = TotalPrice $ abs toamount `withPrecision` NaturalPrecision + | fromcount==1 = TotalPrice $ totalpricesign (abs toamount) `withPrecision` NaturalPrecision | otherwise = UnitPrice $ abs unitprice `withPrecision` unitprecision where fromcount = length $ filter ((==fromcommodity).acommodity) pamounts @@ -580,13 +596,19 @@ postingSetTransaction t p = p{ptransaction=Just t} transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction transactionTransformPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps} +-- | Apply a specified costing and valuation to this transaction's amounts, +-- using the provided price oracle, commodity styles, and reference dates. +-- See amountApplyValuation and amountCost. +transactionApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Transaction -> Transaction +transactionApplyCostValuation priceoracle styles periodlast today cost v = + transactionTransformPostings (postingApplyCostValuation priceoracle styles periodlast today cost v) + -- | 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. -transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Transaction -> ValuationType -> Transaction -transactionApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod t v = - transactionTransformPostings (\p -> postingApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod p v) t +-- the provided price oracle, commodity styles, and reference dates. +-- See amountApplyValuation. +transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction +transactionApplyValuation priceoracle styles periodlast today v = + transactionTransformPostings (postingApplyValuation priceoracle styles periodlast today v) -- | Convert this transaction's amounts to cost, and apply the appropriate amount styles. transactionToCost :: M.Map CommoditySymbol AmountStyle -> Transaction -> Transaction @@ -600,6 +622,21 @@ transactionApplyAliases aliases t = Right ps -> Right $ txnTieKnot $ t{tpostings=ps} Left err -> Left err +-- | Apply a transformation to a transaction's postings. +transactionMapPostings :: (Posting -> Posting) -> Transaction -> Transaction +transactionMapPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps} + +-- | Apply a transformation to a transaction's posting amounts. +transactionMapPostingAmounts :: (Amount -> Amount) -> Transaction -> Transaction +transactionMapPostingAmounts f = transactionMapPostings (postingTransformAmount (mapMixedAmount f)) + +-- | The file path from which this transaction was parsed. +transactionFile :: Transaction -> FilePath +transactionFile Transaction{tsourcepos} = + case tsourcepos of + GenericSourcePos f _ _ -> f + JournalSourcePos f _ -> f + -- tests tests_Transaction :: TestTree @@ -678,7 +715,7 @@ tests_Transaction = Right nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` usd 5]} (fst <$> inferBalancingAmount M.empty nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` (eur 3 @@ usd 4), "c" `post` missingamt]}) @?= Right nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` (eur 3 @@ usd 4), "c" `post` usd 1]} - + , tests "showTransaction" [ test "null transaction" $ showTransaction nulltransaction @?= "0000-01-01\n\n" , test "non-null transaction" $ showTransaction @@ -701,7 +738,7 @@ tests_Transaction = } ] } @?= - unlines + T.unlines [ "2012-05-14=2012-05-15 (code) desc ; tcomment1" , " ; tcomment2" , " * a $1.00" @@ -727,7 +764,7 @@ tests_Transaction = , posting {paccount = "assets:checking", pamount = Mixed [usd (-47.18)], ptransaction = Just t} ] in showTransaction t) @?= - (unlines + (T.unlines [ "2007-01-28 coopportunity" , " expenses:food:groceries $47.18" , " assets:checking $-47.18" @@ -750,7 +787,7 @@ tests_Transaction = [ posting {paccount = "expenses:food:groceries", pamount = Mixed [usd 47.18]} , posting {paccount = "assets:checking", pamount = Mixed [usd (-47.19)]} ])) @?= - (unlines + (T.unlines [ "2007-01-28 coopportunity" , " expenses:food:groceries $47.18" , " assets:checking $-47.19" @@ -771,7 +808,7 @@ tests_Transaction = "" [] [posting {paccount = "expenses:food:groceries", pamount = missingmixedamt}])) @?= - (unlines ["2007-01-28 coopportunity", " expenses:food:groceries", ""]) + (T.unlines ["2007-01-28 coopportunity", " expenses:food:groceries", ""]) , test "show a transaction with a priced commodityless amount" $ (showTransaction (txnTieKnot $ @@ -789,7 +826,7 @@ tests_Transaction = [ posting {paccount = "a", pamount = Mixed [num 1 `at` (usd 2 `withPrecision` Precision 0)]} , posting {paccount = "b", pamount = missingmixedamt} ])) @?= - (unlines ["2010-01-01 x", " a 1 @ $2", " b", ""]) + (T.unlines ["2010-01-01 x", " a 1 @ $2", " b", ""]) ] , tests "balanceTransaction" [ test "detect unbalanced entry, sign error" $ @@ -896,7 +933,7 @@ tests_Transaction = "" [] [ posting {paccount = "a", pamount = Mixed [usd 1 @@ eur 1]} - , posting {paccount = "a", pamount = Mixed [usd (-2) @@ eur 1]} + , posting {paccount = "a", pamount = Mixed [usd (-2) @@ eur (-1)]} ]) ] , tests "isTransactionBalanced" [ diff --git a/Hledger/Data/TransactionModifier.hs b/Hledger/Data/TransactionModifier.hs index 4e31b8e..3a09b03 100644 --- a/Hledger/Data/TransactionModifier.hs +++ b/Hledger/Data/TransactionModifier.hs @@ -26,7 +26,7 @@ import Hledger.Data.Amount import Hledger.Data.Transaction import Hledger.Query import Hledger.Data.Posting (commentJoin, commentAddTag) -import Hledger.Utils.Debug +import Hledger.Utils -- $setup -- >>> :set -XOverloadedStrings @@ -62,7 +62,8 @@ modifyTransactions d tmods ts = do -- postings when certain other postings are present. -- -- >>> t = nulltransaction{tpostings=["ping" `post` usd 1]} --- >>> test = either putStr (putStr.showTransaction) . fmap ($ t) . transactionModifierToFunction nulldate +-- >>> import qualified Data.Text.IO as T +-- >>> test = either putStr (T.putStr.showTransaction) . fmap ($ t) . transactionModifierToFunction nulldate -- >>> test $ TransactionModifier "" ["pong" `post` usd 2] -- 0000-01-01 -- ping $1.00 @@ -119,7 +120,7 @@ tmPostingRuleToFunction querytxt pr = -- Approach 1: convert to a unit price and increase the display precision slightly -- Mixed as = dbg6 "multipliedamount" $ n `multiplyMixedAmount` mixedAmountTotalPriceToUnitPrice matchedamount -- Approach 2: multiply the total price (keeping it positive) as well as the quantity - Mixed as = dbg6 "multipliedamount" $ n `multiplyMixedAmountAndPrice` matchedamount + Mixed as = dbg6 "multipliedamount" $ n `multiplyMixedAmount` matchedamount in case acommodity pramount of "" -> Mixed as @@ -137,7 +138,7 @@ postingRuleMultiplier p = renderPostingCommentDates :: Posting -> Posting renderPostingCommentDates p = p { pcomment = comment' } where - dates = T.concat $ catMaybes [T.pack . showDate <$> pdate p, ("=" <>) . T.pack . showDate <$> pdate2 p] + dates = T.concat $ catMaybes [showDate <$> pdate p, ("=" <>) . showDate <$> pdate2 p] comment' | T.null dates = pcomment p - | otherwise = ("[" <> dates <> "]") `commentJoin` pcomment p + | otherwise = (wrap "[" "]" dates) `commentJoin` pcomment p diff --git a/Hledger/Data/Types.hs b/Hledger/Data/Types.hs index 020456c..1afac7e 100644 --- a/Hledger/Data/Types.hs +++ b/Hledger/Data/Types.hs @@ -132,6 +132,8 @@ data Interval = instance Default Interval where def = NoInterval +type Payee = Text + type AccountName = Text data AccountType = @@ -176,16 +178,16 @@ instance ToMarkup Quantity -- | An amount's per-unit or total cost/selling price in another -- commodity, as recorded in the journal entry eg with @ or @@. -- Docs call this "transaction price". The amount is always positive. -data AmountPrice = UnitPrice Amount | TotalPrice Amount +data AmountPrice = UnitPrice !Amount | TotalPrice !Amount deriving (Eq,Ord,Generic,Show) -- | Display style for an amount. data AmountStyle = AmountStyle { - ascommodityside :: Side, -- ^ does the symbol appear on the left or the right ? - ascommodityspaced :: Bool, -- ^ space between symbol and quantity ? - asprecision :: !AmountPrecision, -- ^ number of digits displayed after the decimal point - asdecimalpoint :: Maybe Char, -- ^ character used as decimal point: period or comma. Nothing means "unspecified, use default" - asdigitgroups :: Maybe DigitGroupStyle -- ^ style for displaying digit groups, if any + ascommodityside :: !Side, -- ^ does the symbol appear on the left or the right ? + ascommodityspaced :: !Bool, -- ^ space between symbol and quantity ? + asprecision :: !AmountPrecision, -- ^ number of digits displayed after the decimal point + asdecimalpoint :: !(Maybe Char), -- ^ character used as decimal point: period or comma. Nothing means "unspecified, use default" + asdigitgroups :: !(Maybe DigitGroupStyle) -- ^ style for displaying digit groups, if any } deriving (Eq,Ord,Read,Generic) instance Show AmountStyle where @@ -197,6 +199,10 @@ instance Show AmountStyle where (show asdecimalpoint) (show asdigitgroups) +-- | The "display precision" for a hledger amount, by which we mean +-- the number of decimal digits to display to the right of the decimal mark. +-- This can be from 0 to 255 digits (the maximum supported by the Decimal library), +-- or NaturalPrecision meaning "show all significant decimal digits". data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (Eq,Ord,Read,Show,Generic) -- | A style for displaying digit groups in the integer part of a @@ -205,7 +211,7 @@ data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (Eq,Ord,Read -- 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]. -data DigitGroupStyle = DigitGroups Char [Word8] +data DigitGroupStyle = DigitGroups !Char ![Word8] deriving (Eq,Ord,Read,Show,Generic) type CommoditySymbol = Text @@ -216,12 +222,12 @@ data Commodity = Commodity { } deriving (Show,Eq,Generic) --,Ord) data Amount = Amount { - acommodity :: CommoditySymbol, -- commodity symbol, or special value "AUTO" - aquantity :: Quantity, -- numeric quantity, or zero in case of "AUTO" - aismultiplier :: Bool, -- ^ kludge: a flag marking this amount and posting as a multiplier - -- in a TMPostingRule. In a regular Posting, should always be false. - astyle :: AmountStyle, - aprice :: Maybe AmountPrice -- ^ the (fixed, transaction-specific) price for this amount, if any + acommodity :: !CommoditySymbol, -- commodity symbol, or special value "AUTO" + aquantity :: !Quantity, -- numeric quantity, or zero in case of "AUTO" + aismultiplier :: !Bool, -- ^ kludge: a flag marking this amount and posting as a multiplier + -- in a TMPostingRule. In a regular Posting, should always be false. + astyle :: !AmountStyle, + aprice :: !(Maybe AmountPrice) -- ^ the (fixed, transaction-specific) price for this amount, if any } deriving (Eq,Ord,Generic,Show) newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Generic,Show) @@ -453,6 +459,7 @@ data Journal = Journal { ,jparsetimeclockentries :: [TimeclockEntry] -- ^ timeclock sessions which have not been clocked out ,jincludefilestack :: [FilePath] -- principal data + ,jdeclaredpayees :: [(Payee,PayeeDeclarationInfo)] -- ^ Payees declared by payee directives, in parse order (after journal finalisation) ,jdeclaredaccounts :: [(AccountName,AccountDeclarationInfo)] -- ^ Accounts declared by account directives, in parse order (after journal finalisation) ,jdeclaredaccounttypes :: M.Map AccountType [AccountName] -- ^ Accounts whose type has been declared in account directives (usually 5 top-level accounts) ,jglobalcommoditystyles :: M.Map CommoditySymbol AmountStyle -- ^ per-commodity display styles declared globally, eg by command line option or import command @@ -482,6 +489,17 @@ type ParsedJournal = Journal -- The --output-format option selects one of these for output. type StorageFormat = String +-- | Extra information found in a payee directive. +data PayeeDeclarationInfo = PayeeDeclarationInfo { + pdicomment :: Text -- ^ any comment lines following the payee directive + ,pditags :: [Tag] -- ^ tags extracted from the comment, if any +} deriving (Eq,Show,Generic) + +nullpayeedeclarationinfo = PayeeDeclarationInfo { + pdicomment = "" + ,pditags = [] +} + -- | Extra information about an account that can be derived from -- its account directive (and the other account directives). data AccountDeclarationInfo = AccountDeclarationInfo { diff --git a/Hledger/Data/Valuation.hs b/Hledger/Data/Valuation.hs index 23d19fe..28110db 100644 --- a/Hledger/Data/Valuation.hs +++ b/Hledger/Data/Valuation.hs @@ -13,12 +13,13 @@ looking up historical market prices (exchange rates) between commodities. {-# LANGUAGE DeriveGeneric #-} module Hledger.Data.Valuation ( - ValuationType(..) + Costing(..) + ,ValuationType(..) ,PriceOracle ,journalPriceOracle - ,unsupportedValueThenError -- ,amountApplyValuation -- ,amountValueAtDate + ,mixedAmountApplyCostValuation ,mixedAmountApplyValuation ,mixedAmountValueAtDate ,marketPriceReverse @@ -34,7 +35,6 @@ import Data.List (partition, intercalate, sortBy) import Data.List.Extra (nubSortBy) import qualified Data.Map as M import qualified Data.Set as S -import Data.Maybe ( fromMaybe ) import qualified Data.Text as T import Data.Time.Calendar (Day, fromGregorian) import Data.MemoUgly (memo) @@ -46,20 +46,24 @@ import Hledger.Data.Types import Hledger.Data.Amount import Hledger.Data.Dates (nulldate) import Hledger.Data.Commodity (showCommoditySymbol) +import Data.Maybe (fromMaybe) +import Text.Printf (printf) ------------------------------------------------------------------------------ -- Types +-- | Whether to convert amounts to cost. +data Costing = Cost | NoCost + deriving (Show,Eq) + -- | What kind of value conversion should be done on amounts ? --- CLI: --value=cost|then|end|now|DATE[,COMM] +-- CLI: --value=then|end|now|DATE[,COMM] data ValuationType = - AtCost (Maybe CommoditySymbol) -- ^ convert to cost commodity using transaction prices, then optionally to given commodity using market prices at posting date - | AtThen (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using market prices at each posting's date + AtThen (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using market prices at each posting's date | AtEnd (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using market prices at period end(s) | AtNow (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using current market prices | AtDate Day (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using market prices on some date - | AtDefault (Maybe CommoditySymbol) -- ^ works like AtNow in single period reports, like AtEnd in multiperiod reports deriving (Show,Eq) -- | A price oracle is a magic memoising function that efficiently @@ -95,13 +99,25 @@ priceDirectiveToMarketPrice PriceDirective{..} = ------------------------------------------------------------------------------ -- Converting things to value +-- | Apply a specified costing and valuation to this mixed amount, +-- using the provided price oracle, commodity styles, and reference dates. +-- Costing is done first if requested, and after that any valuation. +-- See amountApplyValuation and amountCost. +mixedAmountApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> Costing -> Maybe ValuationType -> MixedAmount -> MixedAmount +mixedAmountApplyCostValuation priceoracle styles periodlast today postingdate cost v = + valuation . costing + where + valuation = maybe id (mixedAmountApplyValuation priceoracle styles periodlast today postingdate) v + costing = case cost of + Cost -> styleMixedAmount styles . mixedAmountCost + NoCost -> id + -- | Apply a specified valuation to this mixed amount, using the --- provided price oracle, commodity styles, reference dates, and --- whether this is for a multiperiod report or not. +-- provided price oracle, commodity styles, and reference dates. -- See amountApplyValuation. -mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount -mixedAmountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v (Mixed as) = - Mixed $ map (amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v) as +mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount +mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = + mapMixedAmount (amountApplyValuation priceoracle styles periodlast today postingdate v) -- | Apply a specified valuation to this amount, using the provided -- price oracle, reference dates, and whether this is for a @@ -115,7 +131,7 @@ mixedAmountApplyValuation priceoracle styles periodlast mreportlast today ismult -- -- - a fixed date specified by the ValuationType itself -- (--value=DATE). --- +-- -- - the provided "period end" date - this is typically the last day -- of a subperiod (--value=end with a multi-period report), or of -- the specified report period or the journal (--value=end with a @@ -127,29 +143,17 @@ mixedAmountApplyValuation priceoracle styles periodlast mreportlast today ismult -- - the provided "today" date - (--value=now, or -V/X with no report -- end date). -- --- Note --value=then is not supported by this function, and will cause an error; --- use postingApplyValuation for that. --- -- This is all a bit complicated. See the reference doc at -- https://hledger.org/hledger.html#effect-of-valuation-on-reports -- (hledger_options.m4.md "Effect of valuation on reports"), and #1083. -- -amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> Amount -> Amount -amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v a = +amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> Amount -> Amount +amountApplyValuation priceoracle styles periodlast today postingdate v a = case v of - AtCost Nothing -> styleAmount styles $ amountCost a - AtCost mc -> amountValueAtDate priceoracle styles mc periodlast $ styleAmount styles $ amountCost a - AtThen _mc -> error' unsupportedValueThenError -- PARTIAL: - -- amountValueAtDate priceoracle styles mc periodlast a -- posting date unknown, handle like AtEnd - AtEnd mc -> amountValueAtDate priceoracle styles mc periodlast a - AtNow mc -> amountValueAtDate priceoracle styles mc today a - AtDefault mc | ismultiperiod -> amountValueAtDate priceoracle styles mc periodlast a - AtDefault mc -> amountValueAtDate priceoracle styles mc (fromMaybe today mreportlast) a - AtDate d mc -> amountValueAtDate priceoracle styles mc d a - --- | Standard error message for a report not supporting --value=then. -unsupportedValueThenError :: String -unsupportedValueThenError = "Sorry, --value=then is not yet supported for this kind of report." + AtThen mc -> amountValueAtDate priceoracle styles mc postingdate a + AtEnd mc -> amountValueAtDate priceoracle styles mc periodlast a + AtNow mc -> amountValueAtDate priceoracle styles mc today a + AtDate d mc -> amountValueAtDate priceoracle styles mc d a -- | Find the market value of each component amount in the given -- commodity, or its default valuation commodity, at the given @@ -157,7 +161,7 @@ unsupportedValueThenError = "Sorry, --value=then is not yet supported for this k -- When market prices available on that date are not sufficient to -- calculate the value, amounts are left unchanged. mixedAmountValueAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount -mixedAmountValueAtDate priceoracle styles mc d (Mixed as) = Mixed $ map (amountValueAtDate priceoracle styles mc d) as +mixedAmountValueAtDate priceoracle styles mc d = mapMixedAmount (amountValueAtDate priceoracle styles mc d) -- | Find the market value of this amount in the given valuation -- commodity if any, otherwise the default valuation commodity, at the @@ -220,7 +224,7 @@ priceLookup makepricegraph d from mto = Just to -> -- We have a commodity to convert to. Find the most direct price available, -- according to the rules described in makePriceGraph. - let msg = "seeking " ++ pshowedge' "" from to ++ " price" + let msg = printf "seeking %s to %s price" (showCommoditySymbol from) (showCommoditySymbol to) in case (traceAt 2 (msg++" using forward prices") $ pricesShortestPath from to forwardprices) @@ -285,20 +289,25 @@ data PriceGraph = PriceGraph { -- USD->EUR price and one EUR->USD price. pricesShortestPath :: CommoditySymbol -> CommoditySymbol -> [Edge] -> Maybe Path pricesShortestPath start end edges = - dbg2 ("shortest "++pshowedge' "" start end++" price path") $ + -- at --debug=2 +, print the pretty path and also the detailed prices + let label = printf "shortest path from %s to %s: " (showCommoditySymbol start) (showCommoditySymbol end) in + fmap (dbg2With (("price chain:\n"++).pshow)) $ + dbg2With ((label++).(maybe "none found" (pshowpath ""))) $ + find [([],edges)] + where -- Find the first and shortest complete path using a breadth-first search. find :: [(Path,[Edge])] -> Maybe Path find paths = case concatMap extend paths of [] -> Nothing - _ | iteration > maxiterations -> - trace ("gave up searching for a price chain after "++show maxiterations++" iterations, please report a bug") + _ | pathlength > maxpathlength -> + trace ("gave up searching for a price chain at length "++show maxpathlength++", please report a bug") Nothing where - iteration = 1 + maybe 0 (length . fst) (headMay paths) - maxiterations = 1000 + pathlength = 2 + maybe 0 (length . fst) (headMay paths) + maxpathlength = 1000 paths' -> case completepaths of p:_ -> Just p -- the left-most complete path at this length @@ -329,7 +338,7 @@ pshowpath label = \case p@(e:_) -> prefix label $ pshownode (mpfrom e) ++ ">" ++ intercalate ">" (map (pshownode . mpto) p) -- pshowedges label = prefix label . intercalate ", " . map (pshowedge "") -- pshowedge label MarketPrice{..} = pshowedge' label mpfrom mpto -pshowedge' label from to = prefix label $ pshownode from ++ ">" ++ pshownode to +-- pshowedge' label from to = prefix label $ pshownode from ++ ">" ++ pshownode to pshownode = T.unpack . showCommoditySymbol prefix l = if null l then (""++) else ((l++": ")++) @@ -356,7 +365,7 @@ prefix l = if null l then (""++) else ((l++": ")++) -- -- 1. A *declared market price* or *inferred market price*: -- A's latest market price in B on or before the valuation date --- as declared by a P directive, or (with the `--infer-value` flag) +-- as declared by a P directive, or (with the `--infer-market-price` flag) -- inferred from transaction prices. -- -- 2. A *reverse market price*: @@ -381,7 +390,7 @@ prefix l = if null l then (""++) else ((l++": ")++) -- prices before the valuation date.) -- -- 3. If there are no P directives at all (any commodity or date), and --- the `--infer-value` flag is used, then the price commodity from +-- the `--infer-market-price` flag is used, then the price commodity from -- the latest transaction price for A on or before valuation date." -- makePriceGraph :: [MarketPrice] -> [MarketPrice] -> Day -> PriceGraph @@ -420,7 +429,7 @@ makePriceGraph alldeclaredprices allinferredprices d = where ps | not $ null visibledeclaredprices = visibledeclaredprices | not $ null alldeclaredprices = alldeclaredprices - | otherwise = visibleinferredprices -- will be null without --infer-value + | otherwise = visibleinferredprices -- will be null without --infer-market-price -- | Given a list of P-declared market prices in parse order and a -- list of transaction-inferred market prices in parse order, select diff --git a/Hledger/Query.hs b/Hledger/Query.hs index 5f724c4..94f62a0 100644 --- a/Hledger/Query.hs +++ b/Hledger/Query.hs @@ -44,6 +44,8 @@ module Hledger.Query ( inAccountQuery, -- * matching matchesTransaction, + matchesDescription, + matchesPayeeWIP, matchesPosting, matchesAccount, matchesMixedAmount, @@ -66,6 +68,7 @@ import Data.Maybe (fromMaybe, isJust, mapMaybe) #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid ((<>)) #endif +import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar (Day, fromGregorian ) import Safe (readDef, readMay, maximumByMay, maximumMay, minimumMay) @@ -107,11 +110,11 @@ data Query = Any -- ^ always match instance Default Query where def = Any -- | Construct a payee tag -payeeTag :: Maybe String -> Either RegexError Query +payeeTag :: Maybe Text -> Either RegexError Query payeeTag = fmap (Tag (toRegexCI' "payee")) . maybe (pure Nothing) (fmap Just . toRegexCI) -- | Construct a note tag -noteTag :: Maybe String -> Either RegexError Query +noteTag :: Maybe Text -> Either RegexError Query noteTag = fmap (Tag (toRegexCI' "note")) . maybe (pure Nothing) (fmap Just . toRegexCI) -- | Construct a generated-transaction tag @@ -262,11 +265,11 @@ parseQueryTerm d (T.stripPrefix "not:" -> Just s) = Right (Left m) -> Right $ Left $ Not m Right (Right _) -> Right $ Left Any -- not:somequeryoption will be ignored Left err -> Left err -parseQueryTerm _ (T.stripPrefix "code:" -> Just s) = Left . Code <$> toRegexCI (T.unpack s) -parseQueryTerm _ (T.stripPrefix "desc:" -> Just s) = Left . Desc <$> toRegexCI (T.unpack s) -parseQueryTerm _ (T.stripPrefix "payee:" -> Just s) = Left <$> payeeTag (Just $ T.unpack s) -parseQueryTerm _ (T.stripPrefix "note:" -> Just s) = Left <$> noteTag (Just $ T.unpack s) -parseQueryTerm _ (T.stripPrefix "acct:" -> Just s) = Left . Acct <$> toRegexCI (T.unpack s) +parseQueryTerm _ (T.stripPrefix "code:" -> Just s) = Left . Code <$> toRegexCI s +parseQueryTerm _ (T.stripPrefix "desc:" -> Just s) = Left . Desc <$> toRegexCI s +parseQueryTerm _ (T.stripPrefix "payee:" -> Just s) = Left <$> payeeTag (Just s) +parseQueryTerm _ (T.stripPrefix "note:" -> Just s) = Left <$> noteTag (Just s) +parseQueryTerm _ (T.stripPrefix "acct:" -> Just s) = Left . Acct <$> toRegexCI s parseQueryTerm d (T.stripPrefix "date2:" -> Just s) = case parsePeriodExpr d s of Left e -> Left $ "\"date2:"++T.unpack s++"\" gave a "++showDateParseError e Right (_,span) -> Right $ Left $ Date2 span @@ -283,7 +286,7 @@ parseQueryTerm _ (T.stripPrefix "depth:" -> Just s) | otherwise = Left "depth: should have a positive number" where n = readDef 0 (T.unpack s) -parseQueryTerm _ (T.stripPrefix "cur:" -> Just s) = Left . Sym <$> toRegexCI ('^' : T.unpack s ++ "$") -- support cur: as an alias +parseQueryTerm _ (T.stripPrefix "cur:" -> Just s) = Left . Sym <$> toRegexCI ("^" <> s <> "$") -- support cur: as an alias parseQueryTerm _ (T.stripPrefix "tag:" -> Just s) = Left <$> parseTag s parseQueryTerm _ "" = Right $ Left $ Any parseQueryTerm d s = parseQueryTerm d $ defaultprefix<>":"<>s @@ -322,20 +325,19 @@ parseAmountQueryTerm amtarg = (parse ">" -> Just q) -> Right (AbsGt ,q) (parse "=" -> Just q) -> Right (AbsEq ,q) (parse "" -> Just q) -> Right (AbsEq ,q) - _ -> Left $ - "could not parse as a comparison operator followed by an optionally-signed number: " - ++ T.unpack amtarg + _ -> Left . T.unpack $ + "could not parse as a comparison operator followed by an optionally-signed number: " <> amtarg where -- Strip outer whitespace from the text, require and remove the -- specified prefix, remove all whitespace from the remainder, and -- read it as a simple integer or decimal if possible. parse :: T.Text -> T.Text -> Maybe Quantity - parse p s = (T.stripPrefix p . T.strip) s >>= readMay . filter (not.(==' ')) . T.unpack + parse p s = (T.stripPrefix p . T.strip) s >>= readMay . T.unpack . T.filter (/=' ') parseTag :: T.Text -> Either RegexError Query parseTag s = do - tag <- toRegexCI . T.unpack $ if T.null v then s else n - body <- if T.null v then pure Nothing else Just <$> toRegexCI (tail $ T.unpack v) + tag <- toRegexCI $ if T.null v then s else n + body <- if T.null v then pure Nothing else Just <$> toRegexCI (T.tail v) return $ Tag tag body where (n,v) = T.break (=='=') s @@ -554,7 +556,7 @@ matchesAccount (None) _ = False matchesAccount (Not m) a = not $ matchesAccount m a matchesAccount (Or ms) a = any (`matchesAccount` a) ms matchesAccount (And ms) a = all (`matchesAccount` a) ms -matchesAccount (Acct r) a = regexMatch r $ T.unpack a -- XXX pack +matchesAccount (Acct r) a = regexMatchText r a matchesAccount (Depth d) a = accountNameLevel a <= d matchesAccount (Tag _ _) _ = False matchesAccount _ _ = True @@ -564,7 +566,7 @@ matchesMixedAmount q (Mixed []) = q `matchesAmount` nullamt matchesMixedAmount q (Mixed as) = any (q `matchesAmount`) as matchesCommodity :: Query -> CommoditySymbol -> Bool -matchesCommodity (Sym r) = regexMatch r . T.unpack +matchesCommodity (Sym r) = regexMatchText r matchesCommodity _ = const True -- | Does the match expression match this (simple) amount ? @@ -603,10 +605,10 @@ matchesPosting (Any) _ = True matchesPosting (None) _ = False matchesPosting (Or qs) p = any (`matchesPosting` p) qs matchesPosting (And qs) p = all (`matchesPosting` p) qs -matchesPosting (Code r) p = regexMatch r $ maybe "" (T.unpack . tcode) $ ptransaction p -matchesPosting (Desc r) p = regexMatch r $ maybe "" (T.unpack . tdescription) $ ptransaction p +matchesPosting (Code r) p = maybe False (regexMatchText r . tcode) $ ptransaction p +matchesPosting (Desc r) p = maybe False (regexMatchText r . tdescription) $ ptransaction p matchesPosting (Acct r) p = matches p || matches (originalPosting p) - where matches p = regexMatch r . T.unpack $ paccount p -- XXX pack + where matches = regexMatchText r . paccount matchesPosting (Date span) p = span `spanContainsDate` postingDate p matchesPosting (Date2 span) p = span `spanContainsDate` postingDate2 p matchesPosting (StatusQ s) p = postingStatus p == s @@ -615,8 +617,8 @@ matchesPosting q@(Depth _) Posting{paccount=a} = q `matchesAccount` a matchesPosting q@(Amt _ _) Posting{pamount=amt} = q `matchesMixedAmount` amt matchesPosting (Sym r) Posting{pamount=Mixed as} = any (matchesCommodity (Sym r)) $ map acommodity as matchesPosting (Tag n v) p = case (reString n, v) of - ("payee", Just v) -> maybe False (regexMatch v . T.unpack . transactionPayee) $ ptransaction p - ("note", Just v) -> maybe False (regexMatch v . T.unpack . transactionNote) $ ptransaction p + ("payee", Just v) -> maybe False (regexMatchText v . transactionPayee) $ ptransaction p + ("note", Just v) -> maybe False (regexMatchText v . transactionNote) $ ptransaction p (_, v) -> matchesTags n v $ postingAllTags p -- | Does the match expression match this transaction ? @@ -626,8 +628,8 @@ matchesTransaction (Any) _ = True matchesTransaction (None) _ = False matchesTransaction (Or qs) t = any (`matchesTransaction` t) qs matchesTransaction (And qs) t = all (`matchesTransaction` t) qs -matchesTransaction (Code r) t = regexMatch r $ T.unpack $ tcode t -matchesTransaction (Desc r) t = regexMatch r $ T.unpack $ tdescription t +matchesTransaction (Code r) t = regexMatchText r $ tcode t +matchesTransaction (Desc r) t = regexMatchText r $ tdescription t matchesTransaction q@(Acct _) t = any (q `matchesPosting`) $ tpostings t matchesTransaction (Date span) t = spanContainsDate span $ tdate t matchesTransaction (Date2 span) t = spanContainsDate span $ transactionDate2 t @@ -637,15 +639,42 @@ matchesTransaction q@(Amt _ _) t = any (q `matchesPosting`) $ tpostings t matchesTransaction (Depth d) t = any (Depth d `matchesPosting`) $ tpostings t matchesTransaction q@(Sym _) t = any (q `matchesPosting`) $ tpostings t matchesTransaction (Tag n v) t = case (reString n, v) of - ("payee", Just v) -> regexMatch v . T.unpack . transactionPayee $ t - ("note", Just v) -> regexMatch v . T.unpack . transactionNote $ t + ("payee", Just v) -> regexMatchText v $ transactionPayee t + ("note", Just v) -> regexMatchText v $ transactionNote t (_, v) -> matchesTags n v $ transactionAllTags t +-- | Does the query match this transaction description ? +-- Tests desc: terms, any other terms are ignored. +matchesDescription :: Query -> Text -> Bool +matchesDescription (Not q) d = not $ q `matchesDescription` d +matchesDescription (Any) _ = True +matchesDescription (None) _ = False +matchesDescription (Or qs) d = any (`matchesDescription` d) $ filter queryIsDesc qs +matchesDescription (And qs) d = all (`matchesDescription` d) $ filter queryIsDesc qs +matchesDescription (Code _) _ = False +matchesDescription (Desc r) d = regexMatchText r d +matchesDescription (Acct _) _ = False +matchesDescription (Date _) _ = False +matchesDescription (Date2 _) _ = False +matchesDescription (StatusQ _) _ = False +matchesDescription (Real _) _ = False +matchesDescription (Amt _ _) _ = False +matchesDescription (Depth _) _ = False +matchesDescription (Sym _) _ = False +matchesDescription (Tag _ _) _ = False + +-- | Does the query match this transaction payee ? +-- Tests desc: (and payee: ?) terms, any other terms are ignored. +-- XXX Currently an alias for matchDescription. I'm not sure if more is needed, +-- There's some shenanigan with payee: and "payeeTag" to figure out. +matchesPayeeWIP :: Query -> Payee -> Bool +matchesPayeeWIP q p = matchesDescription q p + -- | Does the query match the name and optionally the value of any of these tags ? matchesTags :: Regexp -> Maybe Regexp -> [Tag] -> Bool matchesTags namepat valuepat = not . null . filter (matches namepat valuepat) where - matches npat vpat (n,v) = regexMatch npat (T.unpack n) && maybe (const True) regexMatch vpat (T.unpack v) + matches npat vpat (n,v) = regexMatchText npat n && maybe (const True) regexMatchText vpat v -- | Does the query match this market price ? matchesPriceDirective :: Query -> PriceDirective -> Bool diff --git a/Hledger/Read.hs b/Hledger/Read.hs index c9e2a3c..006acb9 100644 --- a/Hledger/Read.hs +++ b/Hledger/Read.hs @@ -11,8 +11,9 @@ to import modules below this one. -} --- ** language -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE PackageImports #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PackageImports #-} {-# LANGUAGE ScopedTypeVariables #-} --- ** exports @@ -53,9 +54,13 @@ import Data.List (group, sort, sortBy) import Data.List.NonEmpty (nonEmpty) import Data.Maybe (fromMaybe) import Data.Ord (comparing) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif import Data.Semigroup (sconcat) import Data.Text (Text) import qualified Data.Text as T +import qualified Data.Text.IO as T import Data.Time (Day) import Safe (headDef) import System.Directory (doesFileExist, getHomeDirectory) @@ -63,8 +68,7 @@ import System.Environment (getEnv) import System.Exit (exitFailure) import System.FilePath ((<.>), (</>), splitDirectories, splitFileName) import System.Info (os) -import System.IO (stderr, writeFile) -import Text.Printf (hPrintf, printf) +import System.IO (hPutStr, stderr) import Hledger.Data.Dates (getCurrentDay, parsedateM, showDate) import Hledger.Data.Types @@ -191,9 +195,9 @@ requireJournalFileExists "-" = return () requireJournalFileExists f = do exists <- doesFileExist f when (not exists) $ do -- XXX might not be a journal file - hPrintf stderr "The hledger journal file \"%s\" was not found.\n" f - hPrintf stderr "Please create it first, eg with \"hledger add\" or a text editor.\n" - hPrintf stderr "Or, specify an existing journal file with -f or LEDGER_FILE.\n" + hPutStr stderr $ "The hledger journal file \"" <> show f <> "\" was not found.\n" + hPutStr stderr "Please create it first, eg with \"hledger add\" or a text editor.\n" + hPutStr stderr "Or, specify an existing journal file with -f or LEDGER_FILE.\n" exitFailure -- | Ensure there is a journal file at the given path, creating an empty one if needed. @@ -202,14 +206,14 @@ requireJournalFileExists f = do ensureJournalFileExists :: FilePath -> IO () ensureJournalFileExists f = do when (os/="mingw32" && isWindowsUnsafeDotPath f) $ do - hPrintf stderr "Part of file path %s\n ends with a dot, which is unsafe on Windows; please use a different path.\n" (show f) + hPutStr stderr $ "Part of file path \"" <> show f <> "\"\n ends with a dot, which is unsafe on Windows; please use a different path.\n" exitFailure exists <- doesFileExist f when (not exists) $ do - hPrintf stderr "Creating hledger journal file %s.\n" f + hPutStr stderr $ "Creating hledger journal file " <> show f <> ".\n" -- note Hledger.Utils.UTF8.* do no line ending conversion on windows, -- we currently require unix line endings on all platforms. - newJournalContent >>= writeFile f + newJournalContent >>= T.writeFile f -- | Does any part of this path contain non-. characters and end with a . ? -- Such paths are not safe to use on Windows (cf #1056). @@ -221,10 +225,10 @@ isWindowsUnsafeDotPath = splitDirectories -- | Give the content for a new auto-created journal file. -newJournalContent :: IO String +newJournalContent :: IO Text newJournalContent = do d <- getCurrentDay - return $ printf "; journal created %s by hledger\n" (show d) + return $ "; journal created " <> T.pack (show d) <> " by hledger\n" -- A "LatestDates" is zero or more copies of the same date, -- representing the latest transaction date read from a file, @@ -240,7 +244,7 @@ latestDates = headDef [] . take 1 . group . reverse . sort -- | Remember that these transaction dates were the latest seen when -- reading this journal file. saveLatestDates :: LatestDates -> FilePath -> IO () -saveLatestDates dates f = writeFile (latestDatesFileFor f) $ unlines $ map showDate dates +saveLatestDates dates f = T.writeFile (latestDatesFileFor f) $ T.unlines $ map showDate dates -- | What were the latest transaction dates seen the last time this -- journal file was read ? If there were multiple transactions on the diff --git a/Hledger/Read/Common.hs b/Hledger/Read/Common.hs index 21ac0a4..3d67314 100644 --- a/Hledger/Read/Common.hs +++ b/Hledger/Read/Common.hs @@ -45,6 +45,9 @@ module Hledger.Read.Common ( parseAndFinaliseJournal, parseAndFinaliseJournal', journalFinalise, + journalCheckAccountsDeclared, + journalCheckCommoditiesDeclared, + journalCheckPayeesDeclared, setYear, getYear, setDefaultCommodityAndStyle, @@ -149,6 +152,7 @@ import Text.Megaparsec.Custom import Hledger.Data import Hledger.Utils import Safe (headMay) +import Text.Printf (printf) --- ** doctest setup -- $setup @@ -368,6 +372,22 @@ journalFinalise InputOpts{auto_,ignore_assertions_,commoditystyles_,strict_} f t ) & fmap journalInferMarketPricesFromTransactions -- infer market prices from commodity-exchanging transactions +-- | Check that all the journal's transactions have payees declared with +-- payee directives, returning an error message otherwise. +journalCheckPayeesDeclared :: Journal -> Either String () +journalCheckPayeesDeclared j = sequence_ $ map checkpayee $ jtxns j + where + checkpayee t + | p `elem` ps = Right () + | otherwise = Left $ + printf "undeclared payee \"%s\"\nat: %s\n\n%s" + (T.unpack p) + (showGenericSourcePos $ tsourcepos t) + (linesPrepend2 "> " " " . (<>"\n") . textChomp $ showTransaction t) + where + p = transactionPayee t + ps = journalPayeesDeclared j + -- | Check that all the journal's postings are to accounts declared with -- account directives, returning an error message otherwise. journalCheckAccountsDeclared :: Journal -> Either String () @@ -375,11 +395,13 @@ journalCheckAccountsDeclared j = sequence_ $ map checkacct $ journalPostings j where checkacct Posting{paccount,ptransaction} | paccount `elem` as = Right () - | otherwise = - Left $ "\nstrict mode: undeclared account \""++T.unpack paccount++"\"" - ++ case ptransaction of - Just Transaction{tsourcepos} -> "\nin transaction at: "++showGenericSourcePos tsourcepos - Nothing -> "" + | otherwise = Left $ + (printf "undeclared account \"%s\"\n" (T.unpack paccount)) + ++ case ptransaction of + Nothing -> "" + Just t -> printf "in transaction at: %s\n\n%s" + (showGenericSourcePos $ tsourcepos t) + (linesPrepend " " . (<>"\n") . textChomp $ showTransaction t) where as = journalAccountNamesDeclared j @@ -392,18 +414,21 @@ journalCheckCommoditiesDeclared j = checkcommodities Posting{..} = case mfirstundeclaredcomm of Nothing -> Right () - Just c -> Left $ - "\nstrict mode: undeclared commodity \""++T.unpack c++"\"" + Just c -> Left $ + (printf "undeclared commodity \"%s\"\n" (T.unpack c)) ++ case ptransaction of - Just Transaction{tsourcepos} -> "\nin transaction at: "++showGenericSourcePos tsourcepos - Nothing -> "" + Nothing -> "" + Just t -> printf "in transaction at: %s\n\n%s" + (showGenericSourcePos $ tsourcepos t) + (linesPrepend " " . (<>"\n") . textChomp $ showTransaction t) where - mfirstundeclaredcomm = + mfirstundeclaredcomm = headMay $ filter (not . (`elem` cs)) $ catMaybes $ (acommodity . baamount <$> pbalanceassertion) : (map (Just . acommodity) . filter (/= missingamt) $ amounts pamount) cs = journalCommoditiesDeclared j + setYear :: Year -> JournalParser m () setYear y = modify' (\j -> j{jparsedefaultyear=Just y}) @@ -732,7 +757,7 @@ amountp = label "amount" $ do spaces = lift $ skipNonNewlineSpaces amount <- amountwithoutpricep <* spaces (mprice, _elotprice, _elotdate) <- runPermutation $ - (,,) <$> toPermutationWithDefault Nothing (Just <$> priceamountp <* spaces) + (,,) <$> toPermutationWithDefault Nothing (Just <$> priceamountp amount <* spaces) <*> toPermutationWithDefault Nothing (Just <$> lotpricep <* spaces) <*> toPermutationWithDefault Nothing (Just <$> lotdatep <* spaces) pure $ amount { aprice = mprice } @@ -742,7 +767,7 @@ amountpnolotpricesp = label "amount" $ do let spaces = lift $ skipNonNewlineSpaces amount <- amountwithoutpricep spaces - mprice <- optional $ priceamountp <* spaces + mprice <- optional $ priceamountp amount <* spaces pure $ amount { aprice = mprice } amountwithoutpricep :: JournalParser m Amount @@ -757,6 +782,7 @@ amountwithoutpricep = do c <- lift commoditysymbolp mdecmarkStyle <- getDecimalMarkStyle mcommodityStyle <- getAmountStyle c + -- XXX amounts of this commodity in periodic transaction rules and auto posting rules ? #1461 let suggestedStyle = mdecmarkStyle <|> mcommodityStyle commodityspaced <- lift skipNonNewlineSpaces' sign2 <- lift $ signp @@ -782,6 +808,7 @@ amountwithoutpricep = do Just (commodityspaced, c) -> do mdecmarkStyle <- getDecimalMarkStyle mcommodityStyle <- getAmountStyle c + -- XXX amounts of this commodity in periodic transaction rules and auto posting rules ? #1461 let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle (q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion msuggestedStyle ambiguousRawNum mExponent let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps} @@ -793,6 +820,7 @@ amountwithoutpricep = do mdecmarkStyle <- getDecimalMarkStyle -- a decimal-mark CSV rule mcommodityStyle <- getAmountStyle "" -- a commodity directive for the no-symbol commodity mdefaultStyle <- getDefaultAmountStyle -- a D default commodity directive + -- XXX no-symbol amounts in periodic transaction rules and auto posting rules ? #1461 let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle <|> mdefaultStyle (q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion msuggestedStyle ambiguousRawNum mExponent -- if a default commodity has been set, apply it and its style to this amount @@ -849,18 +877,24 @@ quotedcommoditysymbolp = simplecommoditysymbolp :: TextParser m CommoditySymbol simplecommoditysymbolp = takeWhile1P Nothing (not . isNonsimpleCommodityChar) -priceamountp :: JournalParser m AmountPrice -priceamountp = label "transaction price" $ do +priceamountp :: Amount -> JournalParser m AmountPrice +priceamountp baseAmt = label "transaction price" $ do -- https://www.ledger-cli.org/3.0/doc/ledger3.html#Virtual-posting-costs parenthesised <- option False $ char '(' >> pure True char '@' - priceConstructor <- char '@' *> pure TotalPrice <|> pure UnitPrice + totalPrice <- char '@' *> pure True <|> pure False when parenthesised $ void $ char ')' lift skipNonNewlineSpaces priceAmount <- amountwithoutpricep -- <?> "unpriced amount (specifying a price)" - pure $ priceConstructor priceAmount + let amtsign' = signum $ aquantity baseAmt + amtsign = if amtsign' == 0 then 1 else amtsign' + + pure $ if totalPrice + then TotalPrice priceAmount{aquantity=amtsign * aquantity priceAmount} + else UnitPrice priceAmount + balanceassertionp :: JournalParser m BalanceAssertion balanceassertionp = do @@ -1122,7 +1156,7 @@ digitgroupp :: TextParser m DigitGrp digitgroupp = label "digits" $ makeGroup <$> takeWhile1P (Just "digit") isDigit where - makeGroup = uncurry DigitGrp . foldl' step (0, 0) . T.unpack + makeGroup = uncurry DigitGrp . T.foldl' step (0, 0) step (!l, !a) c = (l+1, a*10 + fromIntegral (digitToInt c)) --- *** comments @@ -1461,7 +1495,7 @@ regexaliasp = do char '=' skipNonNewlineSpaces repl <- anySingle `manyTill` eolof - case toRegexCI re of + case toRegexCI $ T.pack re of Right r -> return $! RegexAlias r repl Left e -> customFailure $! parseErrorAtRegion off1 off2 e diff --git a/Hledger/Read/CsvReader.hs b/Hledger/Read/CsvReader.hs index 6357a9c..6623e00 100644 --- a/Hledger/Read/CsvReader.hs +++ b/Hledger/Read/CsvReader.hs @@ -11,17 +11,17 @@ A reader for CSV data, using an extra rules file to help interpret the data. -- stack haddock hledger-lib --fast --no-haddock-deps --haddock-arguments='--ignore-all-exports' --open --- ** language -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE PackageImports #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PackageImports #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE ViewPatterns #-} --- ** exports module Hledger.Read.CsvReader ( @@ -52,7 +52,6 @@ import Control.Monad.Trans.Class (lift) import Data.Char (toLower, isDigit, isSpace, isAlphaNum, isAscii, ord) import Data.Bifunctor (first) import "base-compat-batteries" Data.List.Compat -import qualified Data.List.Split as LS (splitOn) import Data.Maybe (catMaybes, fromMaybe, isJust) import Data.MemoUgly (memo) import Data.Ord (comparing) @@ -61,6 +60,8 @@ import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.IO as T +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Builder as TB import Data.Time.Calendar (Day) import Data.Time.Format (parseTimeM, defaultTimeLocale) import Safe (atMay, headMay, lastMay, readDef, readMay) @@ -88,7 +89,7 @@ import Hledger.Read.Common (aliasesFromOpts, Reader(..),InputOpts(..), amountp, type CSV = [CsvRecord] type CsvRecord = [CsvValue] -type CsvValue = String +type CsvValue = Text --- ** reader @@ -164,7 +165,7 @@ defaultRulesText csvfile = T.pack $ unlines ," account2 assets:bank:savings\n" ] -addDirective :: (DirectiveName, String) -> CsvRulesParsed -> CsvRulesParsed +addDirective :: (DirectiveName, Text) -> CsvRulesParsed -> CsvRulesParsed addDirective d r = r{rdirectives=d:rdirectives r} addAssignment :: (HledgerFieldName, FieldTemplate) -> CsvRulesParsed -> CsvRulesParsed @@ -181,7 +182,7 @@ addAssignmentsFromList fs r = foldl' maybeAddAssignment r journalfieldnames where maybeAddAssignment rules f = (maybe id addAssignmentFromIndex $ elemIndex f fs) rules where - addAssignmentFromIndex i = addAssignment (f, "%"++show (i+1)) + addAssignmentFromIndex i = addAssignment (f, T.pack $ '%':show (i+1)) addConditionalBlock :: ConditionalBlock -> CsvRulesParsed -> CsvRulesParsed addConditionalBlock b r = r{rconditionalblocks=b:rconditionalblocks r} @@ -205,7 +206,7 @@ expandIncludes dir content = mapM (expandLine dir) (T.lines content) >>= return case line of (T.stripPrefix "include " -> Just f) -> expandIncludes dir' =<< T.readFile f' where - f' = dir </> dropWhile isSpace (T.unpack f) + f' = dir </> T.unpack (T.dropWhile isSpace f) dir' = takeDirectory f' _ -> return line @@ -240,7 +241,7 @@ validateRules rules = do -- | A set of data definitions and account-matching patterns sufficient to -- convert a particular CSV data file into meaningful journal transactions. data CsvRules' a = CsvRules' { - rdirectives :: [(DirectiveName,String)], + rdirectives :: [(DirectiveName,Text)], -- ^ top-level rules, as (keyword, value) pairs rcsvfieldindexes :: [(CsvFieldName, CsvFieldIndex)], -- ^ csv field names and their column number, if declared by a fields list @@ -260,7 +261,7 @@ type CsvRulesParsed = CsvRules' () -- | Type used after parsing is done. Directives, assignments and conditional blocks -- are in the same order as they were in the unput file and rblocksassigning is functional. -- Ready to be used for CSV record processing -type CsvRules = CsvRules' (String -> [ConditionalBlock]) +type CsvRules = CsvRules' (Text -> [ConditionalBlock]) instance Eq CsvRules where r1 == r2 = (rdirectives r1, rcsvfieldindexes r1, rassignments r1) == @@ -277,27 +278,27 @@ instance Show CsvRules where type CsvRulesParser a = StateT CsvRulesParsed SimpleTextParser a -- | The keyword of a CSV rule - "fields", "skip", "if", etc. -type DirectiveName = String +type DirectiveName = Text -- | CSV field name. -type CsvFieldName = String +type CsvFieldName = Text -- | 1-based CSV column number. type CsvFieldIndex = Int -- | Percent symbol followed by a CSV field name or column number. Eg: %date, %1. -type CsvFieldReference = String +type CsvFieldReference = Text -- | One of the standard hledger fields or pseudo-fields that can be assigned to. -- Eg date, account1, amount, amount1-in, date-format. -type HledgerFieldName = String +type HledgerFieldName = Text -- | A text value to be assigned to a hledger field, possibly -- containing csv field references to be interpolated. -type FieldTemplate = String +type FieldTemplate = Text -- | A strptime date parsing pattern, as supported by Data.Time.Format. -type DateFormat = String +type DateFormat = Text -- | A prefix for a matcher test, either & or none (implicit or). data MatcherPrefix = And | None @@ -453,16 +454,16 @@ commentlinep = lift skipNonNewlineSpaces >> commentcharp >> lift restofline >> r commentcharp :: CsvRulesParser Char commentcharp = oneOf (";#*" :: [Char]) -directivep :: CsvRulesParser (DirectiveName, String) +directivep :: CsvRulesParser (DirectiveName, Text) directivep = (do lift $ dbgparse 8 "trying directive" - d <- fmap T.unpack $ choiceInState $ map (lift . string . T.pack) directives + d <- choiceInState $ map (lift . string) directives v <- (((char ':' >> lift (many spacenonewline)) <|> lift (some spacenonewline)) >> directivevalp) <|> (optional (char ':') >> lift skipNonNewlineSpaces >> lift eolof >> return "") return (d, v) ) <?> "directive" -directives :: [String] +directives :: [Text] directives = ["date-format" ,"decimal-mark" @@ -474,8 +475,8 @@ directives = , "balance-type" ] -directivevalp :: CsvRulesParser String -directivevalp = anySingle `manyTill` lift eolof +directivevalp :: CsvRulesParser Text +directivevalp = T.pack <$> anySingle `manyTill` lift eolof fieldnamelistp :: CsvRulesParser [CsvFieldName] fieldnamelistp = (do @@ -487,21 +488,18 @@ fieldnamelistp = (do f <- fromMaybe "" <$> optional fieldnamep fs <- some $ (separator >> fromMaybe "" <$> optional fieldnamep) lift restofline - return $ map (map toLower) $ f:fs + return . map T.toLower $ f:fs ) <?> "field name list" -fieldnamep :: CsvRulesParser String +fieldnamep :: CsvRulesParser Text fieldnamep = quotedfieldnamep <|> barefieldnamep -quotedfieldnamep :: CsvRulesParser String -quotedfieldnamep = do - char '"' - f <- some $ noneOf ("\"\n:;#~" :: [Char]) - char '"' - return f +quotedfieldnamep :: CsvRulesParser Text +quotedfieldnamep = + char '"' *> takeWhile1P Nothing (`notElem` ("\"\n:;#~" :: [Char])) <* char '"' -barefieldnamep :: CsvRulesParser String -barefieldnamep = some $ noneOf (" \t\n,;#~" :: [Char]) +barefieldnamep :: CsvRulesParser Text +barefieldnamep = takeWhile1P Nothing (`notElem` (" \t\n,;#~" :: [Char])) fieldassignmentp :: CsvRulesParser (HledgerFieldName, FieldTemplate) fieldassignmentp = do @@ -513,10 +511,10 @@ fieldassignmentp = do return (f,v) <?> "field assignment" -journalfieldnamep :: CsvRulesParser String +journalfieldnamep :: CsvRulesParser Text journalfieldnamep = do lift (dbgparse 8 "trying journalfieldnamep") - T.unpack <$> choiceInState (map (lift . string . T.pack) journalfieldnames) + choiceInState $ map (lift . string) journalfieldnames maxpostings = 99 @@ -524,14 +522,14 @@ maxpostings = 99 -- Names must precede any other name they contain, for the parser -- (amount-in before amount; date2 before date). TODO: fix journalfieldnames = - concat [[ "account" ++ i - ,"amount" ++ i ++ "-in" - ,"amount" ++ i ++ "-out" - ,"amount" ++ i - ,"balance" ++ i - ,"comment" ++ i - ,"currency" ++ i - ] | x <- [maxpostings, (maxpostings-1)..1], let i = show x] + concat [[ "account" <> i + ,"amount" <> i <> "-in" + ,"amount" <> i <> "-out" + ,"amount" <> i + ,"balance" <> i + ,"comment" <> i + ,"currency" <> i + ] | x <- [maxpostings, (maxpostings-1)..1], let i = T.pack $ show x] ++ ["amount-in" ,"amount-out" @@ -556,10 +554,10 @@ assignmentseparatorp = do ] return () -fieldvalp :: CsvRulesParser String +fieldvalp :: CsvRulesParser Text fieldvalp = do lift $ dbgparse 8 "trying fieldvalp" - anySingle `manyTill` lift eolof + T.pack <$> anySingle `manyTill` lift eolof -- A conditional block: one or more matchers, one per line, followed by one or more indented rules. conditionalblockp :: CsvRulesParser ConditionalBlock @@ -587,14 +585,14 @@ conditionaltablep :: CsvRulesParser [ConditionalBlock] conditionaltablep = do lift $ dbgparse 8 "trying conditionaltablep" start <- getOffset - string "if" + string "if" sep <- lift $ satisfy (\c -> not (isAlphaNum c || isSpace c)) fields <- journalfieldnamep `sepBy1` (char sep) newline body <- flip manyTill (lift eolof) $ do off <- getOffset m <- matcherp' (char sep >> return ()) - vs <- LS.splitOn [sep] <$> lift restofline + vs <- T.split (==sep) . T.pack <$> lift restofline if (length vs /= length fields) then customFailure $ parseErrorAt off $ ((printf "line of conditional table should have %d values, but this one has only %d\n" (length fields) (length vs)) :: String) else return (m,vs) @@ -655,8 +653,7 @@ csvfieldreferencep :: CsvRulesParser CsvFieldReference csvfieldreferencep = do lift $ dbgparse 8 "trying csvfieldreferencep" char '%' - f <- fieldnamep - return $ '%' : quoteIfNeeded f + T.cons '%' . textQuoteIfNeeded <$> fieldnamep -- A single regular expression regexp :: CsvRulesParser () -> CsvRulesParser Regexp @@ -665,7 +662,7 @@ regexp end = do -- notFollowedBy matchoperatorp c <- lift nonspace cs <- anySingle `manyTill` end - case toRegexCI . strip $ c:cs of + case toRegexCI . T.strip . T.pack $ c:cs of Left x -> Fail.fail $ "CSV parser: " ++ x Right x -> return x @@ -721,7 +718,7 @@ readJournalFromCsv mrulesfile csvfile csvdata = let skiplines = case getDirective "skip" rules of Nothing -> 0 Just "" -> 1 - Just s -> readDef (throwerr $ "could not parse skip value: " ++ show s) s + Just s -> readDef (throwerr $ "could not parse skip value: " ++ show s) $ T.unpack s -- parse csv let @@ -779,18 +776,17 @@ readJournalFromCsv mrulesfile csvfile csvdata = when (not rulesfileexists) $ do dbg1IO "creating conversion rules file" rulesfile - writeFile rulesfile $ T.unpack rulestext + T.writeFile rulesfile rulestext return $ Right nulljournal{jtxns=txns''} -- | Parse special separator names TAB and SPACE, or return the first -- character. Return Nothing on empty string -parseSeparator :: String -> Maybe Char -parseSeparator = specials . map toLower +parseSeparator :: Text -> Maybe Char +parseSeparator = specials . T.toLower where specials "space" = Just ' ' specials "tab" = Just '\t' - specials (x:_) = Just x - specials [] = Nothing + specials xs = fst <$> T.uncons xs parseCsv :: Char -> FilePath -> Text -> IO (Either String CSV) parseCsv separator filePath csvdata = @@ -813,15 +809,12 @@ parseResultToCsv :: (Foldable t, Functor t) => t (t B.ByteString) -> CSV parseResultToCsv = toListList . unpackFields where toListList = toList . fmap toList - unpackFields = (fmap . fmap) (T.unpack . T.decodeUtf8) + unpackFields = (fmap . fmap) T.decodeUtf8 -printCSV :: CSV -> String -printCSV records = unlined (printRecord `map` records) - where printRecord = concat . intersperse "," . map printField - printField f = "\"" ++ concatMap escape f ++ "\"" - escape '"' = "\"\"" - escape x = [x] - unlined = concat . intersperse "\n" +printCSV :: CSV -> TL.Text +printCSV = TB.toLazyText . unlinesB . map printRecord + where printRecord = mconcat . map TB.fromText . intersperse "," . map printField + printField = wrap "\"" "\"" . T.replace "\"" "\\\"\\\"" -- | Return the cleaned up and validated CSV data (can be empty), or an error. validateCsv :: CsvRules -> Int -> Either String CSV -> Either String [CsvRecord] @@ -834,7 +827,7 @@ validateCsv rules numhdrlines (Right rs) = validate $ applyConditionalSkips $ dr (Nothing, Nothing) -> Nothing (Just _, _) -> Just maxBound (Nothing, Just "") -> Just 1 - (Nothing, Just x) -> Just (read x) + (Nothing, Just x) -> Just (read $ T.unpack x) applyConditionalSkips [] = [] applyConditionalSkips (r:rest) = case skipCount r of @@ -866,7 +859,7 @@ validateCsv rules numhdrlines (Right rs) = validate $ applyConditionalSkips $ dr --- ** converting csv records to transactions showRules rules record = - unlines $ catMaybes [ (("the "++fld++" rule is: ")++) <$> getEffectiveAssignment rules record fld | fld <- journalfieldnames] + T.unlines $ catMaybes [ (("the "<>fld<>" rule is: ")<>) <$> getEffectiveAssignment rules record fld | fld <- journalfieldnames] -- | Look up the value (template) of a csv rule by rule keyword. csvRule :: CsvRules -> DirectiveName -> Maybe FieldTemplate @@ -880,7 +873,7 @@ hledgerField = getEffectiveAssignment -- | Look up the final value assigned to a hledger field, with csv field -- references interpolated. -hledgerFieldValue :: CsvRules -> CsvRecord -> HledgerFieldName -> Maybe String +hledgerFieldValue :: CsvRules -> CsvRecord -> HledgerFieldName -> Maybe Text hledgerFieldValue rules record = fmap (renderTemplate rules record) . hledgerField rules record transactionFromCsvRecord :: SourcePos -> CsvRules -> CsvRecord -> Transaction @@ -892,18 +885,18 @@ transactionFromCsvRecord sourcepos rules record = t rule = csvRule rules :: DirectiveName -> Maybe FieldTemplate -- ruleval = csvRuleValue rules record :: DirectiveName -> Maybe String field = hledgerField rules record :: HledgerFieldName -> Maybe FieldTemplate - fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe String + fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe Text parsedate = parseDateWithCustomOrDefaultFormats (rule "date-format") - mkdateerror datefield datevalue mdateformat = unlines - ["error: could not parse \""++datevalue++"\" as a date using date format " - ++maybe "\"YYYY/M/D\", \"YYYY-M-D\" or \"YYYY.M.D\"" show mdateformat + mkdateerror datefield datevalue mdateformat = T.unpack $ T.unlines + ["error: could not parse \""<>datevalue<>"\" as a date using date format " + <>maybe "\"YYYY/M/D\", \"YYYY-M-D\" or \"YYYY.M.D\"" (T.pack . show) mdateformat ,showRecord record - ,"the "++datefield++" rule is: "++(fromMaybe "required, but missing" $ field datefield) - ,"the date-format is: "++fromMaybe "unspecified" mdateformat + ,"the "<>datefield<>" rule is: "<>(fromMaybe "required, but missing" $ field datefield) + ,"the date-format is: "<>fromMaybe "unspecified" mdateformat ,"you may need to " - ++"change your "++datefield++" rule, " - ++maybe "add a" (const "change your") mdateformat++" date-format rule, " - ++"or "++maybe "add a" (const "change your") mskip++" skip rule" + <>"change your "<>datefield<>" rule, " + <>maybe "add a" (const "change your") mdateformat<>" date-format rule, " + <>"or "<>maybe "add a" (const "change your") mskip<>" skip rule" ,"for m/d/y or d/m/y dates, use date-format %-m/%-d/%Y or date-format %-d/%-m/%Y" ] where @@ -923,25 +916,27 @@ transactionFromCsvRecord sourcepos rules record = t status = case fieldval "status" of Nothing -> Unmarked - Just s -> either statuserror id $ runParser (statusp <* eof) "" $ T.pack s + Just s -> either statuserror id $ runParser (statusp <* eof) "" s where - statuserror err = error' $ unlines - ["error: could not parse \""++s++"\" as a cleared status (should be *, ! or empty)" - ,"the parse error is: "++customErrorBundlePretty err + statuserror err = error' . T.unpack $ T.unlines + ["error: could not parse \""<>s<>"\" as a cleared status (should be *, ! or empty)" + ,"the parse error is: "<>T.pack (customErrorBundlePretty err) ] code = maybe "" singleline $ fieldval "code" description = maybe "" singleline $ fieldval "description" comment = maybe "" singleline $ fieldval "comment" precomment = maybe "" singleline $ fieldval "precomment" + singleline = T.unwords . filter (not . T.null) . map T.strip . T.lines + ---------------------------------------------------------------------- -- 3. Generate the postings for which an account has been assigned -- (possibly indirectly due to an amount or balance assignment) - p1IsVirtual = (accountNamePostingType . T.pack <$> fieldval "account1") == Just VirtualPosting + p1IsVirtual = (accountNamePostingType <$> fieldval "account1") == Just VirtualPosting ps = [p | n <- [1..maxpostings] - ,let comment = T.pack $ fromMaybe "" $ fieldval ("comment"++show n) - ,let currency = fromMaybe "" (fieldval ("currency"++show n) <|> fieldval "currency") + ,let comment = fromMaybe "" $ fieldval ("comment"<> T.pack (show n)) + ,let currency = fromMaybe "" (fieldval ("currency"<> T.pack (show n)) <|> fieldval "currency") ,let mamount = getAmount rules record currency p1IsVirtual n ,let mbalance = getBalance rules record currency n ,Just (acct,isfinal) <- [getAccount rules record mamount mbalance n] -- skips Nothings @@ -965,10 +960,10 @@ transactionFromCsvRecord sourcepos rules record = t ,tdate = date' ,tdate2 = mdate2' ,tstatus = status - ,tcode = T.pack code - ,tdescription = T.pack description - ,tcomment = T.pack comment - ,tprecedingcomment = T.pack precomment + ,tcode = code + ,tdescription = description + ,tcomment = comment + ,tprecedingcomment = precomment ,tpostings = ps } @@ -979,7 +974,7 @@ transactionFromCsvRecord sourcepos rules record = t -- For postings 1 or 2 it also looks at "amount", "amount-in", "amount-out". -- If more than one of these has a value, it looks for one that is non-zero. -- If there's multiple non-zeros, or no non-zeros but multiple zeros, it throws an error. -getAmount :: CsvRules -> CsvRecord -> String -> Bool -> Int -> Maybe MixedAmount +getAmount :: CsvRules -> CsvRecord -> Text -> Bool -> Int -> Maybe MixedAmount getAmount rules record currency p1IsVirtual n = -- Warning, many tricky corner cases here. -- docs: hledger_csv.m4.md #### amount @@ -988,14 +983,15 @@ getAmount rules record currency p1IsVirtual n = unnumberedfieldnames = ["amount","amount-in","amount-out"] -- amount field names which can affect this posting - fieldnames = map (("amount"++show n)++) ["","-in","-out"] + fieldnames = map (("amount"<> T.pack(show n))<>) ["","-in","-out"] -- For posting 1, also recognise the old amount/amount-in/amount-out names. -- For posting 2, the same but only if posting 1 needs balancing. ++ if n==1 || n==2 && not p1IsVirtual then unnumberedfieldnames else [] -- assignments to any of these field names with non-empty values assignments = [(f,a') | f <- fieldnames - , Just v@(_:_) <- [strip . renderTemplate rules record <$> hledgerField rules record f] + , Just v <- [T.strip . renderTemplate rules record <$> hledgerField rules record f] + , not $ T.null v , let a = parseAmount rules record currency v -- With amount/amount-in/amount-out, in posting 2, -- flip the sign and convert to cost, as they did before 1.17 @@ -1006,7 +1002,7 @@ getAmount rules record currency p1IsVirtual n = assignments' | any isnumbered assignments = filter isnumbered assignments | otherwise = assignments where - isnumbered (f,_) = any (flip elem ['0'..'9']) f + isnumbered (f,_) = T.any (flip elem ['0'..'9']) f -- if there's more than one value and only some are zeros, discard the zeros assignments'' @@ -1017,24 +1013,24 @@ getAmount rules record currency p1IsVirtual n = in case -- dbg0 ("amounts for posting "++show n) assignments'' of [] -> Nothing - [(f,a)] | "-out" `isSuffixOf` f -> Just (-a) -- for -out fields, flip the sign + [(f,a)] | "-out" `T.isSuffixOf` f -> Just (-a) -- for -out fields, flip the sign [(_,a)] -> Just a - fs -> error' $ unlines $ [ -- PARTIAL: + fs -> error' . T.unpack . T.unlines $ [ -- PARTIAL: "multiple non-zero amounts or multiple zero amounts assigned," ,"please ensure just one. (https://hledger.org/csv.html#amount)" - ," " ++ showRecord record - ," for posting: " ++ show n + ," " <> showRecord record + ," for posting: " <> T.pack (show n) ] - ++ [" assignment: " ++ f ++ " " ++ - fromMaybe "" (hledgerField rules record f) ++ - "\t=> value: " ++ showMixedAmount a -- XXX not sure this is showing all the right info + ++ [" assignment: " <> f <> " " <> + fromMaybe "" (hledgerField rules record f) <> + "\t=> value: " <> wbToText (showMixedAmountB noColour a) -- XXX not sure this is showing all the right info | (f,a) <- fs] -- | Figure out the expected balance (assertion or assignment) specified for posting N, -- if any (and its parse position). -getBalance :: CsvRules -> CsvRecord -> String -> Int -> Maybe (Amount, GenericSourcePos) +getBalance :: CsvRules -> CsvRecord -> Text -> Int -> Maybe (Amount, GenericSourcePos) getBalance rules record currency n = do - v <- (fieldval ("balance"++show n) + v <- (fieldval ("balance"<> T.pack (show n)) -- for posting 1, also recognise the old field name <|> if n==1 then fieldval "balance" else Nothing) case v of @@ -1043,30 +1039,29 @@ getBalance rules record currency n = do parseBalanceAmount rules record currency n s ,nullsourcepos -- parse position to show when assertion fails, ) -- XXX the csv record's line number would be good - where - fieldval = fmap strip . hledgerFieldValue rules record :: HledgerFieldName -> Maybe String + fieldval = fmap T.strip . hledgerFieldValue rules record :: HledgerFieldName -> Maybe Text -- | Given a non-empty amount string (from CSV) to parse, along with a -- possibly non-empty currency symbol to prepend, -- parse as a hledger MixedAmount (as in journal format), or raise an error. -- The whole CSV record is provided for the error message. -parseAmount :: CsvRules -> CsvRecord -> String -> String -> MixedAmount +parseAmount :: CsvRules -> CsvRecord -> Text -> Text -> MixedAmount parseAmount rules record currency s = - either mkerror (Mixed . (:[])) $ -- PARTIAL: - runParser (evalStateT (amountp <* eof) journalparsestate) "" $ - T.pack $ (currency++) $ simplifySign s + either mkerror (Mixed . (:[])) $ -- PARTIAL: + runParser (evalStateT (amountp <* eof) journalparsestate) "" $ + currency <> simplifySign s where journalparsestate = nulljournal{jparsedecimalmark=parseDecimalMark rules} - mkerror e = error' $ unlines - ["error: could not parse \""++s++"\" as an amount" + mkerror e = error' . T.unpack $ T.unlines + ["error: could not parse \"" <> s <> "\" as an amount" ,showRecord record ,showRules rules record -- ,"the default-currency is: "++fromMaybe "unspecified" (getDirective "default-currency" rules) - ,"the parse error is: "++customErrorBundlePretty e - ,"you may need to " - ++"change your amount*, balance*, or currency* rules, " - ++"or add or change your skip rule" + ,"the parse error is: " <> T.pack (customErrorBundlePretty e) + ,"you may need to \ + \change your amount*, balance*, or currency* rules, \ + \or add or change your skip rule" ] -- XXX unify these ^v @@ -1076,30 +1071,30 @@ parseAmount rules record currency s = -- possibly non-empty currency symbol to prepend, -- parse as a hledger Amount (as in journal format), or raise an error. -- The CSV record and the field's numeric suffix are provided for the error message. -parseBalanceAmount :: CsvRules -> CsvRecord -> String -> Int -> String -> Amount +parseBalanceAmount :: CsvRules -> CsvRecord -> Text -> Int -> Text -> Amount parseBalanceAmount rules record currency n s = either (mkerror n s) id $ runParser (evalStateT (amountp <* eof) journalparsestate) "" $ - T.pack $ (currency++) $ simplifySign s + currency <> simplifySign s -- the csv record's line number would be good where journalparsestate = nulljournal{jparsedecimalmark=parseDecimalMark rules} - mkerror n s e = error' $ unlines - ["error: could not parse \""++s++"\" as balance"++show n++" amount" + mkerror n s e = error' . T.unpack $ T.unlines + ["error: could not parse \"" <> s <> "\" as balance"<> T.pack (show n) <> " amount" ,showRecord record ,showRules rules record -- ,"the default-currency is: "++fromMaybe "unspecified" mdefaultcurrency - ,"the parse error is: "++customErrorBundlePretty e + ,"the parse error is: "<> T.pack (customErrorBundlePretty e) ] -- Read a valid decimal mark from the decimal-mark rule, if any. -- If the rule is present with an invalid argument, raise an error. parseDecimalMark :: CsvRules -> Maybe DecimalMark -parseDecimalMark rules = - case rules `csvRule` "decimal-mark" of - Nothing -> Nothing - Just [c] | isDecimalMark c -> Just c - Just s -> error' $ "decimal-mark's argument should be \".\" or \",\" (not \""++s++"\")" +parseDecimalMark rules = do + s <- rules `csvRule` "decimal-mark" + case T.uncons s of + Just (c, rest) | T.null rest && isDecimalMark c -> return c + _ -> error' . T.unpack $ "decimal-mark's argument should be \".\" or \",\" (not \""<>s<>"\")" -- | Make a balance assertion for the given amount, with the given parse -- position (to be shown in assertion failures), with the assertion type @@ -1116,8 +1111,8 @@ mkBalanceAssertion rules record (amt, pos) = assrt{baamount=amt, baposition=pos} Just "==" -> nullassertion{batotal=True} Just "=*" -> nullassertion{bainclusive=True} Just "==*" -> nullassertion{batotal=True, bainclusive=True} - Just x -> error' $ unlines -- PARTIAL: - [ "balance-type \"" ++ x ++"\" is invalid. Use =, ==, =* or ==*." + Just x -> error' . T.unpack $ T.unlines -- PARTIAL: + [ "balance-type \"" <> x <>"\" is invalid. Use =, ==, =* or ==*." , showRecord record , showRules rules record ] @@ -1128,8 +1123,8 @@ mkBalanceAssertion rules record (amt, pos) = assrt{baamount=amt, baposition=pos} getAccount :: CsvRules -> CsvRecord -> Maybe MixedAmount -> Maybe (Amount, GenericSourcePos) -> Int -> Maybe (AccountName, Bool) getAccount rules record mamount mbalance n = let - fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe String - maccount = T.pack <$> fieldval ("account"++show n) + fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe Text + maccount = fieldval ("account"<> T.pack (show n)) in case maccount of -- accountN is set to the empty string - no posting will be generated Just "" -> Nothing @@ -1150,14 +1145,21 @@ getAccount rules record mamount mbalance n = unknownExpenseAccount = "expenses:unknown" unknownIncomeAccount = "income:unknown" -type CsvAmountString = String +type CsvAmountString = Text -- | Canonicalise the sign in a CSV amount string. --- Such strings can have a minus sign, negating parentheses, --- or any two of these (which cancels out). +-- Such strings can have a minus sign, parentheses (equivalent to minus), +-- or any two of these (which cancel out), +-- or a plus sign (which is removed), +-- or any sign by itself with no following number (which is removed). +-- See hledger > CSV FORMAT > Tips > Setting amounts. +-- +-- These are supported (note, not every possibile combination): -- -- >>> simplifySign "1" -- "1" +-- >>> simplifySign "+1" +-- "1" -- >>> simplifySign "-1" -- "-1" -- >>> simplifySign "(1)" @@ -1166,23 +1168,36 @@ type CsvAmountString = String -- "1" -- >>> simplifySign "-(1)" -- "1" +-- >>> simplifySign "-+1" +-- "-1" -- >>> simplifySign "(-1)" -- "1" -- >>> simplifySign "((1))" -- "1" +-- >>> simplifySign "-" +-- "" +-- >>> simplifySign "()" +-- "" +-- >>> simplifySign "+" +-- "" simplifySign :: CsvAmountString -> CsvAmountString -simplifySign ('(':s) | lastMay s == Just ')' = simplifySign $ negateStr $ init s -simplifySign ('-':'(':s) | lastMay s == Just ')' = simplifySign $ init s -simplifySign ('-':'-':s) = s -simplifySign s = s - -negateStr :: String -> String -negateStr ('-':s) = s -negateStr s = '-':s +simplifySign amtstr + | Just ('(',t) <- T.uncons amtstr, Just (amt,')') <- T.unsnoc t = simplifySign $ negateStr amt + | Just ('-',b) <- T.uncons amtstr, Just ('(',t) <- T.uncons b, Just (amt,')') <- T.unsnoc t = simplifySign amt + | Just ('-',m) <- T.uncons amtstr, Just ('-',amt) <- T.uncons m = amt + | Just ('-',m) <- T.uncons amtstr, Just ('+',amt) <- T.uncons m = negateStr amt + | amtstr `elem` ["-","+","()"] = "" + | Just ('+',amt) <- T.uncons amtstr = simplifySign amt + | otherwise = amtstr + +negateStr :: Text -> Text +negateStr amtstr = case T.uncons amtstr of + Just ('-',s) -> s + _ -> T.cons '-' amtstr -- | Show a (approximate) recreation of the original CSV record. -showRecord :: CsvRecord -> String -showRecord r = "record values: "++intercalate "," (map show r) +showRecord :: CsvRecord -> Text +showRecord r = "record values: "<>T.intercalate "," (map (wrap "\"" "\"") r) -- | Given the conversion rules, a CSV record and a hledger field name, find -- the value template ultimately assigned to this field, if any, by a field @@ -1208,7 +1223,7 @@ getEffectiveAssignment rules record f = lastMay $ map snd $ assignments where -- does this individual matcher match the current csv record ? matcherMatches :: Matcher -> Bool - matcherMatches (RecordMatcher _ pat) = regexMatch pat' wholecsvline + matcherMatches (RecordMatcher _ pat) = regexMatchText pat' wholecsvline where pat' = dbg7 "regex" pat -- A synthetic whole CSV record to match against. Note, this can be @@ -1217,47 +1232,48 @@ getEffectiveAssignment rules record f = lastMay $ map snd $ assignments -- - any quotes enclosing field values are removed -- - and the field separator is always comma -- which means that a field containing a comma will look like two fields. - wholecsvline = dbg7 "wholecsvline" $ intercalate "," record - matcherMatches (FieldMatcher _ csvfieldref pat) = regexMatch pat csvfieldvalue + wholecsvline = dbg7 "wholecsvline" $ T.intercalate "," record + matcherMatches (FieldMatcher _ csvfieldref pat) = regexMatchText pat csvfieldvalue where -- the value of the referenced CSV field to match against. csvfieldvalue = dbg7 "csvfieldvalue" $ replaceCsvFieldReference rules record csvfieldref -- | Render a field assignment's template, possibly interpolating referenced -- CSV field values. Outer whitespace is removed from interpolated values. -renderTemplate :: CsvRules -> CsvRecord -> FieldTemplate -> String -renderTemplate rules record t = maybe t concat $ parseMaybe +renderTemplate :: CsvRules -> CsvRecord -> FieldTemplate -> Text +renderTemplate rules record t = maybe t mconcat $ parseMaybe (many $ takeWhile1P Nothing (/='%') <|> replaceCsvFieldReference rules record <$> referencep) t where - referencep = liftA2 (:) (char '%') (takeWhile1P (Just "reference") isDescriptorChar) :: Parsec CustomErr String String + referencep = liftA2 T.cons (char '%') (takeWhile1P (Just "reference") isDescriptorChar) :: Parsec CustomErr Text Text isDescriptorChar c = isAscii c && (isAlphaNum c || c == '_' || c == '-') -- | Replace something that looks like a reference to a csv field ("%date" or "%1) -- with that field's value. If it doesn't look like a field reference, or if we -- can't find such a field, leave it unchanged. -replaceCsvFieldReference :: CsvRules -> CsvRecord -> CsvFieldReference -> String -replaceCsvFieldReference rules record s@('%':fieldname) = fromMaybe s $ csvFieldValue rules record fieldname -replaceCsvFieldReference _ _ s = s +replaceCsvFieldReference :: CsvRules -> CsvRecord -> CsvFieldReference -> Text +replaceCsvFieldReference rules record s = case T.uncons s of + Just ('%', fieldname) -> fromMaybe s $ csvFieldValue rules record fieldname + _ -> s -- | Get the (whitespace-stripped) value of a CSV field, identified by its name or -- column number, ("date" or "1"), from the given CSV record, if such a field exists. -csvFieldValue :: CsvRules -> CsvRecord -> CsvFieldName -> Maybe String +csvFieldValue :: CsvRules -> CsvRecord -> CsvFieldName -> Maybe Text csvFieldValue rules record fieldname = do - fieldindex <- if | all isDigit fieldname -> readMay fieldname - | otherwise -> lookup (map toLower fieldname) $ rcsvfieldindexes rules - fieldvalue <- strip <$> atMay record (fieldindex-1) + fieldindex <- if | T.all isDigit fieldname -> readMay $ T.unpack fieldname + | otherwise -> lookup (T.toLower fieldname) $ rcsvfieldindexes rules + fieldvalue <- T.strip <$> atMay record (fieldindex-1) return fieldvalue -- | Parse the date string using the specified date-format, or if unspecified -- the "simple date" formats (YYYY/MM/DD, YYYY-MM-DD, YYYY.MM.DD, leading -- zeroes optional). -parseDateWithCustomOrDefaultFormats :: Maybe DateFormat -> String -> Maybe Day +parseDateWithCustomOrDefaultFormats :: Maybe DateFormat -> Text -> Maybe Day parseDateWithCustomOrDefaultFormats mformat s = asum $ map parsewith formats where - parsewith = flip (parseTimeM True defaultTimeLocale) s - formats = maybe + parsewith = flip (parseTimeM True defaultTimeLocale) (T.unpack s) + formats = map T.unpack $ maybe ["%Y/%-m/%-d" ,"%Y-%-m-%-d" ,"%Y.%-m.%-d" diff --git a/Hledger/Read/JournalReader.hs b/Hledger/Read/JournalReader.hs index 0b941e3..027df37 100644 --- a/Hledger/Read/JournalReader.hs +++ b/Hledger/Read/JournalReader.hs @@ -42,7 +42,7 @@ module Hledger.Read.JournalReader ( -- * Reader-finding utils findReader, splitReaderPrefix, - + -- * Reader reader, @@ -226,6 +226,7 @@ directivep = (do ,applyaccountdirectivep ,commoditydirectivep ,endapplyaccountdirectivep + ,payeedirectivep ,tagdirectivep ,endtagdirectivep ,defaultyeardirectivep @@ -379,8 +380,8 @@ parseAccountTypeCode s = "c" -> Right Cash _ -> Left err where - err = "invalid account type code "++T.unpack s++", should be one of " ++ - (intercalate ", " $ ["A","L","E","R","X","C","Asset","Liability","Equity","Revenue","Expense","Cash"]) + err = T.unpack $ "invalid account type code "<>s<>", should be one of " <> + T.intercalate ", " ["A","L","E","R","X","C","Asset","Liability","Equity","Revenue","Expense","Cash"] -- Add an account declaration to the journal, auto-numbering it. addAccountDeclaration :: (AccountName,Text,[Tag]) -> JournalParser m () @@ -396,6 +397,17 @@ addAccountDeclaration (a,cmt,tags) = in j{jdeclaredaccounts = d:decls}) +-- Add a payee declaration to the journal. +addPayeeDeclaration :: (Payee,Text,[Tag]) -> JournalParser m () +addPayeeDeclaration (p, cmt, tags) = + modify' (\j@Journal{jdeclaredpayees} -> j{jdeclaredpayees=d:jdeclaredpayees}) + where + d = (p + ,nullpayeedeclarationinfo{ + pdicomment = cmt + ,pditags = tags + }) + indentedlinep :: JournalParser m String indentedlinep = lift skipNonNewlineSpaces1 >> (rstrip <$> lift restofline) @@ -519,6 +531,15 @@ endtagdirectivep = do lift restofline return () +payeedirectivep :: JournalParser m () +payeedirectivep = do + string "payee" <?> "payee directive" + lift skipNonNewlineSpaces1 + payee <- lift descriptionp -- all text until ; or \n + (comment, tags) <- lift transactioncommentp + addPayeeDeclaration (payee, comment, tags) + return () + defaultyeardirectivep :: JournalParser m () defaultyeardirectivep = do char 'Y' <?> "default year" @@ -985,6 +1006,11 @@ tests_JournalReader = tests "JournalReader" [ pdamount = usd 922.83 } + ,tests "payeedirectivep" [ + test "simple" $ assertParse payeedirectivep "payee foo\n" + ,test "with-comment" $ assertParse payeedirectivep "payee foo ; comment\n" + ] + ,test "tagdirectivep" $ do assertParse tagdirectivep "tag foo \n" diff --git a/Hledger/Read/TimedotReader.hs b/Hledger/Read/TimedotReader.hs index e8bc0ec..2e17f41 100644 --- a/Hledger/Read/TimedotReader.hs +++ b/Hledger/Read/TimedotReader.hs @@ -182,7 +182,7 @@ entryp = do tstatus = Cleared, tpostings = [ nullposting{paccount=a - ,pamount=Mixed [setAmountPrecision (Precision 2) $ num hours] -- don't assume hours; do set precision to 2 + ,pamount=Mixed [amountSetPrecision (Precision 2) $ num hours] -- don't assume hours; do set precision to 2 ,ptype=VirtualPosting ,ptransaction=Just t } diff --git a/Hledger/Reports/AccountTransactionsReport.hs b/Hledger/Reports/AccountTransactionsReport.hs index ba7506f..6b9c531 100644 --- a/Hledger/Reports/AccountTransactionsReport.hs +++ b/Hledger/Reports/AccountTransactionsReport.hs @@ -18,6 +18,7 @@ where import Data.List import Data.Ord import Data.Maybe +import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar @@ -64,26 +65,20 @@ import Hledger.Utils -- posts to the current account), most recent first. -- Reporting intervals are currently ignored. -- -type AccountTransactionsReport = - (String -- label for the balance column, eg "balance" or "total" - ,[AccountTransactionsReportItem] -- line items, one per transaction - ) +type AccountTransactionsReport = [AccountTransactionsReportItem] -- line items, one per transaction type AccountTransactionsReportItem = ( Transaction -- the transaction, unmodified ,Transaction -- the transaction, as seen from the current account ,Bool -- is this a split (more than one posting to other accounts) ? - ,String -- a display string describing the other account(s), if any + ,Text -- a display string describing the other account(s), if any ,MixedAmount -- the amount posted to the current account(s) (or total amount posted) ,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction ) -totallabel = "Period Total" -balancelabel = "Historical Total" - accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport -accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = (label, items) +accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = items where -- a depth limit should not affect the account transactions report -- seems unnecessary for some reason XXX @@ -116,14 +111,10 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = ( periodlast = fromMaybe (error' "journalApplyValuation: expected a non-empty journal") $ -- XXX shouldn't happen reportPeriodOrJournalLastDay rspec j - mreportlast = reportPeriodLastDay rspec - multiperiod = interval_ ropts /= NoInterval - tval = case value_ ropts of - Just v -> \t -> transactionApplyValuation prices styles periodlast mreportlast (rsToday rspec) multiperiod t v - Nothing -> id + tval = transactionApplyCostValuation prices styles periodlast (rsToday rspec) (cost_ ropts) $ value_ ropts ts4 = ptraceAtWith 5 (("ts4:\n"++).pshowTransactions) $ - map tval ts3 + map tval ts3 -- sort by the transaction's register date, for accurate starting balance -- these are not yet filtered by tdate, we want to search them all for priorps @@ -131,9 +122,9 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = ( ptraceAtWith 5 (("ts5:\n"++).pshowTransactions) $ sortBy (comparing (transactionRegisterDate reportq' thisacctq)) ts4 - (startbal,label) - | balancetype_ ropts == HistoricalBalance = (sumPostings priorps, balancelabel) - | otherwise = (nullmixedamt, totallabel) + startbal + | balancetype_ ropts == HistoricalBalance = sumPostings priorps + | otherwise = nullmixedamt where priorps = dbg5 "priorps" $ filter (matchesPosting @@ -218,9 +209,9 @@ transactionRegisterDate reportq thisacctq t -- | Generate a simplified summary of some postings' accounts. -- To reduce noise, if there are both real and virtual postings, show only the real ones. -summarisePostingAccounts :: [Posting] -> String +summarisePostingAccounts :: [Posting] -> Text summarisePostingAccounts ps = - (intercalate ", " . map (T.unpack . accountSummarisedName) . nub . map paccount) displayps -- XXX pack + T.intercalate ", " . map accountSummarisedName . nub $ map paccount displayps where realps = filter isReal ps displayps | null realps = ps diff --git a/Hledger/Reports/BudgetReport.hs b/Hledger/Reports/BudgetReport.hs index 8b74fa7..1081ab4 100644 --- a/Hledger/Reports/BudgetReport.hs +++ b/Hledger/Reports/BudgetReport.hs @@ -27,27 +27,27 @@ module Hledger.Reports.BudgetReport ( ) where -import Data.Decimal +import Data.Decimal (roundTo) import Data.Default (def) import Data.HashMap.Strict (HashMap) import qualified Data.HashMap.Strict as HM -import Data.List +import Data.List (nub, partition, transpose) import Data.List.Extra (nubSort) -import Data.Maybe +import Data.Maybe (fromMaybe) #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid ((<>)) #endif -import Safe +import Safe (headDef) --import Data.List --import Data.Maybe import qualified Data.Map as Map import Data.Map (Map) +import Data.Text (Text) import qualified Data.Text as T ---import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Builder as TB --import System.Console.CmdArgs.Explicit as C --import Lucid as L - -import Text.Printf (printf) import Text.Tabular as T import Text.Tabular.AsciiWide as T @@ -68,7 +68,7 @@ type BudgetCell = (Maybe Change, Maybe BudgetGoal) type BudgetReportRow = PeriodicReportRow DisplayName BudgetCell type BudgetReport = PeriodicReport DisplayName BudgetCell -type BudgetDisplayCell = ((String, Int), Maybe ((String, Int), Maybe (String, Int))) +type BudgetDisplayCell = ((Text, Int), Maybe ((Text, Int), Maybe (Text, Int))) -- | Calculate per-account, per-period budget (balance change) goals -- from all periodic transactions, calculate actual balance changes @@ -219,27 +219,25 @@ combineBudgetAndActual ropts j totActualByPeriod = Map.fromList $ zip actualperiods actualtots :: Map DateSpan Change -- | Render a budget report as plain text suitable for console output. -budgetReportAsText :: ReportOpts -> BudgetReport -> String -budgetReportAsText ropts@ReportOpts{..} budgetr = - title ++ "\n\n" ++ - renderTable def{tableBorders=False,prettyTable=pretty_tables_} - (alignCell TopLeft) (alignCell TopRight) (uncurry showcell) displayTableWithWidths +budgetReportAsText :: ReportOpts -> BudgetReport -> TL.Text +budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ + TB.fromText title <> TB.fromText "\n\n" <> + renderTableB def{tableBorders=False,prettyTable=pretty_tables_} + (textCell TopLeft) (textCell TopRight) (uncurry showcell) displayTableWithWidths where - multiperiod = interval_ /= NoInterval - title = printf "Budget performance in %s%s:" - (showDateSpan $ periodicReportSpan budgetr) - (case value_ of - Just (AtCost _mc) -> ", valued at cost" - Just (AtThen _mc) -> error' unsupportedValueThenError -- PARTIAL: - Just (AtEnd _mc) -> ", valued at period ends" - Just (AtNow _mc) -> ", current value" - -- XXX duplicates the above - Just (AtDefault _mc) | multiperiod -> ", valued at period ends" - Just (AtDefault _mc) -> ", current value" - Just (AtDate d _mc) -> ", valued at "++showDate d - Nothing -> "") - - displayTableWithWidths :: Table String String ((Int, Int, Int), BudgetDisplayCell) + title = "Budget performance in " <> showDateSpan (periodicReportSpan budgetr) + <> (case cost_ of + Cost -> ", converted to cost" + NoCost -> "") + <> (case value_ of + Just (AtThen _mc) -> ", valued at posting date" + Just (AtEnd _mc) -> ", valued at period ends" + Just (AtNow _mc) -> ", current value" + Just (AtDate d _mc) -> ", valued at " <> showDate d + Nothing -> "") + <> ":" + + displayTableWithWidths :: Table Text Text ((Int, Int, Int), BudgetDisplayCell) displayTableWithWidths = Table rh ch $ map (zipWith (,) widths) displaycells Table rh ch displaycells = case budgetReportAsTable ropts budgetr of Table rh' ch' vals -> maybetranspose . Table rh' ch' $ map (map displayCell) vals @@ -248,8 +246,8 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = where actual' = fromMaybe 0 actual budgetAndPerc b = (showamt b, showper <$> percentage actual' b) - showamt = showMixedOneLine showAmountWithoutPrice Nothing (Just 32) color_ - showper p = let str = show (roundTo 0 p) in (str, length str) + showamt = (\(WideBuilder b w) -> (TL.toStrict $ TB.toLazyText b, w)) . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=Just 32} + showper p = let str = T.pack (show $ roundTo 0 p) in (str, T.length str) cellWidth ((_,wa), Nothing) = (wa, 0, 0) cellWidth ((_,wa), Just ((_,wb), Nothing)) = (wa, wb, 0) cellWidth ((_,wa), Just ((_,wb), Just (_,wp))) = (wa, wb, wp) @@ -263,14 +261,17 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = -- XXX lay out actual, percentage and/or goal in the single table cell for now, should probably use separate cells showcell :: (Int, Int, Int) -> BudgetDisplayCell -> Cell showcell (actualwidth, budgetwidth, percentwidth) ((actual,wa), mbudget) = - Cell TopRight [(replicate (actualwidth - wa) ' ' ++ actual ++ budgetstr, actualwidth + totalbudgetwidth)] + Cell TopRight [WideBuilder ( TB.fromText (T.replicate (actualwidth - wa) " ") + <> TB.fromText actual + <> budgetstr + ) (actualwidth + totalbudgetwidth)] where totalpercentwidth = if percentwidth == 0 then 0 else percentwidth + 5 totalbudgetwidth = if budgetwidth == 0 then 0 else budgetwidth + totalpercentwidth + 3 - budgetstr = case mbudget of - Nothing -> replicate totalbudgetwidth ' ' - Just ((budget, wb), Nothing) -> " [" ++ replicate totalpercentwidth ' ' ++ replicate (budgetwidth - wb) ' ' ++ budget ++ "]" - Just ((budget, wb), Just (pct, wp)) -> " [" ++ replicate (percentwidth - wp) ' ' ++ pct ++ "% of " ++ replicate (budgetwidth - wb) ' ' ++ budget ++ "]" + budgetstr = TB.fromText $ case mbudget of + Nothing -> T.replicate totalbudgetwidth " " + Just ((budget, wb), Nothing) -> " [" <> T.replicate totalpercentwidth " " <> T.replicate (budgetwidth - wb) " " <> budget <> "]" + Just ((budget, wb), Just (pct, wp)) -> " [" <> T.replicate (percentwidth - wp) " " <> pct <> "% of " <> T.replicate (budgetwidth - wb) " " <> budget <> "]" -- | Calculate the percentage of actual change to budget goal to show, if any. -- If valuing at cost, both amounts are converted to cost before comparing. @@ -285,13 +286,15 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = _ -> -- trace (pshow $ (maybecost actual, maybecost budget)) -- debug missing percentage Nothing where - maybecost = if valuationTypeIsCost ropts then mixedAmountCost else id + maybecost = case cost_ of + Cost -> mixedAmountCost + NoCost -> id maybetranspose | transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals) | otherwise = id -- | Build a 'Table' from a multi-column balance report. -budgetReportAsTable :: ReportOpts -> BudgetReport -> Table String String (Maybe MixedAmount, Maybe MixedAmount) +budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text (Maybe MixedAmount, Maybe MixedAmount) budgetReportAsTable ropts@ReportOpts{balancetype_} (PeriodicReport spans rows (PeriodicReportRow _ coltots grandtot grandavg)) = @@ -310,8 +313,8 @@ budgetReportAsTable -- budgetReport sets accountlistmode to ALTree. Find a principled way to do -- this. renderacct row = case accountlistmode_ ropts of - ALTree -> replicate ((prrDepth row - 1)*2) ' ' ++ T.unpack (prrDisplayName row) - ALFlat -> T.unpack . accountNameDrop (drop_ ropts) $ prrFullName row + ALTree -> T.replicate ((prrDepth row - 1)*2) " " <> prrDisplayName row + ALFlat -> accountNameDrop (drop_ ropts) $ prrFullName row rowvals (PeriodicReportRow _ as rowtot rowavg) = as ++ [rowtot | row_total_ ropts] ++ [rowavg | average_ ropts] addtotalrow @@ -334,7 +337,7 @@ budgetReportAsTable -- - all other balance change reports: a description of the datespan, -- abbreviated to compact form if possible (see showDateSpan). -- -reportPeriodName :: BalanceType -> [DateSpan] -> DateSpan -> String +reportPeriodName :: BalanceType -> [DateSpan] -> DateSpan -> T.Text reportPeriodName balancetype spans = case balancetype of PeriodChange -> if multiyear then showDateSpan else showDateSpanMonthAbbrev @@ -346,20 +349,20 @@ reportPeriodName balancetype spans = -- | Render a budget report as CSV. Like multiBalanceReportAsCsv, -- but includes alternating actual and budget amount columns. budgetReportAsCsv :: ReportOpts -> BudgetReport -> CSV -budgetReportAsCsv +budgetReportAsCsv ReportOpts{average_, row_total_, no_total_, transpose_} (PeriodicReport colspans items (PeriodicReportRow _ abtotals (magrandtot,mbgrandtot) (magrandavg,mbgrandavg))) = (if transpose_ then transpose else id) $ -- heading row - ("Account" : + ("Account" : concatMap (\span -> [showDateSpan span, "budget"]) colspans ++ concat [["Total" ,"budget"] | row_total_] ++ concat [["Average","budget"] | average_] ) : -- account rows - [T.unpack (displayFull a) : + [displayFull a : map showmamt (flattentuples abamts) ++ concat [[showmamt mactualrowtot, showmamt mbudgetrowtot] | row_total_] ++ concat [[showmamt mactualrowavg, showmamt mbudgetrowavg] | average_] @@ -371,7 +374,7 @@ budgetReportAsCsv [ "Total:" : map showmamt (flattentuples abtotals) - ++ concat [[showmamt magrandtot,showmamt mbgrandtot] | row_total_] + ++ concat [[showmamt magrandtot,showmamt mbgrandtot] | row_total_] ++ concat [[showmamt magrandavg,showmamt mbgrandavg] | average_] ] | not no_total_ @@ -379,7 +382,7 @@ budgetReportAsCsv where flattentuples abs = concat [[a,b] | (a,b) <- abs] - showmamt = maybe "" (showMixedAmountOneLineWithoutPrice False) + showmamt = maybe "" (wbToText . showMixedAmountB oneLine) -- tests diff --git a/Hledger/Reports/EntriesReport.hs b/Hledger/Reports/EntriesReport.hs index 3357bee..9da8728 100644 --- a/Hledger/Reports/EntriesReport.hs +++ b/Hledger/Reports/EntriesReport.hs @@ -40,12 +40,8 @@ entriesReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j@Journal{..} = -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings} where - pvalue p = maybe p - (postingApplyValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast mreportlast (rsToday rspec) False p) - value_ - where - periodlast = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j - mreportlast = reportPeriodLastDay rspec + pvalue = postingApplyCostValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast (rsToday rspec) cost_ value_ + where periodlast = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j tests_EntriesReport = tests "EntriesReport" [ tests "entriesReport" [ diff --git a/Hledger/Reports/MultiBalanceReport.hs b/Hledger/Reports/MultiBalanceReport.hs index 0bbd313..3d5362a 100644 --- a/Hledger/Reports/MultiBalanceReport.hs +++ b/Hledger/Reports/MultiBalanceReport.hs @@ -23,11 +23,9 @@ module Hledger.Reports.MultiBalanceReport ( sortRowsLike, -- * Helper functions - calculateReportSpan, makeReportQuery, getPostingsByColumn, getPostings, - calculateColSpans, startingBalances, generateMultiBalanceReport, @@ -51,7 +49,7 @@ import Data.Semigroup ((<>)) #endif import Data.Semigroup (sconcat) import Data.Time.Calendar (Day, addDays, fromGregorian) -import Safe (headMay, lastDef, lastMay) +import Safe (lastDef, minimumMay) import Hledger.Data import Hledger.Query @@ -113,22 +111,19 @@ multiBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> MultiBalanceRe multiBalanceReportWith rspec' j priceoracle = report where -- Queries, report/column dates. - reportspan = dbg3 "reportspan" $ calculateReportSpan rspec' j + reportspan = dbg3 "reportspan" $ reportSpan j rspec' rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan - valuation = makeValuation rspec' j priceoracle -- Must use rspec' instead of rspec, - -- so the reportspan isn't used for valuation -- Group postings into their columns. colps = dbg5 "colps" $ getPostingsByColumn rspec j reportspan - colspans = dbg3 "colspans" $ M.keys colps -- The matched accounts with a starting balance. All of these should appear -- in the report, even if they have no postings during the report period. - startbals = dbg5 "startbals" $ startingBalances rspec j reportspan + startbals = dbg5 "startbals" $ startingBalances rspec j priceoracle reportspan -- Generate and postprocess the report, negating balances and taking percentages if needed report = dbg4 "multiBalanceReportWith" $ - generateMultiBalanceReport rspec j valuation colspans colps startbals + generateMultiBalanceReport rspec j priceoracle colps startbals -- | Generate a compound balance report from a list of CBCSubreportSpec. This -- shares postings between the subreports. @@ -144,18 +139,15 @@ compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr where -- Queries, report/column dates. - reportspan = dbg3 "reportspan" $ calculateReportSpan rspec' j + reportspan = dbg3 "reportspan" $ reportSpan j rspec' rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan - valuation = makeValuation rspec' j priceoracle -- Must use ropts' instead of ropts, - -- so the reportspan isn't used for valuation -- Group postings into their columns. - colps = dbg5 "colps" $ getPostingsByColumn rspec{rsOpts=(rsOpts rspec){empty_=True}} j reportspan - colspans = dbg3 "colspans" $ M.keys colps + colps = dbg5 "colps" $ getPostingsByColumn rspec j reportspan -- The matched accounts with a starting balance. All of these should appear -- in the report, even if they have no postings during the report period. - startbals = dbg5 "startbals" $ startingBalances rspec j reportspan + startbals = dbg5 "startbals" $ startingBalances rspec j priceoracle reportspan subreports = map generateSubreport subreportspecs where @@ -163,7 +155,7 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr ( cbcsubreporttitle -- Postprocess the report, negating balances and taking percentages if needed , cbcsubreporttransform $ - generateMultiBalanceReport rspec{rsOpts=ropts} j valuation colspans colps' startbals' + generateMultiBalanceReport rspec{rsOpts=ropts} j priceoracle colps' startbals' , cbcsubreportincreasestotal ) where @@ -184,7 +176,7 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr subreportTotal (_, sr, increasestotal) = (if increasestotal then id else fmap negate) $ prTotals sr - cbr = CompoundPeriodicReport "" colspans subreports overalltotals + cbr = CompoundPeriodicReport "" (M.keys colps) subreports overalltotals -- | Calculate starting balances, if needed for -H @@ -194,14 +186,20 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr -- TODO: Do we want to check whether to bother calculating these? isHistorical -- and startDate is not nothing, otherwise mempty? This currently gives a -- failure with some totals which are supposed to be 0 being blank. -startingBalances :: ReportSpec -> Journal -> DateSpan -> HashMap AccountName Account -startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j reportspan = - acctChangesFromPostings rspec' . map fst $ getPostings rspec' j +startingBalances :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> HashMap AccountName Account +startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle reportspan = + fmap (M.findWithDefault nullacct precedingspan) acctmap where + acctmap = calculateReportMatrix rspec' j priceoracle mempty + . M.singleton precedingspan . map fst $ getPostings rspec' j + rspec' = rspec{rsQuery=startbalq,rsOpts=ropts'} - ropts' = case accountlistmode_ ropts of - ALTree -> ropts{period_=precedingperiod, no_elide_=True} - ALFlat -> ropts{period_=precedingperiod} + -- If we're re-valuing every period, we need to have the unvalued start + -- balance, so we can do it ourselves later. + ropts' = case value_ ropts of + Just (AtEnd _) -> ropts''{value_=Nothing} + _ -> ropts'' + where ropts'' = ropts{period_=precedingperiod, no_elide_=accountlistmode_ ropts == ALTree} -- q projected back before the report start date. -- When there's no report start date, in case there are future txns (the hledger-ui case above), @@ -216,26 +214,6 @@ startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j reportspan = DateSpan Nothing Nothing -> emptydatespan a -> a --- | Calculate the span of the report to be generated. -calculateReportSpan :: ReportSpec -> Journal -> DateSpan -calculateReportSpan ReportSpec{rsQuery=query,rsOpts=ropts} j = reportspan - where - -- The date span specified by -b/-e/-p options and query args if any. - requestedspan = dbg3 "requestedspan" $ queryDateSpan (date2_ ropts) query - -- If the requested span is open-ended, close it using the journal's end dates. - -- This can still be the null (open) span if the journal is empty. - requestedspan' = dbg3 "requestedspan'" $ - requestedspan `spanDefaultsFrom` journalDateSpan (date2_ ropts) j - -- The list of interval spans enclosing the requested span. - -- This list can be empty if the journal was empty, - -- or if hledger-ui has added its special date:-tomorrow to the query - -- and all txns are in the future. - intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspan' - -- The requested span enlarged to enclose a whole number of intervals. - -- This can be the null span if there were no intervals. - reportspan = DateSpan (spanStart =<< headMay intervalspans) - (spanEnd =<< lastMay intervalspans) - -- | Remove any date queries and insert queries from the report span. -- The user's query expanded to the report span -- if there is one (otherwise any date queries are left as-is, which @@ -250,27 +228,15 @@ makeReportQuery rspec reportspan dateless = dbg3 "dateless" . filterQuery (not . queryIsDateOrDate2) dateqcons = if date2_ (rsOpts rspec) then Date2 else Date --- | Make a valuation function for valuating MixedAmounts and a given Day -makeValuation :: ReportSpec -> Journal -> PriceOracle -> (Day -> MixedAmount -> MixedAmount) -makeValuation rspec j priceoracle day = case value_ (rsOpts rspec) of - Nothing -> id - Just v -> mixedAmountApplyValuation priceoracle styles day mreportlast (rsToday rspec) multiperiod v - where - -- Some things needed if doing valuation. - styles = journalCommodityStyles j - mreportlast = reportPeriodLastDay rspec - multiperiod = interval_ (rsOpts rspec) /= NoInterval - -- | Group postings, grouped by their column getPostingsByColumn :: ReportSpec -> Journal -> DateSpan -> Map DateSpan [Posting] getPostingsByColumn rspec j reportspan = columns where -- Postings matching the query within the report period. ps :: [(Posting, Day)] = dbg5 "getPostingsByColumn" $ getPostings rspec j - days = map snd ps -- The date spans to be included as report columns. - colspans = calculateColSpans (rsOpts rspec) reportspan days + colspans = dbg3 "colspans" $ splitSpan (interval_ $ rsOpts rspec) reportspan addPosting (p, d) = maybe id (M.adjust (p:)) $ latestSpanContaining colspans d emptyMap = M.fromList . zip colspans $ repeat [] @@ -296,32 +262,6 @@ getPostings ReportSpec{rsQuery=query,rsOpts=ropts} = PrimaryDate -> postingDate SecondaryDate -> postingDate2 --- | Calculate the DateSpans to be used for the columns of the report. -calculateColSpans :: ReportOpts -> DateSpan -> [Day] -> [DateSpan] -calculateColSpans ropts reportspan days = - splitSpan (interval_ ropts) displayspan - where - displayspan - | empty_ ropts = dbg3 "displayspan (-E)" reportspan -- all the requested intervals - | otherwise = dbg3 "displayspan" $ reportspan `spanIntersect` matchedspan -- exclude leading/trailing empty intervals - matchedspan = dbg3 "matchedspan" $ daysSpan days - - --- | Gather the account balance changes into a regular matrix --- including the accounts from all columns. -calculateAccountChanges :: ReportSpec -> [DateSpan] -> Map DateSpan [Posting] - -> HashMap ClippedAccountName (Map DateSpan Account) -calculateAccountChanges rspec colspans colps - | queryDepth (rsQuery rspec) == Just 0 = acctchanges <> elided - | otherwise = acctchanges - where - -- Transpose to get each account's balance changes across all columns. - acctchanges = transposeMap colacctchanges - - colacctchanges :: Map DateSpan (HashMap ClippedAccountName Account) = - dbg5 "colacctchanges" $ fmap (acctChangesFromPostings rspec) colps - - elided = HM.singleton "..." $ M.fromList [(span, nullacct) | span <- colspans] -- | Given a set of postings, eg for a single report column, gather -- the accounts that have postings and calculate the change amount for @@ -338,70 +278,68 @@ acctChangesFromPostings ReportSpec{rsQuery=query,rsOpts=ropts} ps = filter ((0<) . anumpostings) depthq = dbg3 "depthq" $ filterQuery queryIsDepth query --- | Accumulate and value amounts, as specified by the report options. +-- | Gather the account balance changes into a regular matrix, then +-- accumulate and value amounts, as specified by the report options. -- -- Makes sure all report columns have an entry. -accumValueAmounts :: ReportOpts -> (Day -> MixedAmount -> MixedAmount) -> [DateSpan] - -> HashMap ClippedAccountName Account - -> HashMap ClippedAccountName (Map DateSpan Account) - -> HashMap ClippedAccountName (Map DateSpan Account) -accumValueAmounts ropts valuation colspans startbals acctchanges = -- PARTIAL: +calculateReportMatrix :: ReportSpec -> Journal -> PriceOracle + -> HashMap ClippedAccountName Account + -> Map DateSpan [Posting] + -> HashMap ClippedAccountName (Map DateSpan Account) +calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals colps = -- PARTIAL: -- Ensure all columns have entries, including those with starting balances - HM.mapWithKey rowbals $ ((<>zeros) <$> acctchanges) <> (zeros <$ startbals) + HM.mapWithKey rowbals allchanges where -- The valued row amounts to be displayed: per-period changes, -- zero-based cumulative totals, or -- starting-balance-based historical balances. rowbals name changes = dbg5 "rowbals" $ case balancetype_ ropts of PeriodChange -> changeamts - CumulativeChange -> cumulative + CumulativeChange -> cumulativeSum avalue nullacct changeamts HistoricalBalance -> historical where - historical = cumulativeSum startingBalance - cumulative = cumulativeSum nullacct - changeamts = M.mapWithKey valueAcct changes - - cumulativeSum start = snd $ M.mapAccumWithKey accumValued start changes - where accumValued startAmt date newAmt = (s, valueAcct date s) - where s = sumAcct startAmt newAmt - + -- changes to report on: usually just the changes itself, but use the + -- differences in the historical amount for ValueChangeReports. + changeamts = case reporttype_ ropts of + ChangeReport -> M.mapWithKey avalue changes + BudgetReport -> M.mapWithKey avalue changes + ValueChangeReport -> periodChanges valuedStart historical + historical = cumulativeSum avalue startingBalance changes startingBalance = HM.lookupDefault nullacct name startbals - - -- Add the values of two accounts. Should be right-biased, since it's used - -- in scanl, so other properties (such as anumpostings) stay in the right place - sumAcct Account{aibalance=i1,aebalance=e1} a@Account{aibalance=i2,aebalance=e2} = - a{aibalance = i1 + i2, aebalance = e1 + e2} - - -- We may be converting amounts to value, per hledger_options.m4.md "Effect of --value on reports". - valueAcct (DateSpan _ (Just end)) acct = - acct{aibalance = value (aibalance acct), aebalance = value (aebalance acct)} - where value = valuation (addDays (-1) end) - valueAcct _ _ = error "multiBalanceReport: expected all spans to have an end date" -- XXX should not happen - + valuedStart = avalue (DateSpan Nothing historicalDate) startingBalance + + -- Transpose to get each account's balance changes across all columns, then + -- pad with zeros + allchanges = ((<>zeros) <$> acctchanges) <> (zeros <$ startbals) + acctchanges = dbg5 "acctchanges" . addElided $ transposeMap colacctchanges + colacctchanges = dbg5 "colacctchanges" $ fmap (acctChangesFromPostings rspec) valuedps + valuedps = M.mapWithKey (\colspan -> map (pvalue colspan)) colps + + (pvalue, avalue) = postingAndAccountValuations rspec j priceoracle + addElided = if queryDepth (rsQuery rspec) == Just 0 then HM.insert "..." zeros else id + historicalDate = minimumMay $ mapMaybe spanStart colspans zeros = M.fromList [(span, nullacct) | span <- colspans] + colspans = M.keys colps + -- | Lay out a set of postings grouped by date span into a regular matrix with rows -- given by AccountName and columns by DateSpan, then generate a MultiBalanceReport -- from the columns. -generateMultiBalanceReport :: ReportSpec -> Journal -> (Day -> MixedAmount -> MixedAmount) -> [DateSpan] +generateMultiBalanceReport :: ReportSpec -> Journal -> PriceOracle -> Map DateSpan [Posting] -> HashMap AccountName Account -> MultiBalanceReport -generateMultiBalanceReport rspec@ReportSpec{rsOpts=ropts} j valuation colspans colps startbals = +generateMultiBalanceReport rspec@ReportSpec{rsOpts=ropts} j priceoracle colps startbals = report where - -- Each account's balance changes across all columns. - acctchanges = dbg5 "acctchanges" $ calculateAccountChanges rspec colspans colps - -- Process changes into normal, cumulative, or historical amounts, plus value them - accumvalued = accumValueAmounts ropts valuation colspans startbals acctchanges + matrix = calculateReportMatrix rspec j priceoracle startbals colps -- All account names that will be displayed, possibly depth-clipped. - displaynames = dbg5 "displaynames" $ displayedAccounts rspec accumvalued + displaynames = dbg5 "displaynames" $ displayedAccounts rspec matrix -- All the rows of the report. - rows = dbg5 "rows" - . (if invert_ ropts then map (fmap negate) else id) -- Negate amounts if applicable - $ buildReportRows ropts displaynames accumvalued + rows = dbg5 "rows" . (if invert_ ropts then map (fmap negate) else id) -- Negate amounts if applicable + $ buildReportRows ropts displaynames matrix -- Calculate column totals totalsrow = dbg5 "totalsrow" $ calculateTotalsRow ropts rows @@ -410,7 +348,7 @@ generateMultiBalanceReport rspec@ReportSpec{rsOpts=ropts} j valuation colspans c sortedrows = dbg5 "sortedrows" $ sortRows ropts j rows -- Take percentages if needed - report = reportPercent ropts $ PeriodicReport colspans sortedrows totalsrow + report = reportPercent ropts $ PeriodicReport (M.keys colps) sortedrows totalsrow -- | Build the report rows. -- One row per account, with account name info, row amounts, row total and row average. @@ -560,7 +498,7 @@ reportPercent ropts report@(PeriodicReport spans rows totalrow) -- Makes sure that all DateSpans are present in all rows. transposeMap :: Map DateSpan (HashMap AccountName a) -> HashMap AccountName (Map DateSpan a) -transposeMap xs = M.foldrWithKey addSpan mempty xs +transposeMap = M.foldrWithKey addSpan mempty where addSpan span acctmap seen = HM.foldrWithKey (addAcctSpan span) seen acctmap @@ -593,6 +531,44 @@ perdivide a b = fromMaybe (error' errmsg) $ do -- PARTIAL: return $ mixed [per $ if aquantity b' == 0 then 0 else aquantity a' / abs (aquantity b') * 100] where errmsg = "Cannot calculate percentages if accounts have different commodities (Hint: Try --cost, -V or similar flags.)" +-- Add the values of two accounts. Should be right-biased, since it's used +-- in scanl, so other properties (such as anumpostings) stay in the right place +sumAcct :: Account -> Account -> Account +sumAcct Account{aibalance=i1,aebalance=e1} a@Account{aibalance=i2,aebalance=e2} = + a{aibalance = i1 + i2, aebalance = e1 + e2} + +-- Subtract the values in one account from another. Should be left-biased. +subtractAcct :: Account -> Account -> Account +subtractAcct a@Account{aibalance=i1,aebalance=e1} Account{aibalance=i2,aebalance=e2} = + a{aibalance = i1 - i2, aebalance = e1 - e2} + +-- | Extract period changes from a cumulative list +periodChanges :: Account -> Map k Account -> Map k Account +periodChanges start amtmap = + M.fromDistinctAscList . zip dates $ zipWith subtractAcct amts (start:amts) + where (dates, amts) = unzip $ M.toAscList amtmap + +-- | Calculate a cumulative sum from a list of period changes and a valuation +-- function. +cumulativeSum :: (DateSpan -> Account -> Account) -> Account -> Map DateSpan Account -> Map DateSpan Account +cumulativeSum value start = snd . M.mapAccumWithKey accumValued start + where accumValued startAmt date newAmt = let s = sumAcct startAmt newAmt in (s, value date s) + +-- | Calculate the Posting and Account valuation functions required by this +-- MultiBalanceReport. +postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle + -> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account) +postingAndAccountValuations ReportSpec{rsToday=today, rsOpts=ropts} j priceoracle = case value_ ropts of + Just (AtEnd _) -> (const id, avalue' (cost_ ropts) (value_ ropts)) + _ -> (pvalue' (cost_ ropts) (value_ ropts), const id) + where + avalue' c v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)} + where value = mixedAmountApplyCostValuation priceoracle styles (end span) today (error "multiBalanceReport: did not expect amount valuation to be called ") c v -- PARTIAL: should not happen + pvalue' c v span = postingApplyCostValuation priceoracle styles (end span) today c v + end = fromMaybe (error "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen + . fmap (addDays (-1)) . spanEnd + styles = journalCommodityStyles j + -- tests tests_MultiBalanceReport = tests "MultiBalanceReport" [ diff --git a/Hledger/Reports/PostingsReport.hs b/Hledger/Reports/PostingsReport.hs index 902085e..297d1f6 100644 --- a/Hledger/Reports/PostingsReport.hs +++ b/Hledger/Reports/PostingsReport.hs @@ -24,8 +24,7 @@ where import Data.List import Data.List.Extra (nubSort) import Data.Maybe --- import Data.Text (Text) -import qualified Data.Text as T +import Data.Text (Text) import Data.Time.Calendar import Safe (headMay, lastMay) @@ -35,12 +34,10 @@ import Hledger.Utils import Hledger.Reports.ReportOptions --- | A postings report is a list of postings with a running total, a label --- for the total field, and a little extra transaction info to help with rendering. +-- | A postings report is a list of postings with a running total, and a little extra +-- transaction info to help with rendering. -- This is used eg for the register command. -type PostingsReport = (String -- label for the running balance column XXX remove - ,[PostingsReportItem] -- line items, one per posting - ) +type PostingsReport = [PostingsReportItem] -- line items, one per posting type PostingsReportItem = (Maybe Day -- The posting date, if this is the first posting in a -- transaction or if it's different from the previous -- posting's date. Or if this a summary posting, the @@ -49,7 +46,7 @@ type PostingsReportItem = (Maybe Day -- The posting date, if this is the firs ,Maybe Day -- If this is a summary posting, the report interval's -- end date if this is the first summary posting in -- the interval. - ,Maybe String -- The posting's transaction's description, if this is the first posting in the transaction. + ,Maybe Text -- The posting's transaction's description, if this is the first posting in the transaction. ,Posting -- The posting, possibly with the account name depth-clipped. ,MixedAmount -- The running total after this posting, or with --average, -- the running average posting amount. With --historical, @@ -66,10 +63,9 @@ type SummaryPosting = (Posting, Day) -- | Select postings from the journal and add running balance and other -- information to make a postings report. Used by eg hledger's register command. postingsReport :: ReportSpec -> Journal -> PostingsReport -postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = - (totallabel, items) +postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items where - reportspan = adjustReportDates rspec j + reportspan = reportSpanBothDates j rspec whichdate = whichDateFromOpts ropts mdepth = queryDepth $ rsQuery rspec styles = journalCommodityStyles j @@ -79,19 +75,18 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = -- postings to be included in the report, and similarly-matched postings before the report start date (precedingps, reportps) = matchedPostingsBeforeAndDuring rspec j reportspan + -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". + pvalue periodlast = postingApplyCostValuation priceoracle styles periodlast (rsToday rspec) cost_ value_ + -- Postings, or summary postings with their subperiod's end date, to be displayed. displayps :: [(Posting, Maybe Day)] - | multiperiod && changingValuation ropts = [(pvalue lastday p, Just periodend) | (p, periodend) <- summariseps reportps, let lastday = addDays (-1) periodend] - | multiperiod = [(p, Just periodend) | (p, periodend) <- summariseps valuedps] - | otherwise = [(p, Nothing) | p <- valuedps] + | multiperiod, Just (AtEnd _) <- value_ = [(pvalue lastday p, Just periodend) | (p, periodend) <- summariseps reportps, let lastday = addDays (-1) periodend] + | multiperiod = [(p, Just periodend) | (p, periodend) <- summariseps valuedps] + | otherwise = [(p, Nothing) | p <- valuedps] where summariseps = summarisePostingsByInterval interval_ whichdate mdepth showempty reportspan valuedps = map (pvalue reportorjournallast) reportps showempty = empty_ || average_ - -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". - pvalue periodlast p = maybe p (postingApplyValuation priceoracle styles periodlast mreportlast (rsToday rspec) multiperiod p) value_ - where - mreportlast = reportPeriodLastDay rspec reportorjournallast = fromMaybe (error' "postingsReport: expected a non-empty journal") $ -- PARTIAL: shouldn't happen reportPeriodOrJournalLastDay rspec j @@ -106,19 +101,16 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = -- of --value on reports". -- XXX balance report doesn't value starting balance.. should this ? historical = balancetype_ == HistoricalBalance - startbal | average_ = if historical then bvalue precedingavg else 0 - | otherwise = if historical then bvalue precedingsum else 0 + startbal | average_ = if historical then precedingavg else 0 + | otherwise = if historical then precedingsum else 0 where - precedingsum = sumPostings precedingps + precedingsum = sumPostings $ map (pvalue daybeforereportstart) precedingps precedingavg | null precedingps = 0 | otherwise = divideMixedAmount (fromIntegral $ length precedingps) precedingsum - bvalue = maybe id (mixedAmountApplyValuation priceoracle styles daybeforereportstart Nothing (rsToday rspec) multiperiod) value_ - -- XXX constrain valuation type to AtDate daybeforereportstart here ? - where - daybeforereportstart = - maybe (error' "postingsReport: expected a non-empty journal") -- PARTIAL: shouldn't happen - (addDays (-1)) - $ reportPeriodOrJournalStart rspec j + daybeforereportstart = + maybe (error' "postingsReport: expected a non-empty journal") -- PARTIAL: shouldn't happen + (addDays (-1)) + $ reportPeriodOrJournalStart rspec j runningcalc = registerRunningCalculationFn ropts startnum = if historical then length precedingps + 1 else 1 @@ -132,28 +124,6 @@ registerRunningCalculationFn ropts | average_ ropts = \i avg amt -> avg + divideMixedAmount (fromIntegral i) (amt - avg) | otherwise = \_ bal amt -> bal + amt -totallabel = "Total" - --- | Adjust report start/end dates to more useful ones based on --- journal data and report intervals. Ie: --- 1. If the start date is unspecified, use the earliest date in the journal (if any) --- 2. If the end date is unspecified, use the latest date in the journal (if any) --- 3. If a report interval is specified, enlarge the dates to enclose whole intervals -adjustReportDates :: ReportSpec -> Journal -> DateSpan -adjustReportDates rspec@ReportSpec{rsOpts=ropts} j = reportspan - where - -- see also multiBalanceReport - requestedspan = dbg3 "requestedspan" $ queryDateSpan' $ rsQuery rspec -- span specified by -b/-e/-p options and query args - journalspan = dbg3 "journalspan" $ dates `spanUnion` date2s -- earliest and latest dates (or date2s) in the journal - where - dates = journalDateSpan False j - date2s = journalDateSpan True j - requestedspanclosed = dbg3 "requestedspanclosed" $ requestedspan `spanDefaultsFrom` journalspan -- if open-ended, close it using the journal's dates (if any) - intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspanclosed -- get the whole intervals enclosing that - mreportstart = dbg3 "reportstart" $ maybe Nothing spanStart $ headMay intervalspans -- start of the first interval, or open ended - mreportend = dbg3 "reportend" $ maybe Nothing spanEnd $ lastMay intervalspans -- end of the last interval, or open ended - reportspan = dbg3 "reportspan" $ DateSpan mreportstart mreportend -- the requested span enlarged to whole intervals if possible - -- | Find postings matching a given query, within a given date span, -- and also any similarly-matched postings before that date span. -- Date restrictions and depth restrictions in the query are ignored. @@ -208,14 +178,13 @@ mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Day -> Posting -> Mix mkpostingsReportItem showdate showdesc wd menddate p b = (if showdate then Just date else Nothing ,menddate - ,if showdesc then Just desc else Nothing + ,if showdesc then tdescription <$> ptransaction p else Nothing ,p ,b ) where date = case wd of PrimaryDate -> postingDate p SecondaryDate -> postingDate2 p - desc = T.unpack $ maybe "" tdescription $ ptransaction p -- | Convert a list of postings into summary postings, one per interval, -- aggregated to the specified depth if any. @@ -269,7 +238,7 @@ negatePostingAmount p = p { pamount = negate $ pamount p } tests_PostingsReport = tests "PostingsReport" [ test "postingsReport" $ do - let (query, journal) `gives` n = (length $ snd $ postingsReport defreportspec{rsQuery=query} journal) @?= n + let (query, journal) `gives` n = (length $ postingsReport defreportspec{rsQuery=query} journal) @?= n -- with the query specified explicitly (Any, nulljournal) `gives` 0 (Any, samplejournal) `gives` 13 @@ -278,10 +247,10 @@ tests_PostingsReport = tests "PostingsReport" [ (And [Depth 1, StatusQ Cleared, Acct (toRegex' "expenses")], samplejournal) `gives` 2 (And [And [Depth 1, StatusQ Cleared], Acct (toRegex' "expenses")], samplejournal) `gives` 2 -- with query and/or command-line options - (length $ snd $ postingsReport defreportspec samplejournal) @?= 13 - (length $ snd $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1}} samplejournal) @?= 11 - (length $ snd $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1, empty_=True}} samplejournal) @?= 20 - (length $ snd $ postingsReport defreportspec{rsQuery=Acct $ toRegex' "assets:bank:checking"} samplejournal) @?= 5 + (length $ postingsReport defreportspec samplejournal) @?= 13 + (length $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1}} samplejournal) @?= 11 + (length $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1, empty_=True}} samplejournal) @?= 20 + (length $ postingsReport defreportspec{rsQuery=Acct $ toRegex' "assets:bank:checking"} samplejournal) @?= 5 -- (defreportopts, And [Acct "a a", Acct "'b"], samplejournal2) `gives` 0 -- [(Just (fromGregorian 2008 01 01,"income"),assets:bank:checking $1,$1) diff --git a/Hledger/Reports/ReportOptions.hs b/Hledger/Reports/ReportOptions.hs index 356aad9..f88fb42 100644 --- a/Hledger/Reports/ReportOptions.hs +++ b/Hledger/Reports/ReportOptions.hs @@ -11,6 +11,7 @@ Options common to most hledger reports. module Hledger.Reports.ReportOptions ( ReportOpts(..), ReportSpec(..), + ReportType(..), BalanceType(..), AccountListMode(..), ValuationType(..), @@ -21,9 +22,9 @@ module Hledger.Reports.ReportOptions ( updateReportSpec, updateReportSpecWith, rawOptsToReportSpec, + balanceTypeOverride, flat_, tree_, - changingValuation, reportOptsToggleStatus, simplifyStatuses, whichDateFromOpts, @@ -34,24 +35,23 @@ module Hledger.Reports.ReportOptions ( transactionDateFn, postingDateFn, reportSpan, + reportSpanBothDates, reportStartDate, reportEndDate, reportPeriodStart, reportPeriodOrJournalStart, reportPeriodLastDay, reportPeriodOrJournalLastDay, - valuationTypeIsCost, - valuationTypeIsDefaultValue, ) where import Control.Applicative ((<|>)) import Data.List.Extra (nubSort) -import Data.Maybe (fromMaybe, isJust) +import Data.Maybe (fromMaybe, isJust, mapMaybe) import qualified Data.Text as T import Data.Time.Calendar (Day, addDays) import Data.Default (Default(..)) -import Safe (lastDef, lastMay) +import Safe (headMay, lastDef, lastMay, maximumMay) import System.Console.ANSI (hSupportsANSIColor) import System.Environment (lookupEnv) @@ -63,8 +63,16 @@ import Hledger.Query import Hledger.Utils --- | Which "balance" is being shown in a balance report. -data BalanceType = PeriodChange -- ^ The change of balance in each period. +-- | What is calculated and shown in each cell in a balance report. +data ReportType = ChangeReport -- ^ The sum of posting amounts. + | BudgetReport -- ^ The sum of posting amounts and the goal. + | ValueChangeReport -- ^ The change of value of period-end historical values. + deriving (Eq, Show) + +instance Default ReportType where def = ChangeReport + +-- | Which "accumulation method" is being shown in a balance report. +data BalanceType = PeriodChange -- ^ The accumulate change over a single period. | CumulativeChange -- ^ The accumulated change across multiple periods. | HistoricalBalance -- ^ The historical ending balance, including the effect of -- all postings before the report period. Unless altered by, @@ -87,6 +95,7 @@ data ReportOpts = ReportOpts { period_ :: Period ,interval_ :: Interval ,statuses_ :: [Status] -- ^ Zero, one, or two statuses to be matched + ,cost_ :: Costing -- ^ Should we convert amounts to cost, when present? ,value_ :: Maybe ValuationType -- ^ What value should amounts be converted to ? ,infer_value_ :: Bool -- ^ Infer market prices from transactions ? ,depth_ :: Maybe Int @@ -103,6 +112,7 @@ data ReportOpts = ReportOpts { -- for account transactions reports (aregister) ,txn_dates_ :: Bool -- for balance reports (bal, bs, cf, is) + ,reporttype_ :: ReportType ,balancetype_ :: BalanceType ,accountlistmode_ :: AccountListMode ,drop_ :: Int @@ -136,6 +146,7 @@ defreportopts = ReportOpts { period_ = PeriodAll , interval_ = NoInterval , statuses_ = [] + , cost_ = NoCost , value_ = Nothing , infer_value_ = False , depth_ = Nothing @@ -148,6 +159,7 @@ defreportopts = ReportOpts , average_ = False , related_ = False , txn_dates_ = False + , reporttype_ = def , balancetype_ = def , accountlistmode_ = ALFlat , drop_ = 0 @@ -170,20 +182,22 @@ rawOptsToReportOpts rawopts = do supports_color <- hSupportsANSIColor stdout let colorflag = stringopt "color" rawopts - formatstring = maybestringopt "format" rawopts + formatstring = T.pack <$> maybestringopt "format" rawopts querystring = map T.pack $ listofstringopt "args" rawopts -- doesn't handle an arg like "" right + (costing, valuation) = valuationTypeFromRawOpts rawopts format <- case parseStringFormat <$> formatstring of Nothing -> return defaultBalanceLineFormat Just (Right x) -> return x Just (Left err) -> fail $ "could not parse format option: " ++ err - let reportopts = defreportopts + return defreportopts {period_ = periodFromRawOpts d rawopts ,interval_ = intervalFromRawOpts rawopts ,statuses_ = statusesFromRawOpts rawopts - ,value_ = valuationTypeFromRawOpts rawopts - ,infer_value_ = boolopt "infer-value" rawopts + ,cost_ = costing + ,value_ = valuation + ,infer_value_ = boolopt "infer-market-price" rawopts ,depth_ = maybeposintopt "depth" rawopts ,date2_ = boolopt "date2" rawopts ,empty_ = boolopt "empty" rawopts @@ -194,6 +208,7 @@ rawOptsToReportOpts rawopts = do ,average_ = boolopt "average" rawopts ,related_ = boolopt "related" rawopts ,txn_dates_ = boolopt "txn-dates" rawopts + ,reporttype_ = reporttypeopt rawopts ,balancetype_ = balancetypeopt rawopts ,accountlistmode_ = accountlistmodeopt rawopts ,drop_ = posintopt "drop" rawopts @@ -210,7 +225,6 @@ rawOptsToReportOpts rawopts = do ,forecast_ = forecastPeriodFromRawOpts d rawopts ,transpose_ = boolopt "transpose" rawopts } - return reportopts -- | The result of successfully parsing a ReportOpts on a particular -- Day. Any ambiguous dates are completed and Queries are parsed, @@ -273,13 +287,29 @@ accountlistmodeopt = "flat" -> Just ALFlat _ -> Nothing +reporttypeopt :: RawOpts -> ReportType +reporttypeopt = + fromMaybe ChangeReport . choiceopt parse where + parse = \case + "sum" -> Just ChangeReport + "valuechange" -> Just ValueChangeReport + "budget" -> Just BudgetReport + _ -> Nothing + balancetypeopt :: RawOpts -> BalanceType -balancetypeopt = - fromMaybe PeriodChange . choiceopt parse where +balancetypeopt = fromMaybe PeriodChange . balanceTypeOverride + +balanceTypeOverride :: RawOpts -> Maybe BalanceType +balanceTypeOverride rawopts = choiceopt parse rawopts <|> reportbal + where parse = \case "historical" -> Just HistoricalBalance "cumulative" -> Just CumulativeChange + "change" -> Just PeriodChange _ -> Nothing + reportbal = case reporttypeopt rawopts of + ValueChangeReport -> Just PeriodChange + _ -> Nothing -- Get the period specified by any -b/--begin, -e/--end and/or -p/--period -- options appearing in the command line. @@ -402,27 +432,37 @@ reportOptsToggleStatus s ropts@ReportOpts{statuses_=ss} | s `elem` ss = ropts{statuses_=filter (/= s) ss} | otherwise = ropts{statuses_=simplifyStatuses (s:ss)} --- | Parse the type of valuation to be performed, if any, specified by --- -B/--cost, -V, -X/--exchange, or --value flags. If there's more --- than one of these, the rightmost flag wins. -valuationTypeFromRawOpts :: RawOpts -> Maybe ValuationType -valuationTypeFromRawOpts = lastMay . collectopts valuationfromrawopt +-- | Parse the type of valuation and costing to be performed, if any, +-- specified by -B/--cost, -V, -X/--exchange, or --value flags. It is +-- allowed to combine -B/--cost with any other valuation type. If +-- there's more than one valuation type, the rightmost flag wins. +valuationTypeFromRawOpts :: RawOpts -> (Costing, Maybe ValuationType) +valuationTypeFromRawOpts rawopts = (costing, valuation) where + costing = if (any ((Cost==) . fst) valuationopts) then Cost else NoCost + valuation = case reporttypeopt rawopts of + ValueChangeReport -> case directval of + Nothing -> Just $ AtEnd Nothing -- If no valuation requested for valuechange, use AtEnd + Just (AtEnd _) -> directval -- If AtEnd valuation requested, use it + Just _ -> usageError "--valuechange only produces sensible results with --value=end" + _ -> directval -- Otherwise, use requested valuation + where directval = lastMay $ mapMaybe snd valuationopts + + valuationopts = collectopts valuationfromrawopt rawopts valuationfromrawopt (n,v) -- option name, value - | n == "B" = Just $ AtCost Nothing - | n == "V" = Just $ AtDefault Nothing - | n == "X" = Just $ AtDefault (Just $ T.pack v) - | n == "value" = Just $ valuation v + | n == "B" = Just (Cost, Nothing) -- keep supporting --value=cost for now + | n == "V" = Just (NoCost, Just $ AtEnd Nothing) + | n == "X" = Just (NoCost, Just $ AtEnd (Just $ T.pack v)) + | n == "value" = Just $ valueopt v | otherwise = Nothing - valuation v - | t `elem` ["cost","c"] = AtCost mc - | t `elem` ["then" ,"t"] = AtThen mc - | t `elem` ["end" ,"e"] = AtEnd mc - | t `elem` ["now" ,"n"] = AtNow mc - | otherwise = - case parsedateM t of - Just d -> AtDate d mc - Nothing -> usageError $ "could not parse \""++t++"\" as valuation type, should be: cost|then|end|now|c|t|e|n|YYYY-MM-DD" + valueopt v + | t `elem` ["cost","c"] = (Cost, AtEnd . Just <$> mc) -- keep supporting --value=cost,COMM for now + | t `elem` ["then" ,"t"] = (NoCost, Just $ AtThen mc) + | t `elem` ["end" ,"e"] = (NoCost, Just $ AtEnd mc) + | t `elem` ["now" ,"n"] = (NoCost, Just $ AtNow mc) + | otherwise = case parsedateM t of + Just d -> (NoCost, Just $ AtDate d mc) + Nothing -> usageError $ "could not parse \""++t++"\" as valuation type, should be: then|end|now|t|e|n|YYYY-MM-DD" where -- parse --value's value: TYPE[,COMM] (t,c') = break (==',') v @@ -430,18 +470,6 @@ valuationTypeFromRawOpts = lastMay . collectopts valuationfromrawopt "" -> Nothing c -> Just $ T.pack c -valuationTypeIsCost :: ReportOpts -> Bool -valuationTypeIsCost ropts = - case value_ ropts of - Just (AtCost _) -> True - _ -> False - -valuationTypeIsDefaultValue :: ReportOpts -> Bool -valuationTypeIsDefaultValue ropts = - case value_ ropts of - Just (AtDefault _) -> True - _ -> False - -- | Select the Transaction date accessor based on --date2. transactionDateFn :: ReportOpts -> (Transaction -> Day) transactionDateFn ReportOpts{..} = if date2_ then transactionDate2 else tdate @@ -466,13 +494,12 @@ flat_ = not . tree_ -- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts) -- | Convert this journal's postings' amounts to cost using their --- transaction prices, if specified by options (-B/--value=cost). +-- transaction prices, if specified by options (-B/--cost). -- Maybe soon superseded by newer valuation code. journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal -journalSelectingAmountFromOpts opts = - case value_ opts of - Just (AtCost _) -> journalToCost - _ -> id +journalSelectingAmountFromOpts opts = case cost_ opts of + Cost -> journalToCost + NoCost -> id -- | Convert report options to a query, ignoring any non-flag command line arguments. queryFromFlags :: ReportOpts -> Query @@ -486,28 +513,47 @@ queryFromFlags ReportOpts{..} = simplifyQuery $ And flagsq consIf f b = if b then (f True:) else id consJust f = maybe id ((:) . f) --- | Whether the market price for postings might change when reported in --- different report periods. -changingValuation :: ReportOpts -> Bool -changingValuation ropts = case value_ ropts of - Just (AtCost (Just _)) -> True - Just (AtEnd _) -> True - Just (AtDefault _) -> interval_ ropts /= NoInterval - _ -> False - -- Report dates. -- | The effective report span is the start and end dates specified by -- options or queries, or otherwise the earliest and latest transaction or -- posting dates in the journal. If no dates are specified by options/queries -- and the journal is empty, returns the null date span. +-- The boolean argument flags whether primary and secondary dates are considered +-- equivalently. reportSpan :: Journal -> ReportSpec -> DateSpan -reportSpan j ReportSpec{rsQuery=query} = dbg3 "reportspan" $ DateSpan mstartdate menddate +reportSpan = reportSpanHelper False + +-- | Like reportSpan, but uses both primary and secondary dates when calculating +-- the span. +reportSpanBothDates :: Journal -> ReportSpec -> DateSpan +reportSpanBothDates = reportSpanHelper True + +-- | A helper for reportSpan, which takes a Bool indicating whether to use both +-- primary and secondary dates. +reportSpanHelper :: Bool -> Journal -> ReportSpec -> DateSpan +reportSpanHelper bothdates j ReportSpec{rsQuery=query, rsOpts=ropts} = reportspan where - DateSpan mjournalstartdate mjournalenddate = - dbg3 "journalspan" $ journalDateSpan False j -- ignore secondary dates - mstartdate = queryStartDate False query <|> mjournalstartdate - menddate = queryEndDate False query <|> mjournalenddate + -- The date span specified by -b/-e/-p options and query args if any. + requestedspan = dbg3 "requestedspan" $ if bothdates then queryDateSpan' query else queryDateSpan (date2_ ropts) query + -- If we are requesting period-end valuation, the journal date span should + -- include price directives after the last transaction + journalspan = dbg3 "journalspan" $ if bothdates then journalDateSpanBothDates j else journalDateSpan (date2_ ropts) j + pricespan = dbg3 "pricespan" . DateSpan Nothing $ case value_ ropts of + Just (AtEnd _) -> fmap (addDays 1) . maximumMay . map pddate $ jpricedirectives j + _ -> Nothing + -- If the requested span is open-ended, close it using the journal's start and end dates. + -- This can still be the null (open) span if the journal is empty. + requestedspan' = dbg3 "requestedspan'" $ requestedspan `spanDefaultsFrom` (journalspan `spanUnion` pricespan) + -- The list of interval spans enclosing the requested span. + -- This list can be empty if the journal was empty, + -- or if hledger-ui has added its special date:-tomorrow to the query + -- and all txns are in the future. + intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspan' + -- The requested span enlarged to enclose a whole number of intervals. + -- This can be the null span if there were no intervals. + reportspan = dbg3 "reportspan" $ DateSpan (spanStart =<< headMay intervalspans) + (spanEnd =<< lastMay intervalspans) reportStartDate :: Journal -> ReportSpec -> Maybe Day reportStartDate j = spanStart . reportSpan j @@ -538,8 +584,13 @@ reportPeriodLastDay = fmap (addDays (-1)) . queryEndDate False . rsQuery -- Get the last day of the overall report period, or if no report -- period is specified, the last day of the journal (ie the latest --- posting date). If there's no report period and nothing in the +-- posting date). If we're doing period-end valuation, include price +-- directive dates. If there's no report period and nothing in the -- journal, will be Nothing. reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day -reportPeriodOrJournalLastDay rspec j = - reportPeriodLastDay rspec <|> journalEndDate False j +reportPeriodOrJournalLastDay rspec j = reportPeriodLastDay rspec <|> journalOrPriceEnd + where + journalOrPriceEnd = case value_ $ rsOpts rspec of + Just (AtEnd _) -> max (journalEndDate False j) lastPriceDirective + _ -> journalEndDate False j + lastPriceDirective = fmap (addDays 1) . maximumMay . map pddate $ jpricedirectives j diff --git a/Hledger/Reports/ReportTypes.hs b/Hledger/Reports/ReportTypes.hs index 3c21da0..e982e2e 100644 --- a/Hledger/Reports/ReportTypes.hs +++ b/Hledger/Reports/ReportTypes.hs @@ -32,9 +32,10 @@ module Hledger.Reports.ReportTypes , prrDepth ) where -import Data.Aeson -import Data.Decimal +import Data.Aeson (ToJSON(..)) +import Data.Decimal (Decimal) import Data.Maybe (mapMaybe) +import Data.Text (Text) #if !(MIN_VERSION_base(4,11,0)) import Data.Semigroup (Semigroup(..)) #endif @@ -144,16 +145,16 @@ prrMapMaybeName f row = case f $ prrName row of -- It is used in compound balance report commands like balancesheet, -- cashflow and incomestatement. data CompoundPeriodicReport a b = CompoundPeriodicReport - { cbrTitle :: String + { cbrTitle :: Text , cbrDates :: [DateSpan] - , cbrSubreports :: [(String, PeriodicReport a b, Bool)] + , cbrSubreports :: [(Text, PeriodicReport a b, Bool)] , cbrTotals :: PeriodicReportRow () b } deriving (Show, Functor, Generic, ToJSON) -- | Description of one subreport within a compound balance report. -- Part of a "CompoundBalanceCommandSpec", but also used in hledger-lib. data CBCSubreportSpec a = CBCSubreportSpec - { cbcsubreporttitle :: String -- ^ The title to use for the subreport + { cbcsubreporttitle :: Text -- ^ The title to use for the subreport , cbcsubreportquery :: Journal -> Query -- ^ The Query to use for the subreport , cbcsubreportoptions :: ReportOpts -> ReportOpts -- ^ A function to transform the ReportOpts used to produce the subreport , cbcsubreporttransform :: PeriodicReport DisplayName MixedAmount -> PeriodicReport a MixedAmount -- ^ A function to transform the result of the subreport diff --git a/Hledger/Reports/TransactionsReport.hs b/Hledger/Reports/TransactionsReport.hs index 7caea34..a6cd1a3 100644 --- a/Hledger/Reports/TransactionsReport.hs +++ b/Hledger/Reports/TransactionsReport.hs @@ -23,6 +23,7 @@ where import Data.List import Data.List.Extra (nubSort) +import Data.Text (Text) import Data.Ord import Hledger.Data @@ -34,18 +35,14 @@ import Hledger.Utils -- | A transactions report includes a list of transactions touching multiple accounts -- (posting-filtered and unfiltered variants), a running balance, and some --- other information helpful for rendering a register view (a flag --- indicating multiple other accounts and a display string describing --- them) with or without a notion of current account(s). --- Two kinds of report use this data structure, see transactionsReport +-- other information helpful for rendering a register view with or without a notion +-- of current account(s). Two kinds of report use this data structure, see transactionsReport -- and accountTransactionsReport below for details. -type TransactionsReport = (String -- label for the balance column, eg "balance" or "total" - ,[TransactionsReportItem] -- line items, one per transaction - ) +type TransactionsReport = [TransactionsReportItem] -- line items, one per transaction type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified ,Transaction -- the transaction as seen from a particular account, with postings maybe filtered ,Bool -- is this a split, ie more than one other account posting - ,String -- a display string describing the other account(s), if any + ,Text -- a display string describing the other account(s), if any ,MixedAmount -- the amount posted to the current account(s) by the filtered postings (or total amount posted) ,MixedAmount -- the running total of item amounts, starting from zero; -- or with --historical, the running total including items @@ -59,14 +56,12 @@ triBalance (_,_,_,_,_,a) = a triCommodityAmount c = filterMixedAmountByCommodity c . triAmount triCommodityBalance c = filterMixedAmountByCommodity c . triBalance -totallabel = "Period Total" - -- | Select transactions from the whole journal. This is similar to a -- "postingsReport" except with transaction-based report items which -- are ordered most recent first. XXX Or an EntriesReport - use that instead ? -- This is used by hledger-web's journal view. transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport -transactionsReport opts j q = (totallabel, items) +transactionsReport opts j q = items where -- XXX items' first element should be the full transaction with all postings items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts @@ -79,15 +74,14 @@ transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, Transa transactionsReportByCommodity tr = [(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr] where - transactionsReportCommodities (_,items) = - nubSort . map acommodity $ concatMap (amounts . triAmount) items + transactionsReportCommodities = nubSort . map acommodity . concatMap (amounts . triAmount) -- Remove transaction report items and item amount (and running -- balance amount) components that don't involve the specified -- commodity. Other item fields such as the transaction are left unchanged. filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport -filterTransactionsReportByCommodity c (label,items) = - (label, fixTransactionsReportItemBalances $ concat [filterTransactionsReportItemByCommodity c i | i <- items]) +filterTransactionsReportByCommodity c = + fixTransactionsReportItemBalances . concatMap (filterTransactionsReportItemByCommodity c) where filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal) | c `elem` cs = [item'] diff --git a/Hledger/Utils/Color.hs b/Hledger/Utils/Color.hs index e3b0992..fb79265 100644 --- a/Hledger/Utils/Color.hs +++ b/Hledger/Utils/Color.hs @@ -1,17 +1,25 @@ -- | Basic color helpers for prettifying console output. +{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module Hledger.Utils.Color ( color, bgColor, + colorB, + bgColorB, Color(..), ColorIntensity(..) ) where +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif +import qualified Data.Text.Lazy.Builder as TB import System.Console.ANSI +import Hledger.Utils.Text (WideBuilder(..)) -- | Wrap a string in ANSI codes to set and reset foreground colour. @@ -21,3 +29,13 @@ color int col s = setSGRCode [SetColor Foreground int col] ++ s ++ setSGRCode [] -- | Wrap a string in ANSI codes to set and reset background colour. bgColor :: ColorIntensity -> Color -> String -> String bgColor int col s = setSGRCode [SetColor Background int col] ++ s ++ setSGRCode [] + +-- | Wrap a WideBuilder in ANSI codes to set and reset foreground colour. +colorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder +colorB int col (WideBuilder s w) = + WideBuilder (TB.fromString (setSGRCode [SetColor Foreground int col]) <> s <> TB.fromString (setSGRCode [])) w + +-- | Wrap a WideBuilder in ANSI codes to set and reset background colour. +bgColorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder +bgColorB int col (WideBuilder s w) = + WideBuilder (TB.fromString (setSGRCode [SetColor Background int col]) <> s <> TB.fromString (setSGRCode [])) w diff --git a/Hledger/Utils/Debug.hs b/Hledger/Utils/Debug.hs index ad80336..f3d3be3 100644 --- a/Hledger/Utils/Debug.hs +++ b/Hledger/Utils/Debug.hs @@ -15,6 +15,21 @@ to change the debug level without restarting GHCI, save a dummy change in Debug.hs and do a :reload. (Sometimes it's more convenient to temporarily add dbg0's and :reload.) +In hledger, debug levels are used as follows: + +Debug level: What to show: +------------ --------------------------------------------------------- +0 normal command output only (no warnings, eg) +1 (--debug) useful warnings, most common troubleshooting info, eg valuation +2 common troubleshooting info, more detail +3 report options selection +4 report generation +5 report generation, more detail +6 input file reading +7 input file reading, more detail +8 command line parsing +9 any other rarely needed / more in-depth info + -} -- more: @@ -153,9 +168,11 @@ traceAt level | level > 0 && debugLevel < level = flip const | otherwise = trace --- | Trace (print to stderr) a showable value using a custom show function. -traceAtWith :: (a -> String) -> a -> a -traceAtWith f a = trace (f a) a +-- | Trace (print to stderr) a showable value using a custom show function, +-- if the global debug level is at or above the specified level. +-- At level 0, always prints. Otherwise, uses unsafePerformIO. +traceAtWith :: Int -> (a -> String) -> a -> a +traceAtWith level f a = traceAt level (f a) a -- | Pretty-print a label and a showable value to the console -- if the global debug level is at or above the specified level. diff --git a/Hledger/Utils/Regex.hs b/Hledger/Utils/Regex.hs index d96d72f..4d85c93 100644 --- a/Hledger/Utils/Regex.hs +++ b/Hledger/Utils/Regex.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeSynonymInstances #-} {-| @@ -54,6 +56,7 @@ module Hledger.Utils.Regex ( ,RegexError -- * total regex operations ,regexMatch + ,regexMatchText ,regexReplace ,regexReplaceUnmemo ,regexReplaceAllBy @@ -66,6 +69,10 @@ import Data.Array ((!), elems, indices) import Data.Char (isDigit) import Data.List (foldl') import Data.MemoUgly (memo) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif +import Data.Text (Text) import qualified Data.Text as T import Text.Regex.TDFA ( Regex, CompOption(..), defaultCompOpt, defaultExecOpt, @@ -78,8 +85,8 @@ import Hledger.Utils.UTF8IOCompat (error') -- | Regular expression. Extended regular expression-ish syntax ? But does not support eg (?i) syntax. data Regexp - = Regexp { reString :: String, reCompiled :: Regex } - | RegexpCI { reString :: String, reCompiled :: Regex } + = Regexp { reString :: Text, reCompiled :: Regex } + | RegexpCI { reString :: Text, reCompiled :: Regex } instance Eq Regexp where Regexp s1 _ == Regexp s2 _ = s1 == s2 @@ -93,7 +100,7 @@ instance Ord Regexp where RegexpCI _ _ `compare` Regexp _ _ = GT instance Show Regexp where - showsPrec d r = showParen (d > app_prec) $ reCons . showsPrec (app_prec+1) (reString r) + showsPrec d r = showParen (d > app_prec) $ reCons . showsPrec (app_prec+1) (T.unpack $ reString r) where app_prec = 10 reCons = case r of Regexp _ _ -> showString "Regexp " RegexpCI _ _ -> showString "RegexpCI " @@ -108,8 +115,8 @@ instance Read Regexp where where app_prec = 10 instance ToJSON Regexp where - toJSON (Regexp s _) = String . T.pack $ "Regexp " ++ s - toJSON (RegexpCI s _) = String . T.pack $ "RegexpCI " ++ s + toJSON (Regexp s _) = String $ "Regexp " <> s + toJSON (RegexpCI s _) = String $ "RegexpCI " <> s instance RegexLike Regexp String where matchOnce = matchOnce . reCompiled @@ -124,24 +131,24 @@ instance RegexContext Regexp String String where matchM = matchM . reCompiled -- Convert a Regexp string to a compiled Regex, or return an error message. -toRegex :: String -> Either RegexError Regexp -toRegex = memo $ \s -> mkRegexErr s (Regexp s <$> makeRegexM s) +toRegex :: Text -> Either RegexError Regexp +toRegex = memo $ \s -> mkRegexErr s (Regexp s <$> makeRegexM (T.unpack s)) -- Have to unpack here because Text instance in regex-tdfa only appears in 1.3.1 -- Like toRegex, but make a case-insensitive Regex. -toRegexCI :: String -> Either RegexError Regexp -toRegexCI = memo $ \s -> mkRegexErr s (RegexpCI s <$> makeRegexOptsM defaultCompOpt{caseSensitive=False} defaultExecOpt s) +toRegexCI :: Text -> Either RegexError Regexp +toRegexCI = memo $ \s -> mkRegexErr s (RegexpCI s <$> makeRegexOptsM defaultCompOpt{caseSensitive=False} defaultExecOpt (T.unpack s)) -- Have to unpack here because Text instance in regex-tdfa only appears in 1.3.1 -- | Make a nice error message for a regexp error. -mkRegexErr :: String -> Maybe a -> Either RegexError a +mkRegexErr :: Text -> Maybe a -> Either RegexError a mkRegexErr s = maybe (Left errmsg) Right - where errmsg = "this regular expression could not be compiled: " ++ s + where errmsg = T.unpack $ "this regular expression could not be compiled: " <> s -- Convert a Regexp string to a compiled Regex, throw an error -toRegex' :: String -> Regexp +toRegex' :: Text -> Regexp toRegex' = either error' id . toRegex -- Like toRegex', but make a case-insensitive Regex. -toRegexCI' :: String -> Regexp +toRegexCI' :: Text -> Regexp toRegexCI' = either error' id . toRegexCI -- | A replacement pattern. May include numeric backreferences (\N). @@ -159,6 +166,13 @@ type RegexError = String regexMatch :: Regexp -> String -> Bool regexMatch = matchTest +-- | Tests whether a Regexp matches a Text. +-- +-- This currently unpacks the Text to a String an works on that. This is due to +-- a performance bug in regex-tdfa (#9), which may or may not be relevant here. +regexMatchText :: Regexp -> Text -> Bool +regexMatchText r = matchTest r . T.unpack + -------------------------------------------------------------------------------- -- new total functions diff --git a/Hledger/Utils/String.hs b/Hledger/Utils/String.hs index c6f887c..8a48006 100644 --- a/Hledger/Utils/String.hs +++ b/Hledger/Utils/String.hs @@ -21,6 +21,7 @@ module Hledger.Utils.String ( lstrip, rstrip, chomp, + chomp1, singleline, elideLeft, elideRight, @@ -52,6 +53,8 @@ module Hledger.Utils.String ( import Data.Char (isSpace, toLower, toUpper) import Data.Default (def) import Data.List (intercalate) +import qualified Data.Text as T +import qualified Data.Text.Lazy as TL import Text.Megaparsec ((<|>), between, many, noneOf, sepBy) import Text.Megaparsec.Char (char) import Text.Printf (printf) @@ -59,8 +62,8 @@ import Text.Printf (printf) import Hledger.Utils.Parse import Hledger.Utils.Regex (toRegex', regexReplace) import Text.Tabular (Header(..), Properties(..)) -import Text.Tabular.AsciiWide (Align(..), Cell(..), TableOpts(..), renderRow) -import Text.WideString (strWidth, charWidth) +import Text.Tabular.AsciiWide (Align(..), TableOpts(..), textCell, renderRow) +import Text.WideString (charWidth, strWidth) -- | Take elements from the end of a list. @@ -86,10 +89,14 @@ lstrip = dropWhile isSpace rstrip :: String -> String rstrip = reverse . lstrip . reverse --- | Remove trailing newlines/carriage returns. +-- | Remove all trailing newlines/carriage returns. chomp :: String -> String chomp = reverse . dropWhile (`elem` "\r\n") . reverse +-- | Remove all trailing newline/carriage returns, leaving just one trailing newline. +chomp1 :: String -> String +chomp1 = (++"\n") . chomp + -- | Remove consecutive line breaks, replacing them with single space singleline :: String -> String singleline = unwords . filter (/="") . (map strip) . lines @@ -177,17 +184,14 @@ unbracket s -- | Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded. -- Treats wide characters as double width. concatTopPadded :: [String] -> String -concatTopPadded = renderRow def{tableBorders=False, borderSpaces=False} - . Group NoLine . map (Header . cell) - where cell = Cell BottomLeft . map (\x -> (x, strWidth x)) . lines +concatTopPadded = TL.unpack . renderRow def{tableBorders=False, borderSpaces=False} + . Group NoLine . map (Header . textCell BottomLeft . T.pack) -- | Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded. -- Treats wide characters as double width. concatBottomPadded :: [String] -> String -concatBottomPadded = renderRow def{tableBorders=False, borderSpaces=False} - . Group NoLine . map (Header . cell) - where cell = Cell TopLeft . map (\x -> (x, strWidth x)) . lines - +concatBottomPadded = TL.unpack . renderRow def{tableBorders=False, borderSpaces=False} + . Group NoLine . map (Header . textCell TopLeft . T.pack) -- | Join multi-line strings horizontally, after compressing each of -- them to a single line with a comma and space between each original line. @@ -342,4 +346,4 @@ stripAnsi :: String -> String stripAnsi s = either err id $ regexReplace ansire "" s where err = error "stripAnsi: invalid replacement pattern" -- PARTIAL, shouldn't happen - ansire = toRegex' "\ESC\\[([0-9]+;)*([0-9]+)?[ABCDHJKfmsu]" -- PARTIAL, should succeed + ansire = toRegex' $ T.pack "\ESC\\[([0-9]+;)*([0-9]+)?[ABCDHJKfmsu]" -- PARTIAL, should succeed diff --git a/Hledger/Utils/Text.hs b/Hledger/Utils/Text.hs index c6e47d3..1906a07 100644 --- a/Hledger/Utils/Text.hs +++ b/Hledger/Utils/Text.hs @@ -12,6 +12,8 @@ module Hledger.Utils.Text -- underline, -- stripbrackets, textUnbracket, + wrap, + textChomp, -- -- quoting quoteIfSpaced, textQuoteIfNeeded, @@ -29,10 +31,10 @@ module Hledger.Utils.Text -- -- * single-line layout -- elideLeft, textElideRight, - -- formatString, + formatText, -- -- * multi-line layout textConcatTopPadded, - -- concatBottomPadded, + textConcatBottomPadded, -- concatOneLine, -- vConcatLeftAligned, -- vConcatRightAligned, @@ -43,7 +45,13 @@ module Hledger.Utils.Text -- cliptopleft, -- fitto, fitText, + linesPrepend, + linesPrepend2, + unlinesB, -- -- * wide-character-aware layout + WideBuilder(..), + wbToText, + wbUnpack, textWidth, textTakeWidth, -- fitString, @@ -58,19 +66,20 @@ module Hledger.Utils.Text where import Data.Char (digitToInt) -import Data.List +import Data.Default (def) #if !(MIN_VERSION_base(4,11,0)) -import Data.Monoid +import Data.Semigroup ((<>)) #endif import Data.Text (Text) import qualified Data.Text as T --- import Text.Parsec --- import Text.Printf (printf) +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Builder as TB + +import Hledger.Utils.Test ((@?=), test, tests) +import Text.Tabular (Header(..), Properties(..)) +import Text.Tabular.AsciiWide (Align(..), TableOpts(..), textCell, renderRow) +import Text.WideString (WideBuilder(..), wbToText, wbUnpack, charWidth, textWidth) --- import Hledger.Utils.Parse --- import Hledger.Utils.Regex -import Hledger.Utils.Test -import Text.WideString (charWidth, textWidth) -- lowercase, uppercase :: String -> String -- lowercase = map toLower @@ -87,15 +96,23 @@ textElideRight :: Int -> Text -> Text textElideRight width t = if T.length t > width then T.take (width - 2) t <> ".." else t --- -- | Clip and pad a string to a minimum & maximum width, and/or left/right justify it. --- -- Works on multi-line strings too (but will rewrite non-unix line endings). --- formatString :: Bool -> Maybe Int -> Maybe Int -> String -> String --- formatString leftJustified minwidth maxwidth s = intercalate "\n" $ map (printf fmt) $ lines s --- where --- justify = if leftJustified then "-" else "" --- minwidth' = maybe "" show minwidth --- maxwidth' = maybe "" (("."++).show) maxwidth --- fmt = "%" ++ justify ++ minwidth' ++ maxwidth' ++ "s" +-- | Wrap a Text with the surrounding Text. +wrap :: Text -> Text -> Text -> Text +wrap start end x = start <> x <> end + +-- | Remove trailing newlines/carriage returns. +textChomp :: Text -> Text +textChomp = T.dropWhileEnd (`elem` ['\r', '\n']) + +-- | Clip and pad a string to a minimum & maximum width, and/or left/right justify it. +-- Works on multi-line strings too (but will rewrite non-unix line endings). +formatText :: Bool -> Maybe Int -> Maybe Int -> Text -> Text +formatText leftJustified minwidth maxwidth t = + T.intercalate "\n" . map (pad . clip) $ if T.null t then [""] else T.lines t + where + pad = maybe id justify minwidth + clip = maybe id T.take maxwidth + justify n = if leftJustified then T.justifyLeft n ' ' else T.justifyRight n ' ' -- underline :: String -> String -- underline s = s' ++ replicate (length s) '-' ++ "\n" @@ -108,7 +125,7 @@ textElideRight width t = -- double-quoted. quoteIfSpaced :: T.Text -> T.Text quoteIfSpaced s | isSingleQuoted s || isDoubleQuoted s = s - | not $ any (`elem` (T.unpack s)) whitespacechars = s + | not $ any (\c -> T.any (==c) s) whitespacechars = s | otherwise = textQuoteIfNeeded s -- -- | Wrap a string in double quotes, and \-prefix any embedded single @@ -122,7 +139,7 @@ quoteIfSpaced s | isSingleQuoted s || isDoubleQuoted s = s -- -- | Double-quote this string if it contains whitespace, single quotes -- -- or double-quotes, escaping the quotes as needed. textQuoteIfNeeded :: T.Text -> T.Text -textQuoteIfNeeded s | any (`elem` T.unpack s) (quotechars++whitespacechars) = "\"" <> escapeDoubleQuotes s <> "\"" +textQuoteIfNeeded s | any (\c -> T.any (==c) s) (quotechars++whitespacechars) = "\"" <> escapeDoubleQuotes s <> "\"" | otherwise = s -- -- | Single-quote this string if it contains whitespace or double-quotes. @@ -181,28 +198,14 @@ textUnbracket s -- | Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded. -- Treats wide characters as double width. textConcatTopPadded :: [Text] -> Text -textConcatTopPadded ts = T.intercalate "\n" $ map T.concat $ transpose padded - where - lss = map T.lines ts :: [[Text]] - h = maximum $ map length lss - ypad ls = replicate (difforzero h (length ls)) "" ++ ls - xpad ls = map (textPadLeftWide w) ls - where w | null ls = 0 - | otherwise = maximum $ map textWidth ls - padded = map (xpad . ypad) lss :: [[Text]] - --- -- | Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded. --- -- Treats wide characters as double width. --- concatBottomPadded :: [String] -> String --- concatBottomPadded strs = intercalate "\n" $ map concat $ transpose padded --- where --- lss = map lines strs --- h = maximum $ map length lss --- ypad ls = ls ++ replicate (difforzero h (length ls)) "" --- xpad ls = map (padRightWide w) ls where w | null ls = 0 --- | otherwise = maximum $ map strWidth ls --- padded = map (xpad . ypad) lss +textConcatTopPadded = TL.toStrict . renderRow def{tableBorders=False, borderSpaces=False} + . Group NoLine . map (Header . textCell BottomLeft) +-- | Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded. +-- Treats wide characters as double width. +textConcatBottomPadded :: [Text] -> Text +textConcatBottomPadded = TL.toStrict . renderRow def{tableBorders=False, borderSpaces=False} + . Group NoLine . map (Header . textCell TopLeft) -- -- | Join multi-line strings horizontally, after compressing each of -- -- them to a single line with a comma and space between each original line. @@ -245,9 +248,6 @@ textConcatTopPadded ts = T.intercalate "\n" $ map T.concat $ transpose padded -- ypadded = ls ++ replicate (difforzero h sh) "" -- xpadded = map (padleft sw) ypadded -difforzero :: (Num a, Ord a) => a -> a -> a -difforzero a b = maximum [(a - b), 0] - -- -- | Convert a multi-line string to a rectangular string left-padded to the specified width. -- -- Treats wide characters as double width. -- padleft :: Int -> String -> String @@ -344,11 +344,25 @@ textTakeWidth w t | not (T.null t), = T.cons c $ textTakeWidth (w-cw) (T.tail t) | otherwise = "" +-- | Add a prefix to each line of a string. +linesPrepend :: Text -> Text -> Text +linesPrepend prefix = T.unlines . map (prefix<>) . T.lines + +-- | Add a prefix to the first line of a string, +-- and a different prefix to the remaining lines. +linesPrepend2 :: Text -> Text -> Text -> Text +linesPrepend2 prefix1 prefix2 s = T.unlines $ case T.lines s of + [] -> [] + l:ls -> (prefix1<>l) : map (prefix2<>) ls + +-- | Join a list of Text Builders with a newline after each item. +unlinesB :: [TB.Builder] -> TB.Builder +unlinesB = foldMap (<> TB.singleton '\n') -- | Read a decimal number from a Text. Assumes the input consists only of digit -- characters. readDecimal :: Text -> Integer -readDecimal = foldl' step 0 . T.unpack +readDecimal = T.foldl' step 0 where step a c = a * 10 + toInteger (digitToInt c) diff --git a/Text/Tabular/AsciiWide.hs b/Text/Tabular/AsciiWide.hs index 29dcd5e..bb09748 100644 --- a/Text/Tabular/AsciiWide.hs +++ b/Text/Tabular/AsciiWide.hs @@ -1,14 +1,25 @@ -- | Text.Tabular.AsciiArt from tabular-0.2.2.7, modified to treat -- wide characters as double width. +{-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} + module Text.Tabular.AsciiWide where import Data.Maybe (fromMaybe) import Data.Default (Default(..)) import Data.List (intersperse, transpose) +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup ((<>)) +#endif +import Data.Semigroup (stimesMonoid) +import Data.Text (Text) +import qualified Data.Text as T +import qualified Data.Text.Lazy as TL +import Data.Text.Lazy.Builder (Builder, fromString, fromText, singleton, toLazyText) import Safe (maximumMay) import Text.Tabular -import Text.WideString (strWidth) +import Text.WideString (WideBuilder(..), textWidth) -- | The options to use for rendering a table. @@ -25,8 +36,7 @@ instance Default TableOpts where } -- | Cell contents along an alignment -data Cell = Cell Align [(String, Int)] - deriving (Show) +data Cell = Cell Align [WideBuilder] -- | How to align text in a cell data Align = TopRight | BottomRight | BottomLeft | TopLeft @@ -36,31 +46,40 @@ emptyCell :: Cell emptyCell = Cell TopRight [] -- | Create a single-line cell from the given contents with its natural width. -alignCell :: Align -> String -> Cell -alignCell a x = Cell a [(x, strWidth x)] +textCell :: Align -> Text -> Cell +textCell a x = Cell a . map (\x -> WideBuilder (fromText x) (textWidth x)) $ if T.null x then [""] else T.lines x -- | Return the width of a Cell. cellWidth :: Cell -> Int -cellWidth (Cell _ xs) = fromMaybe 0 . maximumMay $ map snd xs +cellWidth (Cell _ xs) = fromMaybe 0 . maximumMay $ map wbWidth xs -- | Render a table according to common options, for backwards compatibility -render :: Bool -> (rh -> String) -> (ch -> String) -> (a -> String) -> Table rh ch a -> String +render :: Bool -> (rh -> Text) -> (ch -> Text) -> (a -> Text) -> Table rh ch a -> TL.Text render pretty fr fc f = renderTable def{prettyTable=pretty} (cell . fr) (cell . fc) (cell . f) - where cell = alignCell TopRight + where cell = textCell TopRight --- | Render a table according to various cell specifications -renderTable :: TableOpts -- ^ Options controlling Table rendering +-- | Render a table according to various cell specifications> +renderTable :: TableOpts -- ^ Options controlling Table rendering -> (rh -> Cell) -- ^ Rendering function for row headers -> (ch -> Cell) -- ^ Rendering function for column headers -> (a -> Cell) -- ^ Function determining the string and width of a cell -> Table rh ch a - -> String -renderTable topts@TableOpts{prettyTable=pretty, tableBorders=borders} fr fc f (Table rh ch cells) = - unlines . addBorders $ - renderColumns topts sizes ch2 - : bar VM DoubleLine -- +======================================+ - : renderRs (fmap renderR $ zipHeader [] cellContents rowHeaders) + -> TL.Text +renderTable topts fr fc f = toLazyText . renderTableB topts fr fc f + +-- | A version of renderTable which returns the underlying Builder. +renderTableB :: TableOpts -- ^ Options controlling Table rendering + -> (rh -> Cell) -- ^ Rendering function for row headers + -> (ch -> Cell) -- ^ Rendering function for column headers + -> (a -> Cell) -- ^ Function determining the string and width of a cell + -> Table rh ch a + -> Builder +renderTableB topts@TableOpts{prettyTable=pretty, tableBorders=borders} fr fc f (Table rh ch cells) = + unlinesB . addBorders $ + renderColumns topts sizes ch2 + : bar VM DoubleLine -- +======================================+ + : renderRs (fmap renderR $ zipHeader [] cellContents rowHeaders) where renderR (cs,h) = renderColumns topts sizes $ Group DoubleLine [ Header h @@ -83,63 +102,68 @@ renderTable topts@TableOpts{prettyTable=pretty, tableBorders=borders} fr fc f (T -- borders and bars addBorders xs = if borders then bar VT SingleLine : xs ++ [bar VB SingleLine] else xs - bar vpos prop = concat $ renderHLine vpos borders pretty sizes ch2 prop + bar vpos prop = mconcat $ renderHLine vpos borders pretty sizes ch2 prop + unlinesB = foldMap (<> singleton '\n') -- | Render a single row according to cell specifications. -renderRow :: TableOpts -> Header Cell -> String -renderRow topts h = renderColumns topts is h - where is = map (\(Cell _ xs) -> fromMaybe 0 . maximumMay $ map snd xs) $ headerContents h +renderRow :: TableOpts -> Header Cell -> TL.Text +renderRow topts = toLazyText . renderRowB topts + +-- | A version of renderRow which returns the underlying Builder. +renderRowB:: TableOpts -> Header Cell -> Builder +renderRowB topts h = renderColumns topts is h + where is = map cellWidth $ headerContents h verticalBar :: Bool -> Char verticalBar pretty = if pretty then '│' else '|' -leftBar :: Bool -> Bool -> String -leftBar pretty True = verticalBar pretty : " " -leftBar pretty False = [verticalBar pretty] +leftBar :: Bool -> Bool -> Builder +leftBar pretty True = fromString $ verticalBar pretty : " " +leftBar pretty False = singleton $ verticalBar pretty -rightBar :: Bool -> Bool -> String -rightBar pretty True = ' ' : [verticalBar pretty] -rightBar pretty False = [verticalBar pretty] +rightBar :: Bool -> Bool -> Builder +rightBar pretty True = fromString $ ' ' : [verticalBar pretty] +rightBar pretty False = singleton $ verticalBar pretty -midBar :: Bool -> Bool -> String -midBar pretty True = ' ' : verticalBar pretty : " " -midBar pretty False = [verticalBar pretty] +midBar :: Bool -> Bool -> Builder +midBar pretty True = fromString $ ' ' : verticalBar pretty : " " +midBar pretty False = singleton $ verticalBar pretty -doubleMidBar :: Bool -> Bool -> String -doubleMidBar pretty True = if pretty then " ║ " else " || " -doubleMidBar pretty False = if pretty then "║" else "||" +doubleMidBar :: Bool -> Bool -> Builder +doubleMidBar pretty True = fromText $ if pretty then " ║ " else " || " +doubleMidBar pretty False = fromText $ if pretty then "║" else "||" -- | We stop rendering on the shortest list! renderColumns :: TableOpts -- ^ rendering options for the table -> [Int] -- ^ max width for each column -> Header Cell - -> String + -> Builder renderColumns TableOpts{prettyTable=pretty, tableBorders=borders, borderSpaces=spaces} is h = - concat . intersperse "\n" -- Put each line on its own line - . map (addBorders . concat) . transpose -- Change to a list of lines and add borders + mconcat . intersperse "\n" -- Put each line on its own line + . map (addBorders . mconcat) . transpose -- Change to a list of lines and add borders . map (either hsep padCell) . flattenHeader -- We now have a matrix of strings . zipHeader 0 is $ padRow <$> h -- Pad cell height and add width marker where -- Pad each cell to have the appropriate width - padCell (w, Cell TopLeft ls) = map (\(x,xw) -> x ++ replicate (w - xw) ' ') ls - padCell (w, Cell BottomLeft ls) = map (\(x,xw) -> x ++ replicate (w - xw) ' ') ls - padCell (w, Cell TopRight ls) = map (\(x,xw) -> replicate (w - xw) ' ' ++ x) ls - padCell (w, Cell BottomRight ls) = map (\(x,xw) -> replicate (w - xw) ' ' ++ x) ls + padCell (w, Cell TopLeft ls) = map (\x -> wbBuilder x <> fromText (T.replicate (w - wbWidth x) " ")) ls + padCell (w, Cell BottomLeft ls) = map (\x -> wbBuilder x <> fromText (T.replicate (w - wbWidth x) " ")) ls + padCell (w, Cell TopRight ls) = map (\x -> fromText (T.replicate (w - wbWidth x) " ") <> wbBuilder x) ls + padCell (w, Cell BottomRight ls) = map (\x -> fromText (T.replicate (w - wbWidth x) " ") <> wbBuilder x) ls -- Pad each cell to have the same number of lines - padRow (Cell TopLeft ls) = Cell TopLeft $ ls ++ replicate (nLines - length ls) ("",0) - padRow (Cell TopRight ls) = Cell TopRight $ ls ++ replicate (nLines - length ls) ("",0) - padRow (Cell BottomLeft ls) = Cell BottomLeft $ replicate (nLines - length ls) ("",0) ++ ls - padRow (Cell BottomRight ls) = Cell BottomRight $ replicate (nLines - length ls) ("",0) ++ ls + padRow (Cell TopLeft ls) = Cell TopLeft $ ls ++ replicate (nLines - length ls) mempty + padRow (Cell TopRight ls) = Cell TopRight $ ls ++ replicate (nLines - length ls) mempty + padRow (Cell BottomLeft ls) = Cell BottomLeft $ replicate (nLines - length ls) mempty ++ ls + padRow (Cell BottomRight ls) = Cell BottomRight $ replicate (nLines - length ls) mempty ++ ls - hsep :: Properties -> [String] + hsep :: Properties -> [Builder] hsep NoLine = replicate nLines $ if spaces then " " else "" hsep SingleLine = replicate nLines $ midBar pretty spaces hsep DoubleLine = replicate nLines $ doubleMidBar pretty spaces - addBorders xs | borders = leftBar pretty spaces ++ xs ++ rightBar pretty spaces - | spaces = ' ' : xs ++ " " + addBorders xs | borders = leftBar pretty spaces <> xs <> rightBar pretty spaces + | spaces = fromText " " <> xs <> fromText " " | otherwise = xs nLines = fromMaybe 0 . maximumMay . map (\(Cell _ ls) -> length ls) $ headerContents h @@ -150,52 +174,48 @@ renderHLine :: VPos -> [Int] -- ^ width specifications -> Header a -> Properties - -> [String] + -> [Builder] renderHLine _ _ _ _ _ NoLine = [] renderHLine vpos borders pretty w h prop = [renderHLine' vpos borders pretty prop w h] -renderHLine' :: VPos -> Bool -> Bool -> Properties -> [Int] -> Header a -> String -renderHLine' vpos borders pretty prop is h = addBorders $ sep ++ coreLine ++ sep +renderHLine' :: VPos -> Bool -> Bool -> Properties -> [Int] -> Header a -> Builder +renderHLine' vpos borders pretty prop is h = addBorders $ sep <> coreLine <> sep where - addBorders xs = if borders then edge HL ++ xs ++ edge HR else xs + addBorders xs = if borders then edge HL <> xs <> edge HR else xs edge hpos = boxchar vpos hpos SingleLine prop pretty - coreLine = concatMap helper $ flattenHeader $ zipHeader 0 is h + coreLine = foldMap helper $ flattenHeader $ zipHeader 0 is h helper = either vsep dashes - dashes (i,_) = concat (replicate i sep) + dashes (i,_) = stimesMonoid i sep sep = boxchar vpos HM NoLine prop pretty vsep v = case v of - NoLine -> sep ++ sep - _ -> sep ++ cross v prop ++ sep + NoLine -> sep <> sep + _ -> sep <> cross v prop <> sep cross v h = boxchar vpos HM v h pretty data VPos = VT | VM | VB -- top middle bottom data HPos = HL | HM | HR -- left middle right -boxchar :: VPos -> HPos -> Properties -> Properties -> Bool -> String +boxchar :: VPos -> HPos -> Properties -> Properties -> Bool -> Builder boxchar vpos hpos vert horiz = lineart u d l r where - u = - case vpos of - VT -> NoLine - _ -> vert - d = - case vpos of - VB -> NoLine - _ -> vert - l = - case hpos of - HL -> NoLine - _ -> horiz - r = - case hpos of - HR -> NoLine - _ -> horiz - -pick :: String -> String -> Bool -> String -pick x _ True = x -pick _ x False = x - -lineart :: Properties -> Properties -> Properties -> Properties -> Bool -> String + u = case vpos of + VT -> NoLine + _ -> vert + d = case vpos of + VB -> NoLine + _ -> vert + l = case hpos of + HL -> NoLine + _ -> horiz + r = case hpos of + HR -> NoLine + _ -> horiz + +pick :: Text -> Text -> Bool -> Builder +pick x _ True = fromText x +pick _ x False = fromText x + +lineart :: Properties -> Properties -> Properties -> Properties -> Bool -> Builder -- up down left right lineart SingleLine SingleLine SingleLine SingleLine = pick "┼" "+" lineart SingleLine SingleLine SingleLine NoLine = pick "┤" "+" @@ -244,6 +264,4 @@ lineart NoLine SingleLine DoubleLine DoubleLine = pick "╤" "+" lineart SingleLine SingleLine DoubleLine DoubleLine = pick "╪" "+" lineart DoubleLine DoubleLine SingleLine SingleLine = pick "╫" "++" -lineart _ _ _ _ = const "" - --- +lineart _ _ _ _ = const mempty diff --git a/Text/WideString.hs b/Text/WideString.hs index 5ed3821..a055002 100644 --- a/Text/WideString.hs +++ b/Text/WideString.hs @@ -1,14 +1,49 @@ -- | Calculate the width of String and Text, being aware of wide characters. +{-# LANGUAGE CPP #-} + module Text.WideString ( -- * wide-character-aware layout strWidth, textWidth, - charWidth + charWidth, + -- * Text Builders which keep track of length + WideBuilder(..), + wbUnpack, + wbToText ) where +#if !(MIN_VERSION_base(4,11,0)) +import Data.Semigroup (Semigroup(..)) +#endif import Data.Text (Text) import qualified Data.Text as T +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Builder as TB + + +-- | Helper for constructing Builders while keeping track of text width. +data WideBuilder = WideBuilder + { wbBuilder :: !TB.Builder + , wbWidth :: !Int + } + +instance Semigroup WideBuilder where + WideBuilder x i <> WideBuilder y j = WideBuilder (x <> y) (i + j) + +instance Monoid WideBuilder where + mempty = WideBuilder mempty 0 +#if !(MIN_VERSION_base(4,11,0)) + mappend = (<>) +#endif + +-- | Convert a WideBuilder to a strict Text. +wbToText :: WideBuilder -> Text +wbToText = TL.toStrict . TB.toLazyText . wbBuilder + +-- | Convert a WideBuilder to a String. +wbUnpack :: WideBuilder -> String +wbUnpack = TL.unpack . TB.toLazyText . wbBuilder -- | Calculate the render width of a string, considering diff --git a/hledger-lib.cabal b/hledger-lib.cabal index 3af1af1..78aa2e3 100644 --- a/hledger-lib.cabal +++ b/hledger-lib.cabal @@ -4,10 +4,10 @@ cabal-version: 1.12 -- -- see: https://github.com/sol/hpack -- --- hash: 3f8656e682d0ff102bad0022b06b881b2de2ca72cf342fd31090a33f7d87b692 +-- hash: 2724f18a071add9d644b3060aba58a3f4f6c71b66d88af1e8ca3f526043d461f name: hledger-lib -version: 1.20.4 +version: 1.21 synopsis: A reusable library providing the core functionality of hledger description: A reusable library containing hledger's core functionality. This is used by most hledger* packages so that they support the same @@ -34,18 +34,6 @@ extra-source-files: README.md test/unittest.hs test/doctests.hs - hledger_csv.5 - hledger_csv.txt - hledger_csv.info - hledger_journal.5 - hledger_journal.txt - hledger_journal.info - hledger_timedot.5 - hledger_timedot.txt - hledger_timedot.info - hledger_timeclock.5 - hledger_timeclock.txt - hledger_timeclock.info source-repository head type: git @@ -137,7 +125,6 @@ library , pretty-simple >4 && <5 , regex-tdfa , safe >=0.2 - , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , tasty-hunit >=0.10.0.2 @@ -188,7 +175,6 @@ test-suite doctest , pretty-simple >4 && <5 , regex-tdfa , safe >=0.2 - , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , tasty-hunit >=0.10.0.2 @@ -241,7 +227,6 @@ test-suite unittest , pretty-simple >4 && <5 , regex-tdfa , safe >=0.2 - , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , tasty-hunit >=0.10.0.2 diff --git a/hledger_csv.5 b/hledger_csv.5 deleted file mode 100644 index da1f4b5..0000000 --- a/hledger_csv.5 +++ /dev/null @@ -1,1300 +0,0 @@ -.\"t - -.TH "HLEDGER_CSV" "5" "December 2020" "hledger-lib-1.20.4 " "hledger User Manuals" - - - -.SH NAME -.PP -How hledger reads CSV data, and the CSV rules file format. -.SH DESCRIPTION -.PP -hledger can read CSV files (Character Separated Value - usually comma, -semicolon, or tab) containing dated records as if they were journal -files, automatically converting each CSV record into a transaction. -.PP -(To learn about \f[I]writing\f[R] CSV, see CSV output.) -.PP -We describe each CSV file\[aq]s format with a corresponding \f[I]rules -file\f[R]. -By default this is named like the CSV file with a \f[C].rules\f[R] -extension added. -Eg when reading \f[C]FILE.csv\f[R], hledger also looks for -\f[C]FILE.csv.rules\f[R] in the same directory as \f[C]FILE.csv\f[R]. -You can specify a different rules file with the \f[C]--rules-file\f[R] -option. -If a rules file is not found, hledger will create a sample rules file, -which you\[aq]ll need to adjust. -.PP -This file contains rules describing the CSV data (header line, fields -layout, date format etc.), and how to construct hledger journal entries -(transactions) from it. -Often there will also be a list of conditional rules for categorising -transactions based on their descriptions. -Here\[aq]s an overview of the CSV rules; these are described more fully -below, after the examples: -.PP -.TS -tab(@); -lw(30.1n) lw(39.9n). -T{ -\f[B]\f[CB]skip\f[B]\f[R] -T}@T{ -skip one or more header lines or matched CSV records -T} -T{ -\f[B]\f[CB]fields\f[B]\f[R] -T}@T{ -name CSV fields, assign them to hledger fields -T} -T{ -\f[B]field assignment\f[R] -T}@T{ -assign a value to one hledger field, with interpolation -T} -T{ -\f[B]\f[CB]separator\f[B]\f[R] -T}@T{ -a custom field separator -T} -T{ -\f[B]\f[CB]if\f[B] block\f[R] -T}@T{ -apply some rules to CSV records matched by patterns -T} -T{ -\f[B]\f[CB]if\f[B] table\f[R] -T}@T{ -apply some rules to CSV records matched by patterns, alternate syntax -T} -T{ -\f[B]\f[CB]end\f[B]\f[R] -T}@T{ -skip the remaining CSV records -T} -T{ -\f[B]\f[CB]date-format\f[B]\f[R] -T}@T{ -how to parse dates in CSV records -T} -T{ -\f[B]\f[CB]decimal-mark\f[B]\f[R] -T}@T{ -the decimal mark used in CSV amounts, if ambiguous -T} -T{ -\f[B]\f[CB]newest-first\f[B]\f[R] -T}@T{ -disambiguate record order when there\[aq]s only one date -T} -T{ -\f[B]\f[CB]include\f[B]\f[R] -T}@T{ -inline another CSV rules file -T} -T{ -\f[B]\f[CB]balance-type\f[B]\f[R] -T}@T{ -choose which type of balance assignments to use -T} -.TE -.PP -Note, for best error messages when reading CSV files, use a -\f[C].csv\f[R], \f[C].tsv\f[R] or \f[C].ssv\f[R] file extension or file -prefix - see File Extension below. -.PP -There\[aq]s an introductory Convert CSV files tutorial on hledger.org. -.SH EXAMPLES -.PP -Here are some sample hledger CSV rules files. -See also the full collection at: -.PD 0 -.P -.PD -https://github.com/simonmichael/hledger/tree/master/examples/csv -.SS Basic -.PP -At minimum, the rules file must identify the date and amount fields, and -often it also specifies the date format and how many header lines there -are. -Here\[aq]s a simple CSV file and a rules file for it: -.IP -.nf -\f[C] -Date, Description, Id, Amount -12/11/2019, Foo, 123, 10.23 -\f[R] -.fi -.IP -.nf -\f[C] -# basic.csv.rules -skip 1 -fields date, description, _, amount -date-format %d/%m/%Y -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger print -f basic.csv -2019-11-12 Foo - expenses:unknown 10.23 - income:unknown -10.23 -\f[R] -.fi -.PP -Default account names are chosen, since we didn\[aq]t set them. -.SS Bank of Ireland -.PP -Here\[aq]s a CSV with two amount fields (Debit and Credit), and a -balance field, which we can use to add balance assertions, which is not -necessary but provides extra error checking: -.IP -.nf -\f[C] -Date,Details,Debit,Credit,Balance -07/12/2012,LODGMENT 529898,,10.0,131.21 -07/12/2012,PAYMENT,5,,126 -\f[R] -.fi -.IP -.nf -\f[C] -# bankofireland-checking.csv.rules - -# skip the header line -skip - -# name the csv fields, and assign some of them as journal entry fields -fields date, description, amount-out, amount-in, balance - -# We generate balance assertions by assigning to \[dq]balance\[dq] -# above, but you may sometimes need to remove these because: -# -# - the CSV balance differs from the true balance, -# by up to 0.0000000000005 in my experience -# -# - it is sometimes calculated based on non-chronological ordering, -# eg when multiple transactions clear on the same day - -# date is in UK/Ireland format -date-format %d/%m/%Y - -# set the currency -currency EUR - -# set the base account for all txns -account1 assets:bank:boi:checking -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger -f bankofireland-checking.csv print -2012-12-07 LODGMENT 529898 - assets:bank:boi:checking EUR10.0 = EUR131.2 - income:unknown EUR-10.0 - -2012-12-07 PAYMENT - assets:bank:boi:checking EUR-5.0 = EUR126.0 - expenses:unknown EUR5.0 -\f[R] -.fi -.PP -The balance assertions don\[aq]t raise an error above, because we\[aq]re -reading directly from CSV, but they will be checked if these entries are -imported into a journal file. -.SS Amazon -.PP -Here we convert amazon.com order history, and use an if block to -generate a third posting if there\[aq]s a fee. -(In practice you\[aq]d probably get this data from your bank instead, -but it\[aq]s an example.) -.IP -.nf -\f[C] -\[dq]Date\[dq],\[dq]Type\[dq],\[dq]To/From\[dq],\[dq]Name\[dq],\[dq]Status\[dq],\[dq]Amount\[dq],\[dq]Fees\[dq],\[dq]Transaction ID\[dq] -\[dq]Jul 29, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Foo.\[dq],\[dq]Completed\[dq],\[dq]$20.00\[dq],\[dq]$0.00\[dq],\[dq]16000000000000DGLNJPI1P9B8DKPVHL\[dq] -\[dq]Jul 30, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Adapteva, Inc.\[dq],\[dq]Completed\[dq],\[dq]$25.00\[dq],\[dq]$1.00\[dq],\[dq]17LA58JSKRD4HDGLNJPI1P9B8DKPVHL\[dq] -\f[R] -.fi -.IP -.nf -\f[C] -# amazon-orders.csv.rules - -# skip one header line -skip 1 - -# name the csv fields, and assign the transaction\[aq]s date, amount and code. -# Avoided the \[dq]status\[dq] and \[dq]amount\[dq] hledger field names to prevent confusion. -fields date, _, toorfrom, name, amzstatus, amzamount, fees, code - -# how to parse the date -date-format %b %-d, %Y - -# combine two fields to make the description -description %toorfrom %name - -# save the status as a tag -comment status:%amzstatus - -# set the base account for all transactions -account1 assets:amazon -# leave amount1 blank so it can balance the other(s). -# I\[aq]m assuming amzamount excludes the fees, don\[aq]t remember - -# set a generic account2 -account2 expenses:misc -amount2 %amzamount -# and maybe refine it further: -#include categorisation.rules - -# add a third posting for fees, but only if they are non-zero. -if %fees [1-9] - account3 expenses:fees - amount3 %fees -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger -f amazon-orders.csv print -2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed - assets:amazon - expenses:misc $20.00 - -2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed - assets:amazon - expenses:misc $25.00 - expenses:fees $1.00 -\f[R] -.fi -.SS Paypal -.PP -Here\[aq]s a real-world rules file for (customised) Paypal CSV, with -some Paypal-specific rules, and a second rules file included: -.IP -.nf -\f[C] -\[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] -\[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]Calm Radio\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]-6.99\[dq],\[dq]0.00\[dq],\[dq]-6.99\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]memberships\[at]calmradio.com\[dq],\[dq]60P57143A8206782E\[dq],\[dq]MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month\[dq],\[dq]\[dq],\[dq]I-R8YLY094FJYR\[dq],\[dq]\[dq],\[dq]-6.99\[dq],\[dq]\[dq] -\[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]6.99\[dq],\[dq]0.00\[dq],\[dq]6.99\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]0TU1544T080463733\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]60P57143A8206782E\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] -\[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]Patreon\[dq],\[dq]PreApproved Payment Bill User Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]-7.00\[dq],\[dq]0.00\[dq],\[dq]-7.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]support\[at]patreon.com\[dq],\[dq]2722394R5F586712G\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]B-0PG93074E7M86381M\[dq],\[dq]\[dq],\[dq]-7.00\[dq],\[dq]\[dq] -\[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]7.00\[dq],\[dq]0.00\[dq],\[dq]7.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]71854087RG994194F\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]2722394R5F586712G\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] -\[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]Wikimedia Foundation, Inc.\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]-2.00\[dq],\[dq]0.00\[dq],\[dq]-2.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]tle\[at]wikimedia.org\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]Monthly donation to the Wikimedia Foundation\[dq],\[dq]\[dq],\[dq]I-R5C3YUS3285L\[dq],\[dq]\[dq],\[dq]-2.00\[dq],\[dq]\[dq] -\[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]2.00\[dq],\[dq]0.00\[dq],\[dq]2.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]3XJ107139A851061F\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] -\[dq]10/22/2019\[dq],\[dq]05:07:06\[dq],\[dq]PDT\[dq],\[dq]Noble Benefactor\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]10.00\[dq],\[dq]-0.59\[dq],\[dq]9.41\[dq],\[dq]noble\[at]bene.fac.tor\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]6L8L1662YP1334033\[dq],\[dq]Joyful Systems\[dq],\[dq]\[dq],\[dq]I-KC9VBGY2GWDB\[dq],\[dq]\[dq],\[dq]9.41\[dq],\[dq]\[dq] -\f[R] -.fi -.IP -.nf -\f[C] -# paypal-custom.csv.rules - -# Tips: -# Export from Activity -> Statements -> Custom -> Activity download -# Suggested transaction type: \[dq]Balance affecting\[dq] -# Paypal\[aq]s default fields in 2018 were: -# \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Shipping Address\[dq],\[dq]Address Status\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Shipping and Handling Amount\[dq],\[dq]Insurance Amount\[dq],\[dq]Sales Tax\[dq],\[dq]Option 1 Name\[dq],\[dq]Option 1 Value\[dq],\[dq]Option 2 Name\[dq],\[dq]Option 2 Value\[dq],\[dq]Reference Txn ID\[dq],\[dq]Invoice Number\[dq],\[dq]Custom Number\[dq],\[dq]Quantity\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Address Line 1\[dq],\[dq]Address Line 2/District/Neighborhood\[dq],\[dq]Town/City\[dq],\[dq]State/Province/Region/County/Territory/Prefecture/Republic\[dq],\[dq]Zip/Postal Code\[dq],\[dq]Country\[dq],\[dq]Contact Phone Number\[dq],\[dq]Subject\[dq],\[dq]Note\[dq],\[dq]Country Code\[dq],\[dq]Balance Impact\[dq] -# This rules file assumes the following more detailed fields, configured in \[dq]Customize report fields\[dq]: -# \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] - -fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note - -skip 1 - -date-format %-m/%-d/%Y - -# ignore some paypal events -if -In Progress -Temporary Hold -Update to - skip - -# add more fields to the description -description %description_ %itemtitle - -# save some other fields as tags -comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ - -# convert to short currency symbols -if %currency USD - currency $ -if %currency EUR - currency E -if %currency GBP - currency P - -# generate postings - -# the first posting will be the money leaving/entering my paypal account -# (negative means leaving my account, in all amount fields) -account1 assets:online:paypal -amount1 %netamount - -# the second posting will be money sent to/received from other party -# (account2 is set below) -amount2 -%grossamount - -# if there\[aq]s a fee, add a third posting for the money taken by paypal. -if %feeamount [1-9] - account3 expenses:banking:paypal - amount3 -%feeamount - comment3 business: - -# choose an account for the second posting - -# override the default account names: -# if the amount is positive, it\[aq]s income (a debit) -if %grossamount \[ha][\[ha]-] - account2 income:unknown -# if negative, it\[aq]s an expense (a credit) -if %grossamount \[ha]- - account2 expenses:unknown - -# apply common rules for setting account2 & other tweaks -include common.rules - -# apply some overrides specific to this csv - -# Transfers from/to bank. These are usually marked Pending, -# which can be disregarded in this case. -if -Bank Account -Bank Deposit to PP Account - description %type for %referencetxnid %itemtitle - account2 assets:bank:wf:pchecking - account1 assets:online:paypal - -# Currency conversions -if Currency Conversion - account2 equity:currency conversion -\f[R] -.fi -.IP -.nf -\f[C] -# common.rules - -if -darcs -noble benefactor - account2 revenues:foss donations:darcshub - comment2 business: - -if -Calm Radio - account2 expenses:online:apps - -if -electronic frontier foundation -Patreon -wikimedia -Advent of Code - account2 expenses:dues - -if Google - account2 expenses:online:apps - description google | music -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger -f paypal-custom.csv print -2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon\[at]joyful.com, toemail:memberships\[at]calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed - assets:online:paypal $-6.99 = $-6.99 - expenses:online:apps $6.99 - -2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $6.99 = $0.00 - assets:bank:wf:pchecking $-6.99 - -2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon\[at]joyful.com, toemail:support\[at]patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed - assets:online:paypal $-7.00 = $-7.00 - expenses:dues $7.00 - -2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $7.00 = $0.00 - assets:bank:wf:pchecking $-7.00 - -2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon\[at]joyful.com, toemail:tle\[at]wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed - assets:online:paypal $-2.00 = $-2.00 - expenses:dues $2.00 - expenses:banking:paypal ; business: - -2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $2.00 = $0.00 - assets:bank:wf:pchecking $-2.00 - -2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble\[at]bene.fac.tor, toemail:simon\[at]joyful.com, time:05:07:06, type:Subscription Payment, status:Completed - assets:online:paypal $9.41 = $9.41 - revenues:foss donations:darcshub $-10.00 ; business: - expenses:banking:paypal $0.59 ; business: -\f[R] -.fi -.SH CSV RULES -.PP -The following kinds of rule can appear in the rules file, in any order. -Blank lines and lines beginning with \f[C]#\f[R] or \f[C];\f[R] are -ignored. -.SS \f[C]skip\f[R] -.IP -.nf -\f[C] -skip N -\f[R] -.fi -.PP -The word \[dq]skip\[dq] followed by a number (or no number, meaning 1) -tells hledger to ignore this many non-empty lines preceding the CSV -data. -(Empty/blank lines are skipped automatically.) You\[aq]ll need this -whenever your CSV data contains header lines. -.PP -It also has a second purpose: it can be used inside if blocks to ignore -certain CSV records (described below). -.SS \f[C]fields\f[R] -.IP -.nf -\f[C] -fields FIELDNAME1, FIELDNAME2, ... -\f[R] -.fi -.PP -A fields list (the word \[dq]fields\[dq] followed by comma-separated -field names) is the quick way to assign CSV field values to hledger -fields. -It does two things: -.IP "1." 3 -it names the CSV fields. -This is optional, but can be convenient later for interpolating them. -.IP "2." 3 -when you use a standard hledger field name, it assigns the CSV value to -that part of the hledger transaction. -.PP -Here\[aq]s an example that says \[dq]use the 1st, 2nd and 4th fields as -the transaction\[aq]s date, description and amount; name the last two -fields for later reference; and ignore the others\[dq]: -.IP -.nf -\f[C] -fields date, description, , amount, , , somefield, anotherfield -\f[R] -.fi -.PP -Field names may not contain whitespace. -Fields you don\[aq]t care about can be left unnamed. -Currently there must be least two items (there must be at least one -comma). -.PP -Note, always use comma in the fields list, even if your CSV uses another -separator character. -.PP -Here are the standard hledger field/pseudo-field names. -For more about the transaction parts they refer to, see the manual for -hledger\[aq]s journal format. -.SS Transaction field names -.PP -\f[C]date\f[R], \f[C]date2\f[R], \f[C]status\f[R], \f[C]code\f[R], -\f[C]description\f[R], \f[C]comment\f[R] can be used to form the -transaction\[aq]s first line. -.SS Posting field names -.SS account -.PP -\f[C]accountN\f[R], where N is 1 to 99, causes a posting to be -generated, with that account name. -.PP -Most often there are two postings, so you\[aq]ll want to set -\f[C]account1\f[R] and \f[C]account2\f[R]. -Typically \f[C]account1\f[R] is associated with the CSV file, and is set -once with a top-level assignment, while \f[C]account2\f[R] is set based -on each transaction\[aq]s description, and in conditional blocks. -.PP -If a posting\[aq]s account name is left unset but its amount is set (see -below), a default account name will be chosen (like -\[dq]expenses:unknown\[dq] or \[dq]income:unknown\[dq]). -.SS amount -.PP -\f[C]amountN\f[R] sets posting N\[aq]s amount. -If the CSV uses separate fields for inflows and outflows, you can use -\f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] instead. -By assigning to \f[C]amount1\f[R], \f[C]amount2\f[R], ... -etc. -you can generate anywhere from 0 to 99 postings. -.PP -There is also an older, unnumbered form of these names, suitable for -2-posting transactions, which sets both posting 1\[aq]s and (negated) -posting 2\[aq]s amount: \f[C]amount\f[R], or \f[C]amount-in\f[R] and -\f[C]amount-out\f[R]. -This is still supported because it keeps pre-hledger-1.17 csv rules -files working, and because it can be more succinct, and because it -converts posting 2\[aq]s amount to cost if there\[aq]s a transaction -price, which can be useful. -.PP -If you have an existing rules file using the unnumbered form, you might -want to use the numbered form in certain conditional blocks, without -having to update and retest all the old rules. -To facilitate this, posting 1 ignores -\f[C]amount\f[R]/\f[C]amount-in\f[R]/\f[C]amount-out\f[R] if any of -\f[C]amount1\f[R]/\f[C]amount1-in\f[R]/\f[C]amount1-out\f[R] are -assigned, and posting 2 ignores them if any of -\f[C]amount2\f[R]/\f[C]amount2-in\f[R]/\f[C]amount2-out\f[R] are -assigned, avoiding conflicts. -.SS currency -.PP -If the CSV has the currency symbol in a separate field (ie, not part of -the amount field), you can use \f[C]currencyN\f[R] to prepend it to -posting N\[aq]s amount. -Or, \f[C]currency\f[R] with no number affects all postings. -.SS balance -.PP -\f[C]balanceN\f[R] sets a balance assertion amount (or if the posting -amount is left empty, a balance assignment) on posting N. -.PP -Also, for compatibility with hledger <1.17: \f[C]balance\f[R] with no -number is equivalent to \f[C]balance1\f[R]. -.PP -You can adjust the type of assertion/assignment with the -\f[C]balance-type\f[R] rule (see below). -.SS comment -.PP -Finally, \f[C]commentN\f[R] sets a comment on the Nth posting. -Comments can also contain tags, as usual. -.PP -See TIPS below for more about setting amounts and currency. -.SS field assignment -.IP -.nf -\f[C] -HLEDGERFIELDNAME FIELDVALUE -\f[R] -.fi -.PP -Instead of or in addition to a fields list, you can use a \[dq]field -assignment\[dq] rule to set the value of a single hledger field, by -writing its name (any of the standard hledger field names above) -followed by a text value. -The value may contain interpolated CSV fields, referenced by their -1-based position in the CSV record (\f[C]%N\f[R]), or by the name they -were given in the fields list (\f[C]%CSVFIELDNAME\f[R]). -Some examples: -.IP -.nf -\f[C] -# set the amount to the 4th CSV field, with \[dq] USD\[dq] appended -amount %4 USD - -# combine three fields to make a comment, containing note: and date: tags -comment note: %somefield - %anotherfield, date: %1 -\f[R] -.fi -.PP -Interpolation strips outer whitespace (so a CSV value like -\f[C]\[dq] 1 \[dq]\f[R] becomes \f[C]1\f[R] when interpolated) (#1051). -See TIPS below for more about referencing other fields. -.SS \f[C]separator\f[R] -.PP -You can use the \f[C]separator\f[R] rule to read other kinds of -character-separated data. -The argument is any single separator character, or the words -\f[C]tab\f[R] or \f[C]space\f[R] (case insensitive). -Eg, for comma-separated values (CSV): -.IP -.nf -\f[C] -separator , -\f[R] -.fi -.PP -or for semicolon-separated values (SSV): -.IP -.nf -\f[C] -separator ; -\f[R] -.fi -.PP -or for tab-separated values (TSV): -.IP -.nf -\f[C] -separator TAB -\f[R] -.fi -.PP -If the input file has a \f[C].csv\f[R], \f[C].ssv\f[R] or \f[C].tsv\f[R] -file extension (or a \f[C]csv:\f[R], \f[C]ssv:\f[R], \f[C]tsv:\f[R] -prefix), the appropriate separator will be inferred automatically, and -you won\[aq]t need this rule. -.SS \f[C]if\f[R] block -.IP -.nf -\f[C] -if MATCHER - RULE - -if -MATCHER -MATCHER -MATCHER - RULE - RULE -\f[R] -.fi -.PP -Conditional blocks (\[dq]if blocks\[dq]) are a block of rules that are -applied only to CSV records which match certain patterns. -They are often used for customising account names based on transaction -descriptions. -.SS Matching the whole record -.PP -Each MATCHER can be a record matcher, which looks like this: -.IP -.nf -\f[C] -REGEX -\f[R] -.fi -.PP -REGEX is a case-insensitive regular expression which tries to match -anywhere within the CSV record. -It is a POSIX ERE (extended regular expression) that also supports GNU -word boundaries (\f[C]\[rs]b\f[R], \f[C]\[rs]B\f[R], \f[C]\[rs]<\f[R], -\f[C]\[rs]>\f[R]), and nothing else. -If you have trouble, be sure to check our -https://hledger.org/hledger.html#regular-expressions doc. -.PP -Important note: the record that is matched is not the original record, -but a synthetic one, with any enclosing double quotes (but not enclosing -whitespace) removed, and always comma-separated (which means that a -field containing a comma will appear like two fields). -Eg, if the original record is -\f[C]2020-01-01; \[dq]Acme, Inc.\[dq]; 1,000\f[R], the REGEX will -actually see \f[C]2020-01-01,Acme, Inc., 1,000\f[R]). -.SS Matching individual fields -.PP -Or, MATCHER can be a field matcher, like this: -.IP -.nf -\f[C] -%CSVFIELD REGEX -\f[R] -.fi -.PP -which matches just the content of a particular CSV field. -CSVFIELD is a percent sign followed by the field\[aq]s name or column -number, like \f[C]%date\f[R] or \f[C]%1\f[R]. -.SS Combining matchers -.PP -A single matcher can be written on the same line as the \[dq]if\[dq]; or -multiple matchers can be written on the following lines, non-indented. -Multiple matchers are OR\[aq]d (any one of them can match), unless one -begins with an \f[C]&\f[R] symbol, in which case it is AND\[aq]ed with -the previous matcher. -.IP -.nf -\f[C] -if -MATCHER -& MATCHER - RULE -\f[R] -.fi -.SS Rules applied on successful match -.PP -After the patterns there should be one or more rules to apply, all -indented by at least one space. -Three kinds of rule are allowed in conditional blocks: -.IP \[bu] 2 -field assignments (to set a hledger field) -.IP \[bu] 2 -skip (to skip the matched CSV record) -.IP \[bu] 2 -end (to skip all remaining CSV records). -.PP -Examples: -.IP -.nf -\f[C] -# if the CSV record contains \[dq]groceries\[dq], set account2 to \[dq]expenses:groceries\[dq] -if groceries - account2 expenses:groceries -\f[R] -.fi -.IP -.nf -\f[C] -# if the CSV record contains any of these patterns, set account2 and comment as shown -if -monthly service fee -atm transaction fee -banking thru software - account2 expenses:business:banking - comment XXX deductible ? check it -\f[R] -.fi -.SS \f[C]if\f[R] table -.IP -.nf -\f[C] -if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn -MATCHER1,VALUE11,VALUE12,...,VALUE1n -MATCHER2,VALUE21,VALUE22,...,VALUE2n -MATCHER3,VALUE31,VALUE32,...,VALUE3n -<empty line> -\f[R] -.fi -.PP -Conditional tables (\[dq]if tables\[dq]) are a different syntax to -specify field assignments that will be applied only to CSV records which -match certain patterns. -.PP -MATCHER could be either field or record matcher, as described above. -When MATCHER matches, values from that row would be assigned to the CSV -fields named on the \f[C]if\f[R] line, in the same order. -.PP -Therefore \f[C]if\f[R] table is exactly equivalent to a sequence of of -\f[C]if\f[R] blocks: -.IP -.nf -\f[C] -if MATCHER1 - CSVFIELDNAME1 VALUE11 - CSVFIELDNAME2 VALUE12 - ... - CSVFIELDNAMEn VALUE1n - -if MATCHER2 - CSVFIELDNAME1 VALUE21 - CSVFIELDNAME2 VALUE22 - ... - CSVFIELDNAMEn VALUE2n - -if MATCHER3 - CSVFIELDNAME1 VALUE31 - CSVFIELDNAME2 VALUE32 - ... - CSVFIELDNAMEn VALUE3n -\f[R] -.fi -.PP -Each line starting with MATCHER should contain enough (possibly empty) -values for all the listed fields. -.PP -Rules would be checked and applied in the order they are listed in the -table and, like with \f[C]if\f[R] blocks, later rules (in the same or -another table) or \f[C]if\f[R] blocks could override the effect of any -rule. -.PP -Instead of \[aq],\[aq] you can use a variety of other non-alphanumeric -characters as a separator. -First character after \f[C]if\f[R] is taken to be the separator for the -rest of the table. -It is the responsibility of the user to ensure that separator does not -occur inside MATCHERs and values - there is no way to escape separator. -.PP -Example: -.IP -.nf -\f[C] -if,account2,comment -atm transaction fee,expenses:business:banking,deductible? check it -%description groceries,expenses:groceries, -2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out -\f[R] -.fi -.SS \f[C]end\f[R] -.PP -This rule can be used inside if blocks (only), to make hledger stop -reading this CSV file and move on to the next input file, or to command -execution. -Eg: -.IP -.nf -\f[C] -# ignore everything following the first empty record -if ,,,, - end -\f[R] -.fi -.SS \f[C]date-format\f[R] -.IP -.nf -\f[C] -date-format DATEFMT -\f[R] -.fi -.PP -This is a helper for the \f[C]date\f[R] (and \f[C]date2\f[R]) fields. -If your CSV dates are not formatted like \f[C]YYYY-MM-DD\f[R], -\f[C]YYYY/MM/DD\f[R] or \f[C]YYYY.MM.DD\f[R], you\[aq]ll need to add a -date-format rule describing them with a strptime date parsing pattern, -which must parse the CSV date value completely. -Some examples: -.IP -.nf -\f[C] -# MM/DD/YY -date-format %m/%d/%y -\f[R] -.fi -.IP -.nf -\f[C] -# D/M/YYYY -# The - makes leading zeros optional. -date-format %-d/%-m/%Y -\f[R] -.fi -.IP -.nf -\f[C] -# YYYY-Mmm-DD -date-format %Y-%h-%d -\f[R] -.fi -.IP -.nf -\f[C] -# M/D/YYYY HH:MM AM some other junk -# Note the time and junk must be fully parsed, though only the date is used. -date-format %-m/%-d/%Y %l:%M %p some other junk -\f[R] -.fi -.PP -For the supported strptime syntax, see: -.PD 0 -.P -.PD -https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime -.SS \f[C]decimal-mark\f[R] -.IP -.nf -\f[C] -decimal-mark . -\f[R] -.fi -.PP -or: -.IP -.nf -\f[C] -decimal-mark , -\f[R] -.fi -.PP -hledger automatically accepts either period or comma as a decimal mark -when parsing numbers (cf Amounts). -However if any numbers in the CSV contain digit group marks, such as -thousand-separating commas, you should declare the decimal mark -explicitly with this rule, to avoid misparsed numbers. -.SS \f[C]newest-first\f[R] -.PP -hledger always sorts the generated transactions by date. -Transactions on the same date should appear in the same order as their -CSV records, as hledger can usually auto-detect whether the CSV\[aq]s -normal order is oldest first or newest first. -But if all of the following are true: -.IP \[bu] 2 -the CSV might sometimes contain just one day of data (all records having -the same date) -.IP \[bu] 2 -the CSV records are normally in reverse chronological order (newest at -the top) -.IP \[bu] 2 -and you care about preserving the order of same-day transactions -.PP -then, you should add the \f[C]newest-first\f[R] rule as a hint. -Eg: -.IP -.nf -\f[C] -# tell hledger explicitly that the CSV is normally newest first -newest-first -\f[R] -.fi -.SS \f[C]include\f[R] -.IP -.nf -\f[C] -include RULESFILE -\f[R] -.fi -.PP -This includes the contents of another CSV rules file at this point. -\f[C]RULESFILE\f[R] is an absolute file path or a path relative to the -current file\[aq]s directory. -This can be useful for sharing common rules between several rules files, -eg: -.IP -.nf -\f[C] -# someaccount.csv.rules - -## someaccount-specific rules -fields date,description,amount -account1 assets:someaccount -account2 expenses:misc - -## common rules -include categorisation.rules -\f[R] -.fi -.SS \f[C]balance-type\f[R] -.PP -Balance assertions generated by assigning to balanceN are of the simple -\f[C]=\f[R] type by default, which is a single-commodity, -subaccount-excluding assertion. -You may find the subaccount-including variants more useful, eg if you -have created some virtual subaccounts of checking to help with -budgeting. -You can select a different type of assertion with the -\f[C]balance-type\f[R] rule: -.IP -.nf -\f[C] -# balance assertions will consider all commodities and all subaccounts -balance-type ==* -\f[R] -.fi -.PP -Here are the balance assertion types for quick reference: -.IP -.nf -\f[C] -= single commodity, exclude subaccounts -=* single commodity, include subaccounts -== multi commodity, exclude subaccounts -==* multi commodity, include subaccounts -\f[R] -.fi -.SH TIPS -.SS Rapid feedback -.PP -It\[aq]s a good idea to get rapid feedback while -creating/troubleshooting CSV rules. -Here\[aq]s a good way, using entr from http://eradman.com/entrproject : -.IP -.nf -\f[C] -$ ls foo.csv* | entr bash -c \[aq]echo ----; hledger -f foo.csv print desc:SOMEDESC\[aq] -\f[R] -.fi -.PP -A desc: query (eg) is used to select just one, or a few, transactions of -interest. -\[dq]bash -c\[dq] is used to run multiple commands, so we can echo a -separator each time the command re-runs, making it easier to read the -output. -.SS Valid CSV -.PP -hledger accepts CSV conforming to RFC 4180. -When CSV values are enclosed in quotes, note: -.IP \[bu] 2 -they must be double quotes (not single quotes) -.IP \[bu] 2 -spaces outside the quotes are not allowed -.SS File Extension -.PP -To help hledger identify the format and show the right error messages, -CSV/SSV/TSV files should normally be named with a \f[C].csv\f[R], -\f[C].ssv\f[R] or \f[C].tsv\f[R] filename extension. -Or, the file path should be prefixed with \f[C]csv:\f[R], \f[C]ssv:\f[R] -or \f[C]tsv:\f[R]. -Eg: -.IP -.nf -\f[C] -$ hledger -f foo.ssv print -\f[R] -.fi -.PP -or: -.IP -.nf -\f[C] -$ cat foo | hledger -f ssv:- foo -\f[R] -.fi -.PP -You can override the file extension with a separator rule if needed. -See also: Input files in the hledger manual. -.SS Reading multiple CSV files -.PP -If you use multiple \f[C]-f\f[R] options to read multiple CSV files at -once, hledger will look for a correspondingly-named rules file for each -CSV file. -But if you use the \f[C]--rules-file\f[R] option, that rules file will -be used for all the CSV files. -.SS Valid transactions -.PP -After reading a CSV file, hledger post-processes and validates the -generated journal entries as it would for a journal file - balancing -them, applying balance assignments, and canonicalising amount styles. -Any errors at this stage will be reported in the usual way, displaying -the problem entry. -.PP -There is one exception: balance assertions, if you have generated them, -will not be checked, since normally these will work only when the CSV -data is part of the main journal. -If you do need to check balance assertions generated from CSV right -away, pipe into another hledger: -.IP -.nf -\f[C] -$ hledger -f file.csv print | hledger -f- print -\f[R] -.fi -.SS Deduplicating, importing -.PP -When you download a CSV file periodically, eg to get your latest bank -transactions, the new file may overlap with the old one, containing some -of the same records. -.PP -The import command will (a) detect the new transactions, and (b) append -just those transactions to your main journal. -It is idempotent, so you don\[aq]t have to remember how many times you -ran it or with which version of the CSV. -(It keeps state in a hidden \f[C].latest.FILE.csv\f[R] file.) This is -the easiest way to import CSV data. -Eg: -.IP -.nf -\f[C] -# download the latest CSV files, then run this command. -# Note, no -f flags needed here. -$ hledger import *.csv [--dry] -\f[R] -.fi -.PP -This method works for most CSV files. -(Where records have a stable chronological order, and new records appear -only at the new end.) -.PP -A number of other tools and workflows, hledger-specific and otherwise, -exist for converting, deduplicating, classifying and managing CSV data. -See: -.IP \[bu] 2 -https://hledger.org -> sidebar -> real world setups -.IP \[bu] 2 -https://plaintextaccounting.org -> data import/conversion -.SS Setting amounts -.PP -A posting amount can be set in one of these ways: -.IP \[bu] 2 -by assigning (with a fields list or field assignment) to -\f[C]amountN\f[R] (posting N\[aq]s amount) or \f[C]amount\f[R] (posting -1\[aq]s amount) -.IP \[bu] 2 -by assigning to \f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] (or -\f[C]amount-in\f[R] and \f[C]amount-out\f[R]). -For each CSV record, whichever of these has a non-zero value will be -used, with appropriate sign. -If both contain a non-zero value, this may not work. -.IP \[bu] 2 -by assigning to \f[C]balanceN\f[R] (or \f[C]balance\f[R]) instead of the -above, setting the amount indirectly via a balance assignment. -If you do this the default account name may be wrong, so you should set -that explicitly. -.PP -There is some special handling for an amount\[aq]s sign: -.IP \[bu] 2 -If an amount value is parenthesised, it will be de-parenthesised and -sign-flipped. -.IP \[bu] 2 -If an amount value begins with a double minus sign, those cancel out and -are removed. -.IP \[bu] 2 -If an amount value begins with a plus sign, that will be removed -.SS Setting currency/commodity -.PP -If the currency/commodity symbol is included in the CSV\[aq]s amount -field(s): -.IP -.nf -\f[C] -2020-01-01,foo,$123.00 -\f[R] -.fi -.PP -you don\[aq]t have to do anything special for the commodity symbol, it -will be assigned as part of the amount. -Eg: -.IP -.nf -\f[C] -fields date,description,amount -\f[R] -.fi -.IP -.nf -\f[C] -2020-01-01 foo - expenses:unknown $123.00 - income:unknown $-123.00 -\f[R] -.fi -.PP -If the currency is provided as a separate CSV field: -.IP -.nf -\f[C] -2020-01-01,foo,USD,123.00 -\f[R] -.fi -.PP -You can assign that to the \f[C]currency\f[R] pseudo-field, which has -the special effect of prepending itself to every amount in the -transaction (on the left, with no separating space): -.IP -.nf -\f[C] -fields date,description,currency,amount -\f[R] -.fi -.IP -.nf -\f[C] -2020-01-01 foo - expenses:unknown USD123.00 - income:unknown USD-123.00 -\f[R] -.fi -.PP -Or, you can use a field assignment to construct the amount yourself, -with more control. -Eg to put the symbol on the right, and separated by a space: -.IP -.nf -\f[C] -fields date,description,cur,amt -amount %amt %cur -\f[R] -.fi -.IP -.nf -\f[C] -2020-01-01 foo - expenses:unknown 123.00 USD - income:unknown -123.00 USD -\f[R] -.fi -.PP -Note we used a temporary field name (\f[C]cur\f[R]) that is not -\f[C]currency\f[R] - that would trigger the prepending effect, which we -don\[aq]t want here. -.SS Referencing other fields -.PP -In field assignments, you can interpolate only CSV fields, not hledger -fields. -In the example below, there\[aq]s both a CSV field and a hledger field -named amount1, but %amount1 always means the CSV field, not the hledger -field: -.IP -.nf -\f[C] -# Name the third CSV field \[dq]amount1\[dq] -fields date,description,amount1 - -# Set hledger\[aq]s amount1 to the CSV amount1 field followed by USD -amount1 %amount1 USD - -# Set comment to the CSV amount1 (not the amount1 assigned above) -comment %amount1 -\f[R] -.fi -.PP -Here, since there\[aq]s no CSV amount1 field, %amount1 will produce a -literal \[dq]amount1\[dq]: -.IP -.nf -\f[C] -fields date,description,csvamount -amount1 %csvamount USD -# Can\[aq]t interpolate amount1 here -comment %amount1 -\f[R] -.fi -.PP -When there are multiple field assignments to the same hledger field, -only the last one takes effect. -Here, comment\[aq]s value will be be B, or C if \[dq]something\[dq] is -matched, but never A: -.IP -.nf -\f[C] -comment A -comment B -if something - comment C -\f[R] -.fi -.SS How CSV rules are evaluated -.PP -Here\[aq]s how to think of CSV rules being evaluated (if you really need -to). -First, -.IP \[bu] 2 -\f[C]include\f[R] - all includes are inlined, from top to bottom, depth -first. -(At each include point the file is inlined and scanned for further -includes, recursively, before proceeding.) -.PP -Then \[dq]global\[dq] rules are evaluated, top to bottom. -If a rule is repeated, the last one wins: -.IP \[bu] 2 -\f[C]skip\f[R] (at top level) -.IP \[bu] 2 -\f[C]date-format\f[R] -.IP \[bu] 2 -\f[C]newest-first\f[R] -.IP \[bu] 2 -\f[C]fields\f[R] - names the CSV fields, optionally sets up initial -assignments to hledger fields -.PP -Then for each CSV record in turn: -.IP \[bu] 2 -test all \f[C]if\f[R] blocks. -If any of them contain a \f[C]end\f[R] rule, skip all remaining CSV -records. -Otherwise if any of them contain a \f[C]skip\f[R] rule, skip that many -CSV records. -If there are multiple matched \f[C]skip\f[R] rules, the first one wins. -.IP \[bu] 2 -collect all field assignments at top level and in matched \f[C]if\f[R] -blocks. -When there are multiple assignments for a field, keep only the last one. -.IP \[bu] 2 -compute a value for each hledger field - either the one that was -assigned to it (and interpolate the %CSVFIELDNAME references), or a -default -.IP \[bu] 2 -generate a synthetic hledger transaction from these values. -.PP -This is all part of the CSV reader, one of several readers hledger can -use to parse input files. -When all files have been read successfully, the transactions are passed -as input to whichever hledger command the user specified. - - -.SH "REPORTING BUGS" -Report bugs at http://bugs.hledger.org -(or on the #hledger IRC channel or hledger mail list) - -.SH AUTHORS -Simon Michael <simon@joyful.com> and contributors - -.SH COPYRIGHT - -Copyright (C) 2007-2020 Simon Michael. -.br -Released under GNU GPL v3 or later. - -.SH SEE ALSO -hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) - -hledger_journal(5), hledger_csv(5), hledger_timeclock(5), hledger_timedot(5) diff --git a/hledger_csv.info b/hledger_csv.info deleted file mode 100644 index 10b62d8..0000000 --- a/hledger_csv.info +++ /dev/null @@ -1,1352 +0,0 @@ -This is hledger-lib/hledger_csv.info, produced by makeinfo version 4.8 -from stdin. - - -File: hledger_csv.info, Node: Top, Up: (dir) - -hledger_csv(5) -************** - -How hledger reads CSV data, and the CSV rules file format. - - hledger can read CSV files (Character Separated Value - usually -comma, semicolon, or tab) containing dated records as if they were -journal files, automatically converting each CSV record into a -transaction. - - (To learn about _writing_ CSV, see CSV output.) - - We describe each CSV file's format with a corresponding _rules -file_. By default this is named like the CSV file with a `.rules' -extension added. Eg when reading `FILE.csv', hledger also looks for -`FILE.csv.rules' in the same directory as `FILE.csv'. You can specify a -different rules file with the `--rules-file' option. If a rules file is -not found, hledger will create a sample rules file, which you'll need -to adjust. - - This file contains rules describing the CSV data (header line, fields -layout, date format etc.), and how to construct hledger journal entries -(transactions) from it. Often there will also be a list of conditional -rules for categorising transactions based on their descriptions. Here's -an overview of the CSV rules; these are described more fully below, -after the examples: - -*`skip'* skip one or more header lines or matched - CSV records -*`fields'* name CSV fields, assign them to hledger - fields -*field assignment* assign a value to one hledger field, - with interpolation -*`separator'* a custom field separator -*`if' block* apply some rules to CSV records matched - by patterns -*`if' table* apply some rules to CSV records matched - by patterns, alternate syntax -*`end'* skip the remaining CSV records -*`date-format'* how to parse dates in CSV records -*`decimal-mark'* the decimal mark used in CSV amounts, if - ambiguous -*`newest-first'* disambiguate record order when there's - only one date -*`include'* inline another CSV rules file -*`balance-type'* choose which type of balance assignments - to use - - Note, for best error messages when reading CSV files, use a `.csv', -`.tsv' or `.ssv' file extension or file prefix - see File Extension -below. - - There's an introductory Convert CSV files tutorial on hledger.org. - -* Menu: - -* EXAMPLES:: -* CSV RULES:: -* TIPS:: - - -File: hledger_csv.info, Node: EXAMPLES, Next: CSV RULES, Prev: Top, Up: Top - -1 EXAMPLES -********** - -Here are some sample hledger CSV rules files. See also the full -collection at: -https://github.com/simonmichael/hledger/tree/master/examples/csv - -* Menu: - -* Basic:: -* Bank of Ireland:: -* Amazon:: -* Paypal:: - - -File: hledger_csv.info, Node: Basic, Next: Bank of Ireland, Up: EXAMPLES - -1.1 Basic -========= - -At minimum, the rules file must identify the date and amount fields, and -often it also specifies the date format and how many header lines there -are. Here's a simple CSV file and a rules file for it: - - -Date, Description, Id, Amount -12/11/2019, Foo, 123, 10.23 - - -# basic.csv.rules -skip 1 -fields date, description, _, amount -date-format %d/%m/%Y - - -$ hledger print -f basic.csv -2019-11-12 Foo - expenses:unknown 10.23 - income:unknown -10.23 - - Default account names are chosen, since we didn't set them. - - -File: hledger_csv.info, Node: Bank of Ireland, Next: Amazon, Prev: Basic, Up: EXAMPLES - -1.2 Bank of Ireland -=================== - -Here's a CSV with two amount fields (Debit and Credit), and a balance -field, which we can use to add balance assertions, which is not -necessary but provides extra error checking: - - -Date,Details,Debit,Credit,Balance -07/12/2012,LODGMENT 529898,,10.0,131.21 -07/12/2012,PAYMENT,5,,126 - - -# bankofireland-checking.csv.rules - -# skip the header line -skip - -# name the csv fields, and assign some of them as journal entry fields -fields date, description, amount-out, amount-in, balance - -# We generate balance assertions by assigning to "balance" -# above, but you may sometimes need to remove these because: -# -# - the CSV balance differs from the true balance, -# by up to 0.0000000000005 in my experience -# -# - it is sometimes calculated based on non-chronological ordering, -# eg when multiple transactions clear on the same day - -# date is in UK/Ireland format -date-format %d/%m/%Y - -# set the currency -currency EUR - -# set the base account for all txns -account1 assets:bank:boi:checking - - -$ hledger -f bankofireland-checking.csv print -2012-12-07 LODGMENT 529898 - assets:bank:boi:checking EUR10.0 = EUR131.2 - income:unknown EUR-10.0 - -2012-12-07 PAYMENT - assets:bank:boi:checking EUR-5.0 = EUR126.0 - expenses:unknown EUR5.0 - - The balance assertions don't raise an error above, because we're -reading directly from CSV, but they will be checked if these entries are -imported into a journal file. - - -File: hledger_csv.info, Node: Amazon, Next: Paypal, Prev: Bank of Ireland, Up: EXAMPLES - -1.3 Amazon -========== - -Here we convert amazon.com order history, and use an if block to -generate a third posting if there's a fee. (In practice you'd probably -get this data from your bank instead, but it's an example.) - - -"Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" -"Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" -"Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" - - -# amazon-orders.csv.rules - -# skip one header line -skip 1 - -# name the csv fields, and assign the transaction's date, amount and code. -# Avoided the "status" and "amount" hledger field names to prevent confusion. -fields date, _, toorfrom, name, amzstatus, amzamount, fees, code - -# how to parse the date -date-format %b %-d, %Y - -# combine two fields to make the description -description %toorfrom %name - -# save the status as a tag -comment status:%amzstatus - -# set the base account for all transactions -account1 assets:amazon -# leave amount1 blank so it can balance the other(s). -# I'm assuming amzamount excludes the fees, don't remember - -# set a generic account2 -account2 expenses:misc -amount2 %amzamount -# and maybe refine it further: -#include categorisation.rules - -# add a third posting for fees, but only if they are non-zero. -if %fees [1-9] - account3 expenses:fees - amount3 %fees - - -$ hledger -f amazon-orders.csv print -2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed - assets:amazon - expenses:misc $20.00 - -2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed - assets:amazon - expenses:misc $25.00 - expenses:fees $1.00 - - -File: hledger_csv.info, Node: Paypal, Prev: Amazon, Up: EXAMPLES - -1.4 Paypal -========== - -Here's a real-world rules file for (customised) Paypal CSV, with some -Paypal-specific rules, and a second rules file included: - - -"Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" -"10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" -"10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" -"10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" -"10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" -"10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" -"10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" -"10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" - - -# paypal-custom.csv.rules - -# Tips: -# Export from Activity -> Statements -> Custom -> Activity download -# Suggested transaction type: "Balance affecting" -# Paypal's default fields in 2018 were: -# "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" -# This rules file assumes the following more detailed fields, configured in "Customize report fields": -# "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" - -fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note - -skip 1 - -date-format %-m/%-d/%Y - -# ignore some paypal events -if -In Progress -Temporary Hold -Update to - skip - -# add more fields to the description -description %description_ %itemtitle - -# save some other fields as tags -comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ - -# convert to short currency symbols -if %currency USD - currency $ -if %currency EUR - currency E -if %currency GBP - currency P - -# generate postings - -# the first posting will be the money leaving/entering my paypal account -# (negative means leaving my account, in all amount fields) -account1 assets:online:paypal -amount1 %netamount - -# the second posting will be money sent to/received from other party -# (account2 is set below) -amount2 -%grossamount - -# if there's a fee, add a third posting for the money taken by paypal. -if %feeamount [1-9] - account3 expenses:banking:paypal - amount3 -%feeamount - comment3 business: - -# choose an account for the second posting - -# override the default account names: -# if the amount is positive, it's income (a debit) -if %grossamount ^[^-] - account2 income:unknown -# if negative, it's an expense (a credit) -if %grossamount ^- - account2 expenses:unknown - -# apply common rules for setting account2 & other tweaks -include common.rules - -# apply some overrides specific to this csv - -# Transfers from/to bank. These are usually marked Pending, -# which can be disregarded in this case. -if -Bank Account -Bank Deposit to PP Account - description %type for %referencetxnid %itemtitle - account2 assets:bank:wf:pchecking - account1 assets:online:paypal - -# Currency conversions -if Currency Conversion - account2 equity:currency conversion - - -# common.rules - -if -darcs -noble benefactor - account2 revenues:foss donations:darcshub - comment2 business: - -if -Calm Radio - account2 expenses:online:apps - -if -electronic frontier foundation -Patreon -wikimedia -Advent of Code - account2 expenses:dues - -if Google - account2 expenses:online:apps - description google | music - - -$ hledger -f paypal-custom.csv print -2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed - assets:online:paypal $-6.99 = $-6.99 - expenses:online:apps $6.99 - -2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $6.99 = $0.00 - assets:bank:wf:pchecking $-6.99 - -2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed - assets:online:paypal $-7.00 = $-7.00 - expenses:dues $7.00 - -2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $7.00 = $0.00 - assets:bank:wf:pchecking $-7.00 - -2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed - assets:online:paypal $-2.00 = $-2.00 - expenses:dues $2.00 - expenses:banking:paypal ; business: - -2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $2.00 = $0.00 - assets:bank:wf:pchecking $-2.00 - -2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed - assets:online:paypal $9.41 = $9.41 - revenues:foss donations:darcshub $-10.00 ; business: - expenses:banking:paypal $0.59 ; business: - - -File: hledger_csv.info, Node: CSV RULES, Next: TIPS, Prev: EXAMPLES, Up: Top - -2 CSV RULES -*********** - -The following kinds of rule can appear in the rules file, in any order. -Blank lines and lines beginning with `#' or `;' are ignored. - -* Menu: - -* skip:: -* fields:: -* field assignment:: -* separator:: -* if block:: -* if table:: -* end:: -* date-format:: -* decimal-mark:: -* newest-first:: -* include:: -* balance-type:: - - -File: hledger_csv.info, Node: skip, Next: fields, Up: CSV RULES - -2.1 `skip' -========== - - -skip N - -The word "skip" followed by a number (or no number, meaning 1) tells -hledger to ignore this many non-empty lines preceding the CSV data. -(Empty/blank lines are skipped automatically.) You'll need this whenever -your CSV data contains header lines. - - It also has a second purpose: it can be used inside if blocks to -ignore certain CSV records (described below). - - -File: hledger_csv.info, Node: fields, Next: field assignment, Prev: skip, Up: CSV RULES - -2.2 `fields' -============ - - -fields FIELDNAME1, FIELDNAME2, ... - -A fields list (the word "fields" followed by comma-separated field -names) is the quick way to assign CSV field values to hledger fields. It -does two things: - - 1. it names the CSV fields. This is optional, but can be convenient - later for interpolating them. - - 2. when you use a standard hledger field name, it assigns the CSV - value to that part of the hledger transaction. - - - Here's an example that says "use the 1st, 2nd and 4th fields as the -transaction's date, description and amount; name the last two fields for -later reference; and ignore the others": - - -fields date, description, , amount, , , somefield, anotherfield - - Field names may not contain whitespace. Fields you don't care about -can be left unnamed. Currently there must be least two items (there -must be at least one comma). - - Note, always use comma in the fields list, even if your CSV uses -another separator character. - - Here are the standard hledger field/pseudo-field names. For more -about the transaction parts they refer to, see the manual for hledger's -journal format. - -* Menu: - -* Transaction field names:: -* Posting field names:: - - -File: hledger_csv.info, Node: Transaction field names, Next: Posting field names, Up: fields - -2.2.1 Transaction field names ------------------------------ - -`date', `date2', `status', `code', `description', `comment' can be used -to form the transaction's first line. - - -File: hledger_csv.info, Node: Posting field names, Prev: Transaction field names, Up: fields - -2.2.2 Posting field names -------------------------- - -* Menu: - -* account:: -* amount:: -* currency:: -* balance:: -* comment:: - - -File: hledger_csv.info, Node: account, Next: amount, Up: Posting field names - -2.2.2.1 account -............... - -`accountN', where N is 1 to 99, causes a posting to be generated, with -that account name. - - Most often there are two postings, so you'll want to set `account1' -and `account2'. Typically `account1' is associated with the CSV file, -and is set once with a top-level assignment, while `account2' is set -based on each transaction's description, and in conditional blocks. - - If a posting's account name is left unset but its amount is set (see -below), a default account name will be chosen (like "expenses:unknown" -or "income:unknown"). - - -File: hledger_csv.info, Node: amount, Next: currency, Prev: account, Up: Posting field names - -2.2.2.2 amount -.............. - -`amountN' sets posting N's amount. If the CSV uses separate fields for -inflows and outflows, you can use `amountN-in' and `amountN-out' -instead. By assigning to `amount1', `amount2', ... etc. you can -generate anywhere from 0 to 99 postings. - - There is also an older, unnumbered form of these names, suitable for -2-posting transactions, which sets both posting 1's and (negated) -posting 2's amount: `amount', or `amount-in' and `amount-out'. This is -still supported because it keeps pre-hledger-1.17 csv rules files -working, and because it can be more succinct, and because it converts -posting 2's amount to cost if there's a transaction price, which can be -useful. - - If you have an existing rules file using the unnumbered form, you -might want to use the numbered form in certain conditional blocks, -without having to update and retest all the old rules. To facilitate -this, posting 1 ignores `amount'/`amount-in'/`amount-out' if any of -`amount1'/`amount1-in'/`amount1-out' are assigned, and posting 2 -ignores them if any of `amount2'/`amount2-in'/`amount2-out' are -assigned, avoiding conflicts. - - -File: hledger_csv.info, Node: currency, Next: balance, Prev: amount, Up: Posting field names - -2.2.2.3 currency -................ - -If the CSV has the currency symbol in a separate field (ie, not part of -the amount field), you can use `currencyN' to prepend it to posting N's -amount. Or, `currency' with no number affects all postings. - - -File: hledger_csv.info, Node: balance, Next: comment, Prev: currency, Up: Posting field names - -2.2.2.4 balance -............... - -`balanceN' sets a balance assertion amount (or if the posting amount is -left empty, a balance assignment) on posting N. - - Also, for compatibility with hledger <1.17: `balance' with no number -is equivalent to `balance1'. - - You can adjust the type of assertion/assignment with the -`balance-type' rule (see below). - - -File: hledger_csv.info, Node: comment, Prev: balance, Up: Posting field names - -2.2.2.5 comment -............... - -Finally, `commentN' sets a comment on the Nth posting. Comments can -also contain tags, as usual. - - See TIPS below for more about setting amounts and currency. - - -File: hledger_csv.info, Node: field assignment, Next: separator, Prev: fields, Up: CSV RULES - -2.3 field assignment -==================== - - -HLEDGERFIELDNAME FIELDVALUE - -Instead of or in addition to a fields list, you can use a "field -assignment" rule to set the value of a single hledger field, by writing -its name (any of the standard hledger field names above) followed by a -text value. The value may contain interpolated CSV fields, referenced by -their 1-based position in the CSV record (`%N'), or by the name they -were given in the fields list (`%CSVFIELDNAME'). Some examples: - - -# set the amount to the 4th CSV field, with " USD" appended -amount %4 USD - -# combine three fields to make a comment, containing note: and date: tags -comment note: %somefield - %anotherfield, date: %1 - - Interpolation strips outer whitespace (so a CSV value like `" 1 "' -becomes `1' when interpolated) (#1051). See TIPS below for more about -referencing other fields. - - -File: hledger_csv.info, Node: separator, Next: if block, Prev: field assignment, Up: CSV RULES - -2.4 `separator' -=============== - -You can use the `separator' rule to read other kinds of -character-separated data. The argument is any single separator -character, or the words `tab' or `space' (case insensitive). Eg, for -comma-separated values (CSV): - - -separator , - - or for semicolon-separated values (SSV): - - -separator ; - - or for tab-separated values (TSV): - - -separator TAB - - If the input file has a `.csv', `.ssv' or `.tsv' file extension (or -a `csv:', `ssv:', `tsv:' prefix), the appropriate separator will be -inferred automatically, and you won't need this rule. - - -File: hledger_csv.info, Node: if block, Next: if table, Prev: separator, Up: CSV RULES - -2.5 `if' block -============== - - -if MATCHER - RULE - -if -MATCHER -MATCHER -MATCHER - RULE - RULE - -Conditional blocks ("if blocks") are a block of rules that are applied -only to CSV records which match certain patterns. They are often used -for customising account names based on transaction descriptions. - -* Menu: - -* Matching the whole record:: -* Matching individual fields:: -* Combining matchers:: -* Rules applied on successful match:: - - -File: hledger_csv.info, Node: Matching the whole record, Next: Matching individual fields, Up: if block - -2.5.1 Matching the whole record -------------------------------- - -Each MATCHER can be a record matcher, which looks like this: - - -REGEX - - REGEX is a case-insensitive regular expression which tries to match -anywhere within the CSV record. It is a POSIX ERE (extended regular -expression) that also supports GNU word boundaries (`\b', `\B', `\<', -`\>'), and nothing else. If you have trouble, be sure to check our -https://hledger.org/hledger.html#regular-expressions doc. - - Important note: the record that is matched is not the original -record, but a synthetic one, with any enclosing double quotes (but not -enclosing whitespace) removed, and always comma-separated (which means -that a field containing a comma will appear like two fields). Eg, if the -original record is `2020-01-01; "Acme, Inc."; 1,000', the REGEX will -actually see `2020-01-01,Acme, Inc., 1,000'). - - -File: hledger_csv.info, Node: Matching individual fields, Next: Combining matchers, Prev: Matching the whole record, Up: if block - -2.5.2 Matching individual fields --------------------------------- - -Or, MATCHER can be a field matcher, like this: - - -%CSVFIELD REGEX - - which matches just the content of a particular CSV field. CSVFIELD -is a percent sign followed by the field's name or column number, like -`%date' or `%1'. - - -File: hledger_csv.info, Node: Combining matchers, Next: Rules applied on successful match, Prev: Matching individual fields, Up: if block - -2.5.3 Combining matchers ------------------------- - -A single matcher can be written on the same line as the "if"; or -multiple matchers can be written on the following lines, non-indented. -Multiple matchers are OR'd (any one of them can match), unless one -begins with an `&' symbol, in which case it is AND'ed with the previous -matcher. - - -if -MATCHER -& MATCHER - RULE - - -File: hledger_csv.info, Node: Rules applied on successful match, Prev: Combining matchers, Up: if block - -2.5.4 Rules applied on successful match ---------------------------------------- - -After the patterns there should be one or more rules to apply, all -indented by at least one space. Three kinds of rule are allowed in -conditional blocks: - - * field assignments (to set a hledger field) - - * skip (to skip the matched CSV record) - - * end (to skip all remaining CSV records). - - Examples: - - -# if the CSV record contains "groceries", set account2 to "expenses:groceries" -if groceries - account2 expenses:groceries - - -# if the CSV record contains any of these patterns, set account2 and comment as shown -if -monthly service fee -atm transaction fee -banking thru software - account2 expenses:business:banking - comment XXX deductible ? check it - - -File: hledger_csv.info, Node: if table, Next: end, Prev: if block, Up: CSV RULES - -2.6 `if' table -============== - - -if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn -MATCHER1,VALUE11,VALUE12,...,VALUE1n -MATCHER2,VALUE21,VALUE22,...,VALUE2n -MATCHER3,VALUE31,VALUE32,...,VALUE3n -<empty line> - -Conditional tables ("if tables") are a different syntax to specify field -assignments that will be applied only to CSV records which match certain -patterns. - - MATCHER could be either field or record matcher, as described above. -When MATCHER matches, values from that row would be assigned to the CSV -fields named on the `if' line, in the same order. - - Therefore `if' table is exactly equivalent to a sequence of of `if' -blocks: - - -if MATCHER1 - CSVFIELDNAME1 VALUE11 - CSVFIELDNAME2 VALUE12 - ... - CSVFIELDNAMEn VALUE1n - -if MATCHER2 - CSVFIELDNAME1 VALUE21 - CSVFIELDNAME2 VALUE22 - ... - CSVFIELDNAMEn VALUE2n - -if MATCHER3 - CSVFIELDNAME1 VALUE31 - CSVFIELDNAME2 VALUE32 - ... - CSVFIELDNAMEn VALUE3n - - Each line starting with MATCHER should contain enough (possibly -empty) values for all the listed fields. - - Rules would be checked and applied in the order they are listed in -the table and, like with `if' blocks, later rules (in the same or -another table) or `if' blocks could override the effect of any rule. - - Instead of ',' you can use a variety of other non-alphanumeric -characters as a separator. First character after `if' is taken to be -the separator for the rest of the table. It is the responsibility of -the user to ensure that separator does not occur inside MATCHERs and -values - there is no way to escape separator. - - Example: - - -if,account2,comment -atm transaction fee,expenses:business:banking,deductible? check it -%description groceries,expenses:groceries, -2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out - - -File: hledger_csv.info, Node: end, Next: date-format, Prev: if table, Up: CSV RULES - -2.7 `end' -========= - -This rule can be used inside if blocks (only), to make hledger stop -reading this CSV file and move on to the next input file, or to command -execution. Eg: - - -# ignore everything following the first empty record -if ,,,, - end - - -File: hledger_csv.info, Node: date-format, Next: decimal-mark, Prev: end, Up: CSV RULES - -2.8 `date-format' -================= - - -date-format DATEFMT - -This is a helper for the `date' (and `date2') fields. If your CSV dates -are not formatted like `YYYY-MM-DD', `YYYY/MM/DD' or `YYYY.MM.DD', -you'll need to add a date-format rule describing them with a strptime -date parsing pattern, which must parse the CSV date value completely. -Some examples: - - -# MM/DD/YY -date-format %m/%d/%y - - -# D/M/YYYY -# The - makes leading zeros optional. -date-format %-d/%-m/%Y - - -# YYYY-Mmm-DD -date-format %Y-%h-%d - - -# M/D/YYYY HH:MM AM some other junk -# Note the time and junk must be fully parsed, though only the date is used. -date-format %-m/%-d/%Y %l:%M %p some other junk - - For the supported strptime syntax, see: -https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime - - -File: hledger_csv.info, Node: decimal-mark, Next: newest-first, Prev: date-format, Up: CSV RULES - -2.9 `decimal-mark' -================== - - -decimal-mark . - -or: - - -decimal-mark , - - hledger automatically accepts either period or comma as a decimal -mark when parsing numbers (cf Amounts). However if any numbers in the -CSV contain digit group marks, such as thousand-separating commas, you -should declare the decimal mark explicitly with this rule, to avoid -misparsed numbers. - - -File: hledger_csv.info, Node: newest-first, Next: include, Prev: decimal-mark, Up: CSV RULES - -2.10 `newest-first' -=================== - -hledger always sorts the generated transactions by date. Transactions on -the same date should appear in the same order as their CSV records, as -hledger can usually auto-detect whether the CSV's normal order is oldest -first or newest first. But if all of the following are true: - - * the CSV might sometimes contain just one day of data (all records - having the same date) - - * the CSV records are normally in reverse chronological order - (newest at the top) - - * and you care about preserving the order of same-day transactions - - then, you should add the `newest-first' rule as a hint. Eg: - - -# tell hledger explicitly that the CSV is normally newest first -newest-first - - -File: hledger_csv.info, Node: include, Next: balance-type, Prev: newest-first, Up: CSV RULES - -2.11 `include' -============== - - -include RULESFILE - -This includes the contents of another CSV rules file at this point. -`RULESFILE' is an absolute file path or a path relative to the current -file's directory. This can be useful for sharing common rules between -several rules files, eg: - - -# someaccount.csv.rules - -## someaccount-specific rules -fields date,description,amount -account1 assets:someaccount -account2 expenses:misc - -## common rules -include categorisation.rules - - -File: hledger_csv.info, Node: balance-type, Prev: include, Up: CSV RULES - -2.12 `balance-type' -=================== - -Balance assertions generated by assigning to balanceN are of the simple -`=' type by default, which is a single-commodity, subaccount-excluding -assertion. You may find the subaccount-including variants more useful, -eg if you have created some virtual subaccounts of checking to help -with budgeting. You can select a different type of assertion with the -`balance-type' rule: - - -# balance assertions will consider all commodities and all subaccounts -balance-type ==* - - Here are the balance assertion types for quick reference: - - -= single commodity, exclude subaccounts -=* single commodity, include subaccounts -== multi commodity, exclude subaccounts -==* multi commodity, include subaccounts - - -File: hledger_csv.info, Node: TIPS, Prev: CSV RULES, Up: Top - -3 TIPS -****** - -* Menu: - -* Rapid feedback:: -* Valid CSV:: -* File Extension:: -* Reading multiple CSV files:: -* Valid transactions:: -* Deduplicating importing:: -* Setting amounts:: -* Setting currency/commodity:: -* Referencing other fields:: -* How CSV rules are evaluated:: - - -File: hledger_csv.info, Node: Rapid feedback, Next: Valid CSV, Up: TIPS - -3.1 Rapid feedback -================== - -It's a good idea to get rapid feedback while creating/troubleshooting -CSV rules. Here's a good way, using entr from -http://eradman.com/entrproject : - - -$ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' - - A desc: query (eg) is used to select just one, or a few, -transactions of interest. "bash -c" is used to run multiple commands, -so we can echo a separator each time the command re-runs, making it -easier to read the output. - - -File: hledger_csv.info, Node: Valid CSV, Next: File Extension, Prev: Rapid feedback, Up: TIPS - -3.2 Valid CSV -============= - -hledger accepts CSV conforming to RFC 4180. When CSV values are enclosed -in quotes, note: - - * they must be double quotes (not single quotes) - - * spaces outside the quotes are not allowed - - -File: hledger_csv.info, Node: File Extension, Next: Reading multiple CSV files, Prev: Valid CSV, Up: TIPS - -3.3 File Extension -================== - -To help hledger identify the format and show the right error messages, -CSV/SSV/TSV files should normally be named with a `.csv', `.ssv' or -`.tsv' filename extension. Or, the file path should be prefixed with -`csv:', `ssv:' or `tsv:'. Eg: - - -$ hledger -f foo.ssv print - - or: - - -$ cat foo | hledger -f ssv:- foo - - You can override the file extension with a separator rule if needed. -See also: Input files in the hledger manual. - - -File: hledger_csv.info, Node: Reading multiple CSV files, Next: Valid transactions, Prev: File Extension, Up: TIPS - -3.4 Reading multiple CSV files -============================== - -If you use multiple `-f' options to read multiple CSV files at once, -hledger will look for a correspondingly-named rules file for each CSV -file. But if you use the `--rules-file' option, that rules file will be -used for all the CSV files. - - -File: hledger_csv.info, Node: Valid transactions, Next: Deduplicating importing, Prev: Reading multiple CSV files, Up: TIPS - -3.5 Valid transactions -====================== - -After reading a CSV file, hledger post-processes and validates the -generated journal entries as it would for a journal file - balancing -them, applying balance assignments, and canonicalising amount styles. -Any errors at this stage will be reported in the usual way, displaying -the problem entry. - - There is one exception: balance assertions, if you have generated -them, will not be checked, since normally these will work only when the -CSV data is part of the main journal. If you do need to check balance -assertions generated from CSV right away, pipe into another hledger: - - -$ hledger -f file.csv print | hledger -f- print - - -File: hledger_csv.info, Node: Deduplicating importing, Next: Setting amounts, Prev: Valid transactions, Up: TIPS - -3.6 Deduplicating, importing -============================ - -When you download a CSV file periodically, eg to get your latest bank -transactions, the new file may overlap with the old one, containing some -of the same records. - - The import command will (a) detect the new transactions, and (b) -append just those transactions to your main journal. It is idempotent, -so you don't have to remember how many times you ran it or with which -version of the CSV. (It keeps state in a hidden `.latest.FILE.csv' -file.) This is the easiest way to import CSV data. Eg: - - -# download the latest CSV files, then run this command. -# Note, no -f flags needed here. -$ hledger import *.csv [--dry] - - This method works for most CSV files. (Where records have a stable -chronological order, and new records appear only at the new end.) - - A number of other tools and workflows, hledger-specific and -otherwise, exist for converting, deduplicating, classifying and -managing CSV data. See: - - * https://hledger.org -> sidebar -> real world setups - - * https://plaintextaccounting.org -> data import/conversion - - -File: hledger_csv.info, Node: Setting amounts, Next: Setting currency/commodity, Prev: Deduplicating importing, Up: TIPS - -3.7 Setting amounts -=================== - -A posting amount can be set in one of these ways: - - * by assigning (with a fields list or field assignment) to `amountN' - (posting N's amount) or `amount' (posting 1's amount) - - * by assigning to `amountN-in' and `amountN-out' (or `amount-in' and - `amount-out'). For each CSV record, whichever of these has a - non-zero value will be used, with appropriate sign. If both - contain a non-zero value, this may not work. - - * by assigning to `balanceN' (or `balance') instead of the above, - setting the amount indirectly via a balance assignment. If you do - this the default account name may be wrong, so you should set that - explicitly. - - - There is some special handling for an amount's sign: - - * If an amount value is parenthesised, it will be de-parenthesised - and sign-flipped. - - * If an amount value begins with a double minus sign, those cancel - out and are removed. - - * If an amount value begins with a plus sign, that will be removed - - -File: hledger_csv.info, Node: Setting currency/commodity, Next: Referencing other fields, Prev: Setting amounts, Up: TIPS - -3.8 Setting currency/commodity -============================== - -If the currency/commodity symbol is included in the CSV's amount -field(s): - - -2020-01-01,foo,$123.00 - - you don't have to do anything special for the commodity symbol, it -will be assigned as part of the amount. Eg: - - -fields date,description,amount - - -2020-01-01 foo - expenses:unknown $123.00 - income:unknown $-123.00 - - If the currency is provided as a separate CSV field: - - -2020-01-01,foo,USD,123.00 - - You can assign that to the `currency' pseudo-field, which has the -special effect of prepending itself to every amount in the transaction -(on the left, with no separating space): - - -fields date,description,currency,amount - - -2020-01-01 foo - expenses:unknown USD123.00 - income:unknown USD-123.00 - - Or, you can use a field assignment to construct the amount yourself, -with more control. Eg to put the symbol on the right, and separated by a -space: - - -fields date,description,cur,amt -amount %amt %cur - - -2020-01-01 foo - expenses:unknown 123.00 USD - income:unknown -123.00 USD - - Note we used a temporary field name (`cur') that is not `currency' - -that would trigger the prepending effect, which we don't want here. - - -File: hledger_csv.info, Node: Referencing other fields, Next: How CSV rules are evaluated, Prev: Setting currency/commodity, Up: TIPS - -3.9 Referencing other fields -============================ - -In field assignments, you can interpolate only CSV fields, not hledger -fields. In the example below, there's both a CSV field and a hledger -field named amount1, but %amount1 always means the CSV field, not the -hledger field: - - -# Name the third CSV field "amount1" -fields date,description,amount1 - -# Set hledger's amount1 to the CSV amount1 field followed by USD -amount1 %amount1 USD - -# Set comment to the CSV amount1 (not the amount1 assigned above) -comment %amount1 - - Here, since there's no CSV amount1 field, %amount1 will produce a -literal "amount1": - - -fields date,description,csvamount -amount1 %csvamount USD -# Can't interpolate amount1 here -comment %amount1 - - When there are multiple field assignments to the same hledger field, -only the last one takes effect. Here, comment's value will be be B, or C -if "something" is matched, but never A: - - -comment A -comment B -if something - comment C - - -File: hledger_csv.info, Node: How CSV rules are evaluated, Prev: Referencing other fields, Up: TIPS - -3.10 How CSV rules are evaluated -================================ - -Here's how to think of CSV rules being evaluated (if you really need -to). First, - - * `include' - all includes are inlined, from top to bottom, depth - first. (At each include point the file is inlined and scanned for - further includes, recursively, before proceeding.) - - Then "global" rules are evaluated, top to bottom. If a rule is -repeated, the last one wins: - - * `skip' (at top level) - - * `date-format' - - * `newest-first' - - * `fields' - names the CSV fields, optionally sets up initial - assignments to hledger fields - - Then for each CSV record in turn: - - * test all `if' blocks. If any of them contain a `end' rule, skip - all remaining CSV records. Otherwise if any of them contain a - `skip' rule, skip that many CSV records. If there are multiple - matched `skip' rules, the first one wins. - - * collect all field assignments at top level and in matched `if' - blocks. When there are multiple assignments for a field, keep only - the last one. - - * compute a value for each hledger field - either the one that was - assigned to it (and interpolate the %CSVFIELDNAME references), or a - default - - * generate a synthetic hledger transaction from these values. - - This is all part of the CSV reader, one of several readers hledger -can use to parse input files. When all files have been read -successfully, the transactions are passed as input to whichever hledger -command the user specified. - - - -Tag Table: -Node: Top84 -Node: EXAMPLES2746 -Ref: #examples2852 -Node: Basic3059 -Ref: #basic3159 -Node: Bank of Ireland3703 -Ref: #bank-of-ireland3838 -Node: Amazon5303 -Ref: #amazon5421 -Node: Paypal7142 -Ref: #paypal7236 -Node: CSV RULES14884 -Ref: #csv-rules14993 -Node: skip15305 -Ref: #skip15398 -Node: fields15770 -Ref: #fields15892 -Node: Transaction field names17053 -Ref: #transaction-field-names17213 -Node: Posting field names17324 -Ref: #posting-field-names17476 -Node: account17546 -Ref: #account17662 -Node: amount18198 -Ref: #amount18329 -Node: currency19430 -Ref: #currency19565 -Node: balance19770 -Ref: #balance19904 -Node: comment20221 -Ref: #comment20338 -Node: field assignment20500 -Ref: #field-assignment20643 -Node: separator21457 -Ref: #separator21592 -Node: if block22134 -Ref: #if-block22259 -Node: Matching the whole record22657 -Ref: #matching-the-whole-record22832 -Node: Matching individual fields23636 -Ref: #matching-individual-fields23840 -Node: Combining matchers24064 -Ref: #combining-matchers24260 -Node: Rules applied on successful match24574 -Ref: #rules-applied-on-successful-match24765 -Node: if table25422 -Ref: #if-table25541 -Node: end27277 -Ref: #end27389 -Node: date-format27613 -Ref: #date-format27745 -Node: decimal-mark28495 -Ref: #decimal-mark28638 -Node: newest-first28975 -Ref: #newest-first29116 -Node: include29799 -Ref: #include29930 -Node: balance-type30372 -Ref: #balance-type30492 -Node: TIPS31192 -Ref: #tips31274 -Node: Rapid feedback31530 -Ref: #rapid-feedback31647 -Node: Valid CSV32106 -Ref: #valid-csv32236 -Node: File Extension32428 -Ref: #file-extension32580 -Node: Reading multiple CSV files33009 -Ref: #reading-multiple-csv-files33194 -Node: Valid transactions33434 -Ref: #valid-transactions33612 -Node: Deduplicating importing34240 -Ref: #deduplicating-importing34419 -Node: Setting amounts35451 -Ref: #setting-amounts35620 -Node: Setting currency/commodity36607 -Ref: #setting-currencycommodity36799 -Node: Referencing other fields37979 -Ref: #referencing-other-fields38179 -Node: How CSV rules are evaluated39077 -Ref: #how-csv-rules-are-evaluated39250 - -End Tag Table diff --git a/hledger_csv.txt b/hledger_csv.txt deleted file mode 100644 index 766402d..0000000 --- a/hledger_csv.txt +++ /dev/null @@ -1,962 +0,0 @@ - -HLEDGER_CSV(5) hledger User Manuals HLEDGER_CSV(5) - - - -NAME - How hledger reads CSV data, and the CSV rules file format. - -DESCRIPTION - hledger can read CSV files (Character Separated Value - usually comma, - semicolon, or tab) containing dated records as if they were journal - files, automatically converting each CSV record into a transaction. - - (To learn about writing CSV, see CSV output.) - - We describe each CSV file's format with a corresponding rules file. By - default this is named like the CSV file with a .rules extension added. - Eg when reading FILE.csv, hledger also looks for FILE.csv.rules in the - same directory as FILE.csv. You can specify a different rules file - with the --rules-file option. If a rules file is not found, hledger - will create a sample rules file, which you'll need to adjust. - - This file contains rules describing the CSV data (header line, fields - layout, date format etc.), and how to construct hledger journal entries - (transactions) from it. Often there will also be a list of conditional - rules for categorising transactions based on their descriptions. - Here's an overview of the CSV rules; these are described more fully - below, after the examples: - - - skip skip one or more header lines or matched - CSV records - fields name CSV fields, assign them to hledger - fields - field assignment assign a value to one hledger field, - with interpolation - separator a custom field separator - if block apply some rules to CSV records matched - by patterns - if table apply some rules to CSV records matched - by patterns, alternate syntax - end skip the remaining CSV records - date-format how to parse dates in CSV records - decimal-mark the decimal mark used in CSV amounts, if - ambiguous - newest-first disambiguate record order when there's - only one date - include inline another CSV rules file - balance-type choose which type of balance assignments - to use - - Note, for best error messages when reading CSV files, use a .csv, .tsv - or .ssv file extension or file prefix - see File Extension below. - - There's an introductory Convert CSV files tutorial on hledger.org. - -EXAMPLES - Here are some sample hledger CSV rules files. See also the full col- - lection at: - https://github.com/simonmichael/hledger/tree/master/examples/csv - - Basic - At minimum, the rules file must identify the date and amount fields, - and often it also specifies the date format and how many header lines - there are. Here's a simple CSV file and a rules file for it: - - Date, Description, Id, Amount - 12/11/2019, Foo, 123, 10.23 - - # basic.csv.rules - skip 1 - fields date, description, _, amount - date-format %d/%m/%Y - - $ hledger print -f basic.csv - 2019-11-12 Foo - expenses:unknown 10.23 - income:unknown -10.23 - - Default account names are chosen, since we didn't set them. - - Bank of Ireland - Here's a CSV with two amount fields (Debit and Credit), and a balance - field, which we can use to add balance assertions, which is not neces- - sary but provides extra error checking: - - Date,Details,Debit,Credit,Balance - 07/12/2012,LODGMENT 529898,,10.0,131.21 - 07/12/2012,PAYMENT,5,,126 - - # bankofireland-checking.csv.rules - - # skip the header line - skip - - # name the csv fields, and assign some of them as journal entry fields - fields date, description, amount-out, amount-in, balance - - # We generate balance assertions by assigning to "balance" - # above, but you may sometimes need to remove these because: - # - # - the CSV balance differs from the true balance, - # by up to 0.0000000000005 in my experience - # - # - it is sometimes calculated based on non-chronological ordering, - # eg when multiple transactions clear on the same day - - # date is in UK/Ireland format - date-format %d/%m/%Y - - # set the currency - currency EUR - - # set the base account for all txns - account1 assets:bank:boi:checking - - $ hledger -f bankofireland-checking.csv print - 2012-12-07 LODGMENT 529898 - assets:bank:boi:checking EUR10.0 = EUR131.2 - income:unknown EUR-10.0 - - 2012-12-07 PAYMENT - assets:bank:boi:checking EUR-5.0 = EUR126.0 - expenses:unknown EUR5.0 - - The balance assertions don't raise an error above, because we're read- - ing directly from CSV, but they will be checked if these entries are - imported into a journal file. - - Amazon - Here we convert amazon.com order history, and use an if block to gener- - ate a third posting if there's a fee. (In practice you'd probably get - this data from your bank instead, but it's an example.) - - "Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" - "Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" - "Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" - - # amazon-orders.csv.rules - - # skip one header line - skip 1 - - # name the csv fields, and assign the transaction's date, amount and code. - # Avoided the "status" and "amount" hledger field names to prevent confusion. - fields date, _, toorfrom, name, amzstatus, amzamount, fees, code - - # how to parse the date - date-format %b %-d, %Y - - # combine two fields to make the description - description %toorfrom %name - - # save the status as a tag - comment status:%amzstatus - - # set the base account for all transactions - account1 assets:amazon - # leave amount1 blank so it can balance the other(s). - # I'm assuming amzamount excludes the fees, don't remember - - # set a generic account2 - account2 expenses:misc - amount2 %amzamount - # and maybe refine it further: - #include categorisation.rules - - # add a third posting for fees, but only if they are non-zero. - if %fees [1-9] - account3 expenses:fees - amount3 %fees - - $ hledger -f amazon-orders.csv print - 2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed - assets:amazon - expenses:misc $20.00 - - 2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed - assets:amazon - expenses:misc $25.00 - expenses:fees $1.00 - - Paypal - Here's a real-world rules file for (customised) Paypal CSV, with some - Paypal-specific rules, and a second rules file included: - - "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" - "10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" - "10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" - "10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" - "10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" - "10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" - "10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" - "10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" - - # paypal-custom.csv.rules - - # Tips: - # Export from Activity -> Statements -> Custom -> Activity download - # Suggested transaction type: "Balance affecting" - # Paypal's default fields in 2018 were: - # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" - # This rules file assumes the following more detailed fields, configured in "Customize report fields": - # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" - - fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note - - skip 1 - - date-format %-m/%-d/%Y - - # ignore some paypal events - if - In Progress - Temporary Hold - Update to - skip - - # add more fields to the description - description %description_ %itemtitle - - # save some other fields as tags - comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ - - # convert to short currency symbols - if %currency USD - currency $ - if %currency EUR - currency E - if %currency GBP - currency P - - # generate postings - - # the first posting will be the money leaving/entering my paypal account - # (negative means leaving my account, in all amount fields) - account1 assets:online:paypal - amount1 %netamount - - # the second posting will be money sent to/received from other party - # (account2 is set below) - amount2 -%grossamount - - # if there's a fee, add a third posting for the money taken by paypal. - if %feeamount [1-9] - account3 expenses:banking:paypal - amount3 -%feeamount - comment3 business: - - # choose an account for the second posting - - # override the default account names: - # if the amount is positive, it's income (a debit) - if %grossamount ^[^-] - account2 income:unknown - # if negative, it's an expense (a credit) - if %grossamount ^- - account2 expenses:unknown - - # apply common rules for setting account2 & other tweaks - include common.rules - - # apply some overrides specific to this csv - - # Transfers from/to bank. These are usually marked Pending, - # which can be disregarded in this case. - if - Bank Account - Bank Deposit to PP Account - description %type for %referencetxnid %itemtitle - account2 assets:bank:wf:pchecking - account1 assets:online:paypal - - # Currency conversions - if Currency Conversion - account2 equity:currency conversion - - # common.rules - - if - darcs - noble benefactor - account2 revenues:foss donations:darcshub - comment2 business: - - if - Calm Radio - account2 expenses:online:apps - - if - electronic frontier foundation - Patreon - wikimedia - Advent of Code - account2 expenses:dues - - if Google - account2 expenses:online:apps - description google | music - - $ hledger -f paypal-custom.csv print - 2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed - assets:online:paypal $-6.99 = $-6.99 - expenses:online:apps $6.99 - - 2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $6.99 = $0.00 - assets:bank:wf:pchecking $-6.99 - - 2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed - assets:online:paypal $-7.00 = $-7.00 - expenses:dues $7.00 - - 2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $7.00 = $0.00 - assets:bank:wf:pchecking $-7.00 - - 2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed - assets:online:paypal $-2.00 = $-2.00 - expenses:dues $2.00 - expenses:banking:paypal ; business: - - 2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending - assets:online:paypal $2.00 = $0.00 - assets:bank:wf:pchecking $-2.00 - - 2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed - assets:online:paypal $9.41 = $9.41 - revenues:foss donations:darcshub $-10.00 ; business: - expenses:banking:paypal $0.59 ; business: - -CSV RULES - The following kinds of rule can appear in the rules file, in any order. - Blank lines and lines beginning with # or ; are ignored. - - skip - skip N - - The word "skip" followed by a number (or no number, meaning 1) tells - hledger to ignore this many non-empty lines preceding the CSV data. - (Empty/blank lines are skipped automatically.) You'll need this when- - ever your CSV data contains header lines. - - It also has a second purpose: it can be used inside if blocks to ignore - certain CSV records (described below). - - fields - fields FIELDNAME1, FIELDNAME2, ... - - A fields list (the word "fields" followed by comma-separated field - names) is the quick way to assign CSV field values to hledger fields. - It does two things: - - 1. it names the CSV fields. This is optional, but can be convenient - later for interpolating them. - - 2. when you use a standard hledger field name, it assigns the CSV value - to that part of the hledger transaction. - - Here's an example that says "use the 1st, 2nd and 4th fields as the - transaction's date, description and amount; name the last two fields - for later reference; and ignore the others": - - fields date, description, , amount, , , somefield, anotherfield - - Field names may not contain whitespace. Fields you don't care about - can be left unnamed. Currently there must be least two items (there - must be at least one comma). - - Note, always use comma in the fields list, even if your CSV uses - another separator character. - - Here are the standard hledger field/pseudo-field names. For more about - the transaction parts they refer to, see the manual for hledger's jour- - nal format. - - Transaction field names - date, date2, status, code, description, comment can be used to form the - transaction's first line. - - Posting field names - account - accountN, where N is 1 to 99, causes a posting to be generated, with - that account name. - - Most often there are two postings, so you'll want to set account1 and - account2. Typically account1 is associated with the CSV file, and is - set once with a top-level assignment, while account2 is set based on - each transaction's description, and in conditional blocks. - - If a posting's account name is left unset but its amount is set (see - below), a default account name will be chosen (like "expenses:unknown" - or "income:unknown"). - - amount - amountN sets posting N's amount. If the CSV uses separate fields for - inflows and outflows, you can use amountN-in and amountN-out instead. - By assigning to amount1, amount2, ... etc. you can generate anywhere - from 0 to 99 postings. - - There is also an older, unnumbered form of these names, suitable for - 2-posting transactions, which sets both posting 1's and (negated) post- - ing 2's amount: amount, or amount-in and amount-out. This is still - supported because it keeps pre-hledger-1.17 csv rules files working, - and because it can be more succinct, and because it converts posting - 2's amount to cost if there's a transaction price, which can be useful. - - If you have an existing rules file using the unnumbered form, you might - want to use the numbered form in certain conditional blocks, without - having to update and retest all the old rules. To facilitate this, - posting 1 ignores amount/amount-in/amount-out if any of - amount1/amount1-in/amount1-out are assigned, and posting 2 ignores them - if any of amount2/amount2-in/amount2-out are assigned, avoiding con- - flicts. - - currency - If the CSV has the currency symbol in a separate field (ie, not part of - the amount field), you can use currencyN to prepend it to posting N's - amount. Or, currency with no number affects all postings. - - balance - balanceN sets a balance assertion amount (or if the posting amount is - left empty, a balance assignment) on posting N. - - Also, for compatibility with hledger <1.17: balance with no number is - equivalent to balance1. - - You can adjust the type of assertion/assignment with the balance-type - rule (see below). - - comment - Finally, commentN sets a comment on the Nth posting. Comments can also - contain tags, as usual. - - See TIPS below for more about setting amounts and currency. - - field assignment - HLEDGERFIELDNAME FIELDVALUE - - Instead of or in addition to a fields list, you can use a "field - assignment" rule to set the value of a single hledger field, by writing - its name (any of the standard hledger field names above) followed by a - text value. The value may contain interpolated CSV fields, referenced - by their 1-based position in the CSV record (%N), or by the name they - were given in the fields list (%CSVFIELDNAME). Some examples: - - # set the amount to the 4th CSV field, with " USD" appended - amount %4 USD - - # combine three fields to make a comment, containing note: and date: tags - comment note: %somefield - %anotherfield, date: %1 - - Interpolation strips outer whitespace (so a CSV value like " 1 " - becomes 1 when interpolated) (#1051). See TIPS below for more about - referencing other fields. - - separator - You can use the separator rule to read other kinds of character-sepa- - rated data. The argument is any single separator character, or the - words tab or space (case insensitive). Eg, for comma-separated values - (CSV): - - separator , - - or for semicolon-separated values (SSV): - - separator ; - - or for tab-separated values (TSV): - - separator TAB - - If the input file has a .csv, .ssv or .tsv file extension (or a csv:, - ssv:, tsv: prefix), the appropriate separator will be inferred automat- - ically, and you won't need this rule. - - if block - if MATCHER - RULE - - if - MATCHER - MATCHER - MATCHER - RULE - RULE - - Conditional blocks ("if blocks") are a block of rules that are applied - only to CSV records which match certain patterns. They are often used - for customising account names based on transaction descriptions. - - Matching the whole record - Each MATCHER can be a record matcher, which looks like this: - - REGEX - - REGEX is a case-insensitive regular expression which tries to match - anywhere within the CSV record. It is a POSIX ERE (extended regular - expression) that also supports GNU word boundaries (\b, \B, \<, \>), - and nothing else. If you have trouble, be sure to check our - https://hledger.org/hledger.html#regular-expressions doc. - - Important note: the record that is matched is not the original record, - but a synthetic one, with any enclosing double quotes (but not enclos- - ing whitespace) removed, and always comma-separated (which means that a - field containing a comma will appear like two fields). Eg, if the - original record is 2020-01-01; "Acme, Inc."; 1,000, the REGEX will - actually see 2020-01-01,Acme, Inc., 1,000). - - Matching individual fields - Or, MATCHER can be a field matcher, like this: - - %CSVFIELD REGEX - - which matches just the content of a particular CSV field. CSVFIELD is - a percent sign followed by the field's name or column number, like - %date or %1. - - Combining matchers - A single matcher can be written on the same line as the "if"; or multi- - ple matchers can be written on the following lines, non-indented. Mul- - tiple matchers are OR'd (any one of them can match), unless one begins - with an & symbol, in which case it is AND'ed with the previous matcher. - - if - MATCHER - & MATCHER - RULE - - Rules applied on successful match - After the patterns there should be one or more rules to apply, all - indented by at least one space. Three kinds of rule are allowed in - conditional blocks: - - o field assignments (to set a hledger field) - - o skip (to skip the matched CSV record) - - o end (to skip all remaining CSV records). - - Examples: - - # if the CSV record contains "groceries", set account2 to "expenses:groceries" - if groceries - account2 expenses:groceries - - # if the CSV record contains any of these patterns, set account2 and comment as shown - if - monthly service fee - atm transaction fee - banking thru software - account2 expenses:business:banking - comment XXX deductible ? check it - - if table - if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn - MATCHER1,VALUE11,VALUE12,...,VALUE1n - MATCHER2,VALUE21,VALUE22,...,VALUE2n - MATCHER3,VALUE31,VALUE32,...,VALUE3n - <empty line> - - Conditional tables ("if tables") are a different syntax to specify - field assignments that will be applied only to CSV records which match - certain patterns. - - MATCHER could be either field or record matcher, as described above. - When MATCHER matches, values from that row would be assigned to the CSV - fields named on the if line, in the same order. - - Therefore if table is exactly equivalent to a sequence of of if blocks: - - if MATCHER1 - CSVFIELDNAME1 VALUE11 - CSVFIELDNAME2 VALUE12 - ... - CSVFIELDNAMEn VALUE1n - - if MATCHER2 - CSVFIELDNAME1 VALUE21 - CSVFIELDNAME2 VALUE22 - ... - CSVFIELDNAMEn VALUE2n - - if MATCHER3 - CSVFIELDNAME1 VALUE31 - CSVFIELDNAME2 VALUE32 - ... - CSVFIELDNAMEn VALUE3n - - Each line starting with MATCHER should contain enough (possibly empty) - values for all the listed fields. - - Rules would be checked and applied in the order they are listed in the - table and, like with if blocks, later rules (in the same or another ta- - ble) or if blocks could override the effect of any rule. - - Instead of ',' you can use a variety of other non-alphanumeric charac- - ters as a separator. First character after if is taken to be the sepa- - rator for the rest of the table. It is the responsibility of the user - to ensure that separator does not occur inside MATCHERs and values - - there is no way to escape separator. - - Example: - - if,account2,comment - atm transaction fee,expenses:business:banking,deductible? check it - %description groceries,expenses:groceries, - 2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out - - end - This rule can be used inside if blocks (only), to make hledger stop - reading this CSV file and move on to the next input file, or to command - execution. Eg: - - # ignore everything following the first empty record - if ,,,, - end - - date-format - date-format DATEFMT - - This is a helper for the date (and date2) fields. If your CSV dates - are not formatted like YYYY-MM-DD, YYYY/MM/DD or YYYY.MM.DD, you'll - need to add a date-format rule describing them with a strptime date - parsing pattern, which must parse the CSV date value completely. Some - examples: - - # MM/DD/YY - date-format %m/%d/%y - - # D/M/YYYY - # The - makes leading zeros optional. - date-format %-d/%-m/%Y - - # YYYY-Mmm-DD - date-format %Y-%h-%d - - # M/D/YYYY HH:MM AM some other junk - # Note the time and junk must be fully parsed, though only the date is used. - date-format %-m/%-d/%Y %l:%M %p some other junk - - For the supported strptime syntax, see: - https://hackage.haskell.org/package/time/docs/Data-Time-For- - mat.html#v:formatTime - - decimal-mark - decimal-mark . - - or: - - decimal-mark , - - hledger automatically accepts either period or comma as a decimal mark - when parsing numbers (cf Amounts). However if any numbers in the CSV - contain digit group marks, such as thousand-separating commas, you - should declare the decimal mark explicitly with this rule, to avoid - misparsed numbers. - - newest-first - hledger always sorts the generated transactions by date. Transactions - on the same date should appear in the same order as their CSV records, - as hledger can usually auto-detect whether the CSV's normal order is - oldest first or newest first. But if all of the following are true: - - o the CSV might sometimes contain just one day of data (all records - having the same date) - - o the CSV records are normally in reverse chronological order (newest - at the top) - - o and you care about preserving the order of same-day transactions - - then, you should add the newest-first rule as a hint. Eg: - - # tell hledger explicitly that the CSV is normally newest first - newest-first - - include - include RULESFILE - - This includes the contents of another CSV rules file at this point. - RULESFILE is an absolute file path or a path relative to the current - file's directory. This can be useful for sharing common rules between - several rules files, eg: - - # someaccount.csv.rules - - ## someaccount-specific rules - fields date,description,amount - account1 assets:someaccount - account2 expenses:misc - - ## common rules - include categorisation.rules - - balance-type - Balance assertions generated by assigning to balanceN are of the simple - = type by default, which is a single-commodity, subaccount-excluding - assertion. You may find the subaccount-including variants more useful, - eg if you have created some virtual subaccounts of checking to help - with budgeting. You can select a different type of assertion with the - balance-type rule: - - # balance assertions will consider all commodities and all subaccounts - balance-type ==* - - Here are the balance assertion types for quick reference: - - = single commodity, exclude subaccounts - =* single commodity, include subaccounts - == multi commodity, exclude subaccounts - ==* multi commodity, include subaccounts - -TIPS - Rapid feedback - It's a good idea to get rapid feedback while creating/troubleshooting - CSV rules. Here's a good way, using entr from http://eradman.com/entr- - project : - - $ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' - - A desc: query (eg) is used to select just one, or a few, transactions - of interest. "bash -c" is used to run multiple commands, so we can - echo a separator each time the command re-runs, making it easier to - read the output. - - Valid CSV - hledger accepts CSV conforming to RFC 4180. When CSV values are - enclosed in quotes, note: - - o they must be double quotes (not single quotes) - - o spaces outside the quotes are not allowed - - File Extension - To help hledger identify the format and show the right error messages, - CSV/SSV/TSV files should normally be named with a .csv, .ssv or .tsv - filename extension. Or, the file path should be prefixed with csv:, - ssv: or tsv:. Eg: - - $ hledger -f foo.ssv print - - or: - - $ cat foo | hledger -f ssv:- foo - - You can override the file extension with a separator rule if needed. - See also: Input files in the hledger manual. - - Reading multiple CSV files - If you use multiple -f options to read multiple CSV files at once, - hledger will look for a correspondingly-named rules file for each CSV - file. But if you use the --rules-file option, that rules file will be - used for all the CSV files. - - Valid transactions - After reading a CSV file, hledger post-processes and validates the gen- - erated journal entries as it would for a journal file - balancing them, - applying balance assignments, and canonicalising amount styles. Any - errors at this stage will be reported in the usual way, displaying the - problem entry. - - There is one exception: balance assertions, if you have generated them, - will not be checked, since normally these will work only when the CSV - data is part of the main journal. If you do need to check balance - assertions generated from CSV right away, pipe into another hledger: - - $ hledger -f file.csv print | hledger -f- print - - Deduplicating, importing - When you download a CSV file periodically, eg to get your latest bank - transactions, the new file may overlap with the old one, containing - some of the same records. - - The import command will (a) detect the new transactions, and (b) append - just those transactions to your main journal. It is idempotent, so you - don't have to remember how many times you ran it or with which version - of the CSV. (It keeps state in a hidden .latest.FILE.csv file.) This - is the easiest way to import CSV data. Eg: - - # download the latest CSV files, then run this command. - # Note, no -f flags needed here. - $ hledger import *.csv [--dry] - - This method works for most CSV files. (Where records have a stable - chronological order, and new records appear only at the new end.) - - A number of other tools and workflows, hledger-specific and otherwise, - exist for converting, deduplicating, classifying and managing CSV data. - See: - - o https://hledger.org -> sidebar -> real world setups - - o https://plaintextaccounting.org -> data import/conversion - - Setting amounts - A posting amount can be set in one of these ways: - - o by assigning (with a fields list or field assignment) to amountN - (posting N's amount) or amount (posting 1's amount) - - o by assigning to amountN-in and amountN-out (or amount-in and amount- - out). For each CSV record, whichever of these has a non-zero value - will be used, with appropriate sign. If both contain a non-zero - value, this may not work. - - o by assigning to balanceN (or balance) instead of the above, setting - the amount indirectly via a balance assignment. If you do this the - default account name may be wrong, so you should set that explicitly. - - There is some special handling for an amount's sign: - - o If an amount value is parenthesised, it will be de-parenthesised and - sign-flipped. - - o If an amount value begins with a double minus sign, those cancel out - and are removed. - - o If an amount value begins with a plus sign, that will be removed - - Setting currency/commodity - If the currency/commodity symbol is included in the CSV's amount - field(s): - - 2020-01-01,foo,$123.00 - - you don't have to do anything special for the commodity symbol, it will - be assigned as part of the amount. Eg: - - fields date,description,amount - - 2020-01-01 foo - expenses:unknown $123.00 - income:unknown $-123.00 - - If the currency is provided as a separate CSV field: - - 2020-01-01,foo,USD,123.00 - - You can assign that to the currency pseudo-field, which has the special - effect of prepending itself to every amount in the transaction (on the - left, with no separating space): - - fields date,description,currency,amount - - 2020-01-01 foo - expenses:unknown USD123.00 - income:unknown USD-123.00 - - Or, you can use a field assignment to construct the amount yourself, - with more control. Eg to put the symbol on the right, and separated by - a space: - - fields date,description,cur,amt - amount %amt %cur - - 2020-01-01 foo - expenses:unknown 123.00 USD - income:unknown -123.00 USD - - Note we used a temporary field name (cur) that is not currency - that - would trigger the prepending effect, which we don't want here. - - Referencing other fields - In field assignments, you can interpolate only CSV fields, not hledger - fields. In the example below, there's both a CSV field and a hledger - field named amount1, but %amount1 always means the CSV field, not the - hledger field: - - # Name the third CSV field "amount1" - fields date,description,amount1 - - # Set hledger's amount1 to the CSV amount1 field followed by USD - amount1 %amount1 USD - - # Set comment to the CSV amount1 (not the amount1 assigned above) - comment %amount1 - - Here, since there's no CSV amount1 field, %amount1 will produce a lit- - eral "amount1": - - fields date,description,csvamount - amount1 %csvamount USD - # Can't interpolate amount1 here - comment %amount1 - - When there are multiple field assignments to the same hledger field, - only the last one takes effect. Here, comment's value will be be B, or - C if "something" is matched, but never A: - - comment A - comment B - if something - comment C - - How CSV rules are evaluated - Here's how to think of CSV rules being evaluated (if you really need - to). First, - - o include - all includes are inlined, from top to bottom, depth first. - (At each include point the file is inlined and scanned for further - includes, recursively, before proceeding.) - - Then "global" rules are evaluated, top to bottom. If a rule is - repeated, the last one wins: - - o skip (at top level) - - o date-format - - o newest-first - - o fields - names the CSV fields, optionally sets up initial assignments - to hledger fields - - Then for each CSV record in turn: - - o test all if blocks. If any of them contain a end rule, skip all - remaining CSV records. Otherwise if any of them contain a skip rule, - skip that many CSV records. If there are multiple matched skip - rules, the first one wins. - - o collect all field assignments at top level and in matched if blocks. - When there are multiple assignments for a field, keep only the last - one. - - o compute a value for each hledger field - either the one that was - assigned to it (and interpolate the %CSVFIELDNAME references), or a - default - - o generate a synthetic hledger transaction from these values. - - This is all part of the CSV reader, one of several readers hledger can - use to parse input files. When all files have been read successfully, - the transactions are passed as input to whichever hledger command the - user specified. - - - -REPORTING BUGS - Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel - or hledger mail list) - - -AUTHORS - Simon Michael <simon@joyful.com> and contributors - - -COPYRIGHT - Copyright (C) 2007-2020 Simon Michael. - Released under GNU GPL v3 or later. - - -SEE ALSO - hledger(1), hledger-ui(1), hledger-web(1), ledger(1) - - hledger_journal(5), hledger_csv(5), hledger_timeclock(5), hledger_time- - dot(5) - - - -hledger-lib-1.20.4 December 2020 HLEDGER_CSV(5) diff --git a/hledger_journal.5 b/hledger_journal.5 deleted file mode 100644 index c1b6c53..0000000 --- a/hledger_journal.5 +++ /dev/null @@ -1,2153 +0,0 @@ -.\"t - -.TH "HLEDGER_JOURNAL" "5" "December 2020" "hledger-lib-1.20.4 " "hledger User Manuals" - - - -.SH NAME -.PP -hledger\[aq]s default file format, representing a General Journal. -.SH DESCRIPTION -.PP -hledger\[aq]s usual data source is a plain text file containing journal -entries in hledger journal format. -This file represents a standard accounting general journal. -I use file names ending in \f[C].journal\f[R], but that\[aq]s not -required. -The journal file contains a number of transaction entries, each -describing a transfer of money (or any commodity) between two or more -named accounts, in a simple format readable by both hledger and humans. -.PP -hledger\[aq]s journal format is a compatible subset, mostly, of -ledger\[aq]s journal format, so hledger can work with compatible ledger -journal files as well. -It\[aq]s safe, and encouraged, to run both hledger and ledger on the -same journal file, eg to validate the results you\[aq]re getting. -.PP -You can use hledger without learning any more about this file; just use -the add or web or import commands to create and update it. -.PP -Many users, though, edit the journal file with a text editor, and track -changes with a version control system such as git. -Editor addons such as ledger-mode or hledger-mode for Emacs, vim-ledger -for Vim, and hledger-vscode for Visual Studio Code, make this easier, -adding colour, formatting, tab completion, and useful commands. -See Editor configuration at hledger.org for the full list. -.PP -Here\[aq]s a description of each part of the file format (and -hledger\[aq]s data model). -These are mostly in the order you\[aq]ll use them, but in some cases -related concepts have been grouped together for easy reference, or -linked before they are introduced, so feel free to skip over anything -that looks unnecessary right now. -.SH TRANSACTIONS -.PP -Transactions are the main unit of information in a journal file. -They represent events, typically a movement of some quantity of -commodities between two or more named accounts. -.PP -Each transaction is recorded as a journal entry, beginning with a simple -date in column 0. -This can be followed by any of the following optional fields, separated -by spaces: -.IP \[bu] 2 -a status character (empty, \f[C]!\f[R], or \f[C]*\f[R]) -.IP \[bu] 2 -a code (any short number or text, enclosed in parentheses) -.IP \[bu] 2 -a description (any remaining text until end of line or a semicolon) -.IP \[bu] 2 -a comment (any remaining text following a semicolon until end of line, -and any following indented lines beginning with a semicolon) -.IP \[bu] 2 -0 or more indented \f[I]posting\f[R] lines, describing what was -transferred and the accounts involved (indented comment lines are also -allowed, but not blank lines or non-indented lines). -.PP -Here\[aq]s a simple journal file containing one transaction: -.IP -.nf -\f[C] -2008/01/01 income - assets:bank:checking $1 - income:salary $-1 -\f[R] -.fi -.SH DATES -.SS Simple dates -.PP -Dates in the journal file use \f[I]simple dates\f[R] format: -\f[C]YYYY-MM-DD\f[R] or \f[C]YYYY/MM/DD\f[R] or \f[C]YYYY.MM.DD\f[R], -with leading zeros optional. -The year may be omitted, in which case it will be inferred from the -context: the current transaction, the default year set with a default -year directive, or the current date when the command is run. -Some examples: \f[C]2010-01-31\f[R], \f[C]2010/01/31\f[R], -\f[C]2010.1.31\f[R], \f[C]1/31\f[R]. -.PP -(The UI also accepts simple dates, as well as the more flexible smart -dates documented in the hledger manual.) -.SS Secondary dates -.PP -Real-life transactions sometimes involve more than one date - eg the -date you write a cheque, and the date it clears in your bank. -When you want to model this, for more accurate daily balances, you can -specify individual posting dates. -.PP -Or, you can use the older \f[I]secondary date\f[R] feature (Ledger calls -it auxiliary date or effective date). -Note: we support this for compatibility, but I usually recommend -avoiding this feature; posting dates are almost always clearer and -simpler. -.PP -A secondary date is written after the primary date, following an equals -sign. -If the year is omitted, the primary date\[aq]s year is assumed. -When running reports, the primary (left) date is used by default, but -with the \f[C]--date2\f[R] flag (or \f[C]--aux-date\f[R] or -\f[C]--effective\f[R]), the secondary (right) date will be used instead. -.PP -The meaning of secondary dates is up to you, but it\[aq]s best to follow -a consistent rule. -Eg \[dq]primary = the bank\[aq]s clearing date, secondary = date the -transaction was initiated, if different\[dq], as shown here: -.IP -.nf -\f[C] -2010/2/23=2/19 movie ticket - expenses:cinema $10 - assets:checking -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger register checking -2010-02-23 movie ticket assets:checking $-10 $-10 -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger register checking --date2 -2010-02-19 movie ticket assets:checking $-10 $-10 -\f[R] -.fi -.SS Posting dates -.PP -You can give individual postings a different date from their parent -transaction, by adding a posting comment containing a tag (see below) -like \f[C]date:DATE\f[R]. -This is probably the best way to control posting dates precisely. -Eg in this example the expense should appear in May reports, and the -deduction from checking should be reported on 6/1 for easy bank -reconciliation: -.IP -.nf -\f[C] -2015/5/30 - expenses:food $10 ; food purchased on saturday 5/30 - assets:checking ; bank cleared it on monday, date:6/1 -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger -f t.j register food -2015-05-30 expenses:food $10 $10 -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger -f t.j register checking -2015-06-01 assets:checking $-10 $-10 -\f[R] -.fi -.PP -DATE should be a simple date; if the year is not specified it will use -the year of the transaction\[aq]s date. -You can set the secondary date similarly, with \f[C]date2:DATE2\f[R]. -The \f[C]date:\f[R] or \f[C]date2:\f[R] tags must have a valid simple -date value if they are present, eg a \f[C]date:\f[R] tag with no value -is not allowed. -.PP -Ledger\[aq]s earlier, more compact bracketed date syntax is also -supported: \f[C][DATE]\f[R], \f[C][DATE=DATE2]\f[R] or -\f[C][=DATE2]\f[R]. -hledger will attempt to parse any square-bracketed sequence of the -\f[C]0123456789/-.=\f[R] characters in this way. -With this syntax, DATE infers its year from the transaction and DATE2 -infers its year from DATE. -.SH STATUS -.PP -Transactions, or individual postings within a transaction, can have a -status mark, which is a single character before the transaction -description or posting account name, separated from it by a space, -indicating one of three statuses: -.PP -.TS -tab(@); -l l. -T{ -mark \ -T}@T{ -status -T} -_ -T{ -\ -T}@T{ -unmarked -T} -T{ -\f[C]!\f[R] -T}@T{ -pending -T} -T{ -\f[C]*\f[R] -T}@T{ -cleared -T} -.TE -.PP -When reporting, you can filter by status with the -\f[C]-U/--unmarked\f[R], \f[C]-P/--pending\f[R], and -\f[C]-C/--cleared\f[R] flags; or the \f[C]status:\f[R], -\f[C]status:!\f[R], and \f[C]status:*\f[R] queries; or the U, P, C keys -in hledger-ui. -.PP -Note, in Ledger and in older versions of hledger, the \[dq]unmarked\[dq] -state is called \[dq]uncleared\[dq]. -As of hledger 1.3 we have renamed it to unmarked for clarity. -.PP -To replicate Ledger and old hledger\[aq]s behaviour of also matching -pending, combine -U and -P. -.PP -Status marks are optional, but can be helpful eg for reconciling with -real-world accounts. -Some editor modes provide highlighting and shortcuts for working with -status. -Eg in Emacs ledger-mode, you can toggle transaction status with C-c C-e, -or posting status with C-c C-c. -.PP -What \[dq]uncleared\[dq], \[dq]pending\[dq], and \[dq]cleared\[dq] -actually mean is up to you. -Here\[aq]s one suggestion: -.PP -.TS -tab(@); -lw(9.7n) lw(60.3n). -T{ -status -T}@T{ -meaning -T} -_ -T{ -uncleared -T}@T{ -recorded but not yet reconciled; needs review -T} -T{ -pending -T}@T{ -tentatively reconciled (if needed, eg during a big reconciliation) -T} -T{ -cleared -T}@T{ -complete, reconciled as far as possible, and considered correct -T} -.TE -.PP -With this scheme, you would use \f[C]-PC\f[R] to see the current balance -at your bank, \f[C]-U\f[R] to see things which will probably hit your -bank soon (like uncashed checks), and no flags to see the most -up-to-date state of your finances. -.SH DESCRIPTION -.PP -A transaction\[aq]s description is the rest of the line following the -date and status mark (or until a comment begins). -Sometimes called the \[dq]narration\[dq] in traditional bookkeeping, it -can be used for whatever you wish, or left blank. -Transaction descriptions can be queried, unlike comments. -.SS Payee and note -.PP -You can optionally include a \f[C]|\f[R] (pipe) character in -descriptions to subdivide the description into separate fields for -payee/payer name on the left (up to the first \f[C]|\f[R]) and an -additional note field on the right (after the first \f[C]|\f[R]). -This may be worthwhile if you need to do more precise querying and -pivoting by payee or by note. -.SH COMMENTS -.PP -Lines in the journal beginning with a semicolon (\f[C];\f[R]) or hash -(\f[C]#\f[R]) or star (\f[C]*\f[R]) are comments, and will be ignored. -(Star comments cause org-mode nodes to be ignored, allowing emacs users -to fold and navigate their journals with org-mode or orgstruct-mode.) -.PP -You can attach comments to a transaction by writing them after the -description and/or indented on the following lines (before the -postings). -Similarly, you can attach comments to an individual posting by writing -them after the amount and/or indented on the following lines. -Transaction and posting comments must begin with a semicolon -(\f[C];\f[R]). -.PP -Some examples: -.IP -.nf -\f[C] -# a file comment -; another file comment -* also a file comment, useful in org/orgstruct mode - -comment -A multiline file comment, which continues -until a line containing just \[dq]end comment\[dq] -(or end of file). -end comment - -2012/5/14 something ; a transaction comment - ; the transaction comment, continued - posting1 1 ; a comment for posting 1 - posting2 - ; a comment for posting 2 - ; another comment line for posting 2 -; a file comment (because not indented) -\f[R] -.fi -.PP -You can also comment larger regions of a file using \f[C]comment\f[R] -and \f[C]end comment\f[R] directives. -.SH TAGS -.PP -Tags are a way to add extra labels or labelled data to postings and -transactions, which you can then search or pivot on. -.PP -A simple tag is a word (which may contain hyphens) followed by a full -colon, written inside a transaction or posting comment line: -.IP -.nf -\f[C] -2017/1/16 bought groceries ; sometag: -\f[R] -.fi -.PP -Tags can have a value, which is the text after the colon, up to the next -comma or end of line, with leading/trailing whitespace removed: -.IP -.nf -\f[C] - expenses:food $10 ; a-posting-tag: the tag value -\f[R] -.fi -.PP -Note this means hledger\[aq]s tag values can not contain commas or -newlines. -Ending at commas means you can write multiple short tags on one line, -comma separated: -.IP -.nf -\f[C] - assets:checking ; a comment containing tag1:, tag2: some value ... -\f[R] -.fi -.PP -Here, -.IP \[bu] 2 -\[dq]\f[C]a comment containing\f[R]\[dq] is just comment text, not a tag -.IP \[bu] 2 -\[dq]\f[C]tag1\f[R]\[dq] is a tag with no value -.IP \[bu] 2 -\[dq]\f[C]tag2\f[R]\[dq] is another tag, whose value is -\[dq]\f[C]some value ...\f[R]\[dq] -.PP -Tags in a transaction comment affect the transaction and all of its -postings, while tags in a posting comment affect only that posting. -For example, the following transaction has three tags (\f[C]A\f[R], -\f[C]TAG2\f[R], \f[C]third-tag\f[R]) and the posting has four (those -plus \f[C]posting-tag\f[R]): -.IP -.nf -\f[C] -1/1 a transaction ; A:, TAG2: - ; third-tag: a third transaction tag, <- with a value - (a) $1 ; posting-tag: -\f[R] -.fi -.PP -Tags are like Ledger\[aq]s metadata feature, except hledger\[aq]s tag -values are simple strings. -.SH POSTINGS -.PP -A posting is an addition of some amount to, or removal of some amount -from, an account. -Each posting line begins with at least one space or tab (2 or 4 spaces -is common), followed by: -.IP \[bu] 2 -(optional) a status character (empty, \f[C]!\f[R], or \f[C]*\f[R]), -followed by a space -.IP \[bu] 2 -(required) an account name (any text, optionally containing \f[B]single -spaces\f[R], until end of line or a double space) -.IP \[bu] 2 -(optional) \f[B]two or more spaces\f[R] or tabs followed by an amount. -.PP -Positive amounts are being added to the account, negative amounts are -being removed. -.PP -The amounts within a transaction must always sum up to zero. -As a convenience, one amount may be left blank; it will be inferred so -as to balance the transaction. -.PP -Be sure to note the unusual two-space delimiter between account name and -amount. -This makes it easy to write account names containing spaces. -But if you accidentally leave only one space (or tab) before the amount, -the amount will be considered part of the account name. -.SS Virtual postings -.PP -A posting with a parenthesised account name is called a \f[I]virtual -posting\f[R] or \f[I]unbalanced posting\f[R], which means it is exempt -from the usual rule that a transaction\[aq]s postings must balance add -up to zero. -.PP -This is not part of double entry accounting, so you might choose to -avoid this feature. -Or you can use it sparingly for certain special cases where it can be -convenient. -Eg, you could set opening balances without using a balancing equity -account: -.IP -.nf -\f[C] -1/1 opening balances - (assets:checking) $1000 - (assets:savings) $2000 -\f[R] -.fi -.PP -A posting with a bracketed account name is called a \f[I]balanced -virtual posting\f[R]. -The balanced virtual postings in a transaction must add up to zero -(separately from other postings). -Eg: -.IP -.nf -\f[C] -1/1 buy food with cash, update budget envelope subaccounts, & something else - assets:cash $-10 ; <- these balance - expenses:food $7 ; <- - expenses:food $3 ; <- - [assets:checking:budget:food] $-10 ; <- and these balance - [assets:checking:available] $10 ; <- - (something:else) $5 ; <- not required to balance -\f[R] -.fi -.PP -Ordinary non-parenthesised, non-bracketed postings are called \f[I]real -postings\f[R]. -You can exclude virtual postings from reports with the -\f[C]-R/--real\f[R] flag or \f[C]real:1\f[R] query. -.SH ACCOUNT NAMES -.PP -Account names typically have several parts separated by a full colon, -from which hledger derives a hierarchical chart of accounts. -They can be anything you like, but in finance there are traditionally -five top-level accounts: \f[C]assets\f[R], \f[C]liabilities\f[R], -\f[C]income\f[R], \f[C]expenses\f[R], and \f[C]equity\f[R]. -.PP -Account names may contain single spaces, eg: -\f[C]assets:accounts receivable\f[R]. -Because of this, they must always be followed by \f[B]two or more -spaces\f[R] (or newline). -.PP -Account names can be aliased. -.SH AMOUNTS -.PP -After the account name, there is usually an amount. -(Important: between account name and amount, there must be \f[B]two or -more spaces\f[R].) -.PP -hledger\[aq]s amount format is flexible, supporting several -international formats. -Here are some examples. -Amounts have a number (the \[dq]quantity\[dq]): -.IP -.nf -\f[C] -1 -\f[R] -.fi -.PP -\&..and usually a currency or commodity name (the \[dq]commodity\[dq]). -This is a symbol, word, or phrase, to the left or right of the quantity, -with or without a separating space: -.IP -.nf -\f[C] -$1 -4000 AAPL -\f[R] -.fi -.PP -If the commodity name contains spaces, numbers, or punctuation, it must -be enclosed in double quotes: -.IP -.nf -\f[C] -3 \[dq]no. 42 green apples\[dq] -\f[R] -.fi -.PP -Amounts can be preceded by a minus sign (or a plus sign, though plus is -the default), The sign can be written before or after a left-side -commodity symbol: -.IP -.nf -\f[C] --$1 -$-1 -\f[R] -.fi -.PP -One or more spaces between the sign and the number are acceptable when -parsing (but they won\[aq]t be displayed in output): -.IP -.nf -\f[C] -+ $1 -$- 1 -\f[R] -.fi -.PP -Scientific E notation is allowed: -.IP -.nf -\f[C] -1E-6 -EUR 1E3 -\f[R] -.fi -.PP -A decimal mark can be written as a period or a comma: -.IP -.nf -\f[C] -1.23 -1,23456780000009 -\f[R] -.fi -.SS Digit group marks -.PP -In the integer part of the quantity (left of the decimal mark), groups -of digits can optionally be separated by a \[dq]digit group mark\[dq] - -a space, comma, or period (different from the decimal mark): -.IP -.nf -\f[C] - $1,000,000.00 - EUR 2.000.000,00 -INR 9,99,99,999.00 - 1 000 000.9455 -\f[R] -.fi -.PP -Note, a number containing a single group mark and no decimal mark is -ambiguous. -Are these group marks or decimal marks ? -.IP -.nf -\f[C] -1,000 -1.000 -\f[R] -.fi -.PP -hledger will treat them both as decimal marks by default (cf #793). -If you use digit group marks, to prevent confusion and undetected typos -we recommend you write commodity directives at the top of the file to -explicitly declare the decimal mark (and optionally a digit group mark). -Note, these formats (\[dq]amount styles\[dq]) are specific to each -commodity, so if your data uses multiple formats, hledger can handle it: -.IP -.nf -\f[C] -commodity $1,000.00 -commodity EUR 1.000,00 -commodity INR 9,99,99,999.00 -commodity 1 000 000.9455 -\f[R] -.fi -.PP -.SS Commodity display style -.PP -For each commodity, hledger chooses a consistent style to use when -displaying amounts. -(Except price amounts, which are always displayed as written). -The display style is chosen as follows: -.IP \[bu] 2 -If there is a commodity directive (or default commodity directive) for -the commodity, its style is used (see examples above). -.IP \[bu] 2 -Otherwise the style is inferred from the amounts in that commodity seen -in the journal. -.IP \[bu] 2 -Or if there are no such amounts in the journal, a default style is used -(like \f[C]$1000.00\f[R]). -.PP -A style is inferred from the journal amounts in a commodity as follows: -.IP \[bu] 2 -Use the general style (decimal mark, symbol placement) of the first -amount -.IP \[bu] 2 -Use the first-seen digit group style (digit group mark, digit group -sizes), if any -.IP \[bu] 2 -Use the maximum number of decimal places of all. -.PP -Transaction price amounts don\[aq]t affect the commodity display style -directly, but occasionally they can do so indirectly (eg when a -posting\[aq]s amount is inferred using a transaction price). -If you find this causing problems, use a commodity directive to fix the -display style. -.PP -In summary, each commodity\[aq]s amounts will be normalised to -.IP \[bu] 2 -the style declared by a \f[C]commodity\f[R] directive -.IP \[bu] 2 -or, the style of the first posting amount in the journal, with the -first-seen digit group style and the maximum-seen number of decimal -places. -.PP -If reports are showing amounts in a way you don\[aq]t like (eg, with too -many decimal places), use a commodity directive to set your preferred -style. -.SS Rounding -.PP -Amounts are stored internally as decimal numbers with up to 255 decimal -places, and displayed with the number of decimal places specified by the -commodity display style. -Note, hledger uses banker\[aq]s rounding: it rounds to the nearest even -number, eg 0.5 displayed with zero decimal places is \[dq]0\[dq]). -(Guaranteed since hledger 1.17.1; in older versions this could vary if -hledger was built with Decimal < 0.5.1.) -.SH TRANSACTION PRICES -.PP -Within a transaction, you can note an amount\[aq]s price in another -commodity. -This can be used to document the cost (in a purchase) or selling price -(in a sale). -For example, transaction prices are useful to record purchases of a -foreign currency. -Note transaction prices are fixed at the time of the transaction, and do -not change over time. -See also market prices, which represent prevailing exchange rates on a -certain date. -.PP -There are several ways to record a transaction price: -.IP "1." 3 -Write the price per unit, as \f[C]\[at] UNITPRICE\f[R] after the amount: -.RS 4 -.IP -.nf -\f[C] -2009/1/1 - assets:euros \[Eu]100 \[at] $1.35 ; one hundred euros purchased at $1.35 each - assets:dollars ; balancing amount is -$135.00 -\f[R] -.fi -.RE -.IP "2." 3 -Write the total price, as \f[C]\[at]\[at] TOTALPRICE\f[R] after the -amount: -.RS 4 -.IP -.nf -\f[C] -2009/1/1 - assets:euros \[Eu]100 \[at]\[at] $135 ; one hundred euros purchased at $135 for the lot - assets:dollars -\f[R] -.fi -.RE -.IP "3." 3 -Specify amounts for all postings, using exactly two commodities, and let -hledger infer the price that balances the transaction: -.RS 4 -.IP -.nf -\f[C] -2009/1/1 - assets:euros \[Eu]100 ; one hundred euros purchased - assets:dollars $-135 ; for $135 -\f[R] -.fi -.RE -.IP "4." 3 -Like 1, but the \f[C]\[at]\f[R] is parenthesised, i.e. -\f[C](\[at])\f[R]; this is for compatibility with Ledger journals -(Virtual posting costs), and is equivalent to 1 in hledger. -.IP "5." 3 -Like 2, but as in 4 the \f[C]\[at]\[at]\f[R] is parenthesised, i.e. -\f[C](\[at]\[at])\f[R]; in hledger, this is equivalent to 2. -.PP -Use the \f[C]-B/--cost\f[R] flag to convert amounts to their transaction -price\[aq]s commodity, if any. -(mnemonic: \[dq]B\[dq] is from \[dq]cost Basis\[dq], as in Ledger). -Eg here is how -B affects the balance report for the example above: -.IP -.nf -\f[C] -$ hledger bal -N --flat - $-135 assets:dollars - \[Eu]100 assets:euros -$ hledger bal -N --flat -B - $-135 assets:dollars - $135 assets:euros # <- the euros\[aq] cost -\f[R] -.fi -.PP -Note -B is sensitive to the order of postings when a transaction price -is inferred: the inferred price will be in the commodity of the last -amount. -So if example 3\[aq]s postings are reversed, while the transaction is -equivalent, -B shows something different: -.IP -.nf -\f[C] -2009/1/1 - assets:dollars $-135 ; 135 dollars sold - assets:euros \[Eu]100 ; for 100 euros -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger bal -N --flat -B - \[Eu]-100 assets:dollars # <- the dollars\[aq] selling price - \[Eu]100 assets:euros -\f[R] -.fi -.SH LOT PRICES, LOT DATES -.PP -Ledger allows another kind of price, lot price (four variants: -\f[C]{UNITPRICE}\f[R], \f[C]{{TOTALPRICE}}\f[R], -\f[C]{=FIXEDUNITPRICE}\f[R], \f[C]{{=FIXEDTOTALPRICE}}\f[R]), and/or a -lot date (\f[C][DATE]\f[R]) to be specified. -These are normally used to select a lot when selling investments. -hledger will parse these, for compatibility with Ledger journals, but -currently ignores them. -A transaction price, lot price and/or lot date may appear in any order, -after the posting amount and before the balance assertion if any. -.SH BALANCE ASSERTIONS -.PP -hledger supports Ledger-style balance assertions in journal files. -These look like, for example, \f[C]= EXPECTEDBALANCE\f[R] following a -posting\[aq]s amount. -Eg here we assert the expected dollar balance in accounts a and b after -each posting: -.IP -.nf -\f[C] -2013/1/1 - a $1 =$1 - b =$-1 - -2013/1/2 - a $1 =$2 - b $-1 =$-2 -\f[R] -.fi -.PP -After reading a journal file, hledger will check all balance assertions -and report an error if any of them fail. -Balance assertions can protect you from, eg, inadvertently disrupting -reconciled balances while cleaning up old entries. -You can disable them temporarily with the -\f[C]-I/--ignore-assertions\f[R] flag, which can be useful for -troubleshooting or for reading Ledger files. -(Note: this flag currently does not disable balance assignments, below). -.SS Assertions and ordering -.PP -hledger sorts an account\[aq]s postings and assertions first by date and -then (for postings on the same day) by parse order. -Note this is different from Ledger, which sorts assertions only by parse -order. -(Also, Ledger assertions do not see the accumulated effect of repeated -postings to the same account within a transaction.) -.PP -So, hledger balance assertions keep working if you reorder -differently-dated transactions within the journal. -But if you reorder same-dated transactions or postings, assertions might -break and require updating. -This order dependence does bring an advantage: precise control over the -order of postings and assertions within a day, so you can assert -intra-day balances. -.SS Assertions and included files -.PP -With included files, things are a little more complicated. -Including preserves the ordering of postings and assertions. -If you have multiple postings to an account on the same day, split -across different files, and you also want to assert the account\[aq]s -balance on the same day, you\[aq]ll have to put the assertion in the -right file. -.SS Assertions and multiple -f options -.PP -Balance assertions don\[aq]t work well across files specified with -multiple -f options. -Use include or concatenate the files instead. -.SS Assertions and commodities -.PP -The asserted balance must be a simple single-commodity amount, and in -fact the assertion checks only this commodity\[aq]s balance within the -(possibly multi-commodity) account balance. -This is how assertions work in Ledger also. -We could call this a \[dq]partial\[dq] balance assertion. -.PP -To assert the balance of more than one commodity in an account, you can -write multiple postings, each asserting one commodity\[aq]s balance. -.PP -You can make a stronger \[dq]total\[dq] balance assertion by writing a -double equals sign (\f[C]== EXPECTEDBALANCE\f[R]). -This asserts that there are no other unasserted commodities in the -account (or, that their balance is 0). -.IP -.nf -\f[C] -2013/1/1 - a $1 - a 1\[Eu] - b $-1 - c -1\[Eu] - -2013/1/2 ; These assertions succeed - a 0 = $1 - a 0 = 1\[Eu] - b 0 == $-1 - c 0 == -1\[Eu] - -2013/1/3 ; This assertion fails as \[aq]a\[aq] also contains 1\[Eu] - a 0 == $1 -\f[R] -.fi -.PP -It\[aq]s not yet possible to make a complete assertion about a balance -that has multiple commodities. -One workaround is to isolate each commodity into its own subaccount: -.IP -.nf -\f[C] -2013/1/1 - a:usd $1 - a:euro 1\[Eu] - b - -2013/1/2 - a 0 == 0 - a:usd 0 == $1 - a:euro 0 == 1\[Eu] -\f[R] -.fi -.SS Assertions and prices -.PP -Balance assertions ignore transaction prices, and should normally be -written without one: -.IP -.nf -\f[C] -2019/1/1 - (a) $1 \[at] \[Eu]1 = $1 -\f[R] -.fi -.PP -We do allow prices to be written there, however, and print shows them, -even though they don\[aq]t affect whether the assertion passes or fails. -This is for backward compatibility (hledger\[aq]s close command used to -generate balance assertions with prices), and because balance -\f[I]assignments\f[R] do use them (see below). -.SS Assertions and subaccounts -.PP -The balance assertions above (\f[C]=\f[R] and \f[C]==\f[R]) do not count -the balance from subaccounts; they check the account\[aq]s exclusive -balance only. -You can assert the balance including subaccounts by writing \f[C]=*\f[R] -or \f[C]==*\f[R], eg: -.IP -.nf -\f[C] -2019/1/1 - equity:opening balances - checking:a 5 - checking:b 5 - checking 1 ==* 11 -\f[R] -.fi -.SS Assertions and virtual postings -.PP -Balance assertions are checked against all postings, both real and -virtual. -They are not affected by the \f[C]--real/-R\f[R] flag or \f[C]real:\f[R] -query. -.SS Assertions and precision -.PP -Balance assertions compare the exactly calculated amounts, which are not -always what is shown by reports. -Eg a commodity directive may limit the display precision, but this will -not affect balance assertions. -Balance assertion failure messages show exact amounts. -.SH BALANCE ASSIGNMENTS -.PP -Ledger-style balance assignments are also supported. -These are like balance assertions, but with no posting amount on the -left side of the equals sign; instead it is calculated automatically so -as to satisfy the assertion. -This can be a convenience during data entry, eg when setting opening -balances: -.IP -.nf -\f[C] -; starting a new journal, set asset account balances -2016/1/1 opening balances - assets:checking = $409.32 - assets:savings = $735.24 - assets:cash = $42 - equity:opening balances -\f[R] -.fi -.PP -or when adjusting a balance to reality: -.IP -.nf -\f[C] -; no cash left; update balance, record any untracked spending as a generic expense -2016/1/15 - assets:cash = $0 - expenses:misc -\f[R] -.fi -.PP -The calculated amount depends on the account\[aq]s balance in the -commodity at that point (which depends on the previously-dated postings -of the commodity to that account since the last balance assertion or -assignment). -Note that using balance assignments makes your journal a little less -explicit; to know the exact amount posted, you have to run hledger or do -the calculations yourself, instead of just reading it. -.SS Balance assignments and prices -.PP -A transaction price in a balance assignment will cause the calculated -amount to have that price attached: -.IP -.nf -\f[C] -2019/1/1 - (a) = $1 \[at] \[Eu]2 -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger print --explicit -2019-01-01 - (a) $1 \[at] \[Eu]2 = $1 \[at] \[Eu]2 -\f[R] -.fi -.SH DIRECTIVES -.PP -A directive is a line in the journal beginning with a special keyword, -that influences how the journal is processed. -hledger\[aq]s directives are based on a subset of Ledger\[aq]s, but -there are many differences (and also some differences between hledger -versions). -.PP -Directives\[aq] behaviour and interactions can get a little bit complex, -so here is a table summarising the directives and their effects, with -links to more detailed docs. -Note part of this table is hidden when viewed in a web browser - scroll -it sideways to see more. -.PP -.TS -tab(@); -lw(7.8n) lw(8.6n) lw(7.0n) lw(27.8n) lw(18.8n). -T{ -directive -T}@T{ -end directive -T}@T{ -subdirectives -T}@T{ -purpose -T}@T{ -can affect (as of 2018/06) -T} -_ -T{ -\f[C]account\f[R] -T}@T{ -T}@T{ -any text -T}@T{ -document account names, declare account types & display order -T}@T{ -all entries in all files, before or after -T} -T{ -\f[C]alias\f[R] -T}@T{ -\f[C]end aliases\f[R] -T}@T{ -T}@T{ -rewrite account names -T}@T{ -following entries until end of current file or end directive -T} -T{ -\f[C]apply account\f[R] -T}@T{ -\f[C]end apply account\f[R] -T}@T{ -T}@T{ -prepend a common parent to account names -T}@T{ -following entries until end of current file or end directive -T} -T{ -\f[C]comment\f[R] -T}@T{ -\f[C]end comment\f[R] -T}@T{ -T}@T{ -ignore part of journal -T}@T{ -following entries until end of current file or end directive -T} -T{ -\f[C]commodity\f[R] -T}@T{ -T}@T{ -\f[C]format\f[R] -T}@T{ -declare a commodity and its number notation & display style -T}@T{ -number notation: following entries in that commodity in all files ; -display style: amounts of that commodity in reports -T} -T{ -\f[C]D\f[R] -T}@T{ -T}@T{ -T}@T{ -declare a commodity to be used for commodityless amounts, and its number -notation & display style -T}@T{ -default commodity: following commodityless entries until end of current -file; number notation: following entries in that commodity until end of -current file; display style: amounts of that commodity in reports -T} -T{ -\f[C]include\f[R] -T}@T{ -T}@T{ -T}@T{ -include entries/directives from another file -T}@T{ -what the included directives affect -T} -T{ -\f[C]P\f[R] -T}@T{ -T}@T{ -T}@T{ -declare a market price for a commodity -T}@T{ -amounts of that commodity in reports, when -V is used -T} -T{ -\f[C]Y\f[R] -T}@T{ -T}@T{ -T}@T{ -declare a year for yearless dates -T}@T{ -following entries until end of current file -T} -T{ -\f[C]=\f[R] -T}@T{ -T}@T{ -T}@T{ -declare an auto posting rule, adding postings to other transactions -T}@T{ -all entries in parent/current/child files (but not sibling files, see -#1212) -T} -.TE -.PP -And some definitions: -.PP -.TS -tab(@); -lw(6.0n) lw(64.0n). -T{ -subdirective -T}@T{ -optional indented directive line immediately following a parent -directive -T} -T{ -number notation -T}@T{ -how to interpret numbers when parsing journal entries (the identity of -the decimal separator character). -(Currently each commodity can have its own notation, even in the same -file.) -T} -T{ -display style -T}@T{ -how to display amounts of a commodity in reports (symbol side and -spacing, digit groups, decimal separator, decimal places) -T} -T{ -directive scope -T}@T{ -which entries and (when there are multiple files) which files are -affected by a directive -T} -.TE -.PP -As you can see, directives vary in which journal entries and files they -affect, and whether they are focussed on input (parsing) or output -(reports). -Some directives have multiple effects. -.SS Directives and multiple files -.PP -If you use multiple \f[C]-f\f[R]/\f[C]--file\f[R] options, or the -\f[C]include\f[R] directive, hledger will process multiple input files. -But note that directives which affect input (see above) typically last -only until the end of the file in which they occur. -.PP -This may seem inconvenient, but it\[aq]s intentional; it makes reports -stable and deterministic, independent of the order of input. -Otherwise you could see different numbers if you happened to write -f -options in a different order, or if you moved includes around while -cleaning up your files. -.PP -It can be surprising though; for example, it means that \f[C]alias\f[R] -directives do not affect parent or sibling files (see below). -.SS Comment blocks -.PP -A line containing just \f[C]comment\f[R] starts a commented region of -the file, and a line containing just \f[C]end comment\f[R] (or the end -of the current file) ends it. -See also comments. -.SS Including other files -.PP -You can pull in the content of additional files by writing an include -directive, like this: -.IP -.nf -\f[C] -include FILEPATH -\f[R] -.fi -.PP -Only journal files can include, and only journal, timeclock or timedot -files can be included (not CSV files, currently). -.PP -If the file path does not begin with a slash, it is relative to the -current file\[aq]s folder. -.PP -A tilde means home directory, eg: \f[C]include \[ti]/main.journal\f[R]. -.PP -The path may contain glob patterns to match multiple files, eg: -\f[C]include *.journal\f[R]. -.PP -There is limited support for recursive wildcards: \f[C]**/\f[R] (the -slash is required) matches 0 or more subdirectories. -It\[aq]s not super convenient since you have to avoid include cycles and -including directories, but this can be done, eg: -\f[C]include */**/*.journal\f[R]. -.PP -The path may also be prefixed to force a specific file format, -overriding the file extension (as described in hledger.1 -> Input -files): \f[C]include timedot:\[ti]/notes/2020*.md\f[R]. -.SS Default year -.PP -You can set a default year to be used for subsequent dates which -don\[aq]t specify a year. -This is a line beginning with \f[C]Y\f[R] followed by the year. -Eg: -.IP -.nf -\f[C] -Y2009 ; set default year to 2009 - -12/15 ; equivalent to 2009/12/15 - expenses 1 - assets - -Y2010 ; change default year to 2010 - -2009/1/30 ; specifies the year, not affected - expenses 1 - assets - -1/31 ; equivalent to 2010/1/31 - expenses 1 - assets -\f[R] -.fi -.SS Declaring commodities -.PP -The \f[C]commodity\f[R] directive has several functions: -.IP "1." 3 -It declares commodities which may be used in the journal. -This is currently not enforced, but can serve as documentation. -.IP "2." 3 -It declares what decimal mark character (period or comma) to expect when -parsing input - useful to disambiguate international number formats in -your data. -(Without this, hledger will parse both \f[C]1,000\f[R] and -\f[C]1.000\f[R] as 1). -.IP "3." 3 -It declares a commodity\[aq]s display style in output - decimal and -digit group marks, number of decimal places, symbol placement etc. -.PP -You are likely to run into one of the problems solved by commodity -directives, sooner or later, so it\[aq]s a good idea to just always use -them to declare your commodities. -.PP -A commodity directive is just the word \f[C]commodity\f[R] followed by -an amount. -It may be written on a single line, like this: -.IP -.nf -\f[C] -; commodity EXAMPLEAMOUNT - -; display AAAA amounts with the symbol on the right, space-separated, -; using period as decimal point, with four decimal places, and -; separating thousands with comma. -commodity 1,000.0000 AAAA -\f[R] -.fi -.PP -or on multiple lines, using the \[dq]format\[dq] subdirective. -(In this case the commodity symbol appears twice and should be the same -in both places.): -.IP -.nf -\f[C] -; commodity SYMBOL -; format EXAMPLEAMOUNT - -; display indian rupees with currency name on the left, -; thousands, lakhs and crores comma-separated, -; period as decimal point, and two decimal places. -commodity INR - format INR 1,00,00,000.00 -\f[R] -.fi -.PP -The quantity of the amount does not matter; only the format is -significant. -The number must include a decimal mark: either a period or a comma, -followed by 0 or more decimal digits. -.PP -Note hledger normally uses banker\[aq]s rounding, so 0.5 displayed with -zero decimal digits is \[dq]0\[dq]. -(More at Commodity display style.) -.SS Commodity error checking -.PP -In strict mode, enabled with the \f[C]-s\f[R]/\f[C]--strict\f[R] flag, -hledger will report an error if a commodity symbol is used that has not -been declared by a \f[C]commodity\f[R] directive. -This works similarly to account error checking, see the notes there for -more details. -.SS Default commodity -.PP -The \f[C]D\f[R] directive sets a default commodity, to be used for -amounts without a commodity symbol (ie, plain numbers). -This commodity will be applied to all subsequent commodity-less amounts, -or until the next \f[C]D\f[R] directive. -(Note, this is different from Ledger\[aq]s \f[C]D\f[R].) -.PP -For compatibility/historical reasons, \f[C]D\f[R] also acts like a -\f[C]commodity\f[R] directive, setting the commodity\[aq]s display style -(for output) and decimal mark (for parsing input). -As with \f[C]commodity\f[R], the amount must always be written with a -decimal mark (period or comma). -If both directives are used, \f[C]commodity\f[R]\[aq]s style takes -precedence. -.PP -The syntax is \f[C]D AMOUNT\f[R]. -Eg: -.IP -.nf -\f[C] -; commodity-less amounts should be treated as dollars -; (and displayed with the dollar sign on the left, thousands separators and two decimal places) -D $1,000.00 - -1/1 - a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 - b -\f[R] -.fi -.SS Declaring market prices -.PP -The \f[C]P\f[R] directive declares a market price, which is an exchange -rate between two commodities on a certain date. -(In Ledger, they are called \[dq]historical prices\[dq].) These are -often obtained from a stock exchange, cryptocurrency exchange, or the -foreign exchange market. -.PP -Here is the format: -.IP -.nf -\f[C] -P DATE COMMODITYA COMMODITYBAMOUNT -\f[R] -.fi -.IP \[bu] 2 -DATE is a simple date -.IP \[bu] 2 -COMMODITYA is the symbol of the commodity being priced -.IP \[bu] 2 -COMMODITYBAMOUNT is an amount (symbol and quantity) in a second -commodity, giving the price in commodity B of one unit of commodity A. -.PP -These two market price directives say that one euro was worth 1.35 US -dollars during 2009, and $1.40 from 2010 onward: -.IP -.nf -\f[C] -P 2009/1/1 \[Eu] $1.35 -P 2010/1/1 \[Eu] $1.40 -\f[R] -.fi -.PP -The \f[C]-V\f[R], \f[C]-X\f[R] and \f[C]--value\f[R] flags use these -market prices to show amount values in another commodity. -See Valuation. -.SS Declaring accounts -.PP -\f[C]account\f[R] directives can be used to declare accounts (ie, the -places that amounts are transferred from and to). -Though not required, these declarations can provide several benefits: -.IP \[bu] 2 -They can document your intended chart of accounts, providing a -reference. -.IP \[bu] 2 -They can help hledger know your accounts\[aq] types (asset, liability, -equity, revenue, expense), useful for reports like balancesheet and -incomestatement. -.IP \[bu] 2 -They control account display order in reports, allowing non-alphabetic -sorting (eg Revenues to appear above Expenses). -.IP \[bu] 2 -They can store extra information about accounts (account numbers, notes, -etc.) -.IP \[bu] 2 -They help with account name completion in the add command, hledger-iadd, -hledger-web, ledger-mode etc. -.IP \[bu] 2 -In strict mode, they restrict which accounts may be posted to by -transactions, which helps detect typos. -.PP -The simplest form is just the word \f[C]account\f[R] followed by a -hledger-style account name, eg this account directive declares the -\f[C]assets:bank:checking\f[R] account: -.IP -.nf -\f[C] -account assets:bank:checking -\f[R] -.fi -.SS Account error checking -.PP -By default, accounts come into existence when a transaction references -them by name. -This is convenient, but it means hledger can\[aq]t warn you when you -mis-spell an account name in the journal. -Usually you\[aq]ll find the error later, as an extra account in balance -reports, or an incorrect balance when reconciling. -.PP -In strict mode, enabled with the \f[C]-s\f[R]/\f[C]--strict\f[R] flag, -hledger will report an error if any transaction uses an account name -that has not been declared by an account directive. -Some notes: -.IP \[bu] 2 -The declaration is case-sensitive; transactions must use the correct -account name capitalisation. -.IP \[bu] 2 -The account directive\[aq]s scope is \[dq]whole file and below\[dq] (see -directives). -This means it affects all of the current file, and any files it -includes, but not parent or sibling files. -The position of account directives within the file does not matter, -though it\[aq]s usual to put them at the top. -.IP \[bu] 2 -Accounts can only be declared in \f[C]journal\f[R] files (but will -affect included files in other formats). -.IP \[bu] 2 -It\[aq]s currently not possible to declare \[dq]all possible -subaccounts\[dq] with a wildcard; every account posted to must be -declared. -.SS Account comments -.PP -Comments, beginning with a semicolon, can be added: -.IP \[bu] 2 -on the same line, \f[B]after two or more spaces\f[R] (because ; is -allowed in account names) -.IP \[bu] 2 -on the next lines, indented -.PP -An example of both: -.IP -.nf -\f[C] -account assets:bank:checking ; same-line comment, note 2+ spaces before ; - ; next-line comment - ; another with tag, acctno:12345 (not used yet) -\f[R] -.fi -.PP -Same-line comments are not supported by Ledger, or hledger <1.13. -.SS Account subdirectives -.PP -We also allow (and ignore) Ledger-style indented subdirectives, just for -compatibility.: -.IP -.nf -\f[C] -account assets:bank:checking - format blah blah ; <- subdirective, ignored -\f[R] -.fi -.PP -Here is the full syntax of account directives: -.IP -.nf -\f[C] -account ACCTNAME [ACCTTYPE] [;COMMENT] - [;COMMENTS] - [LEDGER-STYLE SUBDIRECTIVES, IGNORED] -\f[R] -.fi -.SS Account types -.PP -hledger recognises five main types of account, corresponding to the -account classes in the accounting equation: -.PP -\f[C]Asset\f[R], \f[C]Liability\f[R], \f[C]Equity\f[R], -\f[C]Revenue\f[R], \f[C]Expense\f[R]. -.PP -These account types are important for controlling which accounts appear -in the balancesheet, balancesheetequity, incomestatement reports (and -probably for other things in future). -.PP -Additionally, we recognise the \f[C]Cash\f[R] type, which is also an -\f[C]Asset\f[R], and which causes accounts to appear in the cashflow -report. -(\[dq]Cash\[dq] here means liquid assets, eg bank balances but typically -not investments or receivables.) -.SS Declaring account types -.PP -Generally, to make these reports work you should declare your top-level -accounts and their types, using account directives with \f[C]type:\f[R] -tags. -.PP -The tag\[aq]s value should be one of: \f[C]Asset\f[R], -\f[C]Liability\f[R], \f[C]Equity\f[R], \f[C]Revenue\f[R], -\f[C]Expense\f[R], \f[C]Cash\f[R], \f[C]A\f[R], \f[C]L\f[R], -\f[C]E\f[R], \f[C]R\f[R], \f[C]X\f[R], \f[C]C\f[R] (all case -insensitive). -The type is inherited by all subaccounts except where they override it. -Here\[aq]s a complete example: -.IP -.nf -\f[C] -account assets ; type: Asset -account assets:bank ; type: Cash -account assets:cash ; type: Cash -account liabilities ; type: Liability -account equity ; type: Equity -account revenues ; type: Revenue -account expenses ; type: Expense -\f[R] -.fi -.SS Auto-detected account types -.PP -If you happen to use common english top-level account names, you may not -need to declare account types, as they will be detected automatically -using the following rules: -.PP -.TS -tab(@); -l l. -T{ -If name matches regular expression: -T}@T{ -account type is: -T} -_ -T{ -\f[C]\[ha]assets?(:|$)\f[R] -T}@T{ -\f[C]Asset\f[R] -T} -T{ -\f[C]\[ha](debts?|liabilit(y|ies))(:|$)\f[R] -T}@T{ -\f[C]Liability\f[R] -T} -T{ -\f[C]\[ha]equity(:|$)\f[R] -T}@T{ -\f[C]Equity\f[R] -T} -T{ -\f[C]\[ha](income|revenue)s?(:|$)\f[R] -T}@T{ -\f[C]Revenue\f[R] -T} -T{ -\f[C]\[ha]expenses?(:|$)\f[R] -T}@T{ -\f[C]Expense\f[R] -T} -.TE -.PP -.TS -tab(@); -lw(56.9n) lw(13.1n). -T{ -If account type is \f[C]Asset\f[R] and name does not contain regular -expression: -T}@T{ -account type is: -T} -_ -T{ -\f[C](investment|receivable|:A/R|:fixed)\f[R] -T}@T{ -\f[C]Cash\f[R] -T} -.TE -.PP -Even so, explicit declarations may be a good idea, for clarity and -predictability. -.SS Interference from auto-detected account types -.PP -If you assign any account type, it\[aq]s a good idea to assign all of -them, to prevent any confusion from mixing declared and auto-detected -types. -Although it\[aq]s unlikely to happen in real life, here\[aq]s an -example: with the following journal, \f[C]balancesheetequity\f[R] shows -\[dq]liabilities\[dq] in both Liabilities and Equity sections. -Declaring another account as \f[C]type:Liability\f[R] would fix it: -.IP -.nf -\f[C] -account liabilities ; type:Equity - -2020-01-01 - assets 1 - liabilities 1 - equity -2 -\f[R] -.fi -.SS Old account type syntax -.PP -In some hledger journals you might instead see this old syntax (the -letters ALERX, separated from the account name by two or more spaces); -this is deprecated and may be removed soon: -.IP -.nf -\f[C] -account assets A -account liabilities L -account equity E -account revenues R -account expenses X -\f[R] -.fi -.SS Account display order -.PP -Account directives also set the order in which accounts are displayed, -eg in reports, the hledger-ui accounts screen, and the hledger-web -sidebar. -By default accounts are listed in alphabetical order. -But if you have these account directives in the journal: -.IP -.nf -\f[C] -account assets -account liabilities -account equity -account revenues -account expenses -\f[R] -.fi -.PP -you\[aq]ll see those accounts displayed in declaration order, not -alphabetically: -.IP -.nf -\f[C] -$ hledger accounts -1 -assets -liabilities -equity -revenues -expenses -\f[R] -.fi -.PP -Undeclared accounts, if any, are displayed last, in alphabetical order. -.PP -Note that sorting is done at each level of the account tree (within each -group of sibling accounts under the same parent). -And currently, this directive: -.IP -.nf -\f[C] -account other:zoo -\f[R] -.fi -.PP -would influence the position of \f[C]zoo\f[R] among -\f[C]other\f[R]\[aq]s subaccounts, but not the position of -\f[C]other\f[R] among the top-level accounts. -This means: -.IP \[bu] 2 -you will sometimes declare parent accounts (eg \f[C]account other\f[R] -above) that you don\[aq]t intend to post to, just to customize their -display order -.IP \[bu] 2 -sibling accounts stay together (you couldn\[aq]t display \f[C]x:y\f[R] -in between \f[C]a:b\f[R] and \f[C]a:c\f[R]). -.SS Rewriting accounts -.PP -You can define account alias rules which rewrite your account names, or -parts of them, before generating reports. -This can be useful for: -.IP \[bu] 2 -expanding shorthand account names to their full form, allowing easier -data entry and a less verbose journal -.IP \[bu] 2 -adapting old journals to your current chart of accounts -.IP \[bu] 2 -experimenting with new account organisations, like a new hierarchy or -combining two accounts into one -.IP \[bu] 2 -customising reports -.PP -Account aliases also rewrite account names in account directives. -They do not affect account names being entered via hledger add or -hledger-web. -.PP -See also Rewrite account names. -.SS Basic aliases -.PP -To set an account alias, use the \f[C]alias\f[R] directive in your -journal file. -This affects all subsequent journal entries in the current file or its -included files. -The spaces around the = are optional: -.IP -.nf -\f[C] -alias OLD = NEW -\f[R] -.fi -.PP -Or, you can use the \f[C]--alias \[aq]OLD=NEW\[aq]\f[R] option on the -command line. -This affects all entries. -It\[aq]s useful for trying out aliases interactively. -.PP -OLD and NEW are case sensitive full account names. -hledger will replace any occurrence of the old account name with the new -one. -Subaccounts are also affected. -Eg: -.IP -.nf -\f[C] -alias checking = assets:bank:wells fargo:checking -; rewrites \[dq]checking\[dq] to \[dq]assets:bank:wells fargo:checking\[dq], or \[dq]checking:a\[dq] to \[dq]assets:bank:wells fargo:checking:a\[dq] -\f[R] -.fi -.SS Regex aliases -.PP -There is also a more powerful variant that uses a regular expression, -indicated by the forward slashes: -.IP -.nf -\f[C] -alias /REGEX/ = REPLACEMENT -\f[R] -.fi -.PP -or \f[C]--alias \[aq]/REGEX/=REPLACEMENT\[aq]\f[R]. -.PP -REGEX is a case-insensitive regular expression. -Anywhere it matches inside an account name, the matched part will be -replaced by REPLACEMENT. -If REGEX contains parenthesised match groups, these can be referenced by -the usual numeric backreferences in REPLACEMENT. -Eg: -.IP -.nf -\f[C] -alias /\[ha](.+):bank:([\[ha]:]+):(.*)/ = \[rs]1:\[rs]2 \[rs]3 -; rewrites \[dq]assets:bank:wells fargo:checking\[dq] to \[dq]assets:wells fargo checking\[dq] -\f[R] -.fi -.PP -Also note that REPLACEMENT continues to the end of line (or on command -line, to end of option argument), so it can contain trailing whitespace. -.SS Combining aliases -.PP -You can define as many aliases as you like, using journal directives -and/or command line options. -.PP -Recursive aliases - where an account name is rewritten by one alias, -then by another alias, and so on - are allowed. -Each alias sees the effect of previously applied aliases. -.PP -In such cases it can be important to understand which aliases will be -applied and in which order. -For (each account name in) each journal entry, we apply: -.IP "1." 3 -\f[C]alias\f[R] directives preceding the journal entry, most recently -parsed first (ie, reading upward from the journal entry, bottom to top) -.IP "2." 3 -\f[C]--alias\f[R] options, in the order they appeared on the command -line (left to right). -.PP -In other words, for (an account name in) a given journal entry: -.IP \[bu] 2 -the nearest alias declaration before/above the entry is applied first -.IP \[bu] 2 -the next alias before/above that will be be applied next, and so on -.IP \[bu] 2 -aliases defined after/below the entry do not affect it. -.PP -This gives nearby aliases precedence over distant ones, and helps -provide semantic stability - aliases will keep working the same way -independent of which files are being read and in which order. -.PP -In case of trouble, adding \f[C]--debug=6\f[R] to the command line will -show which aliases are being applied when. -.SS Aliases and multiple files -.PP -As explained at Directives and multiple files, \f[C]alias\f[R] -directives do not affect parent or sibling files. -Eg in this command, -.IP -.nf -\f[C] -hledger -f a.aliases -f b.journal -\f[R] -.fi -.PP -account aliases defined in a.aliases will not affect b.journal. -Including the aliases doesn\[aq]t work either: -.IP -.nf -\f[C] -include a.aliases - -2020-01-01 ; not affected by a.aliases - foo 1 - bar -\f[R] -.fi -.PP -This means that account aliases should usually be declared at the start -of your top-most file, like this: -.IP -.nf -\f[C] -alias foo=Foo -alias bar=Bar - -2020-01-01 ; affected by aliases above - foo 1 - bar - -include c.journal ; also affected -\f[R] -.fi -.SS \f[C]end aliases\f[R] -.PP -You can clear (forget) all currently defined aliases with the -\f[C]end aliases\f[R] directive: -.IP -.nf -\f[C] -end aliases -\f[R] -.fi -.SS Default parent account -.PP -You can specify a parent account which will be prepended to all accounts -within a section of the journal. -Use the \f[C]apply account\f[R] and \f[C]end apply account\f[R] -directives like so: -.IP -.nf -\f[C] -apply account home - -2010/1/1 - food $10 - cash - -end apply account -\f[R] -.fi -.PP -which is equivalent to: -.IP -.nf -\f[C] -2010/01/01 - home:food $10 - home:cash $-10 -\f[R] -.fi -.PP -If \f[C]end apply account\f[R] is omitted, the effect lasts to the end -of the file. -Included files are also affected, eg: -.IP -.nf -\f[C] -apply account business -include biz.journal -end apply account -apply account personal -include personal.journal -\f[R] -.fi -.PP -Prior to hledger 1.0, legacy \f[C]account\f[R] and \f[C]end\f[R] -spellings were also supported. -.PP -A default parent account also affects account directives. -It does not affect account names being entered via hledger add or -hledger-web. -If account aliases are present, they are applied after the default -parent account. -.SH PERIODIC TRANSACTIONS -.PP -Periodic transaction rules describe transactions that recur. -They allow hledger to generate temporary future transactions to help -with forecasting, so you don\[aq]t have to write out each one in the -journal, and it\[aq]s easy to try out different forecasts. -.PP -Periodic transactions can be a little tricky, so before you use them, -read this whole section - or at least these tips: -.IP "1." 3 -Two spaces accidentally added or omitted will cause you trouble - read -about this below. -.IP "2." 3 -For troubleshooting, show the generated transactions with -\f[C]hledger print --forecast tag:generated\f[R] or -\f[C]hledger register --forecast tag:generated\f[R]. -.IP "3." 3 -Forecasted transactions will begin only after the last non-forecasted -transaction\[aq]s date. -.IP "4." 3 -Forecasted transactions will end 6 months from today, by default. -See below for the exact start/end rules. -.IP "5." 3 -period expressions can be tricky. -Their documentation needs improvement, but is worth studying. -.IP "6." 3 -Some period expressions with a repeating interval must begin on a -natural boundary of that interval. -Eg in \f[C]weekly from DATE\f[R], DATE must be a monday. -\f[C]\[ti] weekly from 2019/10/1\f[R] (a tuesday) will give an error. -.IP "7." 3 -Other period expressions with an interval are automatically expanded to -cover a whole number of that interval. -(This is done to improve reports, but it also affects periodic -transactions. -Yes, it\[aq]s a bit inconsistent with the above.) Eg: -\f[C]\[ti] every 10th day of month from 2020/01\f[R], which is -equivalent to \f[C]\[ti] every 10th day of month from 2020/01/01\f[R], -will be adjusted to start on 2019/12/10. -.PP -Periodic transaction rules also have a second meaning: they are used to -define budget goals, shown in budget reports. -.SS Periodic rule syntax -.PP -A periodic transaction rule looks like a normal journal entry, with the -date replaced by a tilde (\f[C]\[ti]\f[R]) followed by a period -expression (mnemonic: \f[C]\[ti]\f[R] looks like a recurring sine -wave.): -.IP -.nf -\f[C] -\[ti] monthly - expenses:rent $2000 - assets:bank:checking -\f[R] -.fi -.PP -There is an additional constraint on the period expression: the start -date must fall on a natural boundary of the interval. -Eg \f[C]monthly from 2018/1/1\f[R] is valid, but -\f[C]monthly from 2018/1/15\f[R] is not. -.PP -Partial or relative dates (M/D, D, tomorrow, last week) in the period -expression can work (useful or not). -They will be relative to today\[aq]s date, unless a Y default year -directive is in effect, in which case they will be relative to Y/1/1. -.SS Two spaces between period expression and description! -.PP -If the period expression is followed by a transaction description, these -must be separated by \f[B]two or more spaces\f[R]. -This helps hledger know where the period expression ends, so that -descriptions can not accidentally alter their meaning, as in this -example: -.IP -.nf -\f[C] -; 2 or more spaces needed here, so the period is not understood as \[dq]every 2 months in 2020\[dq] -; || -; vv -\[ti] every 2 months in 2020, we will review - assets:bank:checking $1500 - income:acme inc -\f[R] -.fi -.PP -So, -.IP \[bu] 2 -Do write two spaces between your period expression and your transaction -description, if any. -.IP \[bu] 2 -Don\[aq]t accidentally write two spaces in the middle of your period -expression. -.SS Forecasting with periodic transactions -.PP -The \f[C]--forecast\f[R] flag activates any periodic transaction rules -in the journal. -They will generate temporary recurring transactions, which are not saved -in the journal, but will appear in all reports (eg print). -This can be useful for estimating balances into the future, or -experimenting with different scenarios. -Or, it can be used as a data entry aid: describe recurring transactions, -and every so often copy the output of \f[C]print --forecast\f[R] into -the journal. -.PP -These transactions will have an extra tag indicating which periodic rule -generated them: \f[C]generated-transaction:\[ti] PERIODICEXPR\f[R]. -And a similar, hidden tag (beginning with an underscore) which, because -it\[aq]s never displayed by print, can be used to match transactions -generated \[dq]just now\[dq]: -\f[C]_generated-transaction:\[ti] PERIODICEXPR\f[R]. -.PP -Periodic transactions are generated within some forecast period. -By default, this -.IP \[bu] 2 -begins on the later of -.RS 2 -.IP \[bu] 2 -the report start date if specified with -b/-p/date: -.IP \[bu] 2 -the day after the latest normal (non-periodic) transaction in the -journal, or today if there are no normal transactions. -.RE -.IP \[bu] 2 -ends on the report end date if specified with -e/-p/date:, or 6 months -(180 days) from today. -.PP -This means that periodic transactions will begin only after the latest -recorded transaction. -And a recorded transaction dated in the future can prevent generation of -periodic transactions. -(You can avoid that by writing the future transaction as a one-time -periodic rule instead - put tilde before the date, eg -\f[C]\[ti] YYYY-MM-DD ...\f[R]). -.PP -Or, you can set your own arbitrary \[dq]forecast period\[dq], which can -overlap recorded transactions, and need not be in the future, by -providing an option argument, like \f[C]--forecast=PERIODEXPR\f[R]. -Note the equals sign is required, a space won\[aq]t work. -PERIODEXPR is a period expression, which can specify the start date, end -date, or both, like in a \f[C]date:\f[R] query. -(See also hledger.1 -> Report start & end date). -Some examples: \f[C]--forecast=202001-202004\f[R], -\f[C]--forecast=jan-\f[R], \f[C]--forecast=2020\f[R]. -.SS Budgeting with periodic transactions -.PP -With the \f[C]--budget\f[R] flag, currently supported by the balance -command, each periodic transaction rule declares recurring budget goals -for the specified accounts. -Eg the first example above declares a goal of spending $2000 on rent -(and also, a goal of depositing $2000 into checking) every month. -Goals and actual performance can then be compared in budget reports. -.PP -See also: Budgeting and Forecasting. -.PP -.SH AUTO POSTINGS -.PP -\[dq]Automated postings\[dq] or \[dq]auto postings\[dq] are extra -postings which get added automatically to transactions which match -certain queries, defined by \[dq]auto posting rules\[dq], when you use -the \f[C]--auto\f[R] flag. -.PP -An auto posting rule looks a bit like a transaction: -.IP -.nf -\f[C] -= QUERY - ACCOUNT AMOUNT - ... - ACCOUNT [AMOUNT] -\f[R] -.fi -.PP -except the first line is an equals sign (mnemonic: \f[C]=\f[R] suggests -matching), followed by a query (which matches existing postings), and -each \[dq]posting\[dq] line describes a posting to be generated, and the -posting amounts can be: -.IP \[bu] 2 -a normal amount with a commodity symbol, eg \f[C]$2\f[R]. -This will be used as-is. -.IP \[bu] 2 -a number, eg \f[C]2\f[R]. -The commodity symbol (if any) from the matched posting will be added to -this. -.IP \[bu] 2 -a numeric multiplier, eg \f[C]*2\f[R] (a star followed by a number N). -The matched posting\[aq]s amount (and total price, if any) will be -multiplied by N. -.IP \[bu] 2 -a multiplier with a commodity symbol, eg \f[C]*$2\f[R] (a star, number -N, and symbol S). -The matched posting\[aq]s amount will be multiplied by N, and its -commodity symbol will be replaced with S. -.PP -Any query term containing spaces must be enclosed in single or double -quotes, as on the command line. -Eg, note the quotes around the second query term below: -.IP -.nf -\f[C] -= expenses:groceries \[aq]expenses:dining out\[aq] - (budget:funds:dining out) *-1 -\f[R] -.fi -.PP -Some examples: -.IP -.nf -\f[C] -; every time I buy food, schedule a dollar donation -= expenses:food - (liabilities:charity) $-1 - -; when I buy a gift, also deduct that amount from a budget envelope subaccount -= expenses:gifts - assets:checking:gifts *-1 - assets:checking *1 - -2017/12/1 - expenses:food $10 - assets:checking - -2017/12/14 - expenses:gifts $20 - assets:checking -\f[R] -.fi -.IP -.nf -\f[C] -$ hledger print --auto -2017-12-01 - expenses:food $10 - assets:checking - (liabilities:charity) $-1 - -2017-12-14 - expenses:gifts $20 - assets:checking - assets:checking:gifts -$20 - assets:checking $20 -\f[R] -.fi -.SS Auto postings and multiple files -.PP -An auto posting rule can affect any transaction in the current file, or -in any parent file or child file. -Note, currently it will not affect sibling files (when multiple -\f[C]-f\f[R]/\f[C]--file\f[R] are used - see #1212). -.SS Auto postings and dates -.PP -A posting date (or secondary date) in the matched posting, or (taking -precedence) a posting date in the auto posting rule itself, will also be -used in the generated posting. -.SS Auto postings and transaction balancing / inferred amounts / balance assertions -.PP -Currently, auto postings are added: -.IP \[bu] 2 -after missing amounts are inferred, and transactions are checked for -balancedness, -.IP \[bu] 2 -but before balance assertions are checked. -.PP -Note this means that journal entries must be balanced both before and -after auto postings are added. -This changed in hledger 1.12+; see #893 for background. -.SS Auto posting tags -.PP -Automated postings will have some extra tags: -.IP \[bu] 2 -\f[C]generated-posting:= QUERY\f[R] - shows this was generated by an -auto posting rule, and the query -.IP \[bu] 2 -\f[C]_generated-posting:= QUERY\f[R] - a hidden tag, which does not -appear in hledger\[aq]s output. -This can be used to match postings generated \[dq]just now\[dq], rather -than generated in the past and saved to the journal. -.PP -Also, any transaction that has been changed by auto posting rules will -have these tags added: -.IP \[bu] 2 -\f[C]modified:\f[R] - this transaction was modified -.IP \[bu] 2 -\f[C]_modified:\f[R] - a hidden tag not appearing in the comment; this -transaction was modified \[dq]just now\[dq]. - - -.SH "REPORTING BUGS" -Report bugs at http://bugs.hledger.org -(or on the #hledger IRC channel or hledger mail list) - -.SH AUTHORS -Simon Michael <simon@joyful.com> and contributors - -.SH COPYRIGHT - -Copyright (C) 2007-2020 Simon Michael. -.br -Released under GNU GPL v3 or later. - -.SH SEE ALSO -hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) - -hledger_journal(5), hledger_csv(5), hledger_timeclock(5), hledger_timedot(5) diff --git a/hledger_journal.info b/hledger_journal.info deleted file mode 100644 index a94b728..0000000 --- a/hledger_journal.info +++ /dev/null @@ -1,2217 +0,0 @@ -This is hledger-lib/hledger_journal.info, produced by makeinfo version -4.8 from stdin. - - -File: hledger_journal.info, Node: Top, Up: (dir) - -hledger_journal(5) -****************** - -hledger's default file format, representing a General Journal. - - hledger's usual data source is a plain text file containing journal -entries in hledger journal format. This file represents a standard -accounting general journal. I use file names ending in `.journal', but -that's not required. The journal file contains a number of transaction -entries, each describing a transfer of money (or any commodity) between -two or more named accounts, in a simple format readable by both hledger -and humans. - - hledger's journal format is a compatible subset, mostly, of ledger's -journal format, so hledger can work with compatible ledger journal files -as well. It's safe, and encouraged, to run both hledger and ledger on -the same journal file, eg to validate the results you're getting. - - You can use hledger without learning any more about this file; just -use the add or web or import commands to create and update it. - - Many users, though, edit the journal file with a text editor, and -track changes with a version control system such as git. Editor addons -such as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and -hledger-vscode for Visual Studio Code, make this easier, adding colour, -formatting, tab completion, and useful commands. See Editor -configuration at hledger.org for the full list. - - Here's a description of each part of the file format (and hledger's -data model). These are mostly in the order you'll use them, but in some -cases related concepts have been grouped together for easy reference, or -linked before they are introduced, so feel free to skip over anything -that looks unnecessary right now. - -* Menu: - -* TRANSACTIONS:: -* DATES:: -* STATUS:: -* DESCRIPTION:: -* COMMENTS:: -* TAGS:: -* POSTINGS:: -* ACCOUNT NAMES:: -* AMOUNTS:: -* TRANSACTION PRICES:: -* LOT PRICES LOT DATES:: -* BALANCE ASSERTIONS:: -* BALANCE ASSIGNMENTS:: -* DIRECTIVES:: -* PERIODIC TRANSACTIONS:: -* AUTO POSTINGS:: - - -File: hledger_journal.info, Node: TRANSACTIONS, Next: DATES, Prev: Top, Up: Top - -1 TRANSACTIONS -************** - -Transactions are the main unit of information in a journal file. They -represent events, typically a movement of some quantity of commodities -between two or more named accounts. - - Each transaction is recorded as a journal entry, beginning with a -simple date in column 0. This can be followed by any of the following -optional fields, separated by spaces: - - * a status character (empty, `!', or `*') - - * a code (any short number or text, enclosed in parentheses) - - * a description (any remaining text until end of line or a semicolon) - - * a comment (any remaining text following a semicolon until end of - line, and any following indented lines beginning with a semicolon) - - * 0 or more indented _posting_ lines, describing what was transferred - and the accounts involved (indented comment lines are also - allowed, but not blank lines or non-indented lines). - - Here's a simple journal file containing one transaction: - - -2008/01/01 income - assets:bank:checking $1 - income:salary $-1 - - -File: hledger_journal.info, Node: DATES, Next: STATUS, Prev: TRANSACTIONS, Up: Top - -2 DATES -******* - -* Menu: - -* Simple dates:: -* Secondary dates:: -* Posting dates:: - - -File: hledger_journal.info, Node: Simple dates, Next: Secondary dates, Up: DATES - -2.1 Simple dates -================ - -Dates in the journal file use _simple dates_ format: `YYYY-MM-DD' or -`YYYY/MM/DD' or `YYYY.MM.DD', with leading zeros optional. The year may -be omitted, in which case it will be inferred from the context: the -current transaction, the default year set with a default year -directive, or the current date when the command is run. Some examples: -`2010-01-31', `2010/01/31', `2010.1.31', `1/31'. - - (The UI also accepts simple dates, as well as the more flexible smart -dates documented in the hledger manual.) - - -File: hledger_journal.info, Node: Secondary dates, Next: Posting dates, Prev: Simple dates, Up: DATES - -2.2 Secondary dates -=================== - -Real-life transactions sometimes involve more than one date - eg the -date you write a cheque, and the date it clears in your bank. When you -want to model this, for more accurate daily balances, you can specify -individual posting dates. - - Or, you can use the older _secondary date_ feature (Ledger calls it -auxiliary date or effective date). Note: we support this for -compatibility, but I usually recommend avoiding this feature; posting -dates are almost always clearer and simpler. - - A secondary date is written after the primary date, following an -equals sign. If the year is omitted, the primary date's year is -assumed. When running reports, the primary (left) date is used by -default, but with the `--date2' flag (or `--aux-date' or `--effective'), -the secondary (right) date will be used instead. - - The meaning of secondary dates is up to you, but it's best to follow -a consistent rule. Eg "primary = the bank's clearing date, secondary = -date the transaction was initiated, if different", as shown here: - - -2010/2/23=2/19 movie ticket - expenses:cinema $10 - assets:checking - - -$ hledger register checking -2010-02-23 movie ticket assets:checking $-10 $-10 - - -$ hledger register checking --date2 -2010-02-19 movie ticket assets:checking $-10 $-10 - - -File: hledger_journal.info, Node: Posting dates, Prev: Secondary dates, Up: DATES - -2.3 Posting dates -================= - -You can give individual postings a different date from their parent -transaction, by adding a posting comment containing a tag (see below) -like `date:DATE'. This is probably the best way to control posting -dates precisely. Eg in this example the expense should appear in May -reports, and the deduction from checking should be reported on 6/1 for -easy bank reconciliation: - - -2015/5/30 - expenses:food $10 ; food purchased on saturday 5/30 - assets:checking ; bank cleared it on monday, date:6/1 - - -$ hledger -f t.j register food -2015-05-30 expenses:food $10 $10 - - -$ hledger -f t.j register checking -2015-06-01 assets:checking $-10 $-10 - - DATE should be a simple date; if the year is not specified it will -use the year of the transaction's date. You can set the secondary date -similarly, with `date2:DATE2'. The `date:' or `date2:' tags must have a -valid simple date value if they are present, eg a `date:' tag with no -value is not allowed. - - Ledger's earlier, more compact bracketed date syntax is also -supported: `[DATE]', `[DATE=DATE2]' or `[=DATE2]'. hledger will attempt -to parse any square-bracketed sequence of the `0123456789/-.=' -characters in this way. With this syntax, DATE infers its year from the -transaction and DATE2 infers its year from DATE. - - -File: hledger_journal.info, Node: STATUS, Next: DESCRIPTION, Prev: DATES, Up: Top - -3 STATUS -******** - -Transactions, or individual postings within a transaction, can have a -status mark, which is a single character before the transaction -description or posting account name, separated from it by a space, -indicating one of three statuses: - -mark status ------------------ - unmarked -`!' pending -`*' cleared - - When reporting, you can filter by status with the `-U/--unmarked', -`-P/--pending', and `-C/--cleared' flags; or the `status:', `status:!', -and `status:*' queries; or the U, P, C keys in hledger-ui. - - Note, in Ledger and in older versions of hledger, the "unmarked" -state is called "uncleared". As of hledger 1.3 we have renamed it to -unmarked for clarity. - - To replicate Ledger and old hledger's behaviour of also matching -pending, combine -U and -P. - - Status marks are optional, but can be helpful eg for reconciling with -real-world accounts. Some editor modes provide highlighting and -shortcuts for working with status. Eg in Emacs ledger-mode, you can -toggle transaction status with C-c C-e, or posting status with C-c C-c. - - What "uncleared", "pending", and "cleared" actually mean is up to -you. Here's one suggestion: - -status meaning --------------------------------------------------------------------------- -uncleared recorded but not yet reconciled; needs review -pending tentatively reconciled (if needed, eg during a big - reconciliation) -cleared complete, reconciled as far as possible, and considered - correct - - With this scheme, you would use `-PC' to see the current balance at -your bank, `-U' to see things which will probably hit your bank soon -(like uncashed checks), and no flags to see the most up-to-date state -of your finances. - - -File: hledger_journal.info, Node: DESCRIPTION, Next: COMMENTS, Prev: STATUS, Up: Top - -4 DESCRIPTION -************* - -A transaction's description is the rest of the line following the date -and status mark (or until a comment begins). Sometimes called the -"narration" in traditional bookkeeping, it can be used for whatever you -wish, or left blank. Transaction descriptions can be queried, unlike -comments. - -* Menu: - -* Payee and note:: - - -File: hledger_journal.info, Node: Payee and note, Up: DESCRIPTION - -4.1 Payee and note -================== - -You can optionally include a `|' (pipe) character in descriptions to -subdivide the description into separate fields for payee/payer name on -the left (up to the first `|') and an additional note field on the -right (after the first `|'). This may be worthwhile if you need to do -more precise querying and pivoting by payee or by note. - - -File: hledger_journal.info, Node: COMMENTS, Next: TAGS, Prev: DESCRIPTION, Up: Top - -5 COMMENTS -********** - -Lines in the journal beginning with a semicolon (`;') or hash (`#') or -star (`*') are comments, and will be ignored. (Star comments cause -org-mode nodes to be ignored, allowing emacs users to fold and navigate -their journals with org-mode or orgstruct-mode.) - - You can attach comments to a transaction by writing them after the -description and/or indented on the following lines (before the -postings). Similarly, you can attach comments to an individual posting -by writing them after the amount and/or indented on the following lines. -Transaction and posting comments must begin with a semicolon (`;'). - - Some examples: - - -# a file comment -; another file comment -* also a file comment, useful in org/orgstruct mode - -comment -A multiline file comment, which continues -until a line containing just "end comment" -(or end of file). -end comment - -2012/5/14 something ; a transaction comment - ; the transaction comment, continued - posting1 1 ; a comment for posting 1 - posting2 - ; a comment for posting 2 - ; another comment line for posting 2 -; a file comment (because not indented) - - You can also comment larger regions of a file using `comment' and -`end comment' directives. - - -File: hledger_journal.info, Node: TAGS, Next: POSTINGS, Prev: COMMENTS, Up: Top - -6 TAGS -****** - -Tags are a way to add extra labels or labelled data to postings and -transactions, which you can then search or pivot on. - - A simple tag is a word (which may contain hyphens) followed by a full -colon, written inside a transaction or posting comment line: - - -2017/1/16 bought groceries ; sometag: - - Tags can have a value, which is the text after the colon, up to the -next comma or end of line, with leading/trailing whitespace removed: - - - expenses:food $10 ; a-posting-tag: the tag value - - Note this means hledger's tag values can not contain commas or -newlines. Ending at commas means you can write multiple short tags on -one line, comma separated: - - - assets:checking ; a comment containing tag1:, tag2: some value ... - - Here, - - * "`a comment containing'" is just comment text, not a tag - - * "`tag1'" is a tag with no value - - * "`tag2'" is another tag, whose value is "`some value ...'" - - Tags in a transaction comment affect the transaction and all of its -postings, while tags in a posting comment affect only that posting. For -example, the following transaction has three tags (`A', `TAG2', -`third-tag') and the posting has four (those plus `posting-tag'): - - -1/1 a transaction ; A:, TAG2: - ; third-tag: a third transaction tag, <- with a value - (a) $1 ; posting-tag: - - Tags are like Ledger's metadata feature, except hledger's tag values -are simple strings. - - -File: hledger_journal.info, Node: POSTINGS, Next: ACCOUNT NAMES, Prev: TAGS, Up: Top - -7 POSTINGS -********** - -A posting is an addition of some amount to, or removal of some amount -from, an account. Each posting line begins with at least one space or -tab (2 or 4 spaces is common), followed by: - - * (optional) a status character (empty, `!', or `*'), followed by a - space - - * (required) an account name (any text, optionally containing - *single spaces*, until end of line or a double space) - - * (optional) *two or more spaces* or tabs followed by an amount. - - Positive amounts are being added to the account, negative amounts are -being removed. - - The amounts within a transaction must always sum up to zero. As a -convenience, one amount may be left blank; it will be inferred so as to -balance the transaction. - - Be sure to note the unusual two-space delimiter between account name -and amount. This makes it easy to write account names containing -spaces. But if you accidentally leave only one space (or tab) before -the amount, the amount will be considered part of the account name. - -* Menu: - -* Virtual postings:: - - -File: hledger_journal.info, Node: Virtual postings, Up: POSTINGS - -7.1 Virtual postings -==================== - -A posting with a parenthesised account name is called a _virtual -posting_ or _unbalanced posting_, which means it is exempt from the -usual rule that a transaction's postings must balance add up to zero. - - This is not part of double entry accounting, so you might choose to -avoid this feature. Or you can use it sparingly for certain special -cases where it can be convenient. Eg, you could set opening balances -without using a balancing equity account: - - -1/1 opening balances - (assets:checking) $1000 - (assets:savings) $2000 - - A posting with a bracketed account name is called a _balanced -virtual posting_. The balanced virtual postings in a transaction must -add up to zero (separately from other postings). Eg: - - -1/1 buy food with cash, update budget envelope subaccounts, & something else - assets:cash $-10 ; <- these balance - expenses:food $7 ; <- - expenses:food $3 ; <- - [assets:checking:budget:food] $-10 ; <- and these balance - [assets:checking:available] $10 ; <- - (something:else) $5 ; <- not required to balance - - Ordinary non-parenthesised, non-bracketed postings are called _real -postings_. You can exclude virtual postings from reports with the -`-R/--real' flag or `real:1' query. - - -File: hledger_journal.info, Node: ACCOUNT NAMES, Next: AMOUNTS, Prev: POSTINGS, Up: Top - -8 ACCOUNT NAMES -*************** - -Account names typically have several parts separated by a full colon, -from which hledger derives a hierarchical chart of accounts. They can be -anything you like, but in finance there are traditionally five top-level -accounts: `assets', `liabilities', `income', `expenses', and `equity'. - - Account names may contain single spaces, eg: `assets:accounts -receivable'. Because of this, they must always be followed by *two or -more spaces* (or newline). - - Account names can be aliased. - - -File: hledger_journal.info, Node: AMOUNTS, Next: TRANSACTION PRICES, Prev: ACCOUNT NAMES, Up: Top - -9 AMOUNTS -********* - -After the account name, there is usually an amount. (Important: between -account name and amount, there must be *two or more spaces*.) - - hledger's amount format is flexible, supporting several international -formats. Here are some examples. Amounts have a number (the "quantity"): - - -1 - - ..and usually a currency or commodity name (the "commodity"). This -is a symbol, word, or phrase, to the left or right of the quantity, -with or without a separating space: - - -$1 -4000 AAPL - - If the commodity name contains spaces, numbers, or punctuation, it -must be enclosed in double quotes: - - -3 "no. 42 green apples" - - Amounts can be preceded by a minus sign (or a plus sign, though plus -is the default), The sign can be written before or after a left-side -commodity symbol: - - --$1 -$-1 - - One or more spaces between the sign and the number are acceptable -when parsing (but they won't be displayed in output): - - -+ $1 -$- 1 - - Scientific E notation is allowed: - - -1E-6 -EUR 1E3 - - A decimal mark can be written as a period or a comma: - - -1.23 -1,23456780000009 - -* Menu: - -* Digit group marks:: -* Commodity display style:: -* Rounding:: - - -File: hledger_journal.info, Node: Digit group marks, Next: Commodity display style, Up: AMOUNTS - -9.1 Digit group marks -===================== - -In the integer part of the quantity (left of the decimal mark), groups -of digits can optionally be separated by a "digit group mark" - a space, -comma, or period (different from the decimal mark): - - - $1,000,000.00 - EUR 2.000.000,00 -INR 9,99,99,999.00 - 1 000 000.9455 - - Note, a number containing a single group mark and no decimal mark is -ambiguous. Are these group marks or decimal marks ? - - -1,000 -1.000 - - hledger will treat them both as decimal marks by default (cf #793). -If you use digit group marks, to prevent confusion and undetected typos -we recommend you write commodity directives at the top of the file to -explicitly declare the decimal mark (and optionally a digit group mark). -Note, these formats ("amount styles") are specific to each commodity, so -if your data uses multiple formats, hledger can handle it: - - -commodity $1,000.00 -commodity EUR 1.000,00 -commodity INR 9,99,99,999.00 -commodity 1 000 000.9455 - - -File: hledger_journal.info, Node: Commodity display style, Next: Rounding, Prev: Digit group marks, Up: AMOUNTS - -9.2 Commodity display style -=========================== - -For each commodity, hledger chooses a consistent style to use when -displaying amounts. (Except price amounts, which are always displayed as -written). The display style is chosen as follows: - - * If there is a commodity directive (or default commodity directive) - for the commodity, its style is used (see examples above). - - * Otherwise the style is inferred from the amounts in that commodity - seen in the journal. - - * Or if there are no such amounts in the journal, a default style is - used (like `$1000.00'). - - - A style is inferred from the journal amounts in a commodity as -follows: - - * Use the general style (decimal mark, symbol placement) of the first - amount - - * Use the first-seen digit group style (digit group mark, digit group - sizes), if any - - * Use the maximum number of decimal places of all. - - Transaction price amounts don't affect the commodity display style -directly, but occasionally they can do so indirectly (eg when a -posting's amount is inferred using a transaction price). If you find -this causing problems, use a commodity directive to fix the display -style. - - In summary, each commodity's amounts will be normalised to - - * the style declared by a `commodity' directive - - * or, the style of the first posting amount in the journal, with the - first-seen digit group style and the maximum-seen number of decimal - places. - - If reports are showing amounts in a way you don't like (eg, with too -many decimal places), use a commodity directive to set your preferred -style. - - -File: hledger_journal.info, Node: Rounding, Prev: Commodity display style, Up: AMOUNTS - -9.3 Rounding -============ - -Amounts are stored internally as decimal numbers with up to 255 decimal -places, and displayed with the number of decimal places specified by the -commodity display style. Note, hledger uses banker's rounding: it rounds -to the nearest even number, eg 0.5 displayed with zero decimal places is -"0"). (Guaranteed since hledger 1.17.1; in older versions this could -vary if hledger was built with Decimal < 0.5.1.) - - -File: hledger_journal.info, Node: TRANSACTION PRICES, Next: LOT PRICES LOT DATES, Prev: AMOUNTS, Up: Top - -10 TRANSACTION PRICES -********************* - -Within a transaction, you can note an amount's price in another -commodity. This can be used to document the cost (in a purchase) or -selling price (in a sale). For example, transaction prices are useful to -record purchases of a foreign currency. Note transaction prices are -fixed at the time of the transaction, and do not change over time. See -also market prices, which represent prevailing exchange rates on a -certain date. - - There are several ways to record a transaction price: - - 1. Write the price per unit, as `@ UNITPRICE' after the amount: - - - 2009/1/1 - assets:euros €100 @ $1.35 ; one hundred euros purchased at $1.35 each - assets:dollars ; balancing amount is -$135.00 - - 2. Write the total price, as `@@ TOTALPRICE' after the amount: - - - 2009/1/1 - assets:euros €100 @@ $135 ; one hundred euros purchased at $135 for the lot - assets:dollars - - 3. Specify amounts for all postings, using exactly two commodities, - and let hledger infer the price that balances the transaction: - - - 2009/1/1 - assets:euros €100 ; one hundred euros purchased - assets:dollars $-135 ; for $135 - - 4. Like 1, but the `@' is parenthesised, i.e. `(@)'; this is for - compatibility with Ledger journals (Virtual posting costs), and is - equivalent to 1 in hledger. - - 5. Like 2, but as in 4 the `@@' is parenthesised, i.e. `(@@)'; in - hledger, this is equivalent to 2. - - - Use the `-B/--cost' flag to convert amounts to their transaction -price's commodity, if any. (mnemonic: "B" is from "cost Basis", as in -Ledger). Eg here is how -B affects the balance report for the example -above: - - -$ hledger bal -N --flat - $-135 assets:dollars - €100 assets:euros -$ hledger bal -N --flat -B - $-135 assets:dollars - $135 assets:euros # <- the euros' cost - - Note -B is sensitive to the order of postings when a transaction -price is inferred: the inferred price will be in the commodity of the -last amount. So if example 3's postings are reversed, while the -transaction is equivalent, -B shows something different: - - -2009/1/1 - assets:dollars $-135 ; 135 dollars sold - assets:euros €100 ; for 100 euros - - -$ hledger bal -N --flat -B - €-100 assets:dollars # <- the dollars' selling price - €100 assets:euros - - -File: hledger_journal.info, Node: LOT PRICES LOT DATES, Next: BALANCE ASSERTIONS, Prev: TRANSACTION PRICES, Up: Top - -11 LOT PRICES, LOT DATES -************************ - -Ledger allows another kind of price, lot price (four variants: -`{UNITPRICE}', `{{TOTALPRICE}}', `{=FIXEDUNITPRICE}', -`{{=FIXEDTOTALPRICE}}'), and/or a lot date (`[DATE]') to be specified. -These are normally used to select a lot when selling investments. -hledger will parse these, for compatibility with Ledger journals, but -currently ignores them. A transaction price, lot price and/or lot date -may appear in any order, after the posting amount and before the -balance assertion if any. - - -File: hledger_journal.info, Node: BALANCE ASSERTIONS, Next: BALANCE ASSIGNMENTS, Prev: LOT PRICES LOT DATES, Up: Top - -12 BALANCE ASSERTIONS -********************* - -hledger supports Ledger-style balance assertions in journal files. These -look like, for example, `= EXPECTEDBALANCE' following a posting's -amount. Eg here we assert the expected dollar balance in accounts a and -b after each posting: - - -2013/1/1 - a $1 =$1 - b =$-1 - -2013/1/2 - a $1 =$2 - b $-1 =$-2 - - After reading a journal file, hledger will check all balance -assertions and report an error if any of them fail. Balance assertions -can protect you from, eg, inadvertently disrupting reconciled balances -while cleaning up old entries. You can disable them temporarily with the -`-I/--ignore-assertions' flag, which can be useful for troubleshooting -or for reading Ledger files. (Note: this flag currently does not -disable balance assignments, below). - -* Menu: - -* Assertions and ordering:: -* Assertions and included files:: -* Assertions and multiple -f options:: -* Assertions and commodities:: -* Assertions and prices:: -* Assertions and subaccounts:: -* Assertions and virtual postings:: -* Assertions and precision:: - - -File: hledger_journal.info, Node: Assertions and ordering, Next: Assertions and included files, Up: BALANCE ASSERTIONS - -12.1 Assertions and ordering -============================ - -hledger sorts an account's postings and assertions first by date and -then (for postings on the same day) by parse order. Note this is -different from Ledger, which sorts assertions only by parse order. -(Also, Ledger assertions do not see the accumulated effect of repeated -postings to the same account within a transaction.) - - So, hledger balance assertions keep working if you reorder -differently-dated transactions within the journal. But if you reorder -same-dated transactions or postings, assertions might break and require -updating. This order dependence does bring an advantage: precise control -over the order of postings and assertions within a day, so you can -assert intra-day balances. - - -File: hledger_journal.info, Node: Assertions and included files, Next: Assertions and multiple -f options, Prev: Assertions and ordering, Up: BALANCE ASSERTIONS - -12.2 Assertions and included files -================================== - -With included files, things are a little more complicated. Including -preserves the ordering of postings and assertions. If you have multiple -postings to an account on the same day, split across different files, -and you also want to assert the account's balance on the same day, -you'll have to put the assertion in the right file. - - -File: hledger_journal.info, Node: Assertions and multiple -f options, Next: Assertions and commodities, Prev: Assertions and included files, Up: BALANCE ASSERTIONS - -12.3 Assertions and multiple -f options -======================================= - -Balance assertions don't work well across files specified with multiple --f options. Use include or concatenate the files instead. - - -File: hledger_journal.info, Node: Assertions and commodities, Next: Assertions and prices, Prev: Assertions and multiple -f options, Up: BALANCE ASSERTIONS - -12.4 Assertions and commodities -=============================== - -The asserted balance must be a simple single-commodity amount, and in -fact the assertion checks only this commodity's balance within the -(possibly multi-commodity) account balance. This is how assertions work -in Ledger also. We could call this a "partial" balance assertion. - - To assert the balance of more than one commodity in an account, you -can write multiple postings, each asserting one commodity's balance. - - You can make a stronger "total" balance assertion by writing a double -equals sign (`== EXPECTEDBALANCE'). This asserts that there are no -other unasserted commodities in the account (or, that their balance is -0). - - -2013/1/1 - a $1 - a 1€ - b $-1 - c -1€ - -2013/1/2 ; These assertions succeed - a 0 = $1 - a 0 = 1€ - b 0 == $-1 - c 0 == -1€ - -2013/1/3 ; This assertion fails as 'a' also contains 1€ - a 0 == $1 - - It's not yet possible to make a complete assertion about a balance -that has multiple commodities. One workaround is to isolate each -commodity into its own subaccount: - - -2013/1/1 - a:usd $1 - a:euro 1€ - b - -2013/1/2 - a 0 == 0 - a:usd 0 == $1 - a:euro 0 == 1€ - - -File: hledger_journal.info, Node: Assertions and prices, Next: Assertions and subaccounts, Prev: Assertions and commodities, Up: BALANCE ASSERTIONS - -12.5 Assertions and prices -========================== - -Balance assertions ignore transaction prices, and should normally be -written without one: - - -2019/1/1 - (a) $1 @ €1 = $1 - - We do allow prices to be written there, however, and print shows -them, even though they don't affect whether the assertion passes or -fails. This is for backward compatibility (hledger's close command -used to generate balance assertions with prices), and because balance -_assignments_ do use them (see below). - - -File: hledger_journal.info, Node: Assertions and subaccounts, Next: Assertions and virtual postings, Prev: Assertions and prices, Up: BALANCE ASSERTIONS - -12.6 Assertions and subaccounts -=============================== - -The balance assertions above (`=' and `==') do not count the balance -from subaccounts; they check the account's exclusive balance only. You -can assert the balance including subaccounts by writing `=*' or `==*', -eg: - - -2019/1/1 - equity:opening balances - checking:a 5 - checking:b 5 - checking 1 ==* 11 - - -File: hledger_journal.info, Node: Assertions and virtual postings, Next: Assertions and precision, Prev: Assertions and subaccounts, Up: BALANCE ASSERTIONS - -12.7 Assertions and virtual postings -==================================== - -Balance assertions are checked against all postings, both real and -virtual. They are not affected by the `--real/-R' flag or `real:' query. - - -File: hledger_journal.info, Node: Assertions and precision, Prev: Assertions and virtual postings, Up: BALANCE ASSERTIONS - -12.8 Assertions and precision -============================= - -Balance assertions compare the exactly calculated amounts, which are not -always what is shown by reports. Eg a commodity directive may limit the -display precision, but this will not affect balance assertions. Balance -assertion failure messages show exact amounts. - - -File: hledger_journal.info, Node: BALANCE ASSIGNMENTS, Next: DIRECTIVES, Prev: BALANCE ASSERTIONS, Up: Top - -13 BALANCE ASSIGNMENTS -********************** - -Ledger-style balance assignments are also supported. These are like -balance assertions, but with no posting amount on the left side of the -equals sign; instead it is calculated automatically so as to satisfy the -assertion. This can be a convenience during data entry, eg when setting -opening balances: - - -; starting a new journal, set asset account balances -2016/1/1 opening balances - assets:checking = $409.32 - assets:savings = $735.24 - assets:cash = $42 - equity:opening balances - - or when adjusting a balance to reality: - - -; no cash left; update balance, record any untracked spending as a generic expense -2016/1/15 - assets:cash = $0 - expenses:misc - - The calculated amount depends on the account's balance in the -commodity at that point (which depends on the previously-dated postings -of the commodity to that account since the last balance assertion or -assignment). Note that using balance assignments makes your journal a -little less explicit; to know the exact amount posted, you have to run -hledger or do the calculations yourself, instead of just reading it. - -* Menu: - -* Balance assignments and prices:: - - -File: hledger_journal.info, Node: Balance assignments and prices, Up: BALANCE ASSIGNMENTS - -13.1 Balance assignments and prices -=================================== - -A transaction price in a balance assignment will cause the calculated -amount to have that price attached: - - -2019/1/1 - (a) = $1 @ €2 - - -$ hledger print --explicit -2019-01-01 - (a) $1 @ €2 = $1 @ €2 - - -File: hledger_journal.info, Node: DIRECTIVES, Next: PERIODIC TRANSACTIONS, Prev: BALANCE ASSIGNMENTS, Up: Top - -14 DIRECTIVES -************* - -A directive is a line in the journal beginning with a special keyword, -that influences how the journal is processed. hledger's directives are -based on a subset of Ledger's, but there are many differences (and also -some differences between hledger versions). - - Directives' behaviour and interactions can get a little bit complex, -so here is a table summarising the directives and their effects, with -links to more detailed docs. Note part of this table is hidden when -viewed in a web browser - scroll it sideways to see more. - -directiveend subdirectivespurpose can affect (as of - directive 2018/06) ------------------------------------------------------------------------------ -`account' any document account names, all entries in all - text declare account types & files, before or - display order after -`alias' `end rewrite account names following entries - aliases' until end of - current file or - end directive -`apply `end prepend a common parent to following entries -account' apply account names until end of - account' current file or - end directive -`comment'`end ignore part of journal following entries - comment' until end of - current file or - end directive -`commodity' `format'declare a commodity and its number notation: - number notation & display following entries - style in that commodity - in all files ; - display style: - amounts of that - commodity in - reports -`D' declare a commodity to be default commodity: - used for commodityless following - amounts, and its number commodityless - notation & display style entries until end - of current file; - number notation: - following entries - in that commodity - until end of - current file; - display style: - amounts of that - commodity in - reports -`include' include entries/directives what the included - from another file directives affect -`P' declare a market price for a amounts of that - commodity commodity in - reports, when -V - is used -`Y' declare a year for yearless following entries - dates until end of - current file -`=' declare an auto posting all entries in - rule, adding postings to parent/current/child - other transactions files (but not - sibling files, see - #1212) - - And some definitions: - -subdirectiveoptional indented directive line immediately following a parent - directive -number how to interpret numbers when parsing journal entries (the -notationidentity of the decimal separator character). (Currently each - commodity can have its own notation, even in the same file.) -displayhow to display amounts of a commodity in reports (symbol side and -style spacing, digit groups, decimal separator, decimal places) -directivewhich entries and (when there are multiple files) which files are -scope affected by a directive - - As you can see, directives vary in which journal entries and files -they affect, and whether they are focussed on input (parsing) or output -(reports). Some directives have multiple effects. - -* Menu: - -* Directives and multiple files:: -* Comment blocks:: -* Including other files:: -* Default year:: -* Declaring commodities:: -* Default commodity:: -* Declaring market prices:: -* Declaring accounts:: -* Rewriting accounts:: -* Default parent account:: - - -File: hledger_journal.info, Node: Directives and multiple files, Next: Comment blocks, Up: DIRECTIVES - -14.1 Directives and multiple files -================================== - -If you use multiple `-f'/`--file' options, or the `include' directive, -hledger will process multiple input files. But note that directives -which affect input (see above) typically last only until the end of the -file in which they occur. - - This may seem inconvenient, but it's intentional; it makes reports -stable and deterministic, independent of the order of input. Otherwise -you could see different numbers if you happened to write -f options in a -different order, or if you moved includes around while cleaning up your -files. - - It can be surprising though; for example, it means that `alias' -directives do not affect parent or sibling files (see below). - - -File: hledger_journal.info, Node: Comment blocks, Next: Including other files, Prev: Directives and multiple files, Up: DIRECTIVES - -14.2 Comment blocks -=================== - -A line containing just `comment' starts a commented region of the file, -and a line containing just `end comment' (or the end of the current -file) ends it. See also comments. - - -File: hledger_journal.info, Node: Including other files, Next: Default year, Prev: Comment blocks, Up: DIRECTIVES - -14.3 Including other files -========================== - -You can pull in the content of additional files by writing an include -directive, like this: - - -include FILEPATH - - Only journal files can include, and only journal, timeclock or -timedot files can be included (not CSV files, currently). - - If the file path does not begin with a slash, it is relative to the -current file's folder. - - A tilde means home directory, eg: `include ~/main.journal'. - - The path may contain glob patterns to match multiple files, eg: -`include *.journal'. - - There is limited support for recursive wildcards: `**/' (the slash -is required) matches 0 or more subdirectories. It's not super convenient -since you have to avoid include cycles and including directories, but -this can be done, eg: `include */**/*.journal'. - - The path may also be prefixed to force a specific file format, -overriding the file extension (as described in hledger.1 -> Input -files): `include timedot:~/notes/2020*.md'. - - -File: hledger_journal.info, Node: Default year, Next: Declaring commodities, Prev: Including other files, Up: DIRECTIVES - -14.4 Default year -================= - -You can set a default year to be used for subsequent dates which don't -specify a year. This is a line beginning with `Y' followed by the year. -Eg: - - -Y2009 ; set default year to 2009 - -12/15 ; equivalent to 2009/12/15 - expenses 1 - assets - -Y2010 ; change default year to 2010 - -2009/1/30 ; specifies the year, not affected - expenses 1 - assets - -1/31 ; equivalent to 2010/1/31 - expenses 1 - assets - - -File: hledger_journal.info, Node: Declaring commodities, Next: Default commodity, Prev: Default year, Up: DIRECTIVES - -14.5 Declaring commodities -========================== - -The `commodity' directive has several functions: - - 1. It declares commodities which may be used in the journal. This is - currently not enforced, but can serve as documentation. - - 2. It declares what decimal mark character (period or comma) to - expect when parsing input - useful to disambiguate international - number formats in your data. (Without this, hledger will parse - both `1,000' and `1.000' as 1). - - 3. It declares a commodity's display style in output - decimal and - digit group marks, number of decimal places, symbol placement etc. - - - You are likely to run into one of the problems solved by commodity -directives, sooner or later, so it's a good idea to just always use them -to declare your commodities. - - A commodity directive is just the word `commodity' followed by an -amount. It may be written on a single line, like this: - - -; commodity EXAMPLEAMOUNT - -; display AAAA amounts with the symbol on the right, space-separated, -; using period as decimal point, with four decimal places, and -; separating thousands with comma. -commodity 1,000.0000 AAAA - - or on multiple lines, using the "format" subdirective. (In this case -the commodity symbol appears twice and should be the same in both -places.): - - -; commodity SYMBOL -; format EXAMPLEAMOUNT - -; display indian rupees with currency name on the left, -; thousands, lakhs and crores comma-separated, -; period as decimal point, and two decimal places. -commodity INR - format INR 1,00,00,000.00 - - The quantity of the amount does not matter; only the format is -significant. The number must include a decimal mark: either a period or -a comma, followed by 0 or more decimal digits. - - Note hledger normally uses banker's rounding, so 0.5 displayed with -zero decimal digits is "0". (More at Commodity display style.) - -* Menu: - -* Commodity error checking:: - - -File: hledger_journal.info, Node: Commodity error checking, Up: Declaring commodities - -14.5.1 Commodity error checking -------------------------------- - -In strict mode, enabled with the `-s'/`--strict' flag, hledger will -report an error if a commodity symbol is used that has not been -declared by a `commodity' directive. This works similarly to account -error checking, see the notes there for more details. - - -File: hledger_journal.info, Node: Default commodity, Next: Declaring market prices, Prev: Declaring commodities, Up: DIRECTIVES - -14.6 Default commodity -====================== - -The `D' directive sets a default commodity, to be used for amounts -without a commodity symbol (ie, plain numbers). This commodity will be -applied to all subsequent commodity-less amounts, or until the next `D' -directive. (Note, this is different from Ledger's `D'.) - - For compatibility/historical reasons, `D' also acts like a -`commodity' directive, setting the commodity's display style (for -output) and decimal mark (for parsing input). As with `commodity', the -amount must always be written with a decimal mark (period or comma). -If both directives are used, `commodity''s style takes precedence. - - The syntax is `D AMOUNT'. Eg: - - -; commodity-less amounts should be treated as dollars -; (and displayed with the dollar sign on the left, thousands separators and two decimal places) -D $1,000.00 - -1/1 - a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 - b - - -File: hledger_journal.info, Node: Declaring market prices, Next: Declaring accounts, Prev: Default commodity, Up: DIRECTIVES - -14.7 Declaring market prices -============================ - -The `P' directive declares a market price, which is an exchange rate -between two commodities on a certain date. (In Ledger, they are called -"historical prices".) These are often obtained from a stock exchange, -cryptocurrency exchange, or the foreign exchange market. - - Here is the format: - - -P DATE COMMODITYA COMMODITYBAMOUNT - - * DATE is a simple date - - * COMMODITYA is the symbol of the commodity being priced - - * COMMODITYBAMOUNT is an amount (symbol and quantity) in a second - commodity, giving the price in commodity B of one unit of - commodity A. - - These two market price directives say that one euro was worth 1.35 US -dollars during 2009, and $1.40 from 2010 onward: - - -P 2009/1/1 € $1.35 -P 2010/1/1 € $1.40 - - The `-V', `-X' and `--value' flags use these market prices to show -amount values in another commodity. See Valuation. - - -File: hledger_journal.info, Node: Declaring accounts, Next: Rewriting accounts, Prev: Declaring market prices, Up: DIRECTIVES - -14.8 Declaring accounts -======================= - -`account' directives can be used to declare accounts (ie, the places -that amounts are transferred from and to). Though not required, these -declarations can provide several benefits: - - * They can document your intended chart of accounts, providing a - reference. - - * They can help hledger know your accounts' types (asset, liability, - equity, revenue, expense), useful for reports like balancesheet and - incomestatement. - - * They control account display order in reports, allowing - non-alphabetic sorting (eg Revenues to appear above Expenses). - - * They can store extra information about accounts (account numbers, - notes, etc.) - - * They help with account name completion in the add command, - hledger-iadd, hledger-web, ledger-mode etc. - - * In strict mode, they restrict which accounts may be posted to by - transactions, which helps detect typos. - - The simplest form is just the word `account' followed by a -hledger-style account name, eg this account directive declares the -`assets:bank:checking' account: - - -account assets:bank:checking - -* Menu: - -* Account error checking:: -* Account comments:: -* Account subdirectives:: -* Account types:: -* Account display order:: - - -File: hledger_journal.info, Node: Account error checking, Next: Account comments, Up: Declaring accounts - -14.8.1 Account error checking ------------------------------ - -By default, accounts come into existence when a transaction references -them by name. This is convenient, but it means hledger can't warn you -when you mis-spell an account name in the journal. Usually you'll find -the error later, as an extra account in balance reports, or an incorrect -balance when reconciling. - - In strict mode, enabled with the `-s'/`--strict' flag, hledger will -report an error if any transaction uses an account name that has not -been declared by an account directive. Some notes: - - * The declaration is case-sensitive; transactions must use the - correct account name capitalisation. - - * The account directive's scope is "whole file and below" (see - directives). This means it affects all of the current file, and any - files it includes, but not parent or sibling files. The position of - account directives within the file does not matter, though it's - usual to put them at the top. - - * Accounts can only be declared in `journal' files (but will affect - included files in other formats). - - * It's currently not possible to declare "all possible subaccounts" - with a wildcard; every account posted to must be declared. - - -File: hledger_journal.info, Node: Account comments, Next: Account subdirectives, Prev: Account error checking, Up: Declaring accounts - -14.8.2 Account comments ------------------------ - -Comments, beginning with a semicolon, can be added: - - * on the same line, *after two or more spaces* (because ; is allowed - in account names) - - * on the next lines, indented - - An example of both: - - -account assets:bank:checking ; same-line comment, note 2+ spaces before ; - ; next-line comment - ; another with tag, acctno:12345 (not used yet) - - Same-line comments are not supported by Ledger, or hledger <1.13. - - -File: hledger_journal.info, Node: Account subdirectives, Next: Account types, Prev: Account comments, Up: Declaring accounts - -14.8.3 Account subdirectives ----------------------------- - -We also allow (and ignore) Ledger-style indented subdirectives, just for -compatibility.: - - -account assets:bank:checking - format blah blah ; <- subdirective, ignored - - Here is the full syntax of account directives: - - -account ACCTNAME [ACCTTYPE] [;COMMENT] - [;COMMENTS] - [LEDGER-STYLE SUBDIRECTIVES, IGNORED] - - -File: hledger_journal.info, Node: Account types, Next: Account display order, Prev: Account subdirectives, Up: Declaring accounts - -14.8.4 Account types --------------------- - -hledger recognises five main types of account, corresponding to the -account classes in the accounting equation: - - `Asset', `Liability', `Equity', `Revenue', `Expense'. - - These account types are important for controlling which accounts -appear in the balancesheet, balancesheetequity, incomestatement reports -(and probably for other things in future). - - Additionally, we recognise the `Cash' type, which is also an -`Asset', and which causes accounts to appear in the cashflow report. -("Cash" here means liquid assets, eg bank balances but typically not -investments or receivables.) - -* Menu: - -* Declaring account types:: -* Auto-detected account types:: -* Interference from auto-detected account types:: -* Old account type syntax:: - - -File: hledger_journal.info, Node: Declaring account types, Next: Auto-detected account types, Up: Account types - -14.8.4.1 Declaring account types -................................ - -Generally, to make these reports work you should declare your top-level -accounts and their types, using account directives with `type:' tags. - - The tag's value should be one of: `Asset', `Liability', `Equity', -`Revenue', `Expense', `Cash', `A', `L', `E', `R', `X', `C' (all case -insensitive). The type is inherited by all subaccounts except where -they override it. Here's a complete example: - - -account assets ; type: Asset -account assets:bank ; type: Cash -account assets:cash ; type: Cash -account liabilities ; type: Liability -account equity ; type: Equity -account revenues ; type: Revenue -account expenses ; type: Expense - - -File: hledger_journal.info, Node: Auto-detected account types, Next: Interference from auto-detected account types, Prev: Declaring account types, Up: Account types - -14.8.4.2 Auto-detected account types -.................................... - -If you happen to use common english top-level account names, you may not -need to declare account types, as they will be detected automatically -using the following rules: - -If name matches regular account type -expression: is: -------------------------------------------------- -`^assets?(:|$)' `Asset' -`^(debts?|liabilit(y|ies))(:|$)' `Liability' -`^equity(:|$)' `Equity' -`^(income|revenue)s?(:|$)' `Revenue' -`^expenses?(:|$)' `Expense' - -If account type is `Asset' and name does not contain account type -regular expression: is: --------------------------------------------------------------------------- -`(investment|receivable|:A/R|:fixed)' `Cash' - - Even so, explicit declarations may be a good idea, for clarity and -predictability. - - -File: hledger_journal.info, Node: Interference from auto-detected account types, Next: Old account type syntax, Prev: Auto-detected account types, Up: Account types - -14.8.4.3 Interference from auto-detected account types -...................................................... - -If you assign any account type, it's a good idea to assign all of them, -to prevent any confusion from mixing declared and auto-detected types. -Although it's unlikely to happen in real life, here's an example: with -the following journal, `balancesheetequity' shows "liabilities" in both -Liabilities and Equity sections. Declaring another account as -`type:Liability' would fix it: - - -account liabilities ; type:Equity - -2020-01-01 - assets 1 - liabilities 1 - equity -2 - - -File: hledger_journal.info, Node: Old account type syntax, Prev: Interference from auto-detected account types, Up: Account types - -14.8.4.4 Old account type syntax -................................ - -In some hledger journals you might instead see this old syntax (the -letters ALERX, separated from the account name by two or more spaces); -this is deprecated and may be removed soon: - - -account assets A -account liabilities L -account equity E -account revenues R -account expenses X - - -File: hledger_journal.info, Node: Account display order, Prev: Account types, Up: Declaring accounts - -14.8.5 Account display order ----------------------------- - -Account directives also set the order in which accounts are displayed, -eg in reports, the hledger-ui accounts screen, and the hledger-web -sidebar. By default accounts are listed in alphabetical order. But if -you have these account directives in the journal: - - -account assets -account liabilities -account equity -account revenues -account expenses - - you'll see those accounts displayed in declaration order, not -alphabetically: - - -$ hledger accounts -1 -assets -liabilities -equity -revenues -expenses - - Undeclared accounts, if any, are displayed last, in alphabetical -order. - - Note that sorting is done at each level of the account tree (within -each group of sibling accounts under the same parent). And currently, -this directive: - - -account other:zoo - - would influence the position of `zoo' among `other''s subaccounts, -but not the position of `other' among the top-level accounts. This -means: - - * you will sometimes declare parent accounts (eg `account other' - above) that you don't intend to post to, just to customize their - display order - - * sibling accounts stay together (you couldn't display `x:y' in - between `a:b' and `a:c'). - - -File: hledger_journal.info, Node: Rewriting accounts, Next: Default parent account, Prev: Declaring accounts, Up: DIRECTIVES - -14.9 Rewriting accounts -======================= - -You can define account alias rules which rewrite your account names, or -parts of them, before generating reports. This can be useful for: - - * expanding shorthand account names to their full form, allowing - easier data entry and a less verbose journal - - * adapting old journals to your current chart of accounts - - * experimenting with new account organisations, like a new hierarchy - or combining two accounts into one - - * customising reports - - Account aliases also rewrite account names in account directives. -They do not affect account names being entered via hledger add or -hledger-web. - - See also Rewrite account names. - -* Menu: - -* Basic aliases:: -* Regex aliases:: -* Combining aliases:: -* Aliases and multiple files:: -* end aliases:: - - -File: hledger_journal.info, Node: Basic aliases, Next: Regex aliases, Up: Rewriting accounts - -14.9.1 Basic aliases --------------------- - -To set an account alias, use the `alias' directive in your journal -file. This affects all subsequent journal entries in the current file or -its included files. The spaces around the = are optional: - - -alias OLD = NEW - - Or, you can use the `--alias 'OLD=NEW'' option on the command line. -This affects all entries. It's useful for trying out aliases -interactively. - - OLD and NEW are case sensitive full account names. hledger will -replace any occurrence of the old account name with the new one. -Subaccounts are also affected. Eg: - - -alias checking = assets:bank:wells fargo:checking -; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a" - - -File: hledger_journal.info, Node: Regex aliases, Next: Combining aliases, Prev: Basic aliases, Up: Rewriting accounts - -14.9.2 Regex aliases --------------------- - -There is also a more powerful variant that uses a regular expression, -indicated by the forward slashes: - - -alias /REGEX/ = REPLACEMENT - - or `--alias '/REGEX/=REPLACEMENT''. - - REGEX is a case-insensitive regular expression. Anywhere it matches -inside an account name, the matched part will be replaced by -REPLACEMENT. If REGEX contains parenthesised match groups, these can be -referenced by the usual numeric backreferences in REPLACEMENT. Eg: - - -alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 -; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" - - Also note that REPLACEMENT continues to the end of line (or on -command line, to end of option argument), so it can contain trailing -whitespace. - - -File: hledger_journal.info, Node: Combining aliases, Next: Aliases and multiple files, Prev: Regex aliases, Up: Rewriting accounts - -14.9.3 Combining aliases ------------------------- - -You can define as many aliases as you like, using journal directives -and/or command line options. - - Recursive aliases - where an account name is rewritten by one alias, -then by another alias, and so on - are allowed. Each alias sees the -effect of previously applied aliases. - - In such cases it can be important to understand which aliases will be -applied and in which order. For (each account name in) each journal -entry, we apply: - - 1. `alias' directives preceding the journal entry, most recently - parsed first (ie, reading upward from the journal entry, bottom to - top) - - 2. `--alias' options, in the order they appeared on the command line - (left to right). - - In other words, for (an account name in) a given journal entry: - - * the nearest alias declaration before/above the entry is applied - first - - * the next alias before/above that will be be applied next, and so on - - * aliases defined after/below the entry do not affect it. - - This gives nearby aliases precedence over distant ones, and helps -provide semantic stability - aliases will keep working the same way -independent of which files are being read and in which order. - - In case of trouble, adding `--debug=6' to the command line will show -which aliases are being applied when. - - -File: hledger_journal.info, Node: Aliases and multiple files, Next: end aliases, Prev: Combining aliases, Up: Rewriting accounts - -14.9.4 Aliases and multiple files ---------------------------------- - -As explained at Directives and multiple files, `alias' directives do -not affect parent or sibling files. Eg in this command, - - -hledger -f a.aliases -f b.journal - - account aliases defined in a.aliases will not affect b.journal. -Including the aliases doesn't work either: - - -include a.aliases - -2020-01-01 ; not affected by a.aliases - foo 1 - bar - - This means that account aliases should usually be declared at the -start of your top-most file, like this: - - -alias foo=Foo -alias bar=Bar - -2020-01-01 ; affected by aliases above - foo 1 - bar - -include c.journal ; also affected - - -File: hledger_journal.info, Node: end aliases, Prev: Aliases and multiple files, Up: Rewriting accounts - -14.9.5 `end aliases' --------------------- - -You can clear (forget) all currently defined aliases with the `end -aliases' directive: - - -end aliases - - -File: hledger_journal.info, Node: Default parent account, Prev: Rewriting accounts, Up: DIRECTIVES - -14.10 Default parent account -============================ - -You can specify a parent account which will be prepended to all accounts -within a section of the journal. Use the `apply account' and `end apply -account' directives like so: - - -apply account home - -2010/1/1 - food $10 - cash - -end apply account - - which is equivalent to: - - -2010/01/01 - home:food $10 - home:cash $-10 - - If `end apply account' is omitted, the effect lasts to the end of -the file. Included files are also affected, eg: - - -apply account business -include biz.journal -end apply account -apply account personal -include personal.journal - - Prior to hledger 1.0, legacy `account' and `end' spellings were also -supported. - - A default parent account also affects account directives. It does not -affect account names being entered via hledger add or hledger-web. If -account aliases are present, they are applied after the default parent -account. - - -File: hledger_journal.info, Node: PERIODIC TRANSACTIONS, Next: AUTO POSTINGS, Prev: DIRECTIVES, Up: Top - -15 PERIODIC TRANSACTIONS -************************ - -Periodic transaction rules describe transactions that recur. They allow -hledger to generate temporary future transactions to help with -forecasting, so you don't have to write out each one in the journal, and -it's easy to try out different forecasts. - - Periodic transactions can be a little tricky, so before you use them, -read this whole section - or at least these tips: - - 1. Two spaces accidentally added or omitted will cause you trouble - - read about this below. - - 2. For troubleshooting, show the generated transactions with `hledger - print --forecast tag:generated' or `hledger register --forecast - tag:generated'. - - 3. Forecasted transactions will begin only after the last - non-forecasted transaction's date. - - 4. Forecasted transactions will end 6 months from today, by default. - See below for the exact start/end rules. - - 5. period expressions can be tricky. Their documentation needs - improvement, but is worth studying. - - 6. Some period expressions with a repeating interval must begin on a - natural boundary of that interval. Eg in `weekly from DATE', DATE - must be a monday. `~ weekly from 2019/10/1' (a tuesday) will give - an error. - - 7. Other period expressions with an interval are automatically - expanded to cover a whole number of that interval. (This is done - to improve reports, but it also affects periodic transactions. - Yes, it's a bit inconsistent with the above.) Eg: `~ every 10th - day of month from 2020/01', which is equivalent to `~ every 10th - day of month from 2020/01/01', will be adjusted to start on - 2019/12/10. - - Periodic transaction rules also have a second meaning: they are used -to define budget goals, shown in budget reports. - -* Menu: - -* Periodic rule syntax:: -* Two spaces between period expression and description!:: -* Forecasting with periodic transactions:: -* Budgeting with periodic transactions:: - - -File: hledger_journal.info, Node: Periodic rule syntax, Next: Two spaces between period expression and description!, Up: PERIODIC TRANSACTIONS - -15.1 Periodic rule syntax -========================= - -A periodic transaction rule looks like a normal journal entry, with the -date replaced by a tilde (`~') followed by a period expression -(mnemonic: `~' looks like a recurring sine wave.): - - -~ monthly - expenses:rent $2000 - assets:bank:checking - - There is an additional constraint on the period expression: the start -date must fall on a natural boundary of the interval. Eg `monthly from -2018/1/1' is valid, but `monthly from 2018/1/15' is not. - - Partial or relative dates (M/D, D, tomorrow, last week) in the period -expression can work (useful or not). They will be relative to today's -date, unless a Y default year directive is in effect, in which case they -will be relative to Y/1/1. - - -File: hledger_journal.info, Node: Two spaces between period expression and description!, Next: Forecasting with periodic transactions, Prev: Periodic rule syntax, Up: PERIODIC TRANSACTIONS - -15.2 Two spaces between period expression and description! -========================================================== - -If the period expression is followed by a transaction description, these -must be separated by *two or more spaces*. This helps hledger know -where the period expression ends, so that descriptions can not -accidentally alter their meaning, as in this example: - - -; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2020" -; || -; vv -~ every 2 months in 2020, we will review - assets:bank:checking $1500 - income:acme inc - - So, - - * Do write two spaces between your period expression and your - transaction description, if any. - - * Don't accidentally write two spaces in the middle of your period - expression. - - -File: hledger_journal.info, Node: Forecasting with periodic transactions, Next: Budgeting with periodic transactions, Prev: Two spaces between period expression and description!, Up: PERIODIC TRANSACTIONS - -15.3 Forecasting with periodic transactions -=========================================== - -The `--forecast' flag activates any periodic transaction rules in the -journal. They will generate temporary recurring transactions, which are -not saved in the journal, but will appear in all reports (eg print). -This can be useful for estimating balances into the future, or -experimenting with different scenarios. Or, it can be used as a data -entry aid: describe recurring transactions, and every so often copy the -output of `print --forecast' into the journal. - - These transactions will have an extra tag indicating which periodic -rule generated them: `generated-transaction:~ PERIODICEXPR'. And a -similar, hidden tag (beginning with an underscore) which, because it's -never displayed by print, can be used to match transactions generated -"just now": `_generated-transaction:~ PERIODICEXPR'. - - Periodic transactions are generated within some forecast period. By -default, this - - * begins on the later of - * the report start date if specified with -b/-p/date: - - * the day after the latest normal (non-periodic) transaction in - the journal, or today if there are no normal transactions. - - * ends on the report end date if specified with -e/-p/date:, or 6 - months (180 days) from today. - - This means that periodic transactions will begin only after the -latest recorded transaction. And a recorded transaction dated in the -future can prevent generation of periodic transactions. (You can avoid -that by writing the future transaction as a one-time periodic rule -instead - put tilde before the date, eg `~ YYYY-MM-DD ...'). - - Or, you can set your own arbitrary "forecast period", which can -overlap recorded transactions, and need not be in the future, by -providing an option argument, like `--forecast=PERIODEXPR'. Note the -equals sign is required, a space won't work. PERIODEXPR is a period -expression, which can specify the start date, end date, or both, like -in a `date:' query. (See also hledger.1 -> Report start & end date). -Some examples: `--forecast=202001-202004', `--forecast=jan-', -`--forecast=2020'. - - -File: hledger_journal.info, Node: Budgeting with periodic transactions, Prev: Forecasting with periodic transactions, Up: PERIODIC TRANSACTIONS - -15.4 Budgeting with periodic transactions -========================================= - -With the `--budget' flag, currently supported by the balance command, -each periodic transaction rule declares recurring budget goals for the -specified accounts. Eg the first example above declares a goal of -spending $2000 on rent (and also, a goal of depositing $2000 into -checking) every month. Goals and actual performance can then be compared -in budget reports. - - See also: Budgeting and Forecasting. - - -File: hledger_journal.info, Node: AUTO POSTINGS, Prev: PERIODIC TRANSACTIONS, Up: Top - -16 AUTO POSTINGS -**************** - -"Automated postings" or "auto postings" are extra postings which get -added automatically to transactions which match certain queries, defined -by "auto posting rules", when you use the `--auto' flag. - - An auto posting rule looks a bit like a transaction: - - -= QUERY - ACCOUNT AMOUNT - ... - ACCOUNT [AMOUNT] - - except the first line is an equals sign (mnemonic: `=' suggests -matching), followed by a query (which matches existing postings), and -each "posting" line describes a posting to be generated, and the posting -amounts can be: - - * a normal amount with a commodity symbol, eg `$2'. This will be used - as-is. - - * a number, eg `2'. The commodity symbol (if any) from the matched - posting will be added to this. - - * a numeric multiplier, eg `*2' (a star followed by a number N). The - matched posting's amount (and total price, if any) will be - multiplied by N. - - * a multiplier with a commodity symbol, eg `*$2' (a star, number N, - and symbol S). The matched posting's amount will be multiplied by - N, and its commodity symbol will be replaced with S. - - Any query term containing spaces must be enclosed in single or double -quotes, as on the command line. Eg, note the quotes around the second -query term below: - - -= expenses:groceries 'expenses:dining out' - (budget:funds:dining out) *-1 - - Some examples: - - -; every time I buy food, schedule a dollar donation -= expenses:food - (liabilities:charity) $-1 - -; when I buy a gift, also deduct that amount from a budget envelope subaccount -= expenses:gifts - assets:checking:gifts *-1 - assets:checking *1 - -2017/12/1 - expenses:food $10 - assets:checking - -2017/12/14 - expenses:gifts $20 - assets:checking - - -$ hledger print --auto -2017-12-01 - expenses:food $10 - assets:checking - (liabilities:charity) $-1 - -2017-12-14 - expenses:gifts $20 - assets:checking - assets:checking:gifts -$20 - assets:checking $20 - -* Menu: - -* Auto postings and multiple files:: -* Auto postings and dates:: -* Auto postings and transaction balancing / inferred amounts / balance assertions:: -* Auto posting tags:: - - -File: hledger_journal.info, Node: Auto postings and multiple files, Next: Auto postings and dates, Up: AUTO POSTINGS - -16.1 Auto postings and multiple files -===================================== - -An auto posting rule can affect any transaction in the current file, or -in any parent file or child file. Note, currently it will not affect -sibling files (when multiple `-f'/`--file' are used - see #1212). - - -File: hledger_journal.info, Node: Auto postings and dates, Next: Auto postings and transaction balancing / inferred amounts / balance assertions, Prev: Auto postings and multiple files, Up: AUTO POSTINGS - -16.2 Auto postings and dates -============================ - -A posting date (or secondary date) in the matched posting, or (taking -precedence) a posting date in the auto posting rule itself, will also be -used in the generated posting. - - -File: hledger_journal.info, Node: Auto postings and transaction balancing / inferred amounts / balance assertions, Next: Auto posting tags, Prev: Auto postings and dates, Up: AUTO POSTINGS - -16.3 Auto postings and transaction balancing / inferred amounts / -================================================================= - -balance assertions - - Currently, auto postings are added: - - * after missing amounts are inferred, and transactions are checked - for balancedness, - - * but before balance assertions are checked. - - Note this means that journal entries must be balanced both before and -after auto postings are added. This changed in hledger 1.12+; see #893 -for background. - - -File: hledger_journal.info, Node: Auto posting tags, Prev: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: AUTO POSTINGS - -16.4 Auto posting tags -====================== - -Automated postings will have some extra tags: - - * `generated-posting:= QUERY' - shows this was generated by an auto - posting rule, and the query - - * `_generated-posting:= QUERY' - a hidden tag, which does not appear - in hledger's output. This can be used to match postings generated - "just now", rather than generated in the past and saved to the - journal. - - Also, any transaction that has been changed by auto posting rules -will have these tags added: - - * `modified:' - this transaction was modified - - * `_modified:' - a hidden tag not appearing in the comment; this - transaction was modified "just now". - - - -Tag Table: -Node: Top88 -Node: TRANSACTIONS2095 -Ref: #transactions2213 -Node: DATES3230 -Ref: #dates3337 -Node: Simple dates3402 -Ref: #simple-dates3524 -Node: Secondary dates4031 -Ref: #secondary-dates4181 -Node: Posting dates5515 -Ref: #posting-dates5640 -Node: STATUS7009 -Ref: #status7117 -Node: DESCRIPTION8822 -Ref: #description8943 -Node: Payee and note9261 -Ref: #payee-and-note9371 -Node: COMMENTS9705 -Ref: #comments9818 -Node: TAGS11011 -Ref: #tags11113 -Node: POSTINGS12511 -Ref: #postings12626 -Node: Virtual postings13650 -Ref: #virtual-postings13763 -Node: ACCOUNT NAMES15065 -Ref: #account-names15193 -Node: AMOUNTS15678 -Ref: #amounts15804 -Node: Digit group marks16931 -Ref: #digit-group-marks17078 -Node: Commodity display style18018 -Ref: #commodity-display-style18194 -Node: Rounding19738 -Ref: #rounding19858 -Node: TRANSACTION PRICES20268 -Ref: #transaction-prices20425 -Node: LOT PRICES LOT DATES22855 -Ref: #lot-prices-lot-dates23029 -Node: BALANCE ASSERTIONS23516 -Ref: #balance-assertions23685 -Node: Assertions and ordering24715 -Ref: #assertions-and-ordering24899 -Node: Assertions and included files25596 -Ref: #assertions-and-included-files25835 -Node: Assertions and multiple -f options26166 -Ref: #assertions-and-multiple--f-options26418 -Node: Assertions and commodities26549 -Ref: #assertions-and-commodities26777 -Node: Assertions and prices27932 -Ref: #assertions-and-prices28142 -Node: Assertions and subaccounts28583 -Ref: #assertions-and-subaccounts28808 -Node: Assertions and virtual postings29132 -Ref: #assertions-and-virtual-postings29370 -Node: Assertions and precision29511 -Ref: #assertions-and-precision29700 -Node: BALANCE ASSIGNMENTS29965 -Ref: #balance-assignments30126 -Node: Balance assignments and prices31289 -Ref: #balance-assignments-and-prices31457 -Node: DIRECTIVES31683 -Ref: #directives31829 -Node: Directives and multiple files37274 -Ref: #directives-and-multiple-files37453 -Node: Comment blocks38115 -Ref: #comment-blocks38294 -Node: Including other files38469 -Ref: #including-other-files38645 -Node: Default year39569 -Ref: #default-year39734 -Node: Declaring commodities40141 -Ref: #declaring-commodities40320 -Node: Commodity error checking42161 -Ref: #commodity-error-checking42317 -Node: Default commodity42573 -Ref: #default-commodity42755 -Node: Declaring market prices43640 -Ref: #declaring-market-prices43831 -Node: Declaring accounts44689 -Ref: #declaring-accounts44871 -Node: Account error checking46078 -Ref: #account-error-checking46250 -Node: Account comments47427 -Ref: #account-comments47617 -Node: Account subdirectives48043 -Ref: #account-subdirectives48234 -Node: Account types48549 -Ref: #account-types48729 -Node: Declaring account types49464 -Ref: #declaring-account-types49649 -Node: Auto-detected account types50300 -Ref: #auto-detected-account-types50547 -Node: Interference from auto-detected account types51446 -Ref: #interference-from-auto-detected-account-types51729 -Node: Old account type syntax52212 -Ref: #old-account-type-syntax52415 -Node: Account display order52716 -Ref: #account-display-order52882 -Node: Rewriting accounts54033 -Ref: #rewriting-accounts54214 -Node: Basic aliases54973 -Ref: #basic-aliases55115 -Node: Regex aliases55817 -Ref: #regex-aliases55985 -Node: Combining aliases56705 -Ref: #combining-aliases56894 -Node: Aliases and multiple files58171 -Ref: #aliases-and-multiple-files58376 -Node: end aliases58957 -Ref: #end-aliases59110 -Node: Default parent account59212 -Ref: #default-parent-account59376 -Node: PERIODIC TRANSACTIONS60260 -Ref: #periodic-transactions60422 -Node: Periodic rule syntax62339 -Ref: #periodic-rule-syntax62541 -Node: Two spaces between period expression and description!63244 -Ref: #two-spaces-between-period-expression-and-description63559 -Node: Forecasting with periodic transactions64244 -Ref: #forecasting-with-periodic-transactions64545 -Node: Budgeting with periodic transactions66591 -Ref: #budgeting-with-periodic-transactions66826 -Node: AUTO POSTINGS67233 -Ref: #auto-postings67360 -Node: Auto postings and multiple files69543 -Ref: #auto-postings-and-multiple-files69743 -Node: Auto postings and dates69951 -Ref: #auto-postings-and-dates70221 -Node: Auto postings and transaction balancing / inferred amounts / balance assertions70396 -Ref: #auto-postings-and-transaction-balancing-inferred-amounts-balance-assertions70744 -Node: Auto posting tags71089 -Ref: #auto-posting-tags71300 - -End Tag Table diff --git a/hledger_journal.txt b/hledger_journal.txt deleted file mode 100644 index 210741d..0000000 --- a/hledger_journal.txt +++ /dev/null @@ -1,1597 +0,0 @@ - -HLEDGER_JOURNAL(5) hledger User Manuals HLEDGER_JOURNAL(5) - - - -NAME - hledger's default file format, representing a General Journal. - -DESCRIPTION - hledger's usual data source is a plain text file containing journal - entries in hledger journal format. This file represents a standard - accounting general journal. I use file names ending in .journal, but - that's not required. The journal file contains a number of transaction - entries, each describing a transfer of money (or any commodity) between - two or more named accounts, in a simple format readable by both hledger - and humans. - - hledger's journal format is a compatible subset, mostly, of ledger's - journal format, so hledger can work with compatible ledger journal - files as well. It's safe, and encouraged, to run both hledger and - ledger on the same journal file, eg to validate the results you're get- - ting. - - You can use hledger without learning any more about this file; just use - the add or web or import commands to create and update it. - - Many users, though, edit the journal file with a text editor, and track - changes with a version control system such as git. Editor addons such - as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and - hledger-vscode for Visual Studio Code, make this easier, adding colour, - formatting, tab completion, and useful commands. See Editor configura- - tion at hledger.org for the full list. - - Here's a description of each part of the file format (and hledger's - data model). These are mostly in the order you'll use them, but in - some cases related concepts have been grouped together for easy refer- - ence, or linked before they are introduced, so feel free to skip over - anything that looks unnecessary right now. - -TRANSACTIONS - Transactions are the main unit of information in a journal file. They - represent events, typically a movement of some quantity of commodities - between two or more named accounts. - - Each transaction is recorded as a journal entry, beginning with a sim- - ple date in column 0. This can be followed by any of the following - optional fields, separated by spaces: - - o a status character (empty, !, or *) - - o a code (any short number or text, enclosed in parentheses) - - o a description (any remaining text until end of line or a semicolon) - - o a comment (any remaining text following a semicolon until end of - line, and any following indented lines beginning with a semicolon) - - o 0 or more indented posting lines, describing what was transferred and - the accounts involved (indented comment lines are also allowed, but - not blank lines or non-indented lines). - - Here's a simple journal file containing one transaction: - - 2008/01/01 income - assets:bank:checking $1 - income:salary $-1 - -DATES - Simple dates - Dates in the journal file use simple dates format: YYYY-MM-DD or - YYYY/MM/DD or YYYY.MM.DD, with leading zeros optional. The year may be - omitted, in which case it will be inferred from the context: the cur- - rent transaction, the default year set with a default year directive, - or the current date when the command is run. Some examples: - 2010-01-31, 2010/01/31, 2010.1.31, 1/31. - - (The UI also accepts simple dates, as well as the more flexible smart - dates documented in the hledger manual.) - - Secondary dates - Real-life transactions sometimes involve more than one date - eg the - date you write a cheque, and the date it clears in your bank. When you - want to model this, for more accurate daily balances, you can specify - individual posting dates. - - Or, you can use the older secondary date feature (Ledger calls it aux- - iliary date or effective date). Note: we support this for compatibil- - ity, but I usually recommend avoiding this feature; posting dates are - almost always clearer and simpler. - - A secondary date is written after the primary date, following an equals - sign. If the year is omitted, the primary date's year is assumed. - When running reports, the primary (left) date is used by default, but - with the --date2 flag (or --aux-date or --effective), the secondary - (right) date will be used instead. - - The meaning of secondary dates is up to you, but it's best to follow a - consistent rule. Eg "primary = the bank's clearing date, secondary = - date the transaction was initiated, if different", as shown here: - - 2010/2/23=2/19 movie ticket - expenses:cinema $10 - assets:checking - - $ hledger register checking - 2010-02-23 movie ticket assets:checking $-10 $-10 - - $ hledger register checking --date2 - 2010-02-19 movie ticket assets:checking $-10 $-10 - - Posting dates - You can give individual postings a different date from their parent - transaction, by adding a posting comment containing a tag (see below) - like date:DATE. This is probably the best way to control posting dates - precisely. Eg in this example the expense should appear in May - reports, and the deduction from checking should be reported on 6/1 for - easy bank reconciliation: - - 2015/5/30 - expenses:food $10 ; food purchased on saturday 5/30 - assets:checking ; bank cleared it on monday, date:6/1 - - $ hledger -f t.j register food - 2015-05-30 expenses:food $10 $10 - - $ hledger -f t.j register checking - 2015-06-01 assets:checking $-10 $-10 - - DATE should be a simple date; if the year is not specified it will use - the year of the transaction's date. You can set the secondary date - similarly, with date2:DATE2. The date: or date2: tags must have a - valid simple date value if they are present, eg a date: tag with no - value is not allowed. - - Ledger's earlier, more compact bracketed date syntax is also supported: - [DATE], [DATE=DATE2] or [=DATE2]. hledger will attempt to parse any - square-bracketed sequence of the 0123456789/-.= characters in this way. - With this syntax, DATE infers its year from the transaction and DATE2 - infers its year from DATE. - -STATUS - Transactions, or individual postings within a transaction, can have a - status mark, which is a single character before the transaction - description or posting account name, separated from it by a space, - indicating one of three statuses: - - - mark status - ------------------ - unmarked - ! pending - * cleared - - When reporting, you can filter by status with the -U/--unmarked, - -P/--pending, and -C/--cleared flags; or the status:, status:!, and - status:* queries; or the U, P, C keys in hledger-ui. - - Note, in Ledger and in older versions of hledger, the "unmarked" state - is called "uncleared". As of hledger 1.3 we have renamed it to - unmarked for clarity. - - To replicate Ledger and old hledger's behaviour of also matching pend- - ing, combine -U and -P. - - Status marks are optional, but can be helpful eg for reconciling with - real-world accounts. Some editor modes provide highlighting and short- - cuts for working with status. Eg in Emacs ledger-mode, you can toggle - transaction status with C-c C-e, or posting status with C-c C-c. - - What "uncleared", "pending", and "cleared" actually mean is up to you. - Here's one suggestion: - - - status meaning - -------------------------------------------------------------------------- - uncleared recorded but not yet reconciled; needs review - pending tentatively reconciled (if needed, eg during a big reconcil- - iation) - cleared complete, reconciled as far as possible, and considered cor- - rect - - With this scheme, you would use -PC to see the current balance at your - bank, -U to see things which will probably hit your bank soon (like - uncashed checks), and no flags to see the most up-to-date state of your - finances. - -DESCRIPTION - A transaction's description is the rest of the line following the date - and status mark (or until a comment begins). Sometimes called the - "narration" in traditional bookkeeping, it can be used for whatever you - wish, or left blank. Transaction descriptions can be queried, unlike - comments. - - Payee and note - You can optionally include a | (pipe) character in descriptions to sub- - divide the description into separate fields for payee/payer name on the - left (up to the first |) and an additional note field on the right - (after the first |). This may be worthwhile if you need to do more - precise querying and pivoting by payee or by note. - -COMMENTS - Lines in the journal beginning with a semicolon (;) or hash (#) or star - (*) are comments, and will be ignored. (Star comments cause org-mode - nodes to be ignored, allowing emacs users to fold and navigate their - journals with org-mode or orgstruct-mode.) - - You can attach comments to a transaction by writing them after the - description and/or indented on the following lines (before the post- - ings). Similarly, you can attach comments to an individual posting by - writing them after the amount and/or indented on the following lines. - Transaction and posting comments must begin with a semicolon (;). - - Some examples: - - # a file comment - ; another file comment - * also a file comment, useful in org/orgstruct mode - - comment - A multiline file comment, which continues - until a line containing just "end comment" - (or end of file). - end comment - - 2012/5/14 something ; a transaction comment - ; the transaction comment, continued - posting1 1 ; a comment for posting 1 - posting2 - ; a comment for posting 2 - ; another comment line for posting 2 - ; a file comment (because not indented) - - You can also comment larger regions of a file using comment and end - comment directives. - -TAGS - Tags are a way to add extra labels or labelled data to postings and - transactions, which you can then search or pivot on. - - A simple tag is a word (which may contain hyphens) followed by a full - colon, written inside a transaction or posting comment line: - - 2017/1/16 bought groceries ; sometag: - - Tags can have a value, which is the text after the colon, up to the - next comma or end of line, with leading/trailing whitespace removed: - - expenses:food $10 ; a-posting-tag: the tag value - - Note this means hledger's tag values can not contain commas or new- - lines. Ending at commas means you can write multiple short tags on one - line, comma separated: - - assets:checking ; a comment containing tag1:, tag2: some value ... - - Here, - - o "a comment containing" is just comment text, not a tag - - o "tag1" is a tag with no value - - o "tag2" is another tag, whose value is "some value ..." - - Tags in a transaction comment affect the transaction and all of its - postings, while tags in a posting comment affect only that posting. - For example, the following transaction has three tags (A, TAG2, third- - tag) and the posting has four (those plus posting-tag): - - 1/1 a transaction ; A:, TAG2: - ; third-tag: a third transaction tag, <- with a value - (a) $1 ; posting-tag: - - Tags are like Ledger's metadata feature, except hledger's tag values - are simple strings. - -POSTINGS - A posting is an addition of some amount to, or removal of some amount - from, an account. Each posting line begins with at least one space or - tab (2 or 4 spaces is common), followed by: - - o (optional) a status character (empty, !, or *), followed by a space - - o (required) an account name (any text, optionally containing single - spaces, until end of line or a double space) - - o (optional) two or more spaces or tabs followed by an amount. - - Positive amounts are being added to the account, negative amounts are - being removed. - - The amounts within a transaction must always sum up to zero. As a con- - venience, one amount may be left blank; it will be inferred so as to - balance the transaction. - - Be sure to note the unusual two-space delimiter between account name - and amount. This makes it easy to write account names containing spa- - ces. But if you accidentally leave only one space (or tab) before the - amount, the amount will be considered part of the account name. - - Virtual postings - A posting with a parenthesised account name is called a virtual posting - or unbalanced posting, which means it is exempt from the usual rule - that a transaction's postings must balance add up to zero. - - This is not part of double entry accounting, so you might choose to - avoid this feature. Or you can use it sparingly for certain special - cases where it can be convenient. Eg, you could set opening balances - without using a balancing equity account: - - 1/1 opening balances - (assets:checking) $1000 - (assets:savings) $2000 - - A posting with a bracketed account name is called a balanced virtual - posting. The balanced virtual postings in a transaction must add up to - zero (separately from other postings). Eg: - - 1/1 buy food with cash, update budget envelope subaccounts, & something else - assets:cash $-10 ; <- these balance - expenses:food $7 ; <- - expenses:food $3 ; <- - [assets:checking:budget:food] $-10 ; <- and these balance - [assets:checking:available] $10 ; <- - (something:else) $5 ; <- not required to balance - - Ordinary non-parenthesised, non-bracketed postings are called real - postings. You can exclude virtual postings from reports with the - -R/--real flag or real:1 query. - -ACCOUNT NAMES - Account names typically have several parts separated by a full colon, - from which hledger derives a hierarchical chart of accounts. They can - be anything you like, but in finance there are traditionally five top- - level accounts: assets, liabilities, income, expenses, and equity. - - Account names may contain single spaces, eg: assets:accounts receiv- - able. Because of this, they must always be followed by two or more - spaces (or newline). - - Account names can be aliased. - -AMOUNTS - After the account name, there is usually an amount. (Important: - between account name and amount, there must be two or more spaces.) - - hledger's amount format is flexible, supporting several international - formats. Here are some examples. Amounts have a number (the "quan- - tity"): - - 1 - - ..and usually a currency or commodity name (the "commodity"). This is - a symbol, word, or phrase, to the left or right of the quantity, with - or without a separating space: - - $1 - 4000 AAPL - - If the commodity name contains spaces, numbers, or punctuation, it must - be enclosed in double quotes: - - 3 "no. 42 green apples" - - Amounts can be preceded by a minus sign (or a plus sign, though plus is - the default), The sign can be written before or after a left-side com- - modity symbol: - - -$1 - $-1 - - One or more spaces between the sign and the number are acceptable when - parsing (but they won't be displayed in output): - - + $1 - $- 1 - - Scientific E notation is allowed: - - 1E-6 - EUR 1E3 - - A decimal mark can be written as a period or a comma: - - 1.23 - 1,23456780000009 - - Digit group marks - In the integer part of the quantity (left of the decimal mark), groups - of digits can optionally be separated by a "digit group mark" - a - space, comma, or period (different from the decimal mark): - - $1,000,000.00 - EUR 2.000.000,00 - INR 9,99,99,999.00 - 1 000 000.9455 - - Note, a number containing a single group mark and no decimal mark is - ambiguous. Are these group marks or decimal marks ? - - 1,000 - 1.000 - - hledger will treat them both as decimal marks by default (cf #793). If - you use digit group marks, to prevent confusion and undetected typos we - recommend you write commodity directives at the top of the file to - explicitly declare the decimal mark (and optionally a digit group - mark). Note, these formats ("amount styles") are specific to each com- - modity, so if your data uses multiple formats, hledger can handle it: - - commodity $1,000.00 - commodity EUR 1.000,00 - commodity INR 9,99,99,999.00 - commodity 1 000 000.9455 - - - Commodity display style - For each commodity, hledger chooses a consistent style to use when dis- - playing amounts. (Except price amounts, which are always displayed as - written). The display style is chosen as follows: - - o If there is a commodity directive (or default commodity directive) - for the commodity, its style is used (see examples above). - - o Otherwise the style is inferred from the amounts in that commodity - seen in the journal. - - o Or if there are no such amounts in the journal, a default style is - used (like $1000.00). - - A style is inferred from the journal amounts in a commodity as follows: - - o Use the general style (decimal mark, symbol placement) of the first - amount - - o Use the first-seen digit group style (digit group mark, digit group - sizes), if any - - o Use the maximum number of decimal places of all. - - Transaction price amounts don't affect the commodity display style - directly, but occasionally they can do so indirectly (eg when a post- - ing's amount is inferred using a transaction price). If you find this - causing problems, use a commodity directive to fix the display style. - - In summary, each commodity's amounts will be normalised to - - o the style declared by a commodity directive - - o or, the style of the first posting amount in the journal, with the - first-seen digit group style and the maximum-seen number of decimal - places. - - If reports are showing amounts in a way you don't like (eg, with too - many decimal places), use a commodity directive to set your preferred - style. - - Rounding - Amounts are stored internally as decimal numbers with up to 255 decimal - places, and displayed with the number of decimal places specified by - the commodity display style. Note, hledger uses banker's rounding: it - rounds to the nearest even number, eg 0.5 displayed with zero decimal - places is "0"). (Guaranteed since hledger 1.17.1; in older versions - this could vary if hledger was built with Decimal < 0.5.1.) - -TRANSACTION PRICES - Within a transaction, you can note an amount's price in another commod- - ity. This can be used to document the cost (in a purchase) or selling - price (in a sale). For example, transaction prices are useful to - record purchases of a foreign currency. Note transaction prices are - fixed at the time of the transaction, and do not change over time. See - also market prices, which represent prevailing exchange rates on a cer- - tain date. - - There are several ways to record a transaction price: - - 1. Write the price per unit, as @ UNITPRICE after the amount: - - 2009/1/1 - assets:euros EUR100 @ $1.35 ; one hundred euros purchased at $1.35 each - assets:dollars ; balancing amount is -$135.00 - - 2. Write the total price, as @@ TOTALPRICE after the amount: - - 2009/1/1 - assets:euros EUR100 @@ $135 ; one hundred euros purchased at $135 for the lot - assets:dollars - - 3. Specify amounts for all postings, using exactly two commodities, and - let hledger infer the price that balances the transaction: - - 2009/1/1 - assets:euros EUR100 ; one hundred euros purchased - assets:dollars $-135 ; for $135 - - 4. Like 1, but the @ is parenthesised, i.e. (@); this is for compati- - bility with Ledger journals (Virtual posting costs), and is equiva- - lent to 1 in hledger. - - 5. Like 2, but as in 4 the @@ is parenthesised, i.e. (@@); in hledger, - this is equivalent to 2. - - Use the -B/--cost flag to convert amounts to their transaction price's - commodity, if any. (mnemonic: "B" is from "cost Basis", as in Ledger). - Eg here is how -B affects the balance report for the example above: - - $ hledger bal -N --flat - $-135 assets:dollars - EUR100 assets:euros - $ hledger bal -N --flat -B - $-135 assets:dollars - $135 assets:euros # <- the euros' cost - - Note -B is sensitive to the order of postings when a transaction price - is inferred: the inferred price will be in the commodity of the last - amount. So if example 3's postings are reversed, while the transaction - is equivalent, -B shows something different: - - 2009/1/1 - assets:dollars $-135 ; 135 dollars sold - assets:euros EUR100 ; for 100 euros - - $ hledger bal -N --flat -B - EUR-100 assets:dollars # <- the dollars' selling price - EUR100 assets:euros - -LOT PRICES, LOT DATES - Ledger allows another kind of price, lot price (four variants: {UNIT- - PRICE}, {{TOTALPRICE}}, {=FIXEDUNITPRICE}, {{=FIXEDTOTALPRICE}}), - and/or a lot date ([DATE]) to be specified. These are normally used to - select a lot when selling investments. hledger will parse these, for - compatibility with Ledger journals, but currently ignores them. A - transaction price, lot price and/or lot date may appear in any order, - after the posting amount and before the balance assertion if any. - -BALANCE ASSERTIONS - hledger supports Ledger-style balance assertions in journal files. - These look like, for example, = EXPECTEDBALANCE following a posting's - amount. Eg here we assert the expected dollar balance in accounts a - and b after each posting: - - 2013/1/1 - a $1 =$1 - b =$-1 - - 2013/1/2 - a $1 =$2 - b $-1 =$-2 - - After reading a journal file, hledger will check all balance assertions - and report an error if any of them fail. Balance assertions can pro- - tect you from, eg, inadvertently disrupting reconciled balances while - cleaning up old entries. You can disable them temporarily with the - -I/--ignore-assertions flag, which can be useful for troubleshooting or - for reading Ledger files. (Note: this flag currently does not disable - balance assignments, below). - - Assertions and ordering - hledger sorts an account's postings and assertions first by date and - then (for postings on the same day) by parse order. Note this is dif- - ferent from Ledger, which sorts assertions only by parse order. (Also, - Ledger assertions do not see the accumulated effect of repeated post- - ings to the same account within a transaction.) - - So, hledger balance assertions keep working if you reorder differently- - dated transactions within the journal. But if you reorder same-dated - transactions or postings, assertions might break and require updating. - This order dependence does bring an advantage: precise control over the - order of postings and assertions within a day, so you can assert intra- - day balances. - - Assertions and included files - With included files, things are a little more complicated. Including - preserves the ordering of postings and assertions. If you have multi- - ple postings to an account on the same day, split across different - files, and you also want to assert the account's balance on the same - day, you'll have to put the assertion in the right file. - - Assertions and multiple -f options - Balance assertions don't work well across files specified with multiple - -f options. Use include or concatenate the files instead. - - Assertions and commodities - The asserted balance must be a simple single-commodity amount, and in - fact the assertion checks only this commodity's balance within the - (possibly multi-commodity) account balance. This is how assertions - work in Ledger also. We could call this a "partial" balance assertion. - - To assert the balance of more than one commodity in an account, you can - write multiple postings, each asserting one commodity's balance. - - You can make a stronger "total" balance assertion by writing a double - equals sign (== EXPECTEDBALANCE). This asserts that there are no other - unasserted commodities in the account (or, that their balance is 0). - - 2013/1/1 - a $1 - a 1EUR - b $-1 - c -1EUR - - 2013/1/2 ; These assertions succeed - a 0 = $1 - a 0 = 1EUR - b 0 == $-1 - c 0 == -1EUR - - 2013/1/3 ; This assertion fails as 'a' also contains 1EUR - a 0 == $1 - - It's not yet possible to make a complete assertion about a balance that - has multiple commodities. One workaround is to isolate each commodity - into its own subaccount: - - 2013/1/1 - a:usd $1 - a:euro 1EUR - b - - 2013/1/2 - a 0 == 0 - a:usd 0 == $1 - a:euro 0 == 1EUR - - Assertions and prices - Balance assertions ignore transaction prices, and should normally be - written without one: - - 2019/1/1 - (a) $1 @ EUR1 = $1 - - We do allow prices to be written there, however, and print shows them, - even though they don't affect whether the assertion passes or fails. - This is for backward compatibility (hledger's close command used to - generate balance assertions with prices), and because balance assign- - ments do use them (see below). - - Assertions and subaccounts - The balance assertions above (= and ==) do not count the balance from - subaccounts; they check the account's exclusive balance only. You can - assert the balance including subaccounts by writing =* or ==*, eg: - - 2019/1/1 - equity:opening balances - checking:a 5 - checking:b 5 - checking 1 ==* 11 - - Assertions and virtual postings - Balance assertions are checked against all postings, both real and vir- - tual. They are not affected by the --real/-R flag or real: query. - - Assertions and precision - Balance assertions compare the exactly calculated amounts, which are - not always what is shown by reports. Eg a commodity directive may - limit the display precision, but this will not affect balance asser- - tions. Balance assertion failure messages show exact amounts. - -BALANCE ASSIGNMENTS - Ledger-style balance assignments are also supported. These are like - balance assertions, but with no posting amount on the left side of the - equals sign; instead it is calculated automatically so as to satisfy - the assertion. This can be a convenience during data entry, eg when - setting opening balances: - - ; starting a new journal, set asset account balances - 2016/1/1 opening balances - assets:checking = $409.32 - assets:savings = $735.24 - assets:cash = $42 - equity:opening balances - - or when adjusting a balance to reality: - - ; no cash left; update balance, record any untracked spending as a generic expense - 2016/1/15 - assets:cash = $0 - expenses:misc - - The calculated amount depends on the account's balance in the commodity - at that point (which depends on the previously-dated postings of the - commodity to that account since the last balance assertion or assign- - ment). Note that using balance assignments makes your journal a little - less explicit; to know the exact amount posted, you have to run hledger - or do the calculations yourself, instead of just reading it. - - Balance assignments and prices - A transaction price in a balance assignment will cause the calculated - amount to have that price attached: - - 2019/1/1 - (a) = $1 @ EUR2 - - $ hledger print --explicit - 2019-01-01 - (a) $1 @ EUR2 = $1 @ EUR2 - -DIRECTIVES - A directive is a line in the journal beginning with a special keyword, - that influences how the journal is processed. hledger's directives are - based on a subset of Ledger's, but there are many differences (and also - some differences between hledger versions). - - Directives' behaviour and interactions can get a little bit complex, so - here is a table summarising the directives and their effects, with - links to more detailed docs. Note part of this table is hidden when - viewed in a web browser - scroll it sideways to see more. - - - direc- end subdi- purpose can affect (as of - tive directive rec- 2018/06) - tives - ------------------------------------------------------------------------------------ - account any document account names, all entries in all - text declare account types & dis- files, before or - play order after - alias end rewrite account names following entries - aliases until end of cur- - rent file or end - directive - apply end apply prepend a common parent to following entries - account account account names until end of cur- - rent file or end - directive - comment end com- ignore part of journal following entries - ment until end of cur- - rent file or end - directive - commod- format declare a commodity and its number notation: - ity number notation & display following entries - style in that commodity - in all files ; dis- - play style: amounts - of that commodity - in reports - - - - - - - - - - - - - D declare a commodity to be default commodity: - used for commodityless following commod- - amounts, and its number ityless entries - notation & display style until end of cur- - rent file; number - notation: following - entries in that - commodity until end - of current file; - display style: - amounts of that - commodity in - reports - include include entries/directives what the included - from another file directives affect - P declare a market price for a amounts of that - commodity commodity in - reports, when -V is - used - Y declare a year for yearless following entries - dates until end of cur- - rent file - = declare an auto posting all entries in par- - rule, adding postings to ent/current/child - other transactions files (but not sib- - ling files, see - #1212) - - And some definitions: - - - subdi- optional indented directive line immediately following a parent - rec- directive - tive - number how to interpret numbers when parsing journal entries (the iden- - nota- tity of the decimal separator character). (Currently each com- - tion modity can have its own notation, even in the same file.) - dis- how to display amounts of a commodity in reports (symbol side - play and spacing, digit groups, decimal separator, decimal places) - style - direc- which entries and (when there are multiple files) which files - tive are affected by a directive - scope - - As you can see, directives vary in which journal entries and files they - affect, and whether they are focussed on input (parsing) or output - (reports). Some directives have multiple effects. - - Directives and multiple files - If you use multiple -f/--file options, or the include directive, - hledger will process multiple input files. But note that directives - which affect input (see above) typically last only until the end of the - file in which they occur. - - This may seem inconvenient, but it's intentional; it makes reports sta- - ble and deterministic, independent of the order of input. Otherwise - you could see different numbers if you happened to write -f options in - a different order, or if you moved includes around while cleaning up - your files. - - It can be surprising though; for example, it means that alias direc- - tives do not affect parent or sibling files (see below). - - Comment blocks - A line containing just comment starts a commented region of the file, - and a line containing just end comment (or the end of the current file) - ends it. See also comments. - - Including other files - You can pull in the content of additional files by writing an include - directive, like this: - - include FILEPATH - - Only journal files can include, and only journal, timeclock or timedot - files can be included (not CSV files, currently). - - If the file path does not begin with a slash, it is relative to the - current file's folder. - - A tilde means home directory, eg: include ~/main.journal. - - The path may contain glob patterns to match multiple files, eg: include - *.journal. - - There is limited support for recursive wildcards: **/ (the slash is - required) matches 0 or more subdirectories. It's not super convenient - since you have to avoid include cycles and including directories, but - this can be done, eg: include */**/*.journal. - - The path may also be prefixed to force a specific file format, overrid- - ing the file extension (as described in hledger.1 -> Input files): - include timedot:~/notes/2020*.md. - - Default year - You can set a default year to be used for subsequent dates which don't - specify a year. This is a line beginning with Y followed by the year. - Eg: - - Y2009 ; set default year to 2009 - - 12/15 ; equivalent to 2009/12/15 - expenses 1 - assets - - Y2010 ; change default year to 2010 - - 2009/1/30 ; specifies the year, not affected - expenses 1 - assets - - 1/31 ; equivalent to 2010/1/31 - expenses 1 - assets - - Declaring commodities - The commodity directive has several functions: - - 1. It declares commodities which may be used in the journal. This is - currently not enforced, but can serve as documentation. - - 2. It declares what decimal mark character (period or comma) to expect - when parsing input - useful to disambiguate international number - formats in your data. (Without this, hledger will parse both 1,000 - and 1.000 as 1). - - 3. It declares a commodity's display style in output - decimal and - digit group marks, number of decimal places, symbol placement etc. - - You are likely to run into one of the problems solved by commodity - directives, sooner or later, so it's a good idea to just always use - them to declare your commodities. - - A commodity directive is just the word commodity followed by an amount. - It may be written on a single line, like this: - - ; commodity EXAMPLEAMOUNT - - ; display AAAA amounts with the symbol on the right, space-separated, - ; using period as decimal point, with four decimal places, and - ; separating thousands with comma. - commodity 1,000.0000 AAAA - - or on multiple lines, using the "format" subdirective. (In this case - the commodity symbol appears twice and should be the same in both - places.): - - ; commodity SYMBOL - ; format EXAMPLEAMOUNT - - ; display indian rupees with currency name on the left, - ; thousands, lakhs and crores comma-separated, - ; period as decimal point, and two decimal places. - commodity INR - format INR 1,00,00,000.00 - - The quantity of the amount does not matter; only the format is signifi- - cant. The number must include a decimal mark: either a period or a - comma, followed by 0 or more decimal digits. - - Note hledger normally uses banker's rounding, so 0.5 displayed with - zero decimal digits is "0". (More at Commodity display style.) - - Commodity error checking - In strict mode, enabled with the -s/--strict flag, hledger will report - an error if a commodity symbol is used that has not been declared by a - commodity directive. This works similarly to account error checking, - see the notes there for more details. - - Default commodity - The D directive sets a default commodity, to be used for amounts with- - out a commodity symbol (ie, plain numbers). This commodity will be - applied to all subsequent commodity-less amounts, or until the next D - directive. (Note, this is different from Ledger's D.) - - For compatibility/historical reasons, D also acts like a commodity - directive, setting the commodity's display style (for output) and deci- - mal mark (for parsing input). As with commodity, the amount must - always be written with a decimal mark (period or comma). If both - directives are used, commodity's style takes precedence. - - The syntax is D AMOUNT. Eg: - - ; commodity-less amounts should be treated as dollars - ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) - D $1,000.00 - - 1/1 - a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 - b - - Declaring market prices - The P directive declares a market price, which is an exchange rate - between two commodities on a certain date. (In Ledger, they are called - "historical prices".) These are often obtained from a stock exchange, - cryptocurrency exchange, or the foreign exchange market. - - Here is the format: - - P DATE COMMODITYA COMMODITYBAMOUNT - - o DATE is a simple date - - o COMMODITYA is the symbol of the commodity being priced - - o COMMODITYBAMOUNT is an amount (symbol and quantity) in a second com- - modity, giving the price in commodity B of one unit of commodity A. - - These two market price directives say that one euro was worth 1.35 US - dollars during 2009, and $1.40 from 2010 onward: - - P 2009/1/1 EUR $1.35 - P 2010/1/1 EUR $1.40 - - The -V, -X and --value flags use these market prices to show amount - values in another commodity. See Valuation. - - Declaring accounts - account directives can be used to declare accounts (ie, the places that - amounts are transferred from and to). Though not required, these dec- - larations can provide several benefits: - - o They can document your intended chart of accounts, providing a refer- - ence. - - o They can help hledger know your accounts' types (asset, liability, - equity, revenue, expense), useful for reports like balancesheet and - incomestatement. - - o They control account display order in reports, allowing non-alpha- - betic sorting (eg Revenues to appear above Expenses). - - o They can store extra information about accounts (account numbers, - notes, etc.) - - o They help with account name completion in the add command, hledger- - iadd, hledger-web, ledger-mode etc. - - o In strict mode, they restrict which accounts may be posted to by - transactions, which helps detect typos. - - The simplest form is just the word account followed by a hledger-style - account name, eg this account directive declares the assets:bank:check- - ing account: - - account assets:bank:checking - - Account error checking - By default, accounts come into existence when a transaction references - them by name. This is convenient, but it means hledger can't warn you - when you mis-spell an account name in the journal. Usually you'll find - the error later, as an extra account in balance reports, or an incor- - rect balance when reconciling. - - In strict mode, enabled with the -s/--strict flag, hledger will report - an error if any transaction uses an account name that has not been - declared by an account directive. Some notes: - - o The declaration is case-sensitive; transactions must use the correct - account name capitalisation. - - o The account directive's scope is "whole file and below" (see direc- - tives). This means it affects all of the current file, and any files - it includes, but not parent or sibling files. The position of - account directives within the file does not matter, though it's usual - to put them at the top. - - o Accounts can only be declared in journal files (but will affect - included files in other formats). - - o It's currently not possible to declare "all possible subaccounts" - with a wildcard; every account posted to must be declared. - - Account comments - Comments, beginning with a semicolon, can be added: - - o on the same line, after two or more spaces (because ; is allowed in - account names) - - o on the next lines, indented - - An example of both: - - account assets:bank:checking ; same-line comment, note 2+ spaces before ; - ; next-line comment - ; another with tag, acctno:12345 (not used yet) - - Same-line comments are not supported by Ledger, or hledger <1.13. - - Account subdirectives - We also allow (and ignore) Ledger-style indented subdirectives, just - for compatibility.: - - account assets:bank:checking - format blah blah ; <- subdirective, ignored - - Here is the full syntax of account directives: - - account ACCTNAME [ACCTTYPE] [;COMMENT] - [;COMMENTS] - [LEDGER-STYLE SUBDIRECTIVES, IGNORED] - - Account types - hledger recognises five main types of account, corresponding to the - account classes in the accounting equation: - - Asset, Liability, Equity, Revenue, Expense. - - These account types are important for controlling which accounts appear - in the balancesheet, balancesheetequity, incomestatement reports (and - probably for other things in future). - - Additionally, we recognise the Cash type, which is also an Asset, and - which causes accounts to appear in the cashflow report. ("Cash" here - means liquid assets, eg bank balances but typically not investments or - receivables.) - - Declaring account types - Generally, to make these reports work you should declare your top-level - accounts and their types, using account directives with type: tags. - - The tag's value should be one of: Asset, Liability, Equity, Revenue, - Expense, Cash, A, L, E, R, X, C (all case insensitive). The type is - inherited by all subaccounts except where they override it. Here's a - complete example: - - account assets ; type: Asset - account assets:bank ; type: Cash - account assets:cash ; type: Cash - account liabilities ; type: Liability - account equity ; type: Equity - account revenues ; type: Revenue - account expenses ; type: Expense - - Auto-detected account types - If you happen to use common english top-level account names, you may - not need to declare account types, as they will be detected automati- - cally using the following rules: - - - If name matches regular account type is: - expression: - ---------------------------------------------- - ^assets?(:|$) Asset - ^(debts?|lia- Liability - bilit(y|ies))(:|$) - ^equity(:|$) Equity - ^(income|revenue)s?(:|$) Revenue - ^expenses?(:|$) Expense - - - If account type is Asset and name does not contain regu- account type - lar expression: is: - -------------------------------------------------------------------------- - (investment|receivable|:A/R|:fixed) Cash - - Even so, explicit declarations may be a good idea, for clarity and pre- - dictability. - - Interference from auto-detected account types - If you assign any account type, it's a good idea to assign all of them, - to prevent any confusion from mixing declared and auto-detected types. - Although it's unlikely to happen in real life, here's an example: with - the following journal, balancesheetequity shows "liabilities" in both - Liabilities and Equity sections. Declaring another account as - type:Liability would fix it: - - account liabilities ; type:Equity - - 2020-01-01 - assets 1 - liabilities 1 - equity -2 - - Old account type syntax - In some hledger journals you might instead see this old syntax (the - letters ALERX, separated from the account name by two or more spaces); - this is deprecated and may be removed soon: - - account assets A - account liabilities L - account equity E - account revenues R - account expenses X - - Account display order - Account directives also set the order in which accounts are displayed, - eg in reports, the hledger-ui accounts screen, and the hledger-web - sidebar. By default accounts are listed in alphabetical order. But if - you have these account directives in the journal: - - account assets - account liabilities - account equity - account revenues - account expenses - - you'll see those accounts displayed in declaration order, not alphabet- - ically: - - $ hledger accounts -1 - assets - liabilities - equity - revenues - expenses - - Undeclared accounts, if any, are displayed last, in alphabetical order. - - Note that sorting is done at each level of the account tree (within - each group of sibling accounts under the same parent). And currently, - this directive: - - account other:zoo - - would influence the position of zoo among other's subaccounts, but not - the position of other among the top-level accounts. This means: - - o you will sometimes declare parent accounts (eg account other above) - that you don't intend to post to, just to customize their display - order - - o sibling accounts stay together (you couldn't display x:y in between - a:b and a:c). - - Rewriting accounts - You can define account alias rules which rewrite your account names, or - parts of them, before generating reports. This can be useful for: - - o expanding shorthand account names to their full form, allowing easier - data entry and a less verbose journal - - o adapting old journals to your current chart of accounts - - o experimenting with new account organisations, like a new hierarchy or - combining two accounts into one - - o customising reports - - Account aliases also rewrite account names in account directives. They - do not affect account names being entered via hledger add or hledger- - web. - - See also Rewrite account names. - - Basic aliases - To set an account alias, use the alias directive in your journal file. - This affects all subsequent journal entries in the current file or its - included files. The spaces around the = are optional: - - alias OLD = NEW - - Or, you can use the --alias 'OLD=NEW' option on the command line. This - affects all entries. It's useful for trying out aliases interactively. - - OLD and NEW are case sensitive full account names. hledger will - replace any occurrence of the old account name with the new one. Sub- - accounts are also affected. Eg: - - alias checking = assets:bank:wells fargo:checking - ; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a" - - Regex aliases - There is also a more powerful variant that uses a regular expression, - indicated by the forward slashes: - - alias /REGEX/ = REPLACEMENT - - or --alias '/REGEX/=REPLACEMENT'. - - REGEX is a case-insensitive regular expression. Anywhere it matches - inside an account name, the matched part will be replaced by REPLACE- - MENT. If REGEX contains parenthesised match groups, these can be ref- - erenced by the usual numeric backreferences in REPLACEMENT. Eg: - - alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 - ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" - - Also note that REPLACEMENT continues to the end of line (or on command - line, to end of option argument), so it can contain trailing white- - space. - - Combining aliases - You can define as many aliases as you like, using journal directives - and/or command line options. - - Recursive aliases - where an account name is rewritten by one alias, - then by another alias, and so on - are allowed. Each alias sees the - effect of previously applied aliases. - - In such cases it can be important to understand which aliases will be - applied and in which order. For (each account name in) each journal - entry, we apply: - - 1. alias directives preceding the journal entry, most recently parsed - first (ie, reading upward from the journal entry, bottom to top) - - 2. --alias options, in the order they appeared on the command line - (left to right). - - In other words, for (an account name in) a given journal entry: - - o the nearest alias declaration before/above the entry is applied first - - o the next alias before/above that will be be applied next, and so on - - o aliases defined after/below the entry do not affect it. - - This gives nearby aliases precedence over distant ones, and helps pro- - vide semantic stability - aliases will keep working the same way inde- - pendent of which files are being read and in which order. - - In case of trouble, adding --debug=6 to the command line will show - which aliases are being applied when. - - Aliases and multiple files - As explained at Directives and multiple files, alias directives do not - affect parent or sibling files. Eg in this command, - - hledger -f a.aliases -f b.journal - - account aliases defined in a.aliases will not affect b.journal. - Including the aliases doesn't work either: - - include a.aliases - - 2020-01-01 ; not affected by a.aliases - foo 1 - bar - - This means that account aliases should usually be declared at the start - of your top-most file, like this: - - alias foo=Foo - alias bar=Bar - - 2020-01-01 ; affected by aliases above - foo 1 - bar - - include c.journal ; also affected - - end aliases - You can clear (forget) all currently defined aliases with the end - aliases directive: - - end aliases - - Default parent account - You can specify a parent account which will be prepended to all - accounts within a section of the journal. Use the apply account and - end apply account directives like so: - - apply account home - - 2010/1/1 - food $10 - cash - - end apply account - - which is equivalent to: - - 2010/01/01 - home:food $10 - home:cash $-10 - - If end apply account is omitted, the effect lasts to the end of the - file. Included files are also affected, eg: - - apply account business - include biz.journal - end apply account - apply account personal - include personal.journal - - Prior to hledger 1.0, legacy account and end spellings were also sup- - ported. - - A default parent account also affects account directives. It does not - affect account names being entered via hledger add or hledger-web. If - account aliases are present, they are applied after the default parent - account. - -PERIODIC TRANSACTIONS - Periodic transaction rules describe transactions that recur. They - allow hledger to generate temporary future transactions to help with - forecasting, so you don't have to write out each one in the journal, - and it's easy to try out different forecasts. - - Periodic transactions can be a little tricky, so before you use them, - read this whole section - or at least these tips: - - 1. Two spaces accidentally added or omitted will cause you trouble - - read about this below. - - 2. For troubleshooting, show the generated transactions with hledger - print --forecast tag:generated or hledger register --forecast - tag:generated. - - 3. Forecasted transactions will begin only after the last non-fore- - casted transaction's date. - - 4. Forecasted transactions will end 6 months from today, by default. - See below for the exact start/end rules. - - 5. period expressions can be tricky. Their documentation needs - improvement, but is worth studying. - - 6. Some period expressions with a repeating interval must begin on a - natural boundary of that interval. Eg in weekly from DATE, DATE - must be a monday. ~ weekly from 2019/10/1 (a tuesday) will give an - error. - - 7. Other period expressions with an interval are automatically expanded - to cover a whole number of that interval. (This is done to improve - reports, but it also affects periodic transactions. Yes, it's a bit - inconsistent with the above.) Eg: ~ every 10th day of month from - 2020/01, which is equivalent to ~ every 10th day of month from - 2020/01/01, will be adjusted to start on 2019/12/10. - - Periodic transaction rules also have a second meaning: they are used to - define budget goals, shown in budget reports. - - Periodic rule syntax - A periodic transaction rule looks like a normal journal entry, with the - date replaced by a tilde (~) followed by a period expression (mnemonic: - ~ looks like a recurring sine wave.): - - ~ monthly - expenses:rent $2000 - assets:bank:checking - - There is an additional constraint on the period expression: the start - date must fall on a natural boundary of the interval. Eg monthly from - 2018/1/1 is valid, but monthly from 2018/1/15 is not. - - Partial or relative dates (M/D, D, tomorrow, last week) in the period - expression can work (useful or not). They will be relative to today's - date, unless a Y default year directive is in effect, in which case - they will be relative to Y/1/1. - - Two spaces between period expression and description! - If the period expression is followed by a transaction description, - these must be separated by two or more spaces. This helps hledger know - where the period expression ends, so that descriptions can not acciden- - tally alter their meaning, as in this example: - - ; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2020" - ; || - ; vv - ~ every 2 months in 2020, we will review - assets:bank:checking $1500 - income:acme inc - - So, - - o Do write two spaces between your period expression and your transac- - tion description, if any. - - o Don't accidentally write two spaces in the middle of your period - expression. - - Forecasting with periodic transactions - The --forecast flag activates any periodic transaction rules in the - journal. They will generate temporary recurring transactions, which - are not saved in the journal, but will appear in all reports (eg - print). This can be useful for estimating balances into the future, or - experimenting with different scenarios. Or, it can be used as a data - entry aid: describe recurring transactions, and every so often copy the - output of print --forecast into the journal. - - These transactions will have an extra tag indicating which periodic - rule generated them: generated-transaction:~ PERIODICEXPR. And a simi- - lar, hidden tag (beginning with an underscore) which, because it's - never displayed by print, can be used to match transactions generated - "just now": _generated-transaction:~ PERIODICEXPR. - - Periodic transactions are generated within some forecast period. By - default, this - - o begins on the later of - - o the report start date if specified with -b/-p/date: - - o the day after the latest normal (non-periodic) transaction in the - journal, or today if there are no normal transactions. - - o ends on the report end date if specified with -e/-p/date:, or 6 - months (180 days) from today. - - This means that periodic transactions will begin only after the latest - recorded transaction. And a recorded transaction dated in the future - can prevent generation of periodic transactions. (You can avoid that - by writing the future transaction as a one-time periodic rule instead - - put tilde before the date, eg ~ YYYY-MM-DD ...). - - Or, you can set your own arbitrary "forecast period", which can overlap - recorded transactions, and need not be in the future, by providing an - option argument, like --forecast=PERIODEXPR. Note the equals sign is - required, a space won't work. PERIODEXPR is a period expression, which - can specify the start date, end date, or both, like in a date: query. - (See also hledger.1 -> Report start & end date). Some examples: - --forecast=202001-202004, --forecast=jan-, --forecast=2020. - - Budgeting with periodic transactions - With the --budget flag, currently supported by the balance command, - each periodic transaction rule declares recurring budget goals for the - specified accounts. Eg the first example above declares a goal of - spending $2000 on rent (and also, a goal of depositing $2000 into - checking) every month. Goals and actual performance can then be com- - pared in budget reports. - - See also: Budgeting and Forecasting. - - -AUTO POSTINGS - "Automated postings" or "auto postings" are extra postings which get - added automatically to transactions which match certain queries, - defined by "auto posting rules", when you use the --auto flag. - - An auto posting rule looks a bit like a transaction: - - = QUERY - ACCOUNT AMOUNT - ... - ACCOUNT [AMOUNT] - - except the first line is an equals sign (mnemonic: = suggests match- - ing), followed by a query (which matches existing postings), and each - "posting" line describes a posting to be generated, and the posting - amounts can be: - - o a normal amount with a commodity symbol, eg $2. This will be used - as-is. - - o a number, eg 2. The commodity symbol (if any) from the matched post- - ing will be added to this. - - o a numeric multiplier, eg *2 (a star followed by a number N). The - matched posting's amount (and total price, if any) will be multiplied - by N. - - o a multiplier with a commodity symbol, eg *$2 (a star, number N, and - symbol S). The matched posting's amount will be multiplied by N, and - its commodity symbol will be replaced with S. - - Any query term containing spaces must be enclosed in single or double - quotes, as on the command line. Eg, note the quotes around the second - query term below: - - = expenses:groceries 'expenses:dining out' - (budget:funds:dining out) *-1 - - Some examples: - - ; every time I buy food, schedule a dollar donation - = expenses:food - (liabilities:charity) $-1 - - ; when I buy a gift, also deduct that amount from a budget envelope subaccount - = expenses:gifts - assets:checking:gifts *-1 - assets:checking *1 - - 2017/12/1 - expenses:food $10 - assets:checking - - 2017/12/14 - expenses:gifts $20 - assets:checking - - $ hledger print --auto - 2017-12-01 - expenses:food $10 - assets:checking - (liabilities:charity) $-1 - - 2017-12-14 - expenses:gifts $20 - assets:checking - assets:checking:gifts -$20 - assets:checking $20 - - Auto postings and multiple files - An auto posting rule can affect any transaction in the current file, or - in any parent file or child file. Note, currently it will not affect - sibling files (when multiple -f/--file are used - see #1212). - - Auto postings and dates - A posting date (or secondary date) in the matched posting, or (taking - precedence) a posting date in the auto posting rule itself, will also - be used in the generated posting. - - Auto postings and transaction balancing / inferred amounts / balance asser- - tions - Currently, auto postings are added: - - o after missing amounts are inferred, and transactions are checked for - balancedness, - - o but before balance assertions are checked. - - Note this means that journal entries must be balanced both before and - after auto postings are added. This changed in hledger 1.12+; see #893 - for background. - - Auto posting tags - Automated postings will have some extra tags: - - o generated-posting:= QUERY - shows this was generated by an auto post- - ing rule, and the query - - o _generated-posting:= QUERY - a hidden tag, which does not appear in - hledger's output. This can be used to match postings generated "just - now", rather than generated in the past and saved to the journal. - - Also, any transaction that has been changed by auto posting rules will - have these tags added: - - o modified: - this transaction was modified - - o _modified: - a hidden tag not appearing in the comment; this transac- - tion was modified "just now". - - - -REPORTING BUGS - Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel - or hledger mail list) - - -AUTHORS - Simon Michael <simon@joyful.com> and contributors - - -COPYRIGHT - Copyright (C) 2007-2020 Simon Michael. - Released under GNU GPL v3 or later. - - -SEE ALSO - hledger(1), hledger-ui(1), hledger-web(1), ledger(1) - - hledger_journal(5), hledger_csv(5), hledger_timeclock(5), hledger_time- - dot(5) - - - -hledger-lib-1.20.4 December 2020 HLEDGER_JOURNAL(5) diff --git a/hledger_timeclock.5 b/hledger_timeclock.5 deleted file mode 100644 index f502693..0000000 --- a/hledger_timeclock.5 +++ /dev/null @@ -1,90 +0,0 @@ - -.TH "HLEDGER_TIMECLOCK" "5" "December 2020" "hledger-lib-1.20.4 " "hledger User Manuals" - - - -.SH NAME -.PP -The time logging format of timeclock.el, as read by hledger. -.SH DESCRIPTION -.PP -hledger can read timeclock files. -As with Ledger, these are (a subset of) timeclock.el\[aq]s format, -containing clock-in and clock-out entries as in the example below. -The date is a simple date. -The time format is HH:MM[:SS][+-ZZZZ]. -Seconds and timezone are optional. -The timezone, if present, must be four digits and is ignored (currently -the time is always interpreted as a local time). -.IP -.nf -\f[C] -i 2015/03/30 09:00:00 some:account name optional description after two spaces -o 2015/03/30 09:20:00 -i 2015/03/31 22:21:45 another account -o 2015/04/01 02:00:34 -\f[R] -.fi -.PP -hledger treats each clock-in/clock-out pair as a transaction posting -some number of hours to an account. -Or if the session spans more than one day, it is split into several -transactions, one for each day. -For the above time log, \f[C]hledger print\f[R] generates these journal -entries: -.IP -.nf -\f[C] -$ hledger -f t.timeclock print -2015-03-30 * optional description after two spaces - (some:account name) 0.33h - -2015-03-31 * 22:21-23:59 - (another account) 1.64h - -2015-04-01 * 00:00-02:00 - (another account) 2.01h -\f[R] -.fi -.PP -Here is a sample.timeclock to download and some queries to try: -.IP -.nf -\f[C] -$ hledger -f sample.timeclock balance # current time balances -$ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009 -$ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week -\f[R] -.fi -.PP -To generate time logs, ie to clock in and clock out, you could: -.IP \[bu] 2 -use emacs and the built-in timeclock.el, or the extended timeclock-x.el -and perhaps the extras in ledgerutils.el -.IP \[bu] 2 -at the command line, use these bash aliases: -\f[C]shell alias ti=\[dq]echo i \[ga]date \[aq]+%Y-%m-%d %H:%M:%S\[aq]\[ga] \[rs]$* >>$TIMELOG\[dq] alias to=\[dq]echo o \[ga]date \[aq]+%Y-%m-%d %H:%M:%S\[aq]\[ga] >>$TIMELOG\[dq]\f[R] -.IP \[bu] 2 -or use the old \f[C]ti\f[R] and \f[C]to\f[R] scripts in the ledger 2.x -repository. -These rely on a \[dq]timeclock\[dq] executable which I think is just the -ledger 2 executable renamed. - - -.SH "REPORTING BUGS" -Report bugs at http://bugs.hledger.org -(or on the #hledger IRC channel or hledger mail list) - -.SH AUTHORS -Simon Michael <simon@joyful.com> and contributors - -.SH COPYRIGHT - -Copyright (C) 2007-2020 Simon Michael. -.br -Released under GNU GPL v3 or later. - -.SH SEE ALSO -hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) - -hledger_journal(5), hledger_csv(5), hledger_timeclock(5), hledger_timedot(5)< |