{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hledger.Read (
PrefixedFilePath,
defaultJournal,
defaultJournalPath,
readJournalFiles,
readJournalFile,
requireJournalFileExists,
ensureJournalFileExists,
readJournal,
readJournal',
JournalReader.postingp,
findReader,
splitReaderPrefix,
module Hledger.Read.Common,
tests_Read,
) where
import Control.Arrow (right)
import qualified Control.Exception as C
import Control.Monad (when)
import "mtl" Control.Monad.Except (runExceptT)
import Data.Default (def)
import Data.Foldable (asum)
import Data.List (group, sort, sortBy)
import Data.List.NonEmpty (nonEmpty)
import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup ((<>))
#endif
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)
import System.Directory (doesFileExist, getHomeDirectory)
import System.Environment (getEnv)
import System.Exit (exitFailure)
import System.FilePath ((<.>), (</>), splitDirectories, splitFileName)
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.JournalReader as JournalReader
import Hledger.Read.CsvReader (tests_CsvReader)
import Hledger.Utils
import Prelude hiding (getContents, writeFile)
journalEnvVar :: String
journalEnvVar = String
"LEDGER_FILE"
journalEnvVar2 :: String
journalEnvVar2 = String
"LEDGER"
journalDefaultFilename :: String
journalDefaultFilename = String
".hledger.journal"
readJournal' :: Text -> IO Journal
readJournal' :: Text -> IO Journal
readJournal' Text
t = InputOpts -> Maybe String -> Text -> IO (Either String Journal)
readJournal InputOpts
forall a. Default a => a
def Maybe String
forall a. Maybe a
Nothing Text
t IO (Either String Journal)
-> (Either String Journal -> IO Journal) -> IO Journal
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 (m :: * -> *) a. Monad m => a -> m a
return
readJournal :: InputOpts -> Maybe FilePath -> Text -> IO (Either String Journal)
readJournal :: InputOpts -> Maybe String -> Text -> IO (Either String Journal)
readJournal InputOpts
iopts 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 String -> Maybe String -> Maybe (Reader IO)
forall (m :: * -> *).
MonadIO m =>
Maybe String -> Maybe String -> Maybe (Reader m)
findReader (InputOpts -> Maybe String
mformat_ InputOpts
iopts) Maybe String
mpath
String -> String -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg6IO String
"trying reader" (Reader IO -> String
forall (m :: * -> *). Reader m -> String
rFormat Reader IO
r)
(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))
-> (Text -> ExceptT String IO Journal)
-> Text
-> IO (Either String Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (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
defaultJournal :: IO Journal
defaultJournal :: IO Journal
defaultJournal = IO String
defaultJournalPath IO String
-> (String -> IO (Either String Journal))
-> IO (Either String Journal)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= InputOpts -> String -> IO (Either String Journal)
readJournalFile InputOpts
forall a. Default a => a
def IO (Either String Journal)
-> (Either String Journal -> IO Journal) -> IO Journal
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 (m :: * -> *) a. Monad m => a -> m a
return
defaultJournalPath :: IO String
defaultJournalPath :: IO String
defaultJournalPath = do
String
s <- IO String
envJournalPath
if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s then IO String
defaultJournalPath else String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
s
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 (m :: * -> *) a. Monad m => a -> m a
return String
""))
defaultJournalPath :: IO String
defaultJournalPath = 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 (m :: * -> *) a. Monad m => a -> m a
return String
"")
String -> IO String
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
type PrefixedFilePath = FilePath
readJournalFiles :: InputOpts -> [PrefixedFilePath] -> IO (Either String Journal)
readJournalFiles :: InputOpts -> [String] -> IO (Either String Journal)
readJournalFiles InputOpts
iopts =
([Either String Journal] -> Either String Journal)
-> IO [Either String Journal] -> IO (Either String Journal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([Journal] -> Journal)
-> Either String [Journal] -> Either String Journal
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either d b) (Either d c)
right (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)
-> ([Journal] -> Maybe (NonEmpty Journal)) -> [Journal] -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Journal] -> Maybe (NonEmpty Journal)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty) (Either String [Journal] -> Either String Journal)
-> ([Either String Journal] -> Either String [Journal])
-> [Either String Journal]
-> Either String Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either String Journal] -> Either String [Journal]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence) (IO [Either String Journal] -> IO (Either String Journal))
-> ([String] -> IO [Either String Journal])
-> [String]
-> IO (Either String Journal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> IO (Either String Journal))
-> [String] -> IO [Either String Journal]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (InputOpts -> String -> IO (Either String Journal)
readJournalFile InputOpts
iopts)
readJournalFile :: InputOpts -> PrefixedFilePath -> IO (Either String Journal)
readJournalFile :: InputOpts -> String -> IO (Either String Journal)
readJournalFile InputOpts
iopts String
prefixedfile = do
let
(Maybe String
mfmt, String
f) = String -> (Maybe String, String)
splitReaderPrefix String
prefixedfile
iopts' :: InputOpts
iopts' = InputOpts
iopts{mformat_ :: Maybe String
mformat_=[Maybe String] -> Maybe String
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [Maybe String
mfmt, InputOpts -> Maybe String
mformat_ InputOpts
iopts]}
String -> IO ()
requireJournalFileExists String
f
Text
t <- String -> IO Text
readFileOrStdinPortably String
f
Either String Journal
ej <- InputOpts -> Maybe String -> Text -> IO (Either String Journal)
readJournal InputOpts
iopts' (String -> Maybe String
forall a. a -> Maybe a
Just String
f) Text
t
case Either String Journal
ej of
Left String
e -> Either String Journal -> IO (Either String Journal)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Journal -> IO (Either String Journal))
-> Either String Journal -> IO (Either String Journal)
forall a b. (a -> b) -> a -> b
$ String -> Either String Journal
forall a b. a -> Either a b
Left String
e
Right Journal
j | InputOpts -> Bool
new_ InputOpts
iopts -> do
LatestDates
ds <- String -> IO LatestDates
previousLatestDates String
f
let (Journal
newj, LatestDates
newds) = LatestDates -> Journal -> (Journal, LatestDates)
journalFilterSinceLatestDates LatestDates
ds Journal
j
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (InputOpts -> Bool
new_save_ InputOpts
iopts Bool -> Bool -> Bool
&& Bool -> Bool
not (LatestDates -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null LatestDates
newds)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ LatestDates -> String -> IO ()
saveLatestDates LatestDates
newds String
f
Either String Journal -> IO (Either String Journal)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Journal -> IO (Either String Journal))
-> Either String Journal -> IO (Either String Journal)
forall a b. (a -> b) -> a -> b
$ Journal -> Either String Journal
forall a b. b -> Either a b
Right Journal
newj
Right Journal
j -> Either String Journal -> IO (Either String Journal)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Journal -> IO (Either String Journal))
-> Either String Journal -> IO (Either String Journal)
forall a b. (a -> b) -> a -> b
$ Journal -> Either String Journal
forall a b. b -> Either a b
Right Journal
j
requireJournalFileExists :: FilePath -> IO ()
requireJournalFileExists :: String -> IO ()
requireJournalFileExists String
"-" = () -> IO ()
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 ()
when (Bool -> Bool
not 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 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
"\" 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 journal file with -f or LEDGER_FILE.\n"
IO ()
forall a. IO a
exitFailure
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 ()
when (Bool -> Bool
not 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"
IO Text
newJournalContent IO Text -> (Text -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> Text -> IO ()
T.writeFile String
f
isWindowsUnsafeDotPath :: FilePath -> Bool
isWindowsUnsafeDotPath :: String -> Bool
isWindowsUnsafeDotPath =
Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> Bool) -> (String -> [String]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'.')) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'.')(Char -> Bool) -> (String -> Char) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> Char
forall a. [a] -> a
last) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> [String]
splitDirectories
newJournalContent :: IO Text
newJournalContent :: IO Text
newJournalContent = do
Day
d <- IO Day
getCurrentDay
Text -> IO Text
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"
type LatestDates = [Day]
latestDates :: [Day] -> LatestDates
latestDates :: LatestDates -> LatestDates
latestDates = 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
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
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 (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 (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)
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 (m :: * -> *) a. Monad m => a -> m a
return []
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
readFileStrictly :: FilePath -> IO Text
readFileStrictly :: String -> IO Text
readFileStrictly String
f = String -> IO Text
readFilePortably String
f IO Text -> (Text -> IO Text) -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
t -> Int -> IO Int
forall a. a -> IO a
C.evaluate (Text -> Int
T.length Text
t) IO Int -> IO Text -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
t
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 (t :: * -> *) a. Foldable t => t a -> Int
length LatestDates
ds) [Transaction]
samedatets
j' :: Journal
j' = Journal
j{jtxns :: [Transaction]
jtxns=[Transaction]
newsamedatets[Transaction] -> [Transaction] -> [Transaction]
forall a. [a] -> [a] -> [a]
++[Transaction]
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_Read :: TestTree
tests_Read = String -> [TestTree] -> TestTree
tests String
"Read" [
TestTree
tests_Common
,TestTree
tests_CsvReader
,TestTree
tests_JournalReader
]