lib: Make BalanceAssertion a full datatype
Note: simplifies/moves whitespace parsing out of the balance assertion parser.
This commit is contained in:
		
							parent
							
								
									22645881c1
								
							
						
					
					
						commit
						cde91fc5f4
					
				| @ -170,6 +170,7 @@ instance ToJSON AmountStyle where toJSON = genericToJSON defaultOptions | |||||||
| instance ToJSON Side where toJSON = genericToJSON defaultOptions | instance ToJSON Side where toJSON = genericToJSON defaultOptions | ||||||
| instance ToJSON DigitGroupStyle where toJSON = genericToJSON defaultOptions | instance ToJSON DigitGroupStyle where toJSON = genericToJSON defaultOptions | ||||||
| instance ToJSON MixedAmount where toJSON = genericToJSON defaultOptions | instance ToJSON MixedAmount where toJSON = genericToJSON defaultOptions | ||||||
|  | instance ToJSON BalanceAssertion where toJSON = genericToJSON defaultOptions | ||||||
| instance ToJSON Price where toJSON = genericToJSON defaultOptions | instance ToJSON Price where toJSON = genericToJSON defaultOptions | ||||||
| instance ToJSON MarketPrice where toJSON = genericToJSON defaultOptions | instance ToJSON MarketPrice where toJSON = genericToJSON defaultOptions | ||||||
| instance ToJSON PostingType where toJSON = genericToJSON defaultOptions | instance ToJSON PostingType where toJSON = genericToJSON defaultOptions | ||||||
| @ -213,6 +214,7 @@ instance ToSchema AmountStyle | |||||||
| instance ToSchema Side | instance ToSchema Side | ||||||
| instance ToSchema DigitGroupStyle | instance ToSchema DigitGroupStyle | ||||||
| instance ToSchema MixedAmount | instance ToSchema MixedAmount | ||||||
|  | instance ToSchema BalanceAssertion | ||||||
| instance ToSchema Price | instance ToSchema Price | ||||||
| #if MIN_VERSION_swagger2(2,1,5) | #if MIN_VERSION_swagger2(2,1,5) | ||||||
|   where declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions |   where declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions | ||||||
|  | |||||||
| @ -568,12 +568,13 @@ journalCheckBalanceAssertions j = | |||||||
| -- | Check a posting's balance assertion and return an error if it | -- | Check a posting's balance assertion and return an error if it | ||||||
| -- fails. | -- fails. | ||||||
| checkBalanceAssertion :: Posting -> MixedAmount -> Either String () | checkBalanceAssertion :: Posting -> MixedAmount -> Either String () | ||||||
| checkBalanceAssertion p@Posting{ pbalanceassertion = Just (ass,_)} amt | checkBalanceAssertion p@Posting{ pbalanceassertion = Just ass } bal | ||||||
|   | isReallyZeroAmount diff = Right () |   | isReallyZeroAmount diff = Right () | ||||||
|   | True    = Left err |   | True    = Left err | ||||||
|     where assertedcomm = acommodity ass |     where amt = baamount ass | ||||||
|           actualbal = fromMaybe nullamt $ find ((== assertedcomm) . acommodity) (amounts amt) |           assertedcomm = acommodity amt | ||||||
|           diff = ass - actualbal |           actualbal = fromMaybe nullamt $ find ((== assertedcomm) . acommodity) (amounts bal) | ||||||
|  |           diff = amt - actualbal | ||||||
|           diffplus | isNegativeAmount diff == False = "+" |           diffplus | isNegativeAmount diff == False = "+" | ||||||
|                    | otherwise = "" |                    | otherwise = "" | ||||||
|           err = printf (unlines |           err = printf (unlines | ||||||
| @ -591,13 +592,13 @@ checkBalanceAssertion p@Posting{ pbalanceassertion = Just (ass,_)} amt | |||||||
|                Nothing -> ":" -- shouldn't happen |                Nothing -> ":" -- shouldn't happen | ||||||
|                Just t ->  printf " in %s:\nin transaction:\n%s" |                Just t ->  printf " in %s:\nin transaction:\n%s" | ||||||
|                           (showGenericSourcePos pos) (chomp $ showTransaction t) :: String |                           (showGenericSourcePos pos) (chomp $ showTransaction t) :: String | ||||||
|                             where pos = snd $ fromJust $ pbalanceassertion p) |                             where pos = baposition $ fromJust $ pbalanceassertion p) | ||||||
|             (showPostingLine p) |             (showPostingLine p) | ||||||
|             (showDate $ postingDate p) |             (showDate $ postingDate p) | ||||||
|             (T.unpack $ paccount p) -- XXX pack |             (T.unpack $ paccount p) -- XXX pack | ||||||
|             assertedcomm |             assertedcomm | ||||||
|             (showAmount actualbal) |             (showAmount actualbal) | ||||||
|             (showAmount ass) |             (showAmount amt) | ||||||
|             (diffplus ++ showAmount diff) |             (diffplus ++ showAmount diff) | ||||||
| checkBalanceAssertion _ _ = Right () | checkBalanceAssertion _ _ = Right () | ||||||
| 
 | 
 | ||||||
