--- * -*- outline-regexp:"--- \\*"; -*-
--- ** doc
-- In Emacs, use TAB on lines beginning with "-- *" to collapse/expand sections.
{-|

This is the entry point to hledger's reading system, which can read
Journals from various data formats. Use this module if you want to parse
journal data or read journal files. Generally it should not be necessary
to import modules below this one.

== Journal reading

Reading an input file (in journal, csv, timedot, or timeclock format..)
involves these steps:

- select an appropriate file format "reader"
  based on filename extension/file path prefix/function parameter.
  A reader contains a parser and a finaliser (usually @journalFinalise@).

- run the parser to get a ParsedJournal
  (this may run additional sub-parsers to parse included files)

- run the finaliser to get a complete Journal, which passes standard checks

- if reading multiple files: merge the per-file Journals into one
  overall Journal

- if using -s/--strict: run additional strict checks

- if running print --new: save .latest files for each input file.
  (import also does this, as its final step.)

== Journal merging

Journal implements the Semigroup class, so two Journals can be merged
into one Journal with @j1 <> j2@. This is implemented by the
@journalConcat@ function, whose documentation explains what merging
Journals means exactly.

== Journal finalising

This is post-processing done after parsing an input file, such as
inferring missing information, normalising amount styles,
checking for errors and so on - a delicate and influential stage
of data processing. 
In hledger it is done by @journalFinalise@, which converts a
preliminary ParsedJournal to a validated, ready-to-use Journal.
This is called immediately after the parsing of each input file.
It is not called when Journals are merged.

== Journal reading API

There are three main Journal-reading functions:

- readJournal to read from a Text value.
  Selects a reader and calls its parser and finaliser,
  then does strict checking if needed.

- readJournalFile to read one file, or stdin if the file path is @-@.
  Uses the file path/file name to help select the reader,
  calls readJournal,
  then writes .latest files if needed.

- readJournalFiles to read multiple files.
  Calls readJournalFile for each file (without strict checking or .latest file writing)
  then merges the Journals into one,
  then does strict checking and .latest file writing at the end if needed.

Each of these also has an easier variant with ' suffix,
which uses default options and has a simpler type signature.

One more variant, @readJournalFilesAndLatestDates@, is like
readJournalFiles but exposing the latest transaction date
(and how many on the same day) seen for each file.
This is used by the import command.

-}

--- ** language
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE PackageImports      #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

--- ** exports
module Hledger.Read (

  -- * Journal files
  PrefixedFilePath,
  defaultJournal,
  defaultJournalPath,
  requireJournalFileExists,
  ensureJournalFileExists,

  -- * Journal parsing
  runExceptT,
  readJournal,
  readJournalFile,
  readJournalFiles,
  readJournalFilesAndLatestDates,

  -- * Easy journal parsing
  readJournal',
  readJournalFile',
  readJournalFiles',
  orDieTrying,

  -- * Misc
  journalStrictChecks,
  saveLatestDates,
  saveLatestDatesForFiles,

  -- * Re-exported
  JournalReader.tmpostingrulep,
  findReader,
  splitReaderPrefix,
  runJournalParser,
  module Hledger.Read.Common,
  module Hledger.Read.InputOptions,

  -- * Tests
  tests_Read,

) where

--- ** imports
import qualified Control.Exception as C
import Control.Monad (unless, when)
import "mtl" Control.Monad.Except (ExceptT(..), runExceptT, liftEither)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Default (def)
import Data.Foldable (asum)
import Data.List (group, sort, sortBy)
import Data.List.NonEmpty (nonEmpty)
import Data.Maybe (catMaybes, fromMaybe)
import Data.Ord (comparing)
import Data.Semigroup (sconcat)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Time (Day)
import Safe (headDef, headMay)
import System.Directory (doesFileExist, getHomeDirectory)
import System.Environment (getEnv)
import System.Exit (exitFailure)
import System.FilePath ((<.>), (</>), splitDirectories, splitFileName, takeFileName)
import System.Info (os)
import System.IO (hPutStr, stderr)

