lib, cli, web: rename porigin -> poriginal

This commit is contained in:
Simon Michael 2019-02-20 20:07:40 -08:00
parent 2dc716cdb4
commit 0bc16d4af6
7 changed files with 11 additions and 11 deletions

View File

@ -745,7 +745,7 @@ addOrAssignAmountAndCheckAssertionB p@Posting{paccount=acc, pamount=amt, pbalanc
newbal = oldbalothercommodities + assignedbalthiscommodity newbal = oldbalothercommodities + assignedbalthiscommodity
diff <- setAmountB acc newbal diff <- setAmountB acc newbal
return (diff,newbal) return (diff,newbal)
let p' = p{pamount=diff, porigin=Just $ originalPosting p} let p' = p{pamount=diff, poriginal=Just $ originalPosting p}
whenM (R.reader bsAssrt) $ checkBalanceAssertionB p' newbal whenM (R.reader bsAssrt) $ checkBalanceAssertionB p' newbal
return p' return p'
@ -1050,7 +1050,7 @@ transactionPivot fieldortagname t = t{tpostings = map (postingPivot fieldortagna
-- | Replace this posting's account name with the value -- | Replace this posting's account name with the value
-- of the given field or tag, if any, otherwise the empty string. -- of the given field or tag, if any, otherwise the empty string.
postingPivot :: Text -> Posting -> Posting postingPivot :: Text -> Posting -> Posting
postingPivot fieldortagname p = p{paccount = pivotedacct, porigin = Just $ originalPosting p} postingPivot fieldortagname p = p{paccount = pivotedacct, poriginal = Just $ originalPosting p}
where where
pivotedacct pivotedacct
| Just t <- ptransaction p, fieldortagname == "code" = tcode t | Just t <- ptransaction p, fieldortagname == "code" = tcode t

View File

@ -91,7 +91,7 @@ nullposting = Posting
,ptags=[] ,ptags=[]
,pbalanceassertion=Nothing ,pbalanceassertion=Nothing
,ptransaction=Nothing ,ptransaction=Nothing
,porigin=Nothing ,poriginal=Nothing
} }
posting = nullposting posting = nullposting
@ -112,7 +112,7 @@ 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 $ poriginal p
-- XXX once rendered user output, but just for debugging now; clean up -- XXX once rendered user output, but just for debugging now; clean up
showPosting :: Posting -> String showPosting :: Posting -> String

View File

@ -416,7 +416,7 @@ inferBalancingAmount styles t@Transaction{tpostings=ps}
in in
case minferredamt of case minferredamt of
Nothing -> (p, Nothing) Nothing -> (p, Nothing)
Just a -> (p{pamount=a', porigin=Just $ originalPosting p}, Just a') Just a -> (p{pamount=a', poriginal=Just $ originalPosting p}, Just a')
where where
-- Inferred amounts are converted to cost. -- Inferred amounts are converted to cost.
-- Also ensure the new amount has the standard style for its commodity -- Also ensure the new amount has the standard style for its commodity
@ -483,7 +483,7 @@ priceInferrerFor t pt = inferprice
inferprice p@Posting{pamount=Mixed [a]} inferprice p@Posting{pamount=Mixed [a]}
| caninferprices && ptype p == pt && acommodity a == fromcommodity | caninferprices && ptype p == pt && acommodity a == fromcommodity
= p{pamount=Mixed [a{aprice=conversionprice}], porigin=Just $ originalPosting p} = p{pamount=Mixed [a{aprice=conversionprice}], poriginal=Just $ originalPosting p}
where where
fromcommodity = head $ filter (`elem` sumcommodities) pcommodities -- these heads are ugly but should be safe fromcommodity = head $ filter (`elem` sumcommodities) pcommodities -- these heads are ugly but should be safe
conversionprice conversionprice

View File

@ -297,7 +297,7 @@ data Posting = Posting {
-- in a single commodity, excluding subaccounts. -- in a single commodity, excluding subaccounts.
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 poriginal :: 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).
@ -324,7 +324,7 @@ instance Show Posting where
,"ptags=" ++ show ptags ,"ptags=" ++ show ptags
,"pbalanceassertion=" ++ show pbalanceassertion ,"pbalanceassertion=" ++ show pbalanceassertion
,"ptransaction=" ++ show (ptransaction $> "txn") ,"ptransaction=" ++ show (ptransaction $> "txn")
,"porigin=" ++ show porigin ,"poriginal=" ++ show poriginal
] ++ "}" ] ++ "}"
-- TODO: needs renaming, or removal if no longer needed. See also TextPosition in Hledger.UI.Editor -- TODO: needs renaming, or removal if no longer needed. See also TextPosition in Hledger.UI.Editor

View File

@ -171,7 +171,7 @@ budgetRollUp budgetedaccts showunbudgeted j = j { jtxns = remapTxn <$> jtxns j }
remapTxn = mapPostings (map remapPosting) remapTxn = mapPostings (map remapPosting)
where where
mapPostings f t = txnTieKnot $ t { tpostings = f $ tpostings t } mapPostings f t = txnTieKnot $ t { tpostings = f $ tpostings t }
remapPosting p = p { paccount = remapAccount $ paccount p, porigin = Just . fromMaybe p $ porigin p } remapPosting p = p { paccount = remapAccount $ paccount p, poriginal = Just . fromMaybe p $ poriginal p }
where where
remapAccount a remapAccount a
| hasbudget = a | hasbudget = a

View File

@ -69,7 +69,7 @@ instance ToJSON Posting where
-- in a dummy field. When re-parsed, there will be no parent. -- in a dummy field. When re-parsed, there will be no parent.
,"ptransaction_" .= toJSON (maybe "" (show.tindex) ptransaction) ,"ptransaction_" .= toJSON (maybe "" (show.tindex) ptransaction)
-- This is probably not wanted in json, we discard it. -- This is probably not wanted in json, we discard it.
,"porigin" .= toJSON (Nothing :: Maybe Posting) ,"poriginal" .= toJSON (Nothing :: Maybe Posting)
] ]
instance ToJSON Transaction instance ToJSON Transaction
instance ToJSON Account where instance ToJSON Account where

View File

@ -106,7 +106,7 @@ anonymise j
pAnons p = p { paccount = T.intercalate (T.pack ":") . map anon . T.splitOn (T.pack ":") . paccount $ p pAnons p = p { paccount = T.intercalate (T.pack ":") . map anon . T.splitOn (T.pack ":") . paccount $ p
, pcomment = T.empty , pcomment = T.empty
, ptransaction = fmap tAnons . ptransaction $ p , ptransaction = fmap tAnons . ptransaction $ p
, porigin = pAnons <$> porigin p , poriginal = pAnons <$> poriginal p
} }
tAnons txn = txn { tpostings = map pAnons . tpostings $ txn tAnons txn = txn { tpostings = map pAnons . tpostings $ txn
, tdescription = anon . tdescription $ txn , tdescription = anon . tdescription $ txn