explicit-rules-file-argument-and-converting-stdin
* Adding support for telling which rules file to use with "--rules FILE". * Adding support for using stdin when converting files.
This commit is contained in:
		
							parent
							
								
									5084280879
								
							
						
					
					
						commit
						170154edfb
					
				
							
								
								
									
										16
									
								
								MANUAL.md
									
									
									
									
									
								
							
							
						
						
									
										16
									
								
								MANUAL.md
									
									
									
									
									
								
							@ -521,7 +521,13 @@ journal.
 | 
				
			|||||||
convert requires a \*.rules file containing data definitions and rules for
 | 
					convert requires a \*.rules file containing data definitions and rules for
 | 
				
			||||||
assigning destination accounts to transactions; it will be auto-created if
 | 
					assigning destination accounts to transactions; it will be auto-created if
 | 
				
			||||||
missing. Typically you will have one csv file and one rules file per bank
 | 
					missing. Typically you will have one csv file and one rules file per bank
 | 
				
			||||||
account. Here's an example rules file for converting csv data from a Wells
 | 
					account.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					If you have many CSV files for each account, have many accounts in the
 | 
				
			||||||
 | 
					same bank or for any other reason want to re-use the rules file you can
 | 
				
			||||||
 | 
					state it explicitly with the `--rules` argument.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Here's an example rules file for converting csv data from a Wells
 | 
				
			||||||
Fargo checking account:
 | 
					Fargo checking account:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    base-account assets:bank:checking
 | 
					    base-account assets:bank:checking
 | 
				
			||||||
@ -600,6 +606,14 @@ Notes:
 | 
				
			|||||||
    track the expenses in the currencies there were made, while
 | 
					    track the expenses in the currencies there were made, while
 | 
				
			||||||
    keeping your base account in single currency
 | 
					    keeping your base account in single currency
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					The convert command also supports converting standard input if you're
 | 
				
			||||||
 | 
					streaming a CSV file from the web or another tool. Use `-` as the input
 | 
				
			||||||
 | 
					file and hledger will read from stdin:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					    $ cat foo.csv | fixup | hledger convert --rules foo.rules -
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Note that a rules file is required when streaming.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
### histogram
 | 
					### histogram
 | 
				
			||||||
 | 
					
 | 
				
			||||||
The histogram command displays a quick bar chart showing transaction
 | 
					The histogram command displays a quick bar chart showing transaction
 | 
				
			||||||
 | 
				
			|||||||
@ -29,7 +29,6 @@ library
 | 
				
			|||||||
  -- should set patchlevel here as in Makefile
 | 
					  -- should set patchlevel here as in Makefile
 | 
				
			||||||
  cpp-options:    -DPATCHLEVEL=0
 | 
					  cpp-options:    -DPATCHLEVEL=0
 | 
				
			||||||
  exposed-modules:
 | 
					  exposed-modules:
 | 
				
			||||||
                  Hledger
 | 
					 | 
				
			||||||
                  Hledger.Data
 | 
					                  Hledger.Data
 | 
				
			||||||
                  Hledger.Data.Account
 | 
					                  Hledger.Data.Account
 | 
				
			||||||
                  Hledger.Data.AccountName
 | 
					                  Hledger.Data.AccountName
 | 
				
			||||||
 | 
				
			|||||||
@ -4,6 +4,7 @@ format, and print it on stdout. See the manual for more details.
 | 
				
			|||||||
-}
 | 
					-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
module Hledger.Cli.Convert where
 | 
					module Hledger.Cli.Convert where
 | 
				
			||||||
 | 
					import Prelude hiding (getContents)
 | 
				
			||||||
import Control.Monad (when, guard, liftM)
 | 
					import Control.Monad (when, guard, liftM)
 | 
				
			||||||
import Data.Maybe
 | 
					import Data.Maybe
 | 
				
			||||||
import Data.Time.Format (parseTime)
 | 
					import Data.Time.Format (parseTime)
 | 
				
			||||||
@ -16,18 +17,19 @@ import System.FilePath (takeBaseName, replaceExtension)
 | 
				
			|||||||
import System.IO (stderr)
 | 
					import System.IO (stderr)
 | 
				
			||||||
import System.Locale (defaultTimeLocale)
 | 
					import System.Locale (defaultTimeLocale)
 | 
				
			||||||
import Test.HUnit
 | 
					import Test.HUnit
 | 
				
			||||||
import Text.CSV (parseCSVFromFile, printCSV)
 | 
					import Text.CSV (parseCSV, parseCSVFromFile, printCSV, CSV)
 | 
				
			||||||
import Text.ParserCombinators.Parsec
 | 
					import Text.ParserCombinators.Parsec
 | 
				
			||||||
import Text.Printf (hPrintf)
 | 
					import Text.Printf (hPrintf)
 | 
				
			||||||