import Hledger.Data.Dates (getCurrentDay, parsedateM, showDate)
import Hledger.Data.Types
import Hledger.Read.Common
import Hledger.Read.InputOptions
import Hledger.Read.JournalReader as JournalReader
import Hledger.Read.CsvReader (tests_CsvReader)
import Hledger.Read.RulesReader (tests_RulesReader)
-- import Hledger.Read.TimedotReader (tests_TimedotReader)
-- import Hledger.Read.TimeclockReader (tests_TimeclockReader)
import Hledger.Utils
import Prelude hiding (getContents, writeFile)
import Hledger.Data.JournalChecks (journalCheckAccounts, journalCheckCommodities)

--- ** doctest setup
-- $setup
-- >>> :set -XOverloadedStrings

--- ** journal reading

journalEnvVar :: String
journalEnvVar           = String
"LEDGER_FILE"
journalEnvVar2 :: String
journalEnvVar2          = String
"LEDGER"
journalDefaultFilename :: String
journalDefaultFilename  = String
".hledger.journal"

-- | Read the default journal file specified by the environment, or raise an error.
defaultJournal :: IO Journal
defaultJournal :: IO Journal
defaultJournal = IO String
defaultJournalPath IO String
-> (String -> IO (Either String Journal))
-> IO (Either String Journal)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExceptT String IO Journal -> IO (Either String Journal)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT String IO Journal -> IO (Either String Journal))
-> (String -> ExceptT String IO Journal)
-> String
-> IO (Either String Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputOpts -> String -> ExceptT String IO Journal
readJournalFile InputOpts
definputopts IO (Either String Journal)
-> (Either String Journal -> IO Journal) -> IO Journal
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> IO Journal)
-> (Journal -> IO Journal) -> Either String Journal -> IO Journal
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> IO Journal
forall a. String -> a
error' Journal -> IO Journal
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return  -- PARTIAL:

-- | Get the default journal file path specified by the environment.
-- Like ledger, we look first for the LEDGER_FILE environment
-- variable, and if that does not exist, for the legacy LEDGER
-- environment variable. If neither is set, or the value is blank,
-- return the hard-coded default, which is @.hledger.journal@ in the
-- users's home directory (or in the current directory, if we cannot
-- determine a home directory).
defaultJournalPath :: IO String
defaultJournalPath :: IO String
defaultJournalPath = do
  String
p <- IO String
envJournalPath
  if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
p
  then IO String
defpath
  else do
    [String]
ps <- String -> String -> IO [String]
expandGlob String
"." String
p IO [String] -> (IOException -> IO [String]) -> IO [String]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`C.catch` (\(IOException
_::C.IOException) -> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [])
    IO String -> (String -> IO String) -> Maybe String -> IO String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO String
defpath String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> IO String) -> Maybe String -> IO String
forall a b. (a -> b) -> a -> b
$ [String] -> Maybe String
forall a. [a] -> Maybe a
headMay [String]
ps
    where
      envJournalPath :: IO String
envJournalPath =
        String -> IO String
getEnv String
journalEnvVar
         IO String -> (IOException -> IO String) -> IO String
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`C.catch` (\(IOException
_::C.IOException) -> String -> IO String
getEnv String
journalEnvVar2
                                            IO String -> (IOException -> IO String) -> IO String
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`C.catch` (\(IOException
_::C.IOException) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
""))
      defpath :: IO String
defpath = do
        String
home <- IO String
getHomeDirectory IO String -> (IOException -> IO String) -> IO String
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`C.catch` (\(IOException
_::C.IOException) -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"")
        String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String
home String -> String -> String
</> String
journalDefaultFilename

-- | A file path optionally prefixed by a reader name and colon
-- (journal:, csv:, timedot:, etc.).
type PrefixedFilePath = FilePath

-- | @readJournal iopts mfile txt@
--
-- Read a Journal from some text, with strict checks if enabled,
-- or return an error message.
--
-- The reader (data format) is chosen based on, in this order:
--
-- - a reader name provided in @iopts@
--
-- - a reader prefix in the @mfile@ path
--
-- - a file extension in @mfile@
--
-- If none of these is available, or if the reader name is unrecognised,
-- we use the journal reader (for predictability).
--
readJournal :: InputOpts -> Maybe FilePath -> Text -> ExceptT String IO Journal
readJournal :: InputOpts -> Maybe String -> Text -> ExceptT String IO Journal
readJournal iopts :: InputOpts
iopts@InputOpts{Bool
strict_ :: Bool
strict_ :: InputOpts -> Bool
strict_} Maybe String
mpath Text
txt = do
  let Reader IO
