lib: textification: commodity symbols
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>>
This commit is contained in:
		
							parent
							
								
									2538d14ea7
								
							
						
					
					
						commit
						102b76c17f
					
				| @ -1,4 +1,3 @@ | |||||||
| {-# LANGUAGE CPP, StandaloneDeriving, RecordWildCards #-} |  | ||||||
| {-| | {-| | ||||||
| A simple 'Amount' is some quantity of money, shares, or anything else. | A simple 'Amount' is some quantity of money, shares, or anything else. | ||||||
| It has a (possibly null) 'CommoditySymbol' and a numeric quantity: | It has a (possibly null) 'CommoditySymbol' and a numeric quantity: | ||||||
| @ -41,6 +40,8 @@ exchange rates. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
|  | {-# LANGUAGE CPP, StandaloneDeriving, RecordWildCards, OverloadedStrings #-} | ||||||
|  | 
 | ||||||
| module Hledger.Data.Amount ( | module Hledger.Data.Amount ( | ||||||
|   -- * Amount |   -- * Amount | ||||||
|   amount, |   amount, | ||||||
| @ -106,6 +107,8 @@ import Data.Function (on) | |||||||
| import Data.List | import Data.List | ||||||
| import Data.Map (findWithDefault) | import Data.Map (findWithDefault) | ||||||
| import Data.Maybe | import Data.Maybe | ||||||
|  | -- import Data.Text (Text) | ||||||
|  | import qualified Data.Text as T | ||||||
| import Test.HUnit | import Test.HUnit | ||||||
| import Text.Printf | import Text.Printf | ||||||
| import qualified Data.Map as M | import qualified Data.Map as M | ||||||
| @ -258,14 +261,14 @@ showAmountHelper :: Bool -> Amount -> String | |||||||
| showAmountHelper _ Amount{acommodity="AUTO"} = "" | showAmountHelper _ Amount{acommodity="AUTO"} = "" | ||||||
| showAmountHelper showzerocommodity a@(Amount{acommodity=c, aprice=p, astyle=AmountStyle{..}}) = | showAmountHelper showzerocommodity a@(Amount{acommodity=c, aprice=p, astyle=AmountStyle{..}}) = | ||||||
|     case ascommodityside of |     case ascommodityside of | ||||||
|       L -> printf "%s%s%s%s" c' space quantity' price |       L -> printf "%s%s%s%s" (T.unpack c') space quantity' price | ||||||
|       R -> printf "%s%s%s%s" quantity' space c' price |       R -> printf "%s%s%s%s" quantity' space (T.unpack c') price | ||||||
|     where |     where | ||||||
|       quantity = showamountquantity a |       quantity = showamountquantity a | ||||||
|       displayingzero = null $ filter (`elem` digits) $ quantity |       displayingzero = null $ filter (`elem` digits) $ quantity | ||||||
|       (quantity',c') | displayingzero && not showzerocommodity = ("0","") |       (quantity',c') | displayingzero && not showzerocommodity = ("0","") | ||||||
|                      | otherwise = (quantity, quoteCommoditySymbolIfNeeded c) |                      | otherwise = (quantity, quoteCommoditySymbolIfNeeded c) | ||||||
|       space = if (not (null c') && ascommodityspaced) then " " else "" :: String |       space = if (not (T.null c') && ascommodityspaced) then " " else "" :: String | ||||||
|       price = showPrice p |       price = showPrice p | ||||||
| 
 | 
 | ||||||
| -- | Like showAmount, but show a zero amount's commodity if it has one. | -- | Like showAmount, but show a zero amount's commodity if it has one. | ||||||
|  | |||||||
| @ -6,10 +6,16 @@ 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. | are thousands separated by comma, significant decimal places and so on. | ||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
|  | 
 | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
|  | 
 | ||||||
| module Hledger.Data.Commodity | module Hledger.Data.Commodity | ||||||
| where | where | ||||||
| import Data.List | import Data.List | ||||||
| import Data.Maybe (fromMaybe) | import Data.Maybe (fromMaybe) | ||||||
|  | import Data.Monoid | ||||||
|  | -- import Data.Text (Text) | ||||||
|  | import qualified Data.Text as T | ||||||
| import Test.HUnit | import Test.HUnit | ||||||
| -- import qualified Data.Map as M | -- import qualified Data.Map as M | ||||||
| 
 | 
 | ||||||
| @ -18,9 +24,9 @@ import Hledger.Utils | |||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| -- characters that may not be used in a non-quoted commodity symbol | -- characters that may not be used in a non-quoted commodity symbol | ||||||
| nonsimplecommoditychars = "0123456789-+.@;\n \"{}=" :: String | nonsimplecommoditychars = "0123456789-+.@;\n \"{}=" :: [Char] | ||||||
| 
 | 
 | ||||||
| quoteCommoditySymbolIfNeeded s | any (`elem` nonsimplecommoditychars) s = "\"" ++ s ++ "\"" | quoteCommoditySymbolIfNeeded s | any (`elem` nonsimplecommoditychars) (T.unpack s) = "\"" <> s <> "\"" | ||||||
|                                | otherwise = s |                                | otherwise = s | ||||||
| 
 | 
 | ||||||
| commodity = "" | commodity = "" | ||||||
|  | |||||||
| @ -101,7 +101,7 @@ data DigitGroupStyle = DigitGroups Char [Int] | |||||||
| 
 | 
 | ||||||
| instance NFData DigitGroupStyle | instance NFData DigitGroupStyle | ||||||
| 
 | 
 | ||||||
| type CommoditySymbol = String | type CommoditySymbol = Text | ||||||
| 
 | 
 | ||||||
| data Commodity = Commodity { | data Commodity = Commodity { | ||||||
|   csymbol :: CommoditySymbol, |   csymbol :: CommoditySymbol, | ||||||
|  | |||||||
| @ -608,7 +608,7 @@ matchesAmount (Or qs) a = any (`matchesAmount` a) qs | |||||||
| matchesAmount (And qs) a = all (`matchesAmount` a) qs | matchesAmount (And qs) a = all (`matchesAmount` a) qs | ||||||
| -- | -- | ||||||
| matchesAmount (Amt ord n) a = compareAmount ord n a | matchesAmount (Amt ord n) a = compareAmount ord n a | ||||||
| matchesAmount (Sym r) a = regexMatchesCI ("^" ++ r ++ "$") $ acommodity a | matchesAmount (Sym r) a = regexMatchesCI ("^" ++ r ++ "$") $ T.unpack $ acommodity a | ||||||
| -- | -- | ||||||
| matchesAmount _ _ = True | matchesAmount _ _ = True | ||||||
| 
 | 
 | ||||||
| @ -650,7 +650,7 @@ matchesPosting q@(Amt _ _) Posting{pamount=amt} = q `matchesMixedAmount` amt | |||||||
| -- matchesPosting (Empty False) Posting{pamount=a} = True | -- matchesPosting (Empty False) Posting{pamount=a} = True | ||||||
| -- matchesPosting (Empty True) Posting{pamount=a} = isZeroMixedAmount a | -- matchesPosting (Empty True) Posting{pamount=a} = isZeroMixedAmount a | ||||||
| matchesPosting (Empty _) _ = True | matchesPosting (Empty _) _ = True | ||||||
| matchesPosting (Sym r) Posting{pamount=Mixed as} = any (regexMatchesCI $ "^" ++ r ++ "$") $ map acommodity as | matchesPosting (Sym r) Posting{pamount=Mixed as} = any (regexMatchesCI $ "^" ++ r ++ "$") $ map (T.unpack . acommodity) as | ||||||
| matchesPosting (Tag n v) p = not $ null $ matchedTags n v $ postingAllTags p | matchesPosting (Tag n v) p = not $ null $ matchedTags n v $ postingAllTags p | ||||||
| -- matchesPosting _ _ = False | -- matchesPosting _ _ = False | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -13,7 +13,7 @@ Some of these might belong in Hledger.Read.JournalReader or Hledger.Read. | |||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| --- * module | --- * module | ||||||
| {-# LANGUAGE CPP, RecordWildCards, NamedFieldPuns, NoMonoLocalBinds, ScopedTypeVariables, FlexibleContexts, TupleSections #-} | {-# LANGUAGE CPP, RecordWildCards, NamedFieldPuns, NoMonoLocalBinds, ScopedTypeVariables, FlexibleContexts, TupleSections, OverloadedStrings #-} | ||||||
| 
 | 
 | ||||||
| module Hledger.Read.Common | module Hledger.Read.Common | ||||||
| where | where | ||||||
| @ -386,18 +386,18 @@ nosymbolamountp = do | |||||||
|   return $ Amount c q p s |   return $ Amount c q p s | ||||||
|   <?> "no-symbol amount" |   <?> "no-symbol amount" | ||||||
| 
 | 
 | ||||||
| commoditysymbolp :: Monad m => JournalParser m String | commoditysymbolp :: Monad m => JournalParser m CommoditySymbol | ||||||
| commoditysymbolp = (quotedcommoditysymbolp <|> simplecommoditysymbolp) <?> "commodity symbol" | commoditysymbolp = (quotedcommoditysymbolp <|> simplecommoditysymbolp) <?> "commodity symbol" | ||||||
| 
 | 
 | ||||||
| quotedcommoditysymbolp :: Monad m => JournalParser m String | quotedcommoditysymbolp :: Monad m => JournalParser m CommoditySymbol | ||||||
| quotedcommoditysymbolp = do | quotedcommoditysymbolp = do | ||||||
|   char '"' |   char '"' | ||||||
|   s <- many1 $ noneOf ";\n\"" |   s <- many1 $ noneOf ";\n\"" | ||||||
|   char '"' |   char '"' | ||||||
|   return s |   return $ T.pack s | ||||||
| 
 | 
 | ||||||
| simplecommoditysymbolp :: Monad m => JournalParser m String | simplecommoditysymbolp :: Monad m => JournalParser m CommoditySymbol | ||||||
| simplecommoditysymbolp = many1 (noneOf nonsimplecommoditychars) | simplecommoditysymbolp = T.pack <$> many1 (noneOf nonsimplecommoditychars) | ||||||
| 
 | 
 | ||||||
| priceamountp :: Monad m => JournalParser m Price | priceamountp :: Monad m => JournalParser m Price | ||||||
| priceamountp = | priceamountp = | ||||||
|  | |||||||
| @ -126,7 +126,7 @@ registerChartHtml percommoditytxnreports = | |||||||
|            ], |            ], | ||||||
|           /* [] */ |           /* [] */ | ||||||
|         ], |         ], | ||||||
|         label: '#{shownull c}', |         label: '#{shownull $ T.unpack c}', | ||||||
|         color: #{colorForCommodity c}, |         color: #{colorForCommodity c}, | ||||||
|         lines: { |         lines: { | ||||||
|           show: true, |           show: true, | ||||||
|  | |||||||
| @ -4,6 +4,8 @@ A ledger-compatible @print@ command. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
|  | 
 | ||||||
| module Hledger.Cli.Print ( | module Hledger.Cli.Print ( | ||||||
|   printmode |   printmode | ||||||
|  ,print' |  ,print' | ||||||
| @ -13,6 +15,8 @@ module Hledger.Cli.Print ( | |||||||
| where | where | ||||||
| 
 | 
 | ||||||
| import Data.List | import Data.List | ||||||
|  | -- import Data.Text (Text) | ||||||
|  | import qualified Data.Text as T | ||||||
| import System.Console.CmdArgs.Explicit | import System.Console.CmdArgs.Explicit | ||||||
| import Test.HUnit | import Test.HUnit | ||||||
| import Text.CSV | import Text.CSV | ||||||
| @ -124,7 +128,7 @@ postingToCSV p = | |||||||
|   map (\(a@(Amount {aquantity=q,acommodity=c})) -> |   map (\(a@(Amount {aquantity=q,acommodity=c})) -> | ||||||
|     let a_ = a{acommodity=""} in |     let a_ = a{acommodity=""} in | ||||||
|     let amount = showAmount a_ in |     let amount = showAmount a_ in | ||||||
|     let commodity = c in |     let commodity = T.unpack c in | ||||||
|     let credit = if q < 0 then showAmount $ negate a_ else "" in |     let credit = if q < 0 then showAmount $ negate a_ else "" in | ||||||
|     let debit  = if q > 0 then showAmount a_ else "" in |     let debit  = if q > 0 then showAmount a_ else "" in | ||||||
|     account:amount:commodity:credit:debit:status:comment:[]) |     account:amount:commodity:credit:debit:status:comment:[]) | ||||||
|  | |||||||
| @ -4,6 +4,8 @@ Print some statistics for the journal. | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
|  | 
 | ||||||
| module Hledger.Cli.Stats ( | module Hledger.Cli.Stats ( | ||||||
|   statsmode |   statsmode | ||||||
|  ,stats |  ,stats | ||||||
| @ -14,7 +16,8 @@ import Data.List | |||||||
| import Data.Maybe | import Data.Maybe | ||||||
| import Data.Ord | import Data.Ord | ||||||
| import Data.HashSet (size, fromList) | import Data.HashSet (size, fromList) | ||||||
| import Data.Text (pack) | -- import Data.Text (Text) | ||||||
|  | import qualified Data.Text as T | ||||||
| import Data.Time.Calendar | import Data.Time.Calendar | ||||||
| import System.Console.CmdArgs.Explicit | import System.Console.CmdArgs.Explicit | ||||||
| import Text.Printf | import Text.Printf | ||||||
| @ -67,9 +70,9 @@ showLedgerStats l today span = | |||||||
|         ,("Transactions", printf "%d (%0.1f per day)" tnum txnrate) |         ,("Transactions", printf "%d (%0.1f per day)" tnum txnrate) | ||||||
|         ,("Transactions last 30 days", printf "%d (%0.1f per day)" tnum30 txnrate30) |         ,("Transactions last 30 days", printf "%d (%0.1f per day)" tnum30 txnrate30) | ||||||
|         ,("Transactions last 7 days", printf "%d (%0.1f per day)" tnum7 txnrate7) |         ,("Transactions last 7 days", printf "%d (%0.1f per day)" tnum7 txnrate7) | ||||||
|         ,("Payees/descriptions", show $ size $ fromList $ map (pack . tdescription) ts) |         ,("Payees/descriptions", show $ size $ fromList $ map (tdescription) ts) | ||||||
|         ,("Accounts", printf "%d (depth %d)" acctnum acctdepth) |         ,("Accounts", printf "%d (depth %d)" acctnum acctdepth) | ||||||
|         ,("Commodities", printf "%s (%s)" (show $ length cs) (intercalate ", " cs)) |         ,("Commodities", printf "%s (%s)" (show $ length cs) (T.intercalate ", " cs)) | ||||||
|       -- Transactions this month     : %(monthtxns)s (last month in the same period: %(lastmonthtxns)s) |       -- Transactions this month     : %(monthtxns)s (last month in the same period: %(lastmonthtxns)s) | ||||||
|       -- Uncleared transactions      : %(uncleared)s |       -- Uncleared transactions      : %(uncleared)s | ||||||
|       -- Days since reconciliation   : %(reconcileelapsed)s |       -- Days since reconciliation   : %(reconcileelapsed)s | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user