combine patterns into single regexps, fix a bug with print & patterns
This commit is contained in:
		
							parent
							
								
									ce0d4ec85a
								
							
						
					
					
						commit
						d52b365fa0
					
				
							
								
								
									
										65
									
								
								Ledger.hs
									
									
									
									
									
								
							
							
						
						
									
										65
									
								
								Ledger.hs
									
									
									
									
									
								
							| @ -38,14 +38,15 @@ instance Show Ledger where | |||||||
| -- 1. filter based on account/description patterns, if any | -- 1. filter based on account/description patterns, if any | ||||||
| -- 2. cache per-account info | -- 2. cache per-account info | ||||||
| -- also, figure out the precision(s) to use | -- also, figure out the precision(s) to use | ||||||
| cacheLedger :: ([Regex],[Regex]) -> LedgerFile -> Ledger | cacheLedger :: FilterPatterns -> LedgerFile -> Ledger | ||||||
| cacheLedger pats l =  | cacheLedger pats l =  | ||||||
|     let  |     let  | ||||||
|         lprecision = maximum $ map (precision . amount) $ rawLedgerTransactions l |         lprecision = maximum $ map (precision . amount) $ rawLedgerTransactions l | ||||||
|         l' = filterLedgerEntries pats l |         l' = filterLedgerEntries pats l | ||||||
|         ant = rawLedgerAccountNameTree l' |         l'' = filterLedgerTransactions pats l' | ||||||
|  |         ant = rawLedgerAccountNameTree l'' | ||||||
|         ans = flatten ant |         ans = flatten ant | ||||||
|         ts = rawLedgerTransactions l' |         ts = rawLedgerTransactions l'' | ||||||
|         sortedts = sortBy (comparing account) ts |         sortedts = sortBy (comparing account) ts | ||||||
|         groupedts = groupBy (\t1 t2 -> account t1 == account t2) sortedts |         groupedts = groupBy (\t1 t2 -> account t1 == account t2) sortedts | ||||||
|         tmap = Map.union  |         tmap = Map.union  | ||||||
| @ -61,46 +62,30 @@ cacheLedger pats l = | |||||||
|     in |     in | ||||||
|       Ledger l' ant amap lprecision |       Ledger l' ant amap lprecision | ||||||
| 
 | 
 | ||||||
| -- filter entries by descpats and by whether any transactions contain any acctpats | -- filter entries by description and whether any transactions match account patterns | ||||||
| filterLedgerEntries1 :: ([Regex],[Regex]) -> LedgerFile -> LedgerFile | filterLedgerEntries :: FilterPatterns -> LedgerFile -> LedgerFile | ||||||
| filterLedgerEntries1 (acctpats,descpats) (LedgerFile ms ps es) =  | filterLedgerEntries (acctpat,descpat) (LedgerFile ms ps es) =  | ||||||
|     LedgerFile ms ps es' |     LedgerFile ms ps (filter matchdesc $ filter (any matchtxn . etransactions) es) | ||||||
|     where |     where | ||||||
|       es' = intersect |       matchtxn t = case matchRegex (wilddefault acctpat) (taccount t) of | ||||||
|             (concat [filter (matchacct r) es | r <- acctpats]) |                      Nothing -> False | ||||||
|             (concat [filter (matchdesc r) es | r <- descpats]) |                      otherwise -> True | ||||||
|       matchacct :: Regex -> LedgerEntry -> Bool |       matchdesc e = case matchRegex (wilddefault descpat) (edescription e) of | ||||||
|       matchacct r e = any (matchtxn r) (etransactions e) |                       Nothing -> False | ||||||
|       matchtxn :: Regex -> LedgerTransaction -> Bool |                       otherwise -> True | ||||||
|       matchtxn r t = case matchRegex r (taccount t) of |  | ||||||
|                        Nothing -> False |  | ||||||
|                        otherwise -> True |  | ||||||
|       matchdesc :: Regex -> LedgerEntry -> Bool |  | ||||||
|       matchdesc r e = case matchRegex r (edescription e) of |  | ||||||
|                         Nothing -> False |  | ||||||
|                         otherwise -> True |  | ||||||
| 
 | 
 | ||||||