r :: Reader IO = Reader IO -> Maybe (Reader IO) -> Reader IO
forall a. a -> Maybe a -> a
fromMaybe Reader IO
forall (m :: * -> *). MonadIO m => Reader m
JournalReader.reader (Maybe (Reader IO) -> Reader IO) -> Maybe (Reader IO) -> Reader IO
forall a b. (a -> b) -> a -> b
$ Maybe StorageFormat -> Maybe String -> Maybe (Reader IO)
forall (m :: * -> *).
MonadIO m =>
Maybe StorageFormat -> Maybe String -> Maybe (Reader m)
findReader (InputOpts -> Maybe StorageFormat
mformat_ InputOpts
iopts) Maybe String
mpath
  String -> StorageFormat -> ExceptT String IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg6IO String
"readJournal: trying reader" (Reader IO -> StorageFormat
forall (m :: * -> *). Reader m -> StorageFormat
rFormat Reader IO
r)
  Journal
j <- Reader IO
-> InputOpts -> String -> Text -> ExceptT String IO Journal
forall (m :: * -> *).
Reader m
-> InputOpts -> String -> Text -> ExceptT String IO Journal
rReadFn Reader IO
r InputOpts
iopts (String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"(string)" Maybe String
mpath) Text
txt
  Bool -> ExceptT String IO () -> ExceptT String IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
strict_ (ExceptT String IO () -> ExceptT String IO ())
-> ExceptT String IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ Either String () -> ExceptT String IO ()
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Either String () -> ExceptT String IO ())
-> Either String () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ Journal -> Either String ()
journalStrictChecks Journal
j
  Journal -> ExceptT String IO Journal
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Journal
j

-- | Read a Journal from this file, or from stdin if the file path is -,
-- with strict checks if enabled, or return an error message.
-- The file path can have a READER: prefix.
--
-- The reader (data format) to use is determined from (in priority order):
-- the @mformat_@ specified in the input options, if any;
-- the file path's READER: prefix, if any;
-- a recognised file name extension.
-- if none of these identify a known reader, the journal reader is used.
--
-- The input options can also configure balance assertion checking, automated posting
-- generation, a rules file for converting CSV data, etc.
--
-- If using --new, and if latest-file writing is enabled in input options,
-- and after passing strict checks if enabled, a .latest.FILE file will be created/updated
-- (for the main file only, not for included files),
-- to remember the latest transaction date (and how many transactions on this date)
-- successfully read.
--
readJournalFile :: InputOpts -> PrefixedFilePath -> ExceptT String IO Journal
readJournalFile :: InputOpts -> String -> ExceptT String IO Journal
readJournalFile iopts :: InputOpts
iopts@InputOpts{Bool
new_ :: Bool
new_ :: InputOpts -> Bool
new_, Bool
new_save_ :: Bool
new_save_ :: InputOpts -> Bool
new_save_} String
prefixedfile = do
  (Journal
j, Maybe LatestDatesForFile
mlatestdates) <- InputOpts
-> String -> ExceptT String IO (Journal, Maybe LatestDatesForFile)
readJournalFileAndLatestDates InputOpts
iopts String
prefixedfile
  Bool -> ExceptT String IO () -> ExceptT String IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
new_ Bool -> Bool -> Bool
&& Bool
new_save_) (ExceptT String IO () -> ExceptT String IO ())
-> ExceptT String IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> ExceptT String IO ()
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String IO ()) -> IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$
    case Maybe LatestDatesForFile
mlatestdates of
      Maybe LatestDatesForFile
Nothing                        -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      Just (LatestDatesForFile String
f LatestDates
ds) -> LatestDates -> String -> IO ()
saveLatestDates LatestDates
ds String
f
  Journal -> ExceptT String IO Journal
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Journal
j

-- The implementation of readJournalFile.
-- With --new, it also returns the latest transaction date(s) read from each file.
-- readJournalFiles uses this to update .latest files only after a successful read of all.
readJournalFileAndLatestDates :: InputOpts -> PrefixedFilePath -> ExceptT String IO (Journal, Maybe LatestDatesForFile)
readJournalFileAndLatestDates :: InputOpts
-> String -> ExceptT String IO (Journal, Maybe LatestDatesForFile)
readJournalFileAndLatestDates InputOpts
iopts String
prefixedfile = do
  let
    (Maybe StorageFormat
mfmt, String
f) = String -> (Maybe StorageFormat, String)
splitReaderPrefix String
prefixedfile
    iopts' :: InputOpts