import Text.RegexPR (matchRegexPR, gsubRegexPR)
 | 
					import Text.RegexPR (matchRegexPR, gsubRegexPR)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Hledger.Cli.Options (Opt(Debug), progname_cli)
 | 
					import Hledger.Cli.Options (Opt(Debug), progname_cli, rulesFileFromOpts)
 | 
				
			||||||
import Hledger.Cli.Version (progversionstr)
 | 
					import Hledger.Cli.Version (progversionstr)
 | 
				
			||||||
import Hledger.Data (Journal,AccountName,Transaction(..),Posting(..),PostingType(..))
 | 
					import Hledger.Data (Journal,AccountName,Transaction(..),Posting(..),PostingType(..))
 | 
				
			||||||
import Hledger.Data.Amount (nullmixedamt, costOfMixedAmount)
 | 
					import Hledger.Data.Amount (nullmixedamt, costOfMixedAmount)
 | 
				
			||||||
import Hledger.Data.Journal (nullctx)
 | 
					import Hledger.Data.Journal (nullctx)
 | 
				
			||||||
import Hledger.Read.JournalReader (someamount,ledgeraccountname)
 | 
					import Hledger.Read.JournalReader (someamount,ledgeraccountname)
 | 
				
			||||||
import Hledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error')
 | 
					import Hledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error')
 | 
				
			||||||
 | 
					import Hledger.Utils.UTF8 (getContents)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- |
 | 
					{- |
 | 
				
			||||||
A set of data definitions and account-matching patterns sufficient to
 | 
					A set of data definitions and account-matching patterns sufficient to
 | 
				
			||||||
@ -79,12 +81,16 @@ convert :: [Opt] -> [String] -> Journal -> IO ()
 | 
				
			|||||||
convert opts args _ = do
 | 
					convert opts args _ = do
 | 
				
			||||||
  when (null args) $ error' "please specify a csv data file."
 | 
					  when (null args) $ error' "please specify a csv data file."
 | 
				
			||||||
  let csvfile = head args
 | 
					  let csvfile = head args
 | 
				
			||||||
  csvparse <- parseCSVFromFile csvfile
 | 
					  let 
 | 
				
			||||||
 | 
					    rulesFileSpecified = isNothing $ rulesFileFromOpts opts
 | 
				
			||||||
 | 
					    usingStdin = csvfile == "-"
 | 
				
			||||||
 | 
					  when (usingStdin && (not rulesFileSpecified)) $ error' "please specify a files file when converting stdin"
 | 
				
			||||||
 | 
					  csvparse <- parseCsv csvfile
 | 
				
			||||||
  let records = case csvparse of
 | 
					  let records = case csvparse of
 | 
				
			||||||
                  Left e -> error' $ show e
 | 
					                  Left e -> error' $ show e
 | 
				
			||||||
                  Right rs -> reverse $ filter (/= [""]) rs
 | 
					                  Right rs -> reverse $ filter (/= [""]) rs
 | 
				
			||||||
  let debug = Debug `elem` opts
 | 
					  let debug = Debug `elem` opts
 | 
				
			||||||
      rulesfile = rulesFileFor csvfile
 | 
					      rulesfile = rulesFileFor opts csvfile
 | 
				
			||||||
  exists <- doesFileExist rulesfile
 | 
					  exists <- doesFileExist rulesfile
 | 
				
			||||||
  if (not exists) then do
 | 
					  if (not exists) then do
 | 
				
			||||||
                  hPrintf stderr "creating conversion rules file %s, edit this file for better results\n" rulesfile
 | 
					                  hPrintf stderr "creating conversion rules file %s, edit this file for better results\n" rulesfile
 | 
				
			||||||
@ -105,6 +111,12 @@ convert opts args _ = do
 | 
				
			|||||||
                     ]) (show $ head badrecords)
 | 
					                     ]) (show $ head badrecords)
 | 
				
			||||||
     exitFailure
 | 
					     exitFailure
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					parseCsv :: FilePath -> IO (Either ParseError CSV)
 | 
				
			||||||
 | 
					parseCsv path =
 | 
				
			||||||
 | 
					  case path of
 | 
				
			||||||
 | 
					    "-" -> liftM (parseCSV "(stdin)") getContents
 | 
				
			||||||
 | 
					    p   -> parseCSVFromFile p
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | The highest (0-based) field index referenced in the field
 | 
					-- | The highest (0-based) field index referenced in the field
 | 
				
			||||||
-- definitions, or -1 if no fields are defined.
 | 
					-- definitions, or -1 if no fields are defined.
 | 
				
			||||||
maxFieldIndex :: CsvRules -> Int
 | 
					maxFieldIndex :: CsvRules -> Int
 | 
				
			||||||
@ -119,8 +131,13 @@ maxFieldIndex r = maximumDef (-1) $ catMaybes [
 | 
				
			|||||||
                  ,effectiveDateField r
 | 
					                  ,effectiveDateField r
 | 
				
			||||||
                  ]
 | 
					                  ]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
rulesFileFor :: FilePath -> FilePath
 | 
					rulesFileFor :: [Opt] -> FilePath -> FilePath
 | 
				
			||||||
rulesFileFor csvfile = replaceExtension csvfile ".rules"
 | 
					rulesFileFor opts csvfile = 
 | 
				
			||||||
 | 
					    case opt of
 | 
				
			||||||
 | 
					      Just path -> path
 | 
				
			||||||
 | 
					      Nothing   -> replaceExtension csvfile ".rules"
 | 
				
			||||||
 | 
					    where
 | 
				
			||||||
 | 
					      opt = rulesFileFromOpts opts
 | 
				
			||||||
 | 
					
 | 
				
			||||||
initialRulesFileContent :: String
 | 
					initialRulesFileContent :: String
 | 
				
			||||||
initialRulesFileContent =
 | 
					initialRulesFileContent =
 | 
				
			||||||
 | 
				
			|||||||
@ -84,6 +84,7 @@ options_cli = [
 | 
				
			|||||||
 ,Option "M" ["monthly"]      (NoArg  MonthlyOpt)    "register, stats: report by month"
 | 
					 ,Option "M" ["monthly"]      (NoArg  MonthlyOpt)    "register, stats: report by month"
 | 
				
			||||||
 ,Option "Q" ["quarterly"]    (NoArg  QuarterlyOpt)  "register, stats: report by quarter"
 | 
					 ,Option "Q" ["quarterly"]    (NoArg  QuarterlyOpt)  "register, stats: report by quarter"
 | 
				
			||||||
 ,Option "Y" ["yearly"]       (NoArg  YearlyOpt)     "register, stats: report by year"
 | 
					 ,Option "Y" ["yearly"]       (NoArg  YearlyOpt)     "register, stats: report by year"
 | 
				
			||||||
 | 
					 ,Option "r" ["rules"]        (ReqArg RulesFile "FILE") "convert, rules file to use"
 | 
				
			||||||
 ,Option "v" ["verbose"]      (NoArg  Verbose)       "show more verbose output"
 | 
					 ,Option "v" ["verbose"]      (NoArg  Verbose)       "show more verbose output"
 | 
				
			||||||
 ,Option ""  ["debug"]        (NoArg  Debug)         "show extra debug output; implies verbose"
 | 
					 ,Option ""  ["debug"]        (NoArg  Debug)         "show extra debug output; implies verbose"
 | 
				
			||||||
 ,Option ""  ["binary-filename"] (NoArg BinaryFilename) "show the download filename for this hledger build"
 | 
					 ,Option ""  ["binary-filename"] (NoArg BinaryFilename) "show the download filename for this hledger build"
 | 
				
			||||||
@ -115,6 +116,7 @@ data Opt =
 | 
				
			|||||||
    | MonthlyOpt
 | 
					    | MonthlyOpt
 | 
				
			||||||
    | QuarterlyOpt
 | 
					    | QuarterlyOpt
 | 
				
			||||||
    | YearlyOpt
 | 
					    | YearlyOpt
 | 
				
			||||||
 | 
					    | RulesFile   {value::String}
 | 
				
			||||||
    | Help
 | 
					    | Help
 | 
				
			||||||
    | Verbose
 | 
					    | Verbose
 | 
				
			||||||
    | Version
 | 
					    | Version
 | 
				
			||||||
@ -213,6 +215,12 @@ intervalFromOpts opts =
 | 
				
			|||||||
      periodopts   = reverse $ optValuesForConstructor Period opts
 | 
					      periodopts   = reverse $ optValuesForConstructor Period opts
 | 
				
			||||||
      intervalopts = reverse $ filter (`elem` [DailyOpt,WeeklyOpt,MonthlyOpt,QuarterlyOpt,YearlyOpt]) opts
 | 
					      intervalopts = reverse $ filter (`elem` [DailyOpt,WeeklyOpt,MonthlyOpt,QuarterlyOpt,YearlyOpt]) opts
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					rulesFileFromOpts :: [Opt] -> Maybe FilePath
 | 
				
			||||||
 | 
					rulesFileFromOpts opts = listtomaybe $ optValuesForConstructor RulesFile opts
 | 
				
			||||||
 | 
					    where
 | 
				
			||||||
 | 
					      listtomaybe [] = Nothing
 | 
				
			||||||
 | 
					      listtomaybe vs = Just $ head vs
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Get the value of the (last) depth option, if any.
 | 
					-- | Get the value of the (last) depth option, if any.
 | 
				
			||||||
depthFromOpts :: [Opt] -> Maybe Int
 | 
					depthFromOpts :: [Opt] -> Maybe Int
 | 
				
			||||||
depthFromOpts opts = listtomaybeint $ optValuesForConstructor Depth opts
 | 
					depthFromOpts opts = listtomaybeint $ optValuesForConstructor Depth opts
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user