| -- filter txns in each entry by acctpats, then filter the modified entries by descpats | -- filter transactions in each ledger entry by account patterns | ||||||
| -- this seems aggressive, unbalancing entries, but so far so goo- | -- this may unbalance entries | ||||||
| filterLedgerEntries :: ([Regex],[Regex]) -> LedgerFile -> LedgerFile | filterLedgerTransactions :: FilterPatterns -> LedgerFile -> LedgerFile | ||||||
| filterLedgerEntries (acctpats,descpats) (LedgerFile ms ps es) =  | filterLedgerTransactions (acctpat,descpat) (LedgerFile ms ps es) =  | ||||||
|     LedgerFile ms ps es' |     LedgerFile ms ps (map filterentrytxns es) | ||||||
|     where |     where | ||||||
|       es' = filter matchanydesc $ map filtertxns es |       filterentrytxns l@(LedgerEntry _ _ _ _ _ ts) = l{etransactions=filter matchtxn ts} | ||||||
|       filtertxns :: LedgerEntry -> LedgerEntry |       matchtxn t = case matchRegex (wilddefault acctpat) (taccount t) of | ||||||
|       filtertxns (LedgerEntry d s cod desc com ts) = LedgerEntry d s cod desc com $ filter matchanyacct ts |                      Nothing -> False | ||||||
|       matchanyacct :: LedgerTransaction -> Bool |                      otherwise -> True | ||||||
|       matchanyacct t = any (matchtxn t) acctpats | 
 | ||||||
|       matchtxn :: LedgerTransaction -> Regex -> Bool | wilddefault = fromMaybe (mkRegex ".*") | ||||||
|       matchtxn t r = case matchRegex r (taccount t) of |  | ||||||
|                        Nothing -> False |  | ||||||
|                        otherwise -> True |  | ||||||
|       matchanydesc :: LedgerEntry -> Bool |  | ||||||
|       matchanydesc e = any (matchdesc e) descpats |  | ||||||
|       matchdesc :: LedgerEntry -> Regex -> Bool |  | ||||||
|       matchdesc e r = case matchRegex r (edescription e) of |  | ||||||
|                         Nothing -> False |  | ||||||
|                         otherwise -> True |  | ||||||
| 
 | 
 | ||||||
| accountnames :: Ledger -> [AccountName] | accountnames :: Ledger -> [AccountName] | ||||||
| accountnames l = flatten $ accountnametree l | accountnames l = flatten $ accountnametree l | ||||||
|  | |||||||
							
								
								
									
										18
									
								
								Options.hs
									
									
									
									
									
								
							
							
						
						
									
										18
									
								
								Options.hs
									
									
									
									
									
								
							| @ -6,6 +6,7 @@ import System.Environment (getEnv) | |||||||
| import Data.Maybe (fromMaybe) | import Data.Maybe (fromMaybe) | ||||||
|      |      | ||||||
| import Utils | import Utils | ||||||
|  | import Types | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| usagehdr       = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:" | usagehdr       = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:" | ||||||
| @ -73,14 +74,15 @@ tildeExpand xs           =  return xs | |||||||
| 
 | 
 | ||||||
| -- ledger pattern args are 0 or more account patterns optionally followed | -- ledger pattern args are 0 or more account patterns optionally followed | ||||||
| -- by -- and 0 or more description patterns | -- by -- and 0 or more description patterns | ||||||
| parsePatternArgs :: [String] -> ([Regex],[Regex]) | parsePatternArgs :: [String] -> FilterPatterns | ||||||
| parsePatternArgs args = argregexes acctpats descpats | parsePatternArgs args = argpats as ds'  | ||||||
|     where (acctpats, _:descpats) = break (=="--") args |     where (as, ds) = break (=="--") args | ||||||
|  |           ds' = dropWhile (=="--") ds | ||||||
| 
 | 
 | ||||||