iopts' = InputOpts
iopts{mformat_=asum [mfmt, mformat_ iopts]}
  IO () -> ExceptT String IO ()
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String IO ()) -> IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
requireJournalFileExists String
f
  Text
t <-
    Int -> String -> ExceptT String IO Text -> ExceptT String IO Text
forall a. Int -> String -> a -> a
traceOrLogAt Int
6 (String
"readJournalFile: "String -> String -> String
forall a. [a] -> [a] -> [a]
++String -> String
takeFileName String
f) (ExceptT String IO Text -> ExceptT String IO Text)
-> ExceptT String IO Text -> ExceptT String IO Text
forall a b. (a -> b) -> a -> b
$
    IO Text -> ExceptT String IO Text
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> ExceptT String IO Text)
-> IO Text -> ExceptT String IO Text
forall a b. (a -> b) -> a -> b
$ String -> IO Text
readFileOrStdinPortably String
f
    -- <- T.readFile f  -- or without line ending translation, for testing
  Journal
j <- InputOpts -> Maybe String -> Text -> ExceptT String IO Journal
readJournal InputOpts
iopts' (String -> Maybe String
forall a. a -> Maybe a
Just String
f) Text
t
  if InputOpts -> Bool
new_ InputOpts
iopts
    then do
      LatestDates
ds <- IO LatestDates -> ExceptT String IO LatestDates
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LatestDates -> ExceptT String IO LatestDates)
-> IO LatestDates -> ExceptT String IO LatestDates
forall a b. (a -> b) -> a -> b
$ String -> IO LatestDates
previousLatestDates String
f
      let (Journal
newj, LatestDates
newds) = LatestDates -> Journal -> (Journal, LatestDates)
journalFilterSinceLatestDates LatestDates
ds Journal
j
      (Journal, Maybe LatestDatesForFile)
-> ExceptT String IO (Journal, Maybe LatestDatesForFile)
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Journal
newj, LatestDatesForFile -> Maybe LatestDatesForFile
forall a. a -> Maybe a
Just (LatestDatesForFile -> Maybe LatestDatesForFile)
-> LatestDatesForFile -> Maybe LatestDatesForFile
forall a b. (a -> b) -> a -> b
$ String -> LatestDates -> LatestDatesForFile
LatestDatesForFile String
f LatestDates
newds)
    else
      (Journal, Maybe LatestDatesForFile)
-> ExceptT String IO (Journal, Maybe LatestDatesForFile)
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Journal
j, Maybe LatestDatesForFile
forall a. Maybe a
Nothing)

-- | Read a Journal from each specified file path (using @readJournalFile@) 
-- and combine them into one; or return the first error message.
-- Strict checks, if enabled, are deferred till the end.
-- Writing .latest files, if enabled, is also deferred till the end,
-- and happens only if strict checks pass.
--
-- Combining Journals means concatenating them, basically.
-- The parse state resets at the start of each file, which means that
-- directives & aliases do not affect subsequent sibling or parent files.
-- They do affect included child files though.
-- Also the final parse state saved in the Journal does span all files.
--
readJournalFiles :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO Journal
readJournalFiles :: InputOpts -> [String] -> ExceptT String IO Journal
readJournalFiles iopts :: InputOpts
iopts@InputOpts{Bool
strict_ :: InputOpts -> Bool
strict_ :: Bool
strict_,Bool
new_ :: InputOpts -> Bool
new_ :: Bool
new_,Bool
new_save_ :: InputOpts -> Bool
new_save_ :: Bool
new_save_} [String]
prefixedfiles = do
  let iopts' :: InputOpts
iopts' = InputOpts
iopts{strict_=False, new_save_=False}
  (Journal
j, [LatestDatesForFile]
latestdatesforfiles) <-
    Int