| @ -717,7 +718,7 @@ checkInferAndRegisterAmounts (Right oldTx) = do | |||||||
|   where |   where | ||||||
|     inferFromAssignment :: Posting -> CurrentBalancesModifier s Posting |     inferFromAssignment :: Posting -> CurrentBalancesModifier s Posting | ||||||
|     inferFromAssignment p = maybe (return p) |     inferFromAssignment p = maybe (return p) | ||||||
|       (fmap (\a -> p { pamount = a, porigin = Just $ originalPosting p }) . setBalance (paccount p) . fst) |       (fmap (\a -> p { pamount = a, porigin = Just $ originalPosting p }) . setBalance (paccount p) . baamount) | ||||||
|       $ pbalanceassertion p |       $ pbalanceassertion p | ||||||
| 
 | 
 | ||||||
| -- | Adds a posting's amount to the posting's account balance and | -- | Adds a posting's amount to the posting's account balance and | ||||||
|  | |||||||
| @ -15,6 +15,9 @@ module Hledger.Data.Posting ( | |||||||
|   nullposting, |   nullposting, | ||||||
|   posting, |   posting, | ||||||
|   post, |   post, | ||||||
|  |   nullsourcepos, | ||||||
|  |   nullassertion, | ||||||
|  |   assertion, | ||||||
|   -- * operations |   -- * operations | ||||||
|   originalPosting, |   originalPosting, | ||||||
|   postingStatus, |   postingStatus, | ||||||
| @ -96,6 +99,16 @@ posting = nullposting | |||||||
| post :: AccountName -> Amount -> Posting | post :: AccountName -> Amount -> Posting | ||||||
| post acct amt = posting {paccount=acct, pamount=Mixed [amt]} | post acct amt = posting {paccount=acct, pamount=Mixed [amt]} | ||||||
| 
 | 
 | ||||||
|  | nullsourcepos :: GenericSourcePos | ||||||
|  | nullsourcepos = JournalSourcePos "" (1,1) | ||||||
|  | 
 | ||||||
|  | nullassertion, assertion :: BalanceAssertion | ||||||
|  | nullassertion = BalanceAssertion | ||||||
|  |                   {baamount=nullamt | ||||||
|  |                   ,baposition=nullsourcepos | ||||||
|  |                   } | ||||||
|  | assertion = nullassertion | ||||||
|  | 
 | ||||||
| -- Get the original posting, if any. | -- Get the original posting, if any. | ||||||
| originalPosting :: Posting -> Posting | originalPosting :: Posting -> Posting | ||||||
| originalPosting p = fromMaybe p $ porigin p | originalPosting p = fromMaybe p $ porigin p | ||||||
|  | |||||||
| @ -12,7 +12,6 @@ tags. | |||||||
| 
 | 
 | ||||||
| module Hledger.Data.Transaction ( | module Hledger.Data.Transaction ( | ||||||
|   -- * Transaction |   -- * Transaction | ||||||
|   nullsourcepos, |  | ||||||
|   nulltransaction, |   nulltransaction, | ||||||
|   txnTieKnot, |   txnTieKnot, | ||||||
|   txnUntieKnot, |   txnUntieKnot, | ||||||
| @ -77,9 +76,6 @@ showGenericSourcePos = \case | |||||||
|     GenericSourcePos fp line column -> show fp ++ " (line " ++ show line ++ ", column " ++ show column ++ ")" |     GenericSourcePos fp line column -> show fp ++ " (line " ++ show line ++ ", column " ++ show column ++ ")" | ||||||
|     JournalSourcePos fp (line, line') -> show fp ++ " (lines " ++ show line ++ "-" ++ show line' ++ ")" |     JournalSourcePos fp (line, line') -> show fp ++ " (lines " ++ show line ++ "-" ++ show line' ++ ")" | ||||||
| 
 | 
 | ||||||
| nullsourcepos :: GenericSourcePos |  | ||||||
| nullsourcepos = JournalSourcePos "" (1,1) |  | ||||||
| 
 |  | ||||||
| nulltransaction :: Transaction | nulltransaction :: Transaction | ||||||
| nulltransaction = Transaction { | nulltransaction = Transaction { | ||||||
|                     tindex=0, |                     tindex=0, | ||||||
| @ -220,7 +216,7 @@ postingAsLines elideamount onelineamounts pstoalignwith p = concat [ | |||||||
|     | postingblock <- postingblocks] |     | postingblock <- postingblocks] | ||||||
|   where |   where | ||||||
|     postingblocks = [map rstrip $ lines $ concatTopPadded [statusandaccount, "  ", amount, assertion, samelinecomment] | amount <- shownAmounts] |     postingblocks = [map rstrip $ lines $ concatTopPadded [statusandaccount, "  ", amount, assertion, samelinecomment] | amount <- shownAmounts] | ||||||
|     assertion = maybe "" ((" = " ++) . showAmountWithZeroCommodity . fst) $ pbalanceassertion p |     assertion = maybe "" ((" = " ++) . showAmountWithZeroCommodity . baamount) $ pbalanceassertion p | ||||||
|     statusandaccount = indent $ fitString (Just $ minwidth) Nothing False True $ pstatusandacct p |     statusandaccount = indent $ fitString (Just $ minwidth) Nothing False True $ pstatusandacct p | ||||||
|         where |         where | ||||||
|           -- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned   |           -- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned   | ||||||
| @ -681,10 +677,8 @@ tests_Transaction = tests "Transaction" [ | |||||||
|           ,"    assets:checking" |           ,"    assets:checking" | ||||||
|           ,"" |           ,"" | ||||||
|           ] |           ] | ||||||
|     ] |  | ||||||
| 
 | 
 | ||||||
|   ,tests "showTransaction" [ |     ,test "show a balanced transaction, no eliding" $ | ||||||
|      test "show a balanced transaction, no eliding" $ |  | ||||||
|        (let t = Transaction 0 nullsourcepos (parsedate "2007/01/28") Nothing Unmarked "" "coopportunity" "" [] |        (let t = Transaction 0 nullsourcepos (parsedate "2007/01/28") Nothing Unmarked "" "coopportunity" "" [] | ||||||
|                 [posting{paccount="expenses:food:groceries", pamount=Mixed [usd 47.18], ptransaction=Just t} |                 [posting{paccount="expenses:food:groceries", pamount=Mixed [usd 47.18], ptransaction=Just t} | ||||||
|                 ,posting{paccount="assets:checking", pamount=Mixed [usd (-47.18)], ptransaction=Just t} |                 ,posting{paccount="assets:checking", pamount=Mixed [usd (-47.18)], ptransaction=Just t} | ||||||
|  | |||||||
| @ -236,7 +236,12 @@ instance Show Status where -- custom show.. bad idea.. don't do it.. | |||||||
|   show Pending   = "!" |   show Pending   = "!" | ||||||
|   show Cleared   = "*" |   show Cleared   = "*" | ||||||
| 
 | 
 | ||||||
| type BalanceAssertion = Maybe (Amount, GenericSourcePos) | data BalanceAssertion = BalanceAssertion { | ||||||
|  |       baamount   :: Amount, | ||||||
|  |       baposition :: GenericSourcePos | ||||||
|  |     } deriving (Eq,Typeable,Data,Generic,Show) | ||||||
|  | 
 | ||||||
|  | instance NFData BalanceAssertion | ||||||
| 
 | 
 | ||||||
| data Posting = Posting { | data Posting = Posting { | ||||||
|       pdate             :: Maybe Day,         -- ^ this posting's date, if different from the transaction's |       pdate             :: Maybe Day,         -- ^ this posting's date, if different from the transaction's | ||||||
| @ -246,14 +251,14 @@ data Posting = Posting { | |||||||
|       pamount           :: MixedAmount, |       pamount           :: MixedAmount, | ||||||
|       pcomment          :: Text,              -- ^ this posting's comment lines, as a single non-indented multi-line string |       pcomment          :: Text,              -- ^ this posting's comment lines, as a single non-indented multi-line string | ||||||
|       ptype             :: PostingType, |       ptype             :: PostingType, | ||||||
|       ptags             :: [Tag],             -- ^ tag names and values, extracted from the comment |       ptags             :: [Tag],                   -- ^ tag names and values, extracted from the comment | ||||||
|       pbalanceassertion :: BalanceAssertion,  -- ^ optional: the expected balance in this commodity in the account after this posting |       pbalanceassertion :: Maybe BalanceAssertion,  -- ^ optional: the expected balance in this commodity in the account after this posting | ||||||
|       ptransaction      :: Maybe Transaction, -- ^ this posting's parent transaction (co-recursive types). |       ptransaction      :: Maybe Transaction,       -- ^ this posting's parent transaction (co-recursive types). | ||||||
|                                               -- Tying this knot gets tedious, Maybe makes it easier/optional. |                                                     --   Tying this knot gets tedious, Maybe makes it easier/optional. | ||||||
|       porigin           :: Maybe Posting      -- ^ When this posting has been transformed in some way |       porigin           :: Maybe Posting            -- ^ When this posting has been transformed in some way | ||||||
|                                               --   (eg its amount or price was inferred, or the account name was |                                                     --   (eg its amount or price was inferred, or the account name was | ||||||
|                                               --   changed by a pivot or budget report), this references the original  |                                                     --   changed by a pivot or budget report), this references the original  | ||||||
|                                               --   untransformed posting (which will have Nothing in this field). |                                                     --   untransformed posting (which will have Nothing in this field). | ||||||
|     } deriving (Typeable,Data,Generic) |     } deriving (Typeable,Data,Generic) | ||||||
| 
 | 
 | ||||||
| instance NFData Posting | instance NFData Posting | ||||||
|  | |||||||
| @ -74,7 +74,7 @@ module Hledger.Read.Common ( | |||||||
|   mamountp', |   mamountp', | ||||||
|   commoditysymbolp, |   commoditysymbolp, | ||||||
|   priceamountp, |   priceamountp, | ||||||
|   partialbalanceassertionp, |   balanceassertionp, | ||||||
|   fixedlotpricep, |   fixedlotpricep, | ||||||
|   numberp, |   numberp, | ||||||
|   fromRawNumber, |   fromRawNumber, | ||||||
| @ -717,26 +717,16 @@ priceamountp = option NoPrice $ do | |||||||
| 
 | 
 | ||||||
|   pure $ priceConstructor priceAmount |   pure $ priceConstructor priceAmount | ||||||
| 
 | 
 | ||||||
| partialbalanceassertionp :: JournalParser m BalanceAssertion | balanceassertionp :: JournalParser m BalanceAssertion | ||||||
| partialbalanceassertionp = optional $ do | balanceassertionp = do | ||||||
|   sourcepos <- try $ do |   sourcepos <- genericSourcePos <$> lift getSourcePos | ||||||
|     lift (skipMany spacenonewline) |   char '=' | ||||||
|     sourcepos <- genericSourcePos <$> lift getSourcePos |  | ||||||
|     char '=' |  | ||||||
|     pure sourcepos |  | ||||||
|   lift (skipMany spacenonewline) |   lift (skipMany spacenonewline) | ||||||
|   a <- amountp <?> "amount (for a balance assertion or assignment)" -- XXX should restrict to a simple amount |   a <- amountp <?> "amount (for a balance assertion or assignment)" -- XXX should restrict to a simple amount | ||||||
|   return (a, sourcepos) |   return BalanceAssertion | ||||||
| 
 |     { baamount = a | ||||||
| -- balanceassertion :: Monad m => TextParser m (Maybe MixedAmount) |     , baposition = sourcepos | ||||||
| -- balanceassertion = |     } | ||||||
| --     try (do |  | ||||||
| --           lift (skipMany spacenonewline) |  | ||||||
| --           string "==" |  | ||||||
| --           lift (skipMany spacenonewline) |  | ||||||
| --           a <- amountp -- XXX should restrict to a simple amount |  | ||||||
| --           return $ Just $ Mixed [a]) |  | ||||||
| --          <|> return Nothing |  | ||||||
| 
 | 
 | ||||||
| -- http://ledger-cli.org/3.0/doc/ledger3.html#Fixing-Lot-Prices | -- http://ledger-cli.org/3.0/doc/ledger3.html#Fixing-Lot-Prices | ||||||
| fixedlotpricep :: JournalParser m (Maybe Amount) | fixedlotpricep :: JournalParser m (Maybe Amount) | ||||||
|  | |||||||
| @ -748,10 +748,14 @@ transactionFromCsvRecord sourcepos rules record = t | |||||||
|       tcomment                 = T.pack comment, |       tcomment                 = T.pack comment, | ||||||
|       tpreceding_comment_lines = T.pack precomment, |       tpreceding_comment_lines = T.pack precomment, | ||||||
|       tpostings                = |       tpostings                = | ||||||
|         [posting {paccount=account1, pamount=amount1, ptransaction=Just t, pbalanceassertion=balance} |         [posting {paccount=account1, pamount=amount1, ptransaction=Just t, pbalanceassertion=toAssertion <$> balance} | ||||||
|         ,posting {paccount=account2, pamount=amount2, ptransaction=Just t} |         ,posting {paccount=account2, pamount=amount2, ptransaction=Just t} | ||||||
|         ] |         ] | ||||||
|       } |       } | ||||||
|  |     toAssertion (a, b) = BalanceAssertion{ | ||||||
|  |       baamount   = a, | ||||||
|  |       baposition = b | ||||||
|  |       } | ||||||
| 
 | 
 | ||||||
| getAmountStr :: CsvRules -> CsvRecord -> Maybe String | getAmountStr :: CsvRules -> CsvRecord -> Maybe String | ||||||
| getAmountStr rules record = | getAmountStr rules record = | ||||||
|  | |||||||
| @ -589,7 +589,8 @@ postingp mTransactionYear = do | |||||||
|   let (ptype, account') = (accountNamePostingType account, textUnbracket account) |   let (ptype, account') = (accountNamePostingType account, textUnbracket account) | ||||||
|   lift (skipMany spacenonewline) |   lift (skipMany spacenonewline) | ||||||
|   amount <- option missingmixedamt $ Mixed . (:[]) <$> amountp |   amount <- option missingmixedamt $ Mixed . (:[]) <$> amountp | ||||||
|   massertion <- partialbalanceassertionp |   lift (skipMany spacenonewline) | ||||||
|  |   massertion <- optional $ balanceassertionp | ||||||
|   _ <- fixedlotpricep |   _ <- fixedlotpricep | ||||||
|   lift (skipMany spacenonewline) |   lift (skipMany spacenonewline) | ||||||
|   (comment,tags,mdate,mdate2) <- lift $ postingcommentp mTransactionYear |   (comment,tags,mdate,mdate2) <- lift $ postingcommentp mTransactionYear | ||||||
|  | |||||||
| @ -85,7 +85,7 @@ close CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do | |||||||
|       balancingamt = negate $ sum $ map (\(_,_,_,b) -> normaliseMixedAmountSquashPricesForDisplay b) acctbals |       balancingamt = negate $ sum $ map (\(_,_,_,b) -> normaliseMixedAmountSquashPricesForDisplay b) acctbals | ||||||
|       ps = [posting{paccount=a |       ps = [posting{paccount=a | ||||||
|                    ,pamount=mixed [b] |                    ,pamount=mixed [b] | ||||||
|                    ,pbalanceassertion=Just (b,nullsourcepos) |                    ,pbalanceassertion=Just assertion{ baamount=b } | ||||||
|                    } |                    } | ||||||
|            |(a,_,_,mb) <- acctbals |            |(a,_,_,mb) <- acctbals | ||||||
|            ,b <- amounts $ normaliseMixedAmountSquashPricesForDisplay mb |            ,b <- amounts $ normaliseMixedAmountSquashPricesForDisplay mb | ||||||
| @ -93,7 +93,7 @@ close CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do | |||||||
|            ++ [posting{paccount="equity:opening balances", pamount=balancingamt}] |            ++ [posting{paccount="equity:opening balances", pamount=balancingamt}] | ||||||
|       nps = [posting{paccount=a |       nps = [posting{paccount=a | ||||||
|                     ,pamount=mixed [negate b] |                     ,pamount=mixed [negate b] | ||||||
|                     ,pbalanceassertion=Just (b{aquantity=0}, nullsourcepos) |                     ,pbalanceassertion=Just assertion{ baamount=b{aquantity=0} } | ||||||
|                     } |                     } | ||||||
|             |(a,_,_,mb) <- acctbals |             |(a,_,_,mb) <- acctbals | ||||||
|             ,b <- amounts $ normaliseMixedAmountSquashPricesForDisplay mb |             ,b <- amounts $ normaliseMixedAmountSquashPricesForDisplay mb | ||||||
|  | |||||||
| @ -8,6 +8,7 @@ hledger is brought to you by: | |||||||
| -   Roman Cheplyaka - "chart" command, "add" command improvements | -   Roman Cheplyaka - "chart" command, "add" command improvements | ||||||
| -   Michael Snoyman - some additions to the Yesod web interface | -   Michael Snoyman - some additions to the Yesod web interface | ||||||
| -   Marko Kocić - hlint cleanup | -   Marko Kocić - hlint cleanup | ||||||
|  | -   Samuel May - exact assertions | ||||||
| 
 | 
 | ||||||
| Developers who have not yet signed the contributor agreement: | Developers who have not yet signed the contributor agreement: | ||||||
| 
 | 
 | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user