| argregexes :: [String] -> [String] -> ([Regex],[Regex]) | argpats :: [String] -> [String] -> FilterPatterns | ||||||
| argregexes as ds = (regexify as, regexify ds) | argpats as ds = (regexify as, regexify ds) | ||||||
|     where |     where | ||||||
|       regexify = map mkRegex . wilddefault |       regexify :: [String] -> Maybe Regex | ||||||
|       wilddefault [] = [".*"] |       regexify [] = Nothing | ||||||
|       wilddefault a = a |       regexify ss = Just $ mkRegex $ "(" ++ (unwords $ intersperse "|" ss) ++ ")" | ||||||
| 
 | 
 | ||||||
|  | |||||||
							
								
								
									
										4
									
								
								Tests.hs
									
									
									
									
									
								
							
							
						
						
									
										4
									
								
								Tests.hs
									
									
									
									
									
								
							| @ -283,7 +283,7 @@ ledger7 = LedgerFile | |||||||
|                  } |                  } | ||||||
|           ] |           ] | ||||||
| 
 | 
 | ||||||
| l7 = cacheLedger (argregexes [] []) ledger7 | l7 = cacheLedger (argpats [] []) ledger7 | ||||||
| 
 | 
 | ||||||
| timelogentry1_str  = "i 2007/03/11 16:19:00 hledger\n" | timelogentry1_str  = "i 2007/03/11 16:19:00 hledger\n" | ||||||
| timelogentry1 = TimeLogEntry 'i' "2007/03/11 16:19:00" "hledger" | timelogentry1 = TimeLogEntry 'i' "2007/03/11 16:19:00" "hledger" | ||||||
| @ -373,7 +373,7 @@ test_ledgerAccountNames = | |||||||
|     (rawLedgerAccountNames ledger7) |     (rawLedgerAccountNames ledger7) | ||||||
| 
 | 
 | ||||||
| test_cacheLedger = | test_cacheLedger = | ||||||
|     assertEqual' 15 (length $ Map.keys $ accounts $ cacheLedger (argregexes [] []) ledger7) |     assertEqual' 15 (length $ Map.keys $ accounts $ cacheLedger (argpats [] []) ledger7) | ||||||
| 
 | 
 | ||||||
| test_showLedgerAccounts =  | test_showLedgerAccounts =  | ||||||
|     assertEqual' 4 (length $ lines $ showLedgerAccounts l7 1) |     assertEqual' 4 (length $ lines $ showLedgerAccounts l7 1) | ||||||
|  | |||||||
							
								
								
									
										5
									
								
								Types.hs
									
									
									
									
									
								
							
							
						
						
									
										5
									
								
								Types.hs
									
									
									
									
									
								
							| @ -30,6 +30,9 @@ hledger | |||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
|  | -- account and description-matching patterns | ||||||
|  | type FilterPatterns = (Maybe Regex, Maybe Regex) | ||||||
|  |                         | ||||||
| type Date = String | type Date = String | ||||||
| 
 | 
 | ||||||
