cleanup
This commit is contained in:
parent
2eba557d94
commit
caef315906
@ -40,7 +40,7 @@ module ConvertCommand where
|
|||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
import Data.List.Split (splitOn)
|
import Data.List.Split (splitOn)
|
||||||
import Options -- (Opt,Debug)
|
import Options -- (Opt,Debug)
|
||||||
import Ledger.Types (Ledger)
|
import Ledger.Types (Ledger,AccountName)
|
||||||
import Ledger.Utils (strip)
|
import Ledger.Utils (strip)
|
||||||
import System (getArgs)
|
import System (getArgs)
|
||||||
import System.IO (stderr, hPutStrLn)
|
import System.IO (stderr, hPutStrLn)
|
||||||
@ -67,15 +67,15 @@ convert opts args l = do
|
|||||||
mapM_ (print_ledger_txn (Debug `elem` opts) (baseacct,fieldpositions,rules)) records
|
mapM_ (print_ledger_txn (Debug `elem` opts) (baseacct,fieldpositions,rules)) records
|
||||||
|
|
||||||
|
|
||||||
type Rule = (String -- account name to use
|
type Rule = ([[String]] -- list of [pattern,replacement]. replacement may or may not be present.
|
||||||
,[[String]]) -- list of pattern+replacements. The second replacement item may or may not be present.
|
,AccountName) -- account name to use for a transaction matching this rule
|
||||||
|
|
||||||
parseRules :: String -> IO ([Int],[Rule])
|
parseRules :: String -> IO ([Int],[Rule])
|
||||||
parseRules s = do
|
parseRules s = do
|
||||||
let ls = map strip $ lines s
|
let ls = map strip $ lines s
|
||||||
let paras = splitOn [""] ls
|
let paras = splitOn [""] ls
|
||||||
let fieldpositions = map read $ splitOn "," $ head $ head paras
|
let fieldpositions = map read $ splitOn "," $ head $ head paras
|
||||||
let rules = [(last p,map (splitOn "=") $ init p) | p <- tail paras]
|
let rules = [(map (splitOn "=") $ init p, last p) | p <- tail paras]
|
||||||
return (fieldpositions,rules)
|
return (fieldpositions,rules)
|
||||||
|
|
||||||
print_ledger_txn debug (baseacct,fieldpositions,rules) record@(a:b:c:d:e) = do
|
print_ledger_txn debug (baseacct,fieldpositions,rules) record@(a:b:c:d:e) = do
|
||||||
@ -96,8 +96,8 @@ print_ledger_txn _ _ _ = return ()
|
|||||||
choose_acct_desc rules (acct,desc) | null matches = (acct,desc)
|
choose_acct_desc rules (acct,desc) | null matches = (acct,desc)
|
||||||
| otherwise = (a,d)
|
| otherwise = (a,d)
|
||||||
where
|
where
|
||||||
matches = filter (any (desc =~) . map head . snd) rules
|
matches = filter (any (desc =~) . map head . fst) rules
|
||||||
(a,pats) = head matches :: Rule
|
(pats,a) = head matches :: Rule
|
||||||
((before,match,after,groups),repl) = head $ filter isMatch $ map (\(pat:repl) -> (desc=~pat,repl)) pats
|
((before,match,after,groups),repl) = head $ filter isMatch $ map (\(pat:repl) -> (desc=~pat,repl)) pats
|
||||||
d = head $ repl ++ [match] -- show the replacement text if any, or the matched text
|
d = head $ repl ++ [match] -- show the replacement text if any, or the matched text
|
||||||
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user