hledger/hledger-lib/Hledger/Data/Commodity.hs

71 lines
2.1 KiB
Haskell
Raw Normal View History

{-|
2008-10-15 06:11:30 +04:00
A 'Commodity' is a symbol representing a currency or some other kind of
2008-10-18 23:30:07 +04:00
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.
-}
2010-05-20 03:08:53 +04:00
module Hledger.Data.Commodity
where
2011-05-28 08:11:44 +04:00
import Data.List
import Data.Maybe (fromMaybe)
2011-05-28 08:11:44 +04:00
import Test.HUnit
-- import qualified Data.Map as M
2011-05-28 08:11:44 +04:00
import Hledger.Data.Types
import Hledger.Utils
-- characters that may not be used in a non-quoted commodity symbol
nonsimplecommoditychars = "0123456789-+.@;\n \"{}=" :: String
quoteCommoditySymbolIfNeeded s | any (`elem` nonsimplecommoditychars) s = "\"" ++ s ++ "\""
| otherwise = s
commodity = ""
2008-10-15 10:00:10 +04:00
-- 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 -> Commodity
comm name = snd $ fromMaybe
(error' "commodity lookup failed")
(find (\n -> fst n == name) commoditysymbols)
2008-10-18 23:30:07 +04:00
-- | Find the conversion rate between two commodities. Currently returns 1.
conversionRate :: Commodity -> Commodity -> 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 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
2010-12-27 23:26:22 +03:00
tests_Hledger_Data_Commodity = TestList [
]