| type DateTime = String | type DateTime = String | ||||||
| @ -116,7 +119,7 @@ data Account = Account { | |||||||
| 
 | 
 | ||||||
| -- a ledger with account information cached for faster queries | -- a ledger with account information cached for faster queries | ||||||
| data Ledger = Ledger { | data Ledger = Ledger { | ||||||
|       rawledger :: LedgerFile,  |       rawledger :: LedgerFile, | ||||||
|       accountnametree :: Tree AccountName, |       accountnametree :: Tree AccountName, | ||||||
|       accounts :: Map.Map AccountName Account, |       accounts :: Map.Map AccountName Account, | ||||||
|       lprecision :: Int |       lprecision :: Int | ||||||
|  | |||||||
							
								
								
									
										2
									
								
								Utils.hs
									
									
									
									
									
								
							
							
						
						
									
										2
									
								
								Utils.hs
									
									
									
									
									
								
							| @ -6,6 +6,7 @@ module Utils ( | |||||||
|               module Data.Tree, |               module Data.Tree, | ||||||
|               module Data.Map, |               module Data.Map, | ||||||
|               module Data.Ord, |               module Data.Ord, | ||||||
|  |               module Data.Maybe, | ||||||
|               module Text.Printf, |               module Text.Printf, | ||||||
|               module Text.Regex, |               module Text.Regex, | ||||||
|               module Debug.Trace, |               module Debug.Trace, | ||||||
| @ -18,6 +19,7 @@ import Data.List | |||||||
| import Data.Tree | import Data.Tree | ||||||
| import qualified Data.Map | import qualified Data.Map | ||||||
| import Data.Ord | import Data.Ord | ||||||
|  | import Data.Maybe | ||||||
| import Text.Printf | import Text.Printf | ||||||
| import Text.Regex | import Text.Regex | ||||||
| import Debug.Trace | import Debug.Trace | ||||||
|  | |||||||
							
								
								
									
										11
									
								
								hledger.hs
									
									
									
									
									
								
							
							
						
						
									
										11
									
								
								hledger.hs
									
									
									
									
									
								
							| @ -32,16 +32,16 @@ main = do | |||||||
|             | cmd `isPrefixOf` "balance"  = balance  opts pats |             | cmd `isPrefixOf` "balance"  = balance  opts pats | ||||||
|             | otherwise                   = putStr usage |             | otherwise                   = putStr usage | ||||||
| 
 | 
 | ||||||
| doWithFilteredLedger :: [Flag] -> ([Regex],[Regex]) -> (Ledger -> IO ()) -> IO () | doWithFilteredLedger :: [Flag] -> FilterPatterns -> (Ledger -> IO ()) -> IO () | ||||||
| doWithFilteredLedger opts pats cmd = do | doWithFilteredLedger opts pats cmd = do | ||||||
|     ledgerFilePath opts >>= parseLedgerFile >>= doWithParsed pats cmd |     ledgerFilePath opts >>= parseLedgerFile >>= doWithParsed pats cmd | ||||||
| 
 | 
 | ||||||
| doWithParsed :: ([Regex],[Regex]) -> (Ledger -> IO ()) -> (Either ParseError LedgerFile) -> IO () | doWithParsed :: FilterPatterns -> (Ledger -> IO ()) -> (Either ParseError LedgerFile) -> IO () | ||||||
| doWithParsed pats cmd parsed = do | doWithParsed pats cmd parsed = do | ||||||
|   case parsed of Left e -> parseError e |   case parsed of Left e -> parseError e | ||||||
|                  Right l -> cmd $ cacheLedger pats l  |                  Right l -> cmd $ cacheLedger pats l  | ||||||
| 
 | 
 | ||||||
| type Command = [Flag] -> ([Regex],[Regex]) -> IO () | type Command = [Flag] -> FilterPatterns -> IO () | ||||||
| 
 | 
 | ||||||
| test :: Command | test :: Command | ||||||
| test opts pats = do  | test opts pats = do  | ||||||
| @ -74,9 +74,8 @@ balance opts pats = do | |||||||
|           putStr $ showLedgerAccounts l depth |           putStr $ showLedgerAccounts l depth | ||||||
|               where  |               where  | ||||||
|                 showsubs = (ShowSubs `elem` opts) |                 showsubs = (ShowSubs `elem` opts) | ||||||
|                 (acctpats,_) = pats |                 depth = case (pats, showsubs) of | ||||||
|                 depth = case (acctpats, showsubs) of |                           ((Nothing,_), False) -> 1 | ||||||
|                           ([],False) -> 1 |  | ||||||
|                           otherwise  -> 9999 |                           otherwise  -> 9999 | ||||||
| 
 | 
 | ||||||
| {- | {- | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user