lib: Commodity now has a CommoditySymbol and style
This commit is contained in:
		
							parent
							
								
									8312573fed
								
							
						
					
					
						commit
						207922a023
					
				| @ -104,7 +104,7 @@ type HledgerApi = | ||||
|          "accountnames" :> Get '[JSON] [AccountName] | ||||
|     :<|> "transactions" :> Get '[JSON] [Transaction] | ||||
|     :<|> "prices"       :> Get '[JSON] [MarketPrice] | ||||
|     :<|> "commodities"  :> Get '[JSON] [Commodity] | ||||
|     :<|> "commodities"  :> Get '[JSON] [CommoditySymbol] | ||||
|     :<|> "accounts"     :> Get '[JSON] [Account] | ||||
|     :<|> "accounts"     :> Capture "acct" AccountName :> Get '[JSON] AccountTransactionsReport | ||||
|     ) | ||||
|  | ||||
| @ -1,7 +1,7 @@ | ||||
| {-# LANGUAGE CPP, StandaloneDeriving, RecordWildCards #-} | ||||
| {-| | ||||
| A simple 'Amount' is some quantity of money, shares, or anything else. | ||||
| It has a (possibly null) 'Commodity' and a numeric quantity: | ||||
| It has a (possibly null) 'CommoditySymbol' and a numeric quantity: | ||||
| 
 | ||||
| @ | ||||
|   $1 | ||||
| @ -180,7 +180,7 @@ similarAmountsOp op Amount{acommodity=_,  aquantity=q1, astyle=AmountStyle{aspre | ||||
| 
 | ||||
| -- | Convert an amount to the specified commodity, ignoring and discarding | ||||
| -- any assigned prices and assuming an exchange rate of 1. | ||||
| amountWithCommodity :: Commodity -> Amount -> Amount | ||||
| amountWithCommodity :: CommoditySymbol -> Amount -> Amount | ||||
| amountWithCommodity c a = a{acommodity=c, aprice=NoPrice} | ||||
| 
 | ||||
| -- | Convert an amount to the commodity of its assigned price, if any.  Notes: | ||||
| @ -340,7 +340,7 @@ maxprecisionwithpoint = 999999 | ||||
| 
 | ||||
| -- like journalCanonicaliseAmounts | ||||
| -- | Canonicalise an amount's display style using the provided commodity style map. | ||||
| canonicaliseAmount :: M.Map Commodity AmountStyle -> Amount -> Amount | ||||
| canonicaliseAmount :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount | ||||
| canonicaliseAmount styles a@Amount{acommodity=c, astyle=s} = a{astyle=s'} | ||||
|     where | ||||
|       s' = findWithDefault s c styles | ||||
| @ -468,7 +468,7 @@ filterMixedAmount p (Mixed as) = Mixed $ filter p as | ||||
| -- with the specified commodity and the quantity of that commodity | ||||
| -- found in the original. NB if Amount's quantity is zero it will be | ||||
| -- discarded next time the MixedAmount gets normalised. | ||||
| filterMixedAmountByCommodity :: Commodity -> MixedAmount -> MixedAmount | ||||
| filterMixedAmountByCommodity :: CommoditySymbol -> MixedAmount -> MixedAmount | ||||
| filterMixedAmountByCommodity c (Mixed as) = Mixed as' | ||||
|   where | ||||
|     as' = case filter ((==c) . acommodity) as of | ||||
| @ -580,7 +580,7 @@ showMixedAmountOneLineWithoutPrice m = concat $ intersperse ", " $ map showAmoun | ||||
|       stripPrices (Mixed as) = Mixed $ map stripprice as where stripprice a = a{aprice=NoPrice} | ||||
| 
 | ||||
| -- | Canonicalise a mixed amount's display styles using the provided commodity style map. | ||||
| canonicaliseMixedAmount :: M.Map Commodity AmountStyle -> MixedAmount -> MixedAmount | ||||
| canonicaliseMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount | ||||
| canonicaliseMixedAmount styles (Mixed as) = Mixed $ map (canonicaliseAmount styles) as | ||||
| 
 | ||||
| ------------------------------------------------------------------------------- | ||||
|  | ||||
| @ -42,18 +42,18 @@ commoditysymbols = | ||||
|   ] | ||||
| 
 | ||||
| -- | Look up one of the sample commodities' symbol by name. | ||||
| comm :: String -> Commodity | ||||
| comm :: String -> CommoditySymbol | ||||
| comm name = snd $ fromMaybe | ||||
|               (error' "commodity lookup failed") | ||||
|               (find (\n -> fst n == name) commoditysymbols) | ||||
| 
 | ||||
| -- | Find the conversion rate between two commodities. Currently returns 1. | ||||
| conversionRate :: Commodity -> Commodity -> Double | ||||
| conversionRate :: CommoditySymbol -> CommoditySymbol -> Double | ||||
| conversionRate _ _ = 1 | ||||
| 
 | ||||
| -- -- | Convert a list of commodities to a map from commodity symbols to | ||||
| -- -- unique, display-preference-canonicalised commodities. | ||||
| -- canonicaliseCommodities :: [Commodity] -> Map.Map String Commodity | ||||
| -- canonicaliseCommodities :: [CommoditySymbol] -> Map.Map String CommoditySymbol | ||||
| -- canonicaliseCommodities cs = | ||||
| --     Map.fromList [(s,firstc{precision=maxp}) | s <- symbols, | ||||
| --                   let cs = commoditymap ! s, | ||||
|  | ||||
| @ -534,7 +534,7 @@ journalApplyCommodityStyles j@Journal{jtxns=ts, jmarketprices=mps} = j'' | ||||
|       fixamount a@Amount{acommodity=c} = a{astyle=journalCommodityStyle j' c} | ||||
| 
 | ||||
| -- | Get this journal's standard display style for the given commodity, or the null style. | ||||
| journalCommodityStyle :: Journal -> Commodity -> AmountStyle | ||||
| journalCommodityStyle :: Journal -> CommoditySymbol -> AmountStyle | ||||
| journalCommodityStyle j c = M.findWithDefault amountstyle c $ jcommoditystyles j | ||||
| 
 | ||||
| -- | Choose a standard display style for each commodity. | ||||
| @ -552,7 +552,7 @@ journalChooseCommodityStyles j = | ||||
| 
 | ||||
| -- | Given a list of amounts in parse order, build a map from their commodity names | ||||
| -- to standard commodity display formats. | ||||
| commodityStylesFromAmounts :: [Amount] -> M.Map Commodity AmountStyle | ||||
| commodityStylesFromAmounts :: [Amount] -> M.Map CommoditySymbol AmountStyle | ||||
| commodityStylesFromAmounts amts = M.fromList commstyles | ||||
|   where | ||||
|     samecomm = \a1 a2 -> acommodity a1 == acommodity a2 | ||||
| @ -591,8 +591,8 @@ canonicalStyleFrom ss@(first:_) = | ||||
| 
 | ||||
| -- -- | Get the price for a commodity on the specified day from the price database, if known. | ||||
| -- -- Does only one lookup step, ie will not look up the price of a price. | ||||
| -- journalMarketPriceFor :: Journal -> Day -> Commodity -> Maybe MixedAmount | ||||
| -- journalMarketPriceFor j d Commodity{symbol=s} = do | ||||
| -- journalMarketPriceFor :: Journal -> Day -> CommoditySymbol -> Maybe MixedAmount | ||||
| -- journalMarketPriceFor j d CommoditySymbol{symbol=s} = do | ||||
| --   let ps = reverse $ filter ((<= d).mpdate) $ filter ((s==).hsymbol) $ sortBy (comparing mpdate) $ jmarketprices j | ||||
| --   case ps of (MarketPrice{mpamount=a}:_) -> Just a | ||||
| --              _ -> Nothing | ||||
| @ -613,19 +613,19 @@ journalConvertAmountsToCost j@Journal{jtxns=ts} = j{jtxns=map fixtransaction ts} | ||||
|       fixamount = canonicaliseAmount (jcommoditystyles j) . costOfAmount | ||||
| 
 | ||||
| -- -- | Get this journal's unique, display-preference-canonicalised commodities, by symbol. | ||||
| -- journalCanonicalCommodities :: Journal -> M.Map String Commodity | ||||
| -- journalCanonicalCommodities :: Journal -> M.Map String CommoditySymbol | ||||
| -- journalCanonicalCommodities j = canonicaliseCommodities $ journalAmountCommodities j | ||||
| 
 | ||||
| -- -- | Get all this journal's amounts' commodities, in the order parsed. | ||||
| -- journalAmountCommodities :: Journal -> [Commodity] | ||||
| -- journalAmountCommodities :: Journal -> [CommoditySymbol] | ||||
| -- journalAmountCommodities = map acommodity . concatMap amounts . journalAmounts | ||||
| 
 | ||||
| -- -- | Get all this journal's amount and price commodities, in the order parsed. | ||||
| -- journalAmountAndPriceCommodities :: Journal -> [Commodity] | ||||
| -- journalAmountAndPriceCommodities :: Journal -> [CommoditySymbol] | ||||
| -- journalAmountAndPriceCommodities = concatMap amountCommodities . concatMap amounts . journalAmounts | ||||
| 
 | ||||
| -- -- | Get this amount's commodity and any commodities referenced in its price. | ||||
| -- amountCommodities :: Amount -> [Commodity] | ||||
| -- amountCommodities :: Amount -> [CommoditySymbol] | ||||
| -- amountCommodities Amount{acommodity=c,aprice=p} = | ||||
| --     case p of Nothing -> [c] | ||||
| --               Just (UnitPrice ma)  -> c:(concatMap amountCommodities $ amounts ma) | ||||
|  | ||||
| @ -84,7 +84,7 @@ ledgerDateSpan :: Ledger -> DateSpan | ||||
| ledgerDateSpan = postingsDateSpan . ledgerPostings | ||||
| 
 | ||||
| -- | All commodities used in this ledger. | ||||
| ledgerCommodities :: Ledger -> [Commodity] | ||||
| ledgerCommodities :: Ledger -> [CommoditySymbol] | ||||
| ledgerCommodities = M.keys . jcommoditystyles . ljournal | ||||
| 
 | ||||
| 
 | ||||
|  | ||||
| @ -270,7 +270,7 @@ transactionPostingBalances t = (sumPostings $ realPostings t | ||||
| -- | Is this transaction balanced ? A balanced transaction's real | ||||
| -- (non-virtual) postings sum to 0, and any balanced virtual postings | ||||
| -- also sum to 0. | ||||
| isTransactionBalanced :: Maybe (Map.Map Commodity AmountStyle) -> Transaction -> Bool | ||||
| isTransactionBalanced :: Maybe (Map.Map CommoditySymbol AmountStyle) -> Transaction -> Bool | ||||
| isTransactionBalanced styles t = | ||||
|     -- isReallyZeroMixedAmountCost rsum && isReallyZeroMixedAmountCost bvsum | ||||
|     isZeroMixedAmount rsum' && isZeroMixedAmount bvsum' | ||||
| @ -284,7 +284,7 @@ isTransactionBalanced styles t = | ||||
| -- amount or conversion price(s), or return an error message. | ||||
| -- Balancing is affected by commodity display precisions, so those can | ||||
| -- (optionally) be provided. | ||||
| balanceTransaction :: Maybe (Map.Map Commodity AmountStyle) -> Transaction -> Either String Transaction | ||||
| balanceTransaction :: Maybe (Map.Map CommoditySymbol AmountStyle) -> Transaction -> Either String Transaction | ||||
| balanceTransaction styles t = | ||||
|   case inferBalancingAmount t of | ||||
|     Left err -> Left err | ||||
|  | ||||
| @ -64,8 +64,6 @@ data Side = L | R deriving (Eq,Show,Read,Ord,Typeable,Data,Generic) | ||||
| 
 | ||||
| instance NFData Side | ||||
| 
 | ||||
| type Commodity = String | ||||
| 
 | ||||
| -- | The basic numeric type used in amounts. Different implementations | ||||
| -- can be selected via cabal flag for testing and benchmarking purposes. | ||||
| numberRepresentation :: String | ||||
| @ -111,8 +109,15 @@ data DigitGroupStyle = DigitGroups Char [Int] | ||||
| 
 | ||||
| instance NFData DigitGroupStyle | ||||
| 
 | ||||
| type CommoditySymbol = String | ||||
| 
 | ||||
| data Commodity = Commodity { | ||||
|   csymbol :: CommoditySymbol, | ||||
|   cformat :: Maybe AmountStyle | ||||
|   } -- deriving (Eq,Ord,Typeable,Data,Generic) | ||||
| 
 | ||||
| data Amount = Amount { | ||||
|       acommodity :: Commodity, | ||||
|       acommodity :: CommoditySymbol, | ||||
|       aquantity :: Quantity, | ||||
|       aprice :: Price,                -- ^ the (fixed) price for this amount, if any | ||||
|       astyle :: AmountStyle | ||||
| @ -217,7 +222,7 @@ instance NFData TimeclockEntry | ||||
| 
 | ||||
| data MarketPrice = MarketPrice { | ||||
|       mpdate :: Day, | ||||
|       mpcommodity :: Commodity, | ||||
|       mpcommodity :: CommoditySymbol, | ||||
|       mpamount :: Amount | ||||
|     } deriving (Eq,Ord,Typeable,Data,Generic) -- & Show (in Amount.hs) | ||||
| 
 | ||||
| @ -231,7 +236,7 @@ type Year = Integer | ||||
| -- is saved for later use by eg the add command. | ||||
| data JournalContext = Ctx { | ||||
|       ctxYear      :: !(Maybe Year)      -- ^ the default year most recently specified with Y | ||||
|     , ctxDefaultCommodityAndStyle :: !(Maybe (Commodity,AmountStyle)) -- ^ the default commodity and amount style most recently specified with D | ||||
|     , ctxDefaultCommodityAndStyle :: !(Maybe (CommoditySymbol,AmountStyle)) -- ^ the default commodity and amount style most recently specified with D | ||||
|     , ctxAccounts :: ![AccountName]      -- ^ the accounts that have been defined with account directives so far | ||||
|     , ctxParentAccount :: ![AccountName] -- ^ the current stack of parent accounts/account name components | ||||
|                                          --   specified with "apply account" directive(s). Concatenated, these | ||||
| @ -261,7 +266,7 @@ data Journal = Journal { | ||||
|                                             -- first followed by any included files in the | ||||
|                                             -- order encountered. | ||||
|       filereadtime :: ClockTime,            -- ^ when this journal was last read from its file(s) | ||||
|       jcommoditystyles :: M.Map Commodity AmountStyle  -- ^ how to display amounts in each commodity | ||||
|       jcommoditystyles :: M.Map CommoditySymbol AmountStyle  -- ^ how to display amounts in each commodity | ||||
|     } deriving (Eq, Typeable, Data, Generic) | ||||
| 
 | ||||
| instance NFData Journal | ||||
|  | ||||
| @ -232,10 +232,10 @@ setYear y = modifyState (\ctx -> ctx{ctxYear=Just y}) | ||||
| getYear :: Monad m => JournalParser m (Maybe Integer) | ||||
| getYear = liftM ctxYear getState | ||||
| 
 | ||||
| setDefaultCommodityAndStyle :: Monad m => (Commodity,AmountStyle) -> JournalParser m () | ||||
| setDefaultCommodityAndStyle :: Monad m => (CommoditySymbol,AmountStyle) -> JournalParser m () | ||||
| setDefaultCommodityAndStyle cs = modifyState (\ctx -> ctx{ctxDefaultCommodityAndStyle=Just cs}) | ||||
| 
 | ||||
| getDefaultCommodityAndStyle :: Monad m => JournalParser m (Maybe (Commodity,AmountStyle)) | ||||
| getDefaultCommodityAndStyle :: Monad m => JournalParser m (Maybe (CommoditySymbol,AmountStyle)) | ||||
| getDefaultCommodityAndStyle = ctxDefaultCommodityAndStyle `fmap` getState | ||||
| 
 | ||||
| pushAccount :: Monad m => String -> JournalParser m () | ||||
|  | ||||
| @ -156,7 +156,7 @@ amountValue j d a = | ||||
| -- the given date, in the commodity in which it has most recently been | ||||
| -- market-priced (ie the commodity mentioned in the most recent | ||||
| -- applicable historical price directive before this date). | ||||
| commodityValue :: Journal -> Day -> Commodity -> Maybe Amount | ||||
| commodityValue :: Journal -> Day -> CommoditySymbol -> Maybe Amount | ||||
| commodityValue j d c | ||||
|     | null applicableprices = Nothing | ||||
|     | otherwise             = Just $ mpamount $ last applicableprices | ||||
|  | ||||
| @ -217,7 +217,7 @@ filterTransactionPostings m t@Transaction{tpostings=ps} = t{tpostings=filter (m | ||||
| 
 | ||||
| -- | Split a transactions report whose items may involve several commodities, | ||||
| -- into one or more single-commodity transactions reports. | ||||
| transactionsReportByCommodity :: TransactionsReport -> [(Commodity, TransactionsReport)] | ||||
| transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)] | ||||
| transactionsReportByCommodity tr = | ||||
|   [(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr] | ||||
|   where | ||||
| @ -227,7 +227,7 @@ transactionsReportByCommodity tr = | ||||
| -- 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 :: Commodity -> TransactionsReport -> TransactionsReport | ||||
| filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport | ||||
| filterTransactionsReportByCommodity c (label,items) = | ||||
|   (label, fixTransactionsReportItemBalances $ concat [filterTransactionsReportItemByCommodity c i | i <- items]) | ||||
|   where | ||||
|  | ||||
| @ -99,7 +99,7 @@ registerItemsHtml _ vd (balancelabel,items) = [hamlet| | ||||
|                --                      Data.Foldable.Foldable t1 => | ||||
|                --                      t1 (Transaction, t2, t3, t4, t5, MixedAmount) | ||||
|                --                      -> t -> Text.Blaze.Internal.HtmlM () | ||||
| registerChartHtml :: [(Commodity, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute | ||||
| registerChartHtml :: [(CommoditySymbol, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute | ||||
| registerChartHtml percommoditytxnreports = | ||||
|  -- have to make sure plot is not called when our container (maincontent) | ||||
|  -- is hidden, eg with add form toggled | ||||
| @ -171,6 +171,6 @@ registerChartHtml percommoditytxnreports = | ||||
|            of "" -> "" | ||||
|               s  -> s++":" | ||||
|    colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex | ||||
|    commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(Commodity,Int)] | ||||
|    commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)] | ||||
|    simpleMixedAmountQuantity = maybe 0 aquantity . headMay . amounts | ||||
|    shownull c = if null c then " " else c | ||||
|  | ||||
| @ -320,7 +320,7 @@ balance opts@CliOpts{reportopts_=ropts} j = do | ||||
| -- in which it has most recently been market-priced, ie the commodity | ||||
| -- mentioned in the most recent applicable historical price directive | ||||
| -- before this date. | ||||
| -- defaultValuationCommodity :: Journal -> Day -> Commodity -> Maybe Commodity | ||||
| -- defaultValuationCommodity :: Journal -> Day -> CommoditySymbol -> Maybe CommoditySymbol | ||||
| -- defaultValuationCommodity j d c = mpamount <$> commodityValue j d c | ||||
| 
 | ||||
| -- | Render a single-column balance report as CSV. | ||||
|  | ||||
| @ -926,7 +926,7 @@ Posting -- AccountName | ||||
| Account -- "2" MixedAmount | ||||
| Posting -- MixedAmount | ||||
| MixedAmount *-- "*" Amount | ||||
| Amount -- Commodity | ||||
| Amount -- CommoditySymbol | ||||
| Amount -- Quantity | ||||
| Amount -- Price | ||||
| Amount -- AmountStyle | ||||
| @ -942,7 +942,7 @@ each containing multiple | ||||
| of some | ||||
| [MixedAmount](http://hackage.haskell.org/package/hledger-lib-0.23.2/docs/Hledger-Data-Types.html#t:MixedAmount) | ||||
| (multiple | ||||
| single-[Commodity](http://hackage.haskell.org/package/hledger-lib-0.23.2/docs/Hledger-Data-Types.html#t:Commodity) | ||||
| single-[CommoditySymbol](http://hackage.haskell.org/package/hledger-lib-0.23.2/docs/Hledger-Data-Types.html#t:CommoditySymbol) | ||||
| [Amounts](http://hackage.haskell.org/package/hledger-lib-0.23.2/docs/Hledger-Data-Types.html#t:Amount)) | ||||
| to some | ||||
| [AccountName](http://hackage.haskell.org/package/hledger-lib-0.23.2/docs/Hledger-Data-Types.html#t:AccountName). | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user