hledger -f data/100x100x10.journal stats <<ghc: 39288536 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.016 MUT (0.028 elapsed), 0.009 GC (0.012 elapsed) :ghc>> <<ghc: 39290808 bytes, 77 GCs, 196608/269560 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.003 elapsed), 0.015 MUT (0.021 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats <<ghc: 314268960 bytes, 612 GCs, 2143219/6826152 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.009 elapsed), 0.135 MUT (0.151 elapsed), 0.065 GC (0.178 elapsed) :ghc>> <<ghc: 314254512 bytes, 612 GCs, 2072377/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.130 MUT (0.134 elapsed), 0.064 GC (0.075 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats <<ghc: 3070016592 bytes, 5965 GCs, 13138220/64266016 avg/max bytes residency (10 samples), 128M in use, 0.000 INIT (0.000 elapsed), 1.272 MUT (1.322 elapsed), 0.527 GC (0.595 elapsed) :ghc>> <<ghc: 3069989896 bytes, 5973 GCs, 12687877/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.295 MUT (1.324 elapsed), 0.511 GC (0.570 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats <<ghc: 30753448072 bytes, 59763 GCs, 121502982/673169248 avg/max bytes residency (14 samples), 1640M in use, 0.000 INIT (0.007 elapsed), 12.421 MUT (12.672 elapsed), 6.240 GC (7.812 elapsed) :ghc>> <<ghc: 30753350528 bytes, 59811 GCs, 117616668/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.001 INIT (0.011 elapsed), 13.209 MUT (13.683 elapsed), 6.137 GC (7.117 elapsed) :ghc>>
		
			
				
	
	
		
			77 lines
		
	
	
		
			2.3 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			77 lines
		
	
	
		
			2.3 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-|
 | |
| 
 | |
| 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 Data.List
 | |
| import Data.Maybe (fromMaybe)
 | |
| import Data.Monoid
 | |
| -- import Data.Text (Text)
 | |
| import qualified Data.Text as T
 | |
| import Test.HUnit
 | |
| -- import qualified Data.Map as M
 | |
| 
 | |
| import Hledger.Data.Types
 | |
| import Hledger.Utils
 | |
| 
 | |
| 
 | |
| -- characters that may not be used in a non-quoted commodity symbol
 | |
| nonsimplecommoditychars = "0123456789-+.@;\n \"{}=" :: [Char]
 | |
| 
 | |
| quoteCommoditySymbolIfNeeded s | any (`elem` nonsimplecommoditychars) (T.unpack 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")
 | |
|               (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
 | |
| 
 | |
| tests_Hledger_Data_Commodity = TestList [
 | |
|  ]
 | |
| 
 |