pkg!: Remove Hledger.Data.Commodity module.
There are no modules which depend on Hledger.Data.Commodity which don't also depend on Hledger.Data.Amount. Though Hledger.Data.Amount is a very large module and might be broken up, Hledger.Data.Commodity only defines three very small functions which are used, and so can be combined with little cost.
This commit is contained in:
		
							parent
							
								
									a0f9d7560f
								
							
						
					
					
						commit
						1c402edb06
					
				| @ -12,7 +12,6 @@ module Hledger.Data ( | |||||||
|                module Hledger.Data.Account, |                module Hledger.Data.Account, | ||||||
|                module Hledger.Data.AccountName, |                module Hledger.Data.AccountName, | ||||||
|                module Hledger.Data.Amount, |                module Hledger.Data.Amount, | ||||||
|                module Hledger.Data.Commodity, |  | ||||||
|                module Hledger.Data.Dates, |                module Hledger.Data.Dates, | ||||||
|                module Hledger.Data.Journal, |                module Hledger.Data.Journal, | ||||||
|                module Hledger.Data.Json, |                module Hledger.Data.Json, | ||||||
| @ -34,7 +33,6 @@ where | |||||||
| import Hledger.Data.Account | import Hledger.Data.Account | ||||||
| import Hledger.Data.AccountName | import Hledger.Data.AccountName | ||||||
| import Hledger.Data.Amount | import Hledger.Data.Amount | ||||||
| import Hledger.Data.Commodity |  | ||||||
| import Hledger.Data.Dates | import Hledger.Data.Dates | ||||||
| import Hledger.Data.Journal | import Hledger.Data.Journal | ||||||
| import Hledger.Data.Json | import Hledger.Data.Json | ||||||
|  | |||||||
| @ -44,6 +44,10 @@ exchange rates. | |||||||
| {-# LANGUAGE RecordWildCards    #-} | {-# LANGUAGE RecordWildCards    #-} | ||||||
| 
 | 
 | ||||||
| module Hledger.Data.Amount ( | module Hledger.Data.Amount ( | ||||||
|  |   -- * Commodity | ||||||
|  |   showCommoditySymbol, | ||||||
|  |   isNonsimpleCommodityChar, | ||||||
|  |   quoteCommoditySymbolIfNeeded, | ||||||
|   -- * Amount |   -- * Amount | ||||||
|   amount, |   amount, | ||||||
|   nullamt, |   nullamt, | ||||||
| @ -144,7 +148,9 @@ module Hledger.Data.Amount ( | |||||||
|   tests_Amount |   tests_Amount | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
|  | import Control.Applicative (liftA2) | ||||||
| import Control.Monad (foldM) | import Control.Monad (foldM) | ||||||
|  | import Data.Char (isDigit) | ||||||
| import Data.Decimal (DecimalRaw(..), decimalPlaces, normalizeDecimal, roundTo) | import Data.Decimal (DecimalRaw(..), decimalPlaces, normalizeDecimal, roundTo) | ||||||
| import Data.Default (Default(..)) | import Data.Default (Default(..)) | ||||||
| import Data.Foldable (toList) | import Data.Foldable (toList) | ||||||
| @ -162,10 +168,31 @@ import System.Console.ANSI (Color(..),ColorIntensity(..)) | |||||||
| import Text.Printf (printf) | import Text.Printf (printf) | ||||||
| 
 | 
 | ||||||
| import Hledger.Data.Types | import Hledger.Data.Types | ||||||
| import Hledger.Data.Commodity |  | ||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
|  | -- A 'Commodity' is a symbol representing a currency or some other kind of | ||||||
|  | -- thing we are tracking, and some display preferences that tell how to | ||||||
|  | -- display 'Amount's of the commodity - is the symbol on the left or right, | ||||||
|  | -- are thousands separated by comma, significant decimal places and so on. | ||||||
|  | 
 | ||||||
|  | -- | Show space-containing commodity symbols quoted, as they are in a journal. | ||||||
|  | showCommoditySymbol :: T.Text -> T.Text | ||||||
|  | showCommoditySymbol = textQuoteIfNeeded | ||||||
|  | 
 | ||||||
|  | -- characters that may not be used in a non-quoted commodity symbol | ||||||
|  | isNonsimpleCommodityChar :: Char -> Bool | ||||||
|  | isNonsimpleCommodityChar = liftA2 (||) isDigit isOther | ||||||
|  |   where | ||||||
|  |     otherChars = "-+.@*;\t\n \"{}=" :: T.Text | ||||||
|  |     isOther c = T.any (==c) otherChars | ||||||
|  | 
 | ||||||
|  | quoteCommoditySymbolIfNeeded :: T.Text -> T.Text | ||||||
|  | quoteCommoditySymbolIfNeeded s | ||||||
|  |   | T.any isNonsimpleCommodityChar s = "\"" <> s <> "\"" | ||||||
|  |   | otherwise = s | ||||||
|  | 
 | ||||||
|  | 
 | ||||||
| -- | Options for the display of Amount and MixedAmount. | -- | Options for the display of Amount and MixedAmount. | ||||||
| data AmountDisplayOpts = AmountDisplayOpts | data AmountDisplayOpts = AmountDisplayOpts | ||||||
|   { displayPrice         :: Bool       -- ^ Whether to display the Price of an Amount. |   { displayPrice         :: Bool       -- ^ Whether to display the Price of an Amount. | ||||||
|  | |||||||
| @ -1,80 +0,0 @@ | |||||||
| {-| |  | ||||||
| 
 |  | ||||||
| A 'Commodity' is a symbol representing a currency or some other kind of |  | ||||||
| thing we are tracking, and some display preferences that tell how to |  | ||||||
| display 'Amount's of the commodity - is the symbol on the left or right, |  | ||||||
| are thousands separated by comma, significant decimal places and so on. |  | ||||||
| 
 |  | ||||||
| -} |  | ||||||
| 
 |  | ||||||
| {-# LANGUAGE OverloadedStrings #-} |  | ||||||
| 
 |  | ||||||
| module Hledger.Data.Commodity |  | ||||||
| where |  | ||||||
| import Control.Applicative (liftA2) |  | ||||||
| import Data.Char (isDigit) |  | ||||||
| import Data.List |  | ||||||
| import Data.Maybe (fromMaybe) |  | ||||||
| import qualified Data.Text as T |  | ||||||
| -- import qualified Data.Map as M |  | ||||||
| 
 |  | ||||||
| import Hledger.Data.Types |  | ||||||
| import Hledger.Utils |  | ||||||
| 
 |  | ||||||
| -- Show space-containing commodity symbols quoted, as they are in a journal. |  | ||||||
| showCommoditySymbol = textQuoteIfNeeded |  | ||||||
| 
 |  | ||||||
| -- characters that may not be used in a non-quoted commodity symbol |  | ||||||
| isNonsimpleCommodityChar :: Char -> Bool |  | ||||||
| isNonsimpleCommodityChar = liftA2 (||) isDigit isOther |  | ||||||
|   where |  | ||||||
|     otherChars = "-+.@*;\t\n \"{}=" :: T.Text |  | ||||||
|     isOther c = T.any (==c) otherChars |  | ||||||
| 
 |  | ||||||
| quoteCommoditySymbolIfNeeded :: T.Text -> T.Text |  | ||||||
| quoteCommoditySymbolIfNeeded s |  | ||||||
|   | T.any isNonsimpleCommodityChar s = "\"" <> s <> "\"" |  | ||||||
|   | otherwise = s |  | ||||||
| 
 |  | ||||||
| commodity = "" |  | ||||||
| 
 |  | ||||||
| -- handy constructors for tests |  | ||||||
| -- unknown = commodity |  | ||||||
| -- usd     = "$" |  | ||||||
| -- eur     = "€" |  | ||||||
| -- gbp     = "£" |  | ||||||
| -- hour    = "h" |  | ||||||
| 
 |  | ||||||
| -- Some sample commodity' names and symbols, for use in tests.. |  | ||||||
| commoditysymbols = |  | ||||||
|   [("unknown","") |  | ||||||
|   ,("usd","$") |  | ||||||
|   ,("eur","€") |  | ||||||
|   ,("gbp","£") |  | ||||||
|   ,("hour","h") |  | ||||||
|   ] |  | ||||||
| 
 |  | ||||||
| -- | Look up one of the sample commodities' symbol by name. |  | ||||||
| comm :: String -> CommoditySymbol |  | ||||||
| comm name = snd $ fromMaybe |  | ||||||
|               (error' "commodity lookup failed")  -- PARTIAL: |  | ||||||
|               (find (\n -> fst n == name) commoditysymbols) |  | ||||||
| 
 |  | ||||||
| -- | Find the conversion rate between two commodities. Currently returns 1. |  | ||||||
| conversionRate :: CommoditySymbol -> CommoditySymbol -> Double |  | ||||||
| conversionRate _ _ = 1 |  | ||||||
| 
 |  | ||||||
| -- -- | Convert a list of commodities to a map from commodity symbols to |  | ||||||
| -- -- unique, display-preference-canonicalised commodities. |  | ||||||
| -- canonicaliseCommodities :: [CommoditySymbol] -> Map.Map String CommoditySymbol |  | ||||||
| -- canonicaliseCommodities cs = |  | ||||||
| --     Map.fromList [(s,firstc{precision=maxp}) | s <- symbols, |  | ||||||
| --                   let cs = commoditymap ! s, |  | ||||||
| --                   let firstc = head cs, |  | ||||||
| --                   let maxp = maximum $ map precision cs |  | ||||||
| --                  ] |  | ||||||
| --   where |  | ||||||
| --     commoditymap = Map.fromList [(s, commoditieswithsymbol s) | s <- symbols] |  | ||||||
| --     commoditieswithsymbol s = filter ((s==) . symbol) cs |  | ||||||
| --     symbols = nub $ map symbol cs |  | ||||||
| 
 |  | ||||||
| @ -45,7 +45,6 @@ import Hledger.Utils | |||||||
| import Hledger.Data.Types | import Hledger.Data.Types | ||||||
| import Hledger.Data.Amount | import Hledger.Data.Amount | ||||||
| import Hledger.Data.Dates (nulldate) | import Hledger.Data.Dates (nulldate) | ||||||
| import Hledger.Data.Commodity (showCommoditySymbol) |  | ||||||
| import Text.Printf (printf) | import Text.Printf (printf) | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -45,7 +45,6 @@ library | |||||||
|       Hledger.Data.Account |       Hledger.Data.Account | ||||||
|       Hledger.Data.AccountName |       Hledger.Data.AccountName | ||||||
|       Hledger.Data.Amount |       Hledger.Data.Amount | ||||||
|       Hledger.Data.Commodity |  | ||||||
|       Hledger.Data.Dates |       Hledger.Data.Dates | ||||||
|       Hledger.Read.InputOptions |       Hledger.Read.InputOptions | ||||||
|       Hledger.Data.Journal |       Hledger.Data.Journal | ||||||
|  | |||||||
| @ -96,7 +96,6 @@ library: | |||||||
|   - Hledger.Data.Account |   - Hledger.Data.Account | ||||||
|   - Hledger.Data.AccountName |   - Hledger.Data.AccountName | ||||||
|   - Hledger.Data.Amount |   - Hledger.Data.Amount | ||||||
|   - Hledger.Data.Commodity |  | ||||||
|   - Hledger.Data.Dates |   - Hledger.Data.Dates | ||||||
|   - Hledger.Read.InputOptions |   - Hledger.Read.InputOptions | ||||||
|   - Hledger.Data.Journal |   - Hledger.Data.Journal | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user