-> String
-> ExceptT String IO (Journal, [LatestDatesForFile])
-> ExceptT String IO (Journal, [LatestDatesForFile])
forall a. Int -> String -> a -> a
traceOrLogAt Int
6 (String
"readJournalFiles: "String -> String -> String
forall a. [a] -> [a] -> [a]
++[String] -> String
forall a. Show a => a -> String
show [String]
prefixedfiles) (ExceptT String IO (Journal, [LatestDatesForFile])
 -> ExceptT String IO (Journal, [LatestDatesForFile]))
-> ExceptT String IO (Journal, [LatestDatesForFile])
-> ExceptT String IO (Journal, [LatestDatesForFile])
forall a b. (a -> b) -> a -> b
$
    InputOpts
-> [String] -> ExceptT String IO (Journal, [LatestDatesForFile])
readJournalFilesAndLatestDates InputOpts
iopts' [String]
prefixedfiles
  Bool -> ExceptT String IO () -> ExceptT String IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
strict_ (ExceptT String IO () -> ExceptT String IO ())
-> ExceptT String IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ Either String () -> ExceptT String IO ()
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Either String () -> ExceptT String IO ())
-> Either String () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ Journal -> Either String ()
journalStrictChecks Journal
j
  Bool -> ExceptT String IO () -> ExceptT String IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
new_ Bool -> Bool -> Bool
&& Bool
new_save_) (ExceptT String IO () -> ExceptT String IO ())
-> ExceptT String IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> ExceptT String IO ()
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String IO ()) -> IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ [LatestDatesForFile] -> IO ()
saveLatestDatesForFiles [LatestDatesForFile]
latestdatesforfiles
  Journal -> ExceptT String IO Journal
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Journal
j

-- The implementation of readJournalFiles, but with --new, 
-- also returns the latest transaction date(s) read in each file.
-- Used by the import command, to save those at the end.
readJournalFilesAndLatestDates :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO (Journal, [LatestDatesForFile])
readJournalFilesAndLatestDates :: InputOpts
-> [String] -> ExceptT String IO (Journal, [LatestDatesForFile])
readJournalFilesAndLatestDates InputOpts
iopts [String]
pfs = do
  ([Journal]
js, [Maybe LatestDatesForFile]
lastdates) <- [(Journal, Maybe LatestDatesForFile)]
-> ([Journal], [Maybe LatestDatesForFile])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Journal, Maybe LatestDatesForFile)]
 -> ([Journal], [Maybe LatestDatesForFile]))
-> ExceptT String IO [(Journal, Maybe LatestDatesForFile)]
-> ExceptT String IO ([Journal], [Maybe LatestDatesForFile])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> ExceptT String IO (Journal, Maybe LatestDatesForFile))
-> [String]
-> ExceptT String IO [(Journal, Maybe LatestDatesForFile)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (InputOpts
-> String -> ExceptT String IO (Journal, Maybe LatestDatesForFile)
readJournalFileAndLatestDates InputOpts
iopts) [String]
pfs
  (Journal, [LatestDatesForFile])
-> ExceptT String IO (Journal, [LatestDatesForFile])
forall a. a -> ExceptT String IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Journal
-> (NonEmpty Journal -> Journal)
-> Maybe (NonEmpty Journal)
-> Journal
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Journal
forall a. Default a => a
def NonEmpty Journal -> Journal
forall a. Semigroup a => NonEmpty a -> a
sconcat (Maybe (NonEmpty Journal) -> Journal)
-> Maybe (NonEmpty Journal) -> Journal
forall a b. (a -> b) -> a -> b
$ [Journal] -> Maybe (NonEmpty Journal)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty [Journal]
js, [Maybe LatestDatesForFile] -> [LatestDatesForFile]
forall a. [Maybe a] -> [a]
catMaybes [Maybe LatestDatesForFile]
lastdates)

-- | Run the extra -s/--strict checks on a journal,
-- returning the first error message if any of them fail.
journalStrictChecks :: Journal -> Either String ()
journalStrictChecks :: Journal -> Either String ()
journalStrictChecks Journal
j = do
  Journal -> Either String ()
journalCheckAccounts Journal
j
  Journal -> Either String ()
journalCheckCommodities Journal
j

-- | An easy version of 'readJournal' which assumes default options, and fails
-- in the IO monad.
readJournal' :: Text -> IO Journal
readJournal' :: Text -> IO Journal
readJournal' = ExceptT String IO Journal -> IO Journal
forall (m :: * -> *) a. MonadIO m => ExceptT String m a -> m a
orDieTrying (ExceptT String IO Journal -> IO Journal)
-> (Text -> ExceptT String IO Journal) -> Text -> IO Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputOpts -> Maybe String -> Text -> ExceptT String IO Journal
readJournal InputOpts
definputopts Maybe String
forall a. Maybe a
Nothing

-- | An easy version of 'readJournalFile' which assumes default options, and fails
-- in the IO monad.
readJournalFile' :: PrefixedFilePath -> IO Journal
readJournalFile' :: String -> IO Journal
readJournalFile' = ExceptT String IO Journal -> IO Journal
forall (m :: * -> *) a. MonadIO m => ExceptT String m a -> m a
orDieTrying (ExceptT String IO Journal -> IO Journal)
-> (String -> ExceptT String IO Journal) -> String -> IO Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputOpts -> String -> ExceptT String IO Journal
readJournalFile InputOpts
definputopts

-- | An easy version of 'readJournalFiles'' which assumes default options, and fails
-- in the IO monad.
readJournalFiles' :: [PrefixedFilePath] -> IO Journal
readJournalFiles' :: [String] -> IO Journal
readJournalFiles' = ExceptT String IO Journal -> IO Journal
forall (m :: * -> *) a. MonadIO m => ExceptT String m a -> m a
orDieTrying (ExceptT String IO Journal -> IO Journal)
-> ([String] -> ExceptT String IO Journal)
-> [String]
-> IO Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputOpts -> [String] -> ExceptT String IO Journal
readJournalFiles InputOpts
definputopts

--- ** utilities

-- | Extract ExceptT to the IO monad, failing with an error message if necessary.
orDieTrying :: MonadIO m => ExceptT String m a -> m a
orDieTrying :: forall (m :: * -> *) a. MonadIO m => ExceptT String m a -> m a
orDieTrying ExceptT String m a
a = (String -> m a) -> (a -> m a) -> Either String a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> (String -> IO a) -> String -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO a
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail) a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String a -> m a) -> m (Either String a) -> m a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ExceptT String m a -> m (Either String a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT String m a
a

-- | If the specified journal file does not exist (and is not "-"), give a helpful error and quit.
-- (Using "journal file" generically here; it could be in any of hledger's supported formats.)
requireJournalFileExists :: FilePath -> IO ()
requireJournalFileExists :: String -> IO ()
requireJournalFileExists String
"-" = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
requireJournalFileExists String
f = do
  Bool
exists <- String -> IO Bool
doesFileExist String
f
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Handle -> String -> IO ()
hPutStr Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"The hledger data file \"" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
f String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\" was not found.\n"
    Handle -> String -> IO ()
hPutStr Handle
stderr String
"Please create it first, eg with \"hledger add\" or a text editor.\n"
    Handle -> String -> IO ()
hPutStr Handle
stderr String
"Or, specify an existing data file with -f or $LEDGER_FILE.\n"
    IO ()
forall a. IO a
exitFailure

-- | Ensure there is a journal file at the given path, creating an empty one if needed.
-- On Windows, also ensure that the path contains no trailing dots
-- which could cause data loss (see 'isWindowsUnsafeDotPath').
ensureJournalFileExists :: FilePath -> IO ()
ensureJournalFileExists :: String -> IO ()
ensureJournalFileExists String
f = do
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
osString -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
"mingw32" Bool -> Bool -> Bool
&& String -> Bool
isWindowsUnsafeDotPath String
f) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Handle -> String -> IO ()
hPutStr Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Part of file path \"" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String -> String
forall a. Show a => a -> String
show String
f String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\"\n ends with a dot, which is unsafe on Windows; please use a different path.\n"
    IO ()
forall a. IO a
exitFailure
  Bool
exists <- String -> IO Bool
doesFileExist String
f
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Handle -> String -> IO ()
hPutStr Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Creating hledger journal file " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String -> String
forall a. Show a => a -> String
show String
f String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
".\n"
    -- note Hledger.Utils.UTF8.* do no line ending conversion on windows,
    -- we currently require unix line endings on all platforms.
    IO Text
newJournalContent IO Text -> (Text -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> Text -> IO ()
T.writeFile String
f

-- | Does any part of this path contain non-. characters and end with a . ?
-- Such paths are not safe to use on Windows (cf #1056).
isWindowsUnsafeDotPath :: FilePath -> Bool
isWindowsUnsafeDotPath :: String -> Bool
isWindowsUnsafeDotPath = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\String
x -> String -> Char
forall a. HasCallStack => [a] -> a
last String
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'.') String
x) ([String] -> Bool) -> (String -> [String]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitDirectories

-- | Give the content for a new auto-created journal file.
newJournalContent :: IO Text
newJournalContent :: IO Text
newJournalContent = do
  Day
d <- IO Day
getCurrentDay
  Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ Text
"; journal created " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Day -> String
forall a. Show a => a -> String
show Day
d) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" by hledger\n"

-- A "LatestDates" is zero or more copies of the same date,
-- representing the latest transaction date read from a file,
-- and how many transactions there were on that date.
type LatestDates = [Day]

-- The path of an input file, and its current "LatestDates".
data LatestDatesForFile = LatestDatesForFile FilePath LatestDates

-- | Get all instances of the latest date in an unsorted list of dates.
-- Ie, if the latest date appears once, return it in a one-element list,
-- if it appears three times (anywhere), return three of it.
latestDates :: [Day] -> LatestDates
latestDates :: LatestDates -> LatestDates
latestDates = {-# HLINT ignore "Avoid reverse" #-}
  LatestDates -> [LatestDates] -> LatestDates
forall a. a -> [a] -> a
headDef [] ([LatestDates] -> LatestDates)
-> (LatestDates -> [LatestDates]) -> LatestDates -> LatestDates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [LatestDates] -> [LatestDates]
forall a. Int -> [a] -> [a]
take Int
1 ([LatestDates] -> [LatestDates])
-> (LatestDates -> [LatestDates]) -> LatestDates -> [LatestDates]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LatestDates -> [LatestDates]
forall a. Eq a => [a] -> [[a]]
group (LatestDates -> [LatestDates])
-> (LatestDates -> LatestDates) -> LatestDates -> [LatestDates]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LatestDates -> LatestDates
forall a. [a] -> [a]
reverse (LatestDates -> LatestDates)
-> (LatestDates -> LatestDates) -> LatestDates -> LatestDates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LatestDates -> LatestDates
forall a. Ord a => [a] -> [a]
sort

-- | Save the given latest date(s) seen in the given data FILE,
-- in a hidden file named .latest.FILE, creating it if needed.
saveLatestDates :: LatestDates -> FilePath -> IO ()
saveLatestDates :: LatestDates -> String -> IO ()
saveLatestDates LatestDates
dates String
f = String -> Text -> IO ()
T.writeFile (String -> String
latestDatesFileFor String
f) (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Day -> Text) -> LatestDates -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Day -> Text
showDate LatestDates
dates

-- | Save each file's latest dates.
saveLatestDatesForFiles :: [LatestDatesForFile] -> IO ()
saveLatestDatesForFiles :: [LatestDatesForFile] -> IO ()
saveLatestDatesForFiles = (LatestDatesForFile -> IO ()) -> [LatestDatesForFile] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(LatestDatesForFile String
f LatestDates
ds) -> LatestDates -> String -> IO ()
saveLatestDates LatestDates
ds String
f)

-- | What were the latest transaction dates seen the last time this
-- journal file was read ? If there were multiple transactions on the
-- latest date, that number of dates is returned, otherwise just one.
-- Or none if no transactions were read, or if latest dates info is not
-- available for this file.
previousLatestDates :: FilePath -> IO LatestDates
previousLatestDates :: String -> IO LatestDates
previousLatestDates String
f = do
  let latestfile :: String
latestfile = String -> String
latestDatesFileFor String
f
      parsedate :: String -> m Day
parsedate String
s = m Day -> (Day -> m Day) -> Maybe Day -> m Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> m Day
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m Day) -> String -> m Day
forall a b. (a -> b) -> a -> b
$ String
"could not parse date \"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\"") Day -> m Day
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Day -> m Day) -> Maybe Day -> m Day
forall a b. (a -> b) -> a -> b
$
                      String -> Maybe Day
parsedateM String
s
  Bool
exists <- String -> IO Bool
doesFileExist String
latestfile
  if Bool
exists
  then (Text -> IO Day) -> [Text] -> IO LatestDates
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (String -> IO Day
forall {m :: * -> *}. MonadFail m => String -> m Day
parsedate (String -> IO Day) -> (Text -> String) -> Text -> IO Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip) ([Text] -> IO LatestDates)
-> (Text -> [Text]) -> Text -> IO LatestDates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines (Text -> IO LatestDates) -> IO Text -> IO LatestDates
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO Text
readFileStrictly String
latestfile
  else LatestDates -> IO LatestDates
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []

-- | Where to save latest transaction dates for the given file path.
-- (.latest.FILE)
latestDatesFileFor :: FilePath -> FilePath
latestDatesFileFor :: String -> String
latestDatesFileFor String
f = String
dir String -> String -> String
</> String
".latest" String -> String -> String
<.> String
fname
  where
    (String
dir, String
fname) = String -> (String, String)
splitFileName String
f

-- | Given zero or more latest dates (all the same, representing the
-- latest previously seen transaction date, and how many transactions
-- were seen on that date), remove transactions with earlier dates
-- from the journal, and the same number of transactions on the
-- latest date, if any, leaving only transactions that we can assume
-- are newer. Also returns the new latest dates of the new journal.
journalFilterSinceLatestDates :: LatestDates -> Journal -> (Journal, LatestDates)
journalFilterSinceLatestDates :: LatestDates -> Journal -> (Journal, LatestDates)
journalFilterSinceLatestDates [] Journal
j       = (Journal
j,  LatestDates -> LatestDates
latestDates (LatestDates -> LatestDates) -> LatestDates -> LatestDates
forall a b. (a -> b) -> a -> b
$ (Transaction -> Day) -> [Transaction] -> LatestDates
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> Day
tdate ([Transaction] -> LatestDates) -> [Transaction] -> LatestDates
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns Journal
j)
journalFilterSinceLatestDates ds :: LatestDates
ds@(Day
d:LatestDates
_) Journal
j = (Journal
j', LatestDates
ds')
  where
    samedateorlaterts :: [Transaction]
samedateorlaterts     = (Transaction -> Bool) -> [Transaction] -> [Transaction]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Day -> Day -> Bool
forall a. Ord a => a -> a -> Bool
>= Day
d)(Day -> Bool) -> (Transaction -> Day) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Transaction -> Day
tdate) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns Journal
j
    ([Transaction]
samedatets, [Transaction]
laterts) = (Transaction -> Bool)
-> [Transaction] -> ([Transaction], [Transaction])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span ((Day -> Day -> Bool
forall a. Eq a => a -> a -> Bool
== Day
d)(Day -> Bool) -> (Transaction -> Day) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Transaction -> Day
tdate) ([Transaction] -> ([Transaction], [Transaction]))
-> [Transaction] -> ([Transaction], [Transaction])
forall a b. (a -> b) -> a -> b
$ (Transaction -> Transaction -> Ordering)
-> [Transaction] -> [Transaction]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Transaction -> Day) -> Transaction -> Transaction -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing Transaction -> Day
tdate) [Transaction]
samedateorlaterts
    newsamedatets :: [Transaction]
newsamedatets         = Int -> [Transaction] -> [Transaction]
forall a. Int -> [a] -> [a]
drop (LatestDates -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length LatestDates
ds) [Transaction]
samedatets
    j' :: Journal
j'                    = Journal
j{jtxns=newsamedatets++laterts}
    ds' :: LatestDates
ds'                   = LatestDates -> LatestDates
latestDates (LatestDates -> LatestDates) -> LatestDates -> LatestDates
forall a b. (a -> b) -> a -> b
$ (Transaction -> Day) -> [Transaction] -> LatestDates
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> Day
tdate ([Transaction] -> LatestDates) -> [Transaction] -> LatestDates
forall a b. (a -> b) -> a -> b
$ [Transaction]
samedatets[Transaction] -> [Transaction] -> [Transaction]
forall a. [a] -> [a] -> [a]
++[Transaction]
laterts

--- ** tests

tests_Read :: TestTree
tests_Read = String -> [TestTree] -> TestTree
testGroup String
"Read" [
   TestTree
tests_Common
  ,TestTree
tests_CsvReader
  ,TestTree
tests_JournalReader
  ,TestTree
tests_RulesReader
  ]