read multiple files: internals
This commit is contained in:
		
							parent
							
								
									2eb4073651
								
							
						
					
					
						commit
						3f15b80520
					
				@ -15,6 +15,7 @@ module Hledger.Read (
 | 
				
			|||||||
       readJournal,
 | 
					       readJournal,
 | 
				
			||||||
       readJournal',
 | 
					       readJournal',
 | 
				
			||||||
       readJournalFile,
 | 
					       readJournalFile,
 | 
				
			||||||
 | 
					       readJournalFiles,
 | 
				
			||||||
       requireJournalFileExists,
 | 
					       requireJournalFileExists,
 | 
				
			||||||
       ensureJournalFileExists,
 | 
					       ensureJournalFileExists,
 | 
				
			||||||
       -- * Parsers used elsewhere
 | 
					       -- * Parsers used elsewhere
 | 
				
			||||||
@ -39,7 +40,7 @@ import System.Directory (doesFileExist, getHomeDirectory)
 | 
				
			|||||||
import System.Environment (getEnv)
 | 
					import System.Environment (getEnv)
 | 
				
			||||||
import System.Exit (exitFailure)
 | 
					import System.Exit (exitFailure)
 | 
				
			||||||
import System.FilePath ((</>))
 | 
					import System.FilePath ((</>))
 | 
				
			||||||
import System.IO (IOMode(..), withFile, stdin, stderr, hSetNewlineMode, universalNewlineMode)
 | 
					import System.IO (IOMode(..), openFile, stdin, stderr, hSetNewlineMode, universalNewlineMode)
 | 
				
			||||||
import Test.HUnit
 | 
					import Test.HUnit
 | 
				
			||||||
import Text.Printf
 | 
					import Text.Printf
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -51,7 +52,7 @@ import Hledger.Read.TimelogReader as TimelogReader
 | 
				
			|||||||
import Hledger.Read.CsvReader as CsvReader
 | 
					import Hledger.Read.CsvReader as CsvReader
 | 
				
			||||||
import Hledger.Utils
 | 
					import Hledger.Utils
 | 
				
			||||||
import Prelude hiding (getContents, writeFile)
 | 
					import Prelude hiding (getContents, writeFile)
 | 
				
			||||||
import Hledger.Utils.UTF8IOCompat (getContents, hGetContents, writeFile)
 | 
					import Hledger.Utils.UTF8IOCompat (hGetContents, writeFile)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
journalEnvVar           = "LEDGER_FILE"
 | 
					journalEnvVar           = "LEDGER_FILE"
 | 
				
			||||||
@ -163,17 +164,24 @@ readersForPathAndData (f,s) = filter (\r -> (rDetector r) f s) readers
 | 
				
			|||||||
-- conversion of that format. Also there is a flag specifying whether
 | 
					-- conversion of that format. Also there is a flag specifying whether
 | 
				
			||||||
-- to check or ignore balance assertions in the journal.
 | 
					-- to check or ignore balance assertions in the journal.
 | 
				
			||||||
readJournalFile :: Maybe StorageFormat -> Maybe FilePath -> Bool -> FilePath -> IO (Either String Journal)
 | 
					readJournalFile :: Maybe StorageFormat -> Maybe FilePath -> Bool -> FilePath -> IO (Either String Journal)
 | 
				
			||||||
readJournalFile format rulesfile assrt "-" = do
 | 
					readJournalFile format rulesfile assrt f = readJournalFiles format rulesfile assrt [f]
 | 
				
			||||||
  hSetNewlineMode stdin universalNewlineMode
 | 
					
 | 
				
			||||||
  getContents >>= readJournal format rulesfile assrt (Just "-")
 | 
					readJournalFiles :: Maybe StorageFormat -> Maybe FilePath -> Bool -> [FilePath] -> IO (Either String Journal)
 | 
				
			||||||
readJournalFile format rulesfile assrt f = do
 | 
					readJournalFiles format rulesfile assrt f = do
 | 
				
			||||||
 | 
					  contents <- fmap concat $ mapM readFileAnyNewline f
 | 
				
			||||||
 | 
					  readJournal format rulesfile assrt (listToMaybe f) contents
 | 
				
			||||||
 | 
					 where
 | 
				
			||||||
 | 
					  readFileAnyNewline f = do
 | 
				
			||||||
    requireJournalFileExists f
 | 
					    requireJournalFileExists f
 | 
				
			||||||
  withFile f ReadMode $ \h -> do
 | 
					    h <- fileHandle f
 | 
				
			||||||
    hSetNewlineMode h universalNewlineMode
 | 
					    hSetNewlineMode h universalNewlineMode
 | 
				
			||||||
    hGetContents h >>= readJournal format rulesfile assrt (Just f)
 | 
					    hGetContents h
 | 
				
			||||||
 | 
					  fileHandle "-" = return stdin
 | 
				
			||||||
 | 
					  fileHandle f = openFile f ReadMode
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | If the specified journal file does not exist, give a helpful error and quit.
 | 
					-- | If the specified journal file does not exist, give a helpful error and quit.
 | 
				
			||||||
requireJournalFileExists :: FilePath -> IO ()
 | 
					requireJournalFileExists :: FilePath -> IO ()
 | 
				
			||||||
 | 
					requireJournalFileExists "-" = return ()
 | 
				
			||||||
requireJournalFileExists f = do
 | 
					requireJournalFileExists f = do
 | 
				
			||||||
  exists <- doesFileExist f
 | 
					  exists <- doesFileExist f
 | 
				
			||||||
  when (not exists) $ do
 | 
					  when (not exists) $ do
 | 
				
			||||||
 | 
				
			|||||||
@ -68,7 +68,7 @@ withJournalDo opts cmd = do
 | 
				
			|||||||
  -- to let the add command work.
 | 
					  -- to let the add command work.
 | 
				
			||||||
  rulespath <- rulesFilePathFromOpts opts
 | 
					  rulespath <- rulesFilePathFromOpts opts
 | 
				
			||||||
  journalpath <- journalFilePathFromOpts opts
 | 
					  journalpath <- journalFilePathFromOpts opts
 | 
				
			||||||
  ej <- readJournalFile Nothing rulespath (not $ ignore_assertions_ opts) (head journalpath)
 | 
					  ej <- readJournalFiles Nothing rulespath (not $ ignore_assertions_ opts) journalpath
 | 
				
			||||||
  either error' (cmd opts . journalApplyAliases (aliasesFromOpts opts)) ej
 | 
					  either error' (cmd opts . journalApplyAliases (aliasesFromOpts opts)) ej
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Write some output to stdout or to a file selected by --output-file.
 | 
					-- | Write some output to stdout or to a file selected by --output-file.
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user