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

A reader for hledger's journal file format
(<http://hledger.org/hledger.html#the-journal-file>).  hledger's journal
format is a compatible subset of c++ ledger's
(<http://ledger-cli.org/3.0/doc/ledger3.html#Journal-Format>), so this
reader should handle many ledger files as well. Example:

@
2012\/3\/24 gift
    expenses:gifts  $10
    assets:cash
@

Journal format supports the include directive which can read files in
other formats, so the other file format readers need to be importable
and invocable here.

Some important parts of journal parsing are therefore kept in
Hledger.Read.Common, to avoid import cycles.

-}

--- ** language

{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE NamedFieldPuns      #-}
{-# LANGUAGE NoMonoLocalBinds    #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE PackageImports      #-}
{-# LANGUAGE ScopedTypeVariables #-}

--- ** exports
module Hledger.Read.JournalReader (

  -- * Reader-finding utils
  findReader,
  splitReaderPrefix,

  -- * Reader
  reader,

  -- * Parsing utils
  parseAndFinaliseJournal,
  runJournalParser,
  rjp,
  runErroringJournalParser,
  rejp,

  -- * Parsers used elsewhere
  getParentAccount,
  journalp,
  directivep,
  defaultyeardirectivep,
  marketpricedirectivep,
  datetimep,
  datep,
  modifiedaccountnamep,
  tmpostingrulep,
  statusp,
  emptyorcommentlinep,
  followingcommentp,
  accountaliasp

  -- * Tests
  ,tests_JournalReader
)
where

--- ** imports
import qualified Control.Monad.Fail as Fail (fail)
import qualified Control.Exception as C
import Control.Monad (forM_, when, void, unless)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Except (ExceptT(..), runExceptT)
import Control.Monad.State.Strict (evalStateT,get,modify',put)
import Control.Monad.Trans.Class (lift)
import Data.Char (toLower)
import Data.Either (isRight, lefts)
import qualified Data.Map.Strict as M
import Data.Text (Text)
import Data.String
import Data.List
import Data.Maybe
import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.LocalTime
import Safe
import Text.Megaparsec hiding (parse)
import Text.Megaparsec.Char
import Text.Megaparsec.Custom
import Text.Printf
import System.FilePath
import "Glob" System.FilePath.Glob hiding (match)

import Hledger.Data
import Hledger.Read.Common
import Hledger.Utils

import qualified Hledger.Read.CsvReader as CsvReader (reader)
import qualified Hledger.Read.RulesReader as RulesReader (reader)
import qualified Hledger.Read.TimeclockReader as TimeclockReader (reader)
import qualified Hledger.Read.TimedotReader as TimedotReader (reader)

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

-- | Run a journal parser in some monad. See also: parseWithState.
runJournalParser, rjp
  :: Monad m
  => JournalParser m a -> Text -> m (Either HledgerParseErrors a)
runJournalParser :: forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
runJournalParser JournalParser m a
p = ParsecT HledgerParseErrorData Text m a
-> [Char] -> Text -> m (Either HledgerParseErrors a)
forall (m :: * -> *) e s a.
Monad m =>
ParsecT e s m a
-> [Char] -> s -> m (Either (ParseErrorBundle s e) a)
runParserT (JournalParser m a
-> Journal -> ParsecT HledgerParseErrorData Text m a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT JournalParser m a
p Journal
nulljournal) [Char]
""
rjp :: forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
rjp = JournalParser m a -> Text -> m (Either HledgerParseErrors a)
forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
runJournalParser

-- | Run an erroring journal parser in some monad. See also: parseWithState.
runErroringJournalParser, rejp
  :: Monad m
  => ErroringJournalParser m a
  -> Text
  -> m (Either FinalParseError (Either HledgerParseErrors a))
runErroringJournalParser :: forall (m :: * -> *) a.
Monad m =>
ErroringJournalParser m a
-> Text -> m (Either FinalParseError (Either HledgerParseErrors a))
runErroringJournalParser ErroringJournalParser m a
p Text
t =
  ExceptT FinalParseError m (Either HledgerParseErrors a)
-> m (Either FinalParseError (Either HledgerParseErrors a))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT FinalParseError m (Either HledgerParseErrors a)
 -> m (Either FinalParseError (Either HledgerParseErrors a)))
-> ExceptT FinalParseError m (Either HledgerParseErrors a)
-> m (Either FinalParseError (Either HledgerParseErrors a))
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) a
-> [Char]
-> Text
-> ExceptT FinalParseError m (Either HledgerParseErrors a)
forall (m :: * -> *) e s a.
Monad m =>
ParsecT e s m a
-> [Char] -> s -> m (Either (ParseErrorBundle s e) a)
runParserT (ErroringJournalParser m a
-> Journal
-> ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT ErroringJournalParser m a
p Journal
nulljournal) [Char]
"" Text
t
rejp :: forall (m :: * -> *) a.
Monad m =>
ErroringJournalParser m a
-> Text -> m (Either FinalParseError (Either HledgerParseErrors a))
rejp = ErroringJournalParser m a
-> Text -> m (Either FinalParseError (Either HledgerParseErrors a))
forall (m :: * -> *) a.
Monad m =>
ErroringJournalParser m a
-> Text -> m (Either FinalParseError (Either HledgerParseErrors a))
runErroringJournalParser


--- ** reader finding utilities
-- Defined here rather than Hledger.Read so that we can use them in includedirectivep below.

-- The available journal readers, each one handling a particular data format.
readers' :: MonadIO m => [Reader m]
readers' :: forall (m :: * -> *). MonadIO m => [Reader m]
readers' = [
  Reader m
forall (m :: * -> *). MonadIO m => Reader m
reader
 ,Reader m
forall (m :: * -> *). MonadIO m => Reader m
TimeclockReader.reader
 ,Reader m
forall (m :: * -> *). MonadIO m => Reader m
TimedotReader.reader
 ,Reader m
forall (m :: * -> *). MonadIO m => Reader m
RulesReader.reader
 ,Reader m
forall (m :: * -> *). MonadIO m => Reader m
CsvReader.reader
--  ,LedgerReader.reader
 ]

readerNames :: [String]
readerNames :: [[Char]]
readerNames = (Reader IO -> [Char]) -> [Reader IO] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Reader IO -> [Char]
forall (m :: * -> *). Reader m -> [Char]
rFormat ([Reader IO]
forall (m :: * -> *). MonadIO m => [Reader m]
readers'::[Reader IO])

-- | @findReader mformat mpath@
--
-- Find the reader named by @mformat@, if provided.
-- Or, if a file path is provided, find the first reader that handles
-- its file extension, if any.
findReader :: MonadIO m => Maybe StorageFormat -> Maybe FilePath -> Maybe (Reader m)
findReader :: forall (m :: * -> *).
MonadIO m =>
Maybe [Char] -> Maybe [Char] -> Maybe (Reader m)
findReader Maybe [Char]
Nothing Maybe [Char]
Nothing     = Maybe (Reader m)
forall a. Maybe a
Nothing
findReader (Just [Char]
fmt) Maybe [Char]
_        = [Reader m] -> Maybe (Reader m)
forall a. [a] -> Maybe a
headMay [Reader m
r | Reader m
r <- [Reader m]
forall (m :: * -> *). MonadIO m => [Reader m]
readers', Reader m -> [Char]
forall (m :: * -> *). Reader m -> [Char]
rFormat Reader m
r [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
fmt]
findReader Maybe [Char]
Nothing (Just [Char]
path) =
  case Maybe [Char]
prefix of
    Just [Char]
fmt -> [Reader m] -> Maybe (Reader m)
forall a. [a] -> Maybe a
headMay [Reader m
r | Reader m
r <- [Reader m]
forall (m :: * -> *). MonadIO m => [Reader m]
readers', Reader m -> [Char]
forall (m :: * -> *). Reader m -> [Char]
rFormat Reader m
r [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
fmt]
    Maybe [Char]
Nothing  -> [Reader m] -> Maybe (Reader m)
forall a. [a] -> Maybe a
headMay [Reader m
r | Reader m
r <- [Reader m]
forall (m :: * -> *). MonadIO m => [Reader m]
readers', [Char]
ext [Char] -> [[Char]] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Reader m -> [[Char]]
forall (m :: * -> *). Reader m -> [[Char]]
rExtensions Reader m
r]
  where
    (Maybe [Char]
prefix,[Char]
path') = [Char] -> (Maybe [Char], [Char])
splitReaderPrefix [Char]
path
    ext :: [Char]
ext            = (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
drop Int
1 ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
takeExtension [Char]
path'

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

-- | If a filepath is prefixed by one of the reader names and a colon,
-- split that off. Eg "csv:-" -> (Just "csv", "-").
splitReaderPrefix :: PrefixedFilePath -> (Maybe String, FilePath)
splitReaderPrefix :: [Char] -> (Maybe [Char], [Char])
splitReaderPrefix [Char]
f =
  (Maybe [Char], [Char])
-> [(Maybe [Char], [Char])] -> (Maybe [Char], [Char])
forall a. a -> [a] -> a
headDef (Maybe [Char]
forall a. Maybe a
Nothing, [Char]
f) ([(Maybe [Char], [Char])] -> (Maybe [Char], [Char]))
-> [(Maybe [Char], [Char])] -> (Maybe [Char], [Char])
forall a b. (a -> b) -> a -> b
$
  [([Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
r, Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
drop ([Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) [Char]
f) | [Char]
r <- [[Char]]
readerNames, ([Char]
r[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
":") [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [Char]
f]

--- ** reader

reader :: MonadIO m => Reader m
reader :: forall (m :: * -> *). MonadIO m => Reader m
reader = Reader
  {rFormat :: [Char]
rFormat     = [Char]
"journal"
  ,rExtensions :: [[Char]]
rExtensions = [[Char]
"journal", [Char]
"j", [Char]
"hledger", [Char]
"ledger"]
  ,rReadFn :: InputOpts -> [Char] -> Text -> ExceptT [Char] IO Journal
rReadFn     = InputOpts -> [Char] -> Text -> ExceptT [Char] IO Journal
parse
  ,rParser :: MonadIO m => ErroringJournalParser m Journal
rParser    = ErroringJournalParser m Journal
MonadIO m => ErroringJournalParser m Journal
forall (m :: * -> *). MonadIO m => ErroringJournalParser m Journal
journalp  -- no need to add command line aliases like journalp'
                           -- when called as a subparser I think
  }

-- | Parse and post-process a "Journal" from hledger's journal file
-- format, or give an error.
parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal
parse :: InputOpts -> [Char] -> Text -> ExceptT [Char] IO Journal
parse InputOpts
iopts [Char]
f = ErroringJournalParser IO Journal
-> InputOpts -> [Char] -> Text -> ExceptT [Char] IO Journal
parseAndFinaliseJournal ErroringJournalParser IO Journal
journalp' InputOpts
iopts [Char]
f
  where
    journalp' :: ErroringJournalParser IO Journal
journalp' = do
      -- reverse parsed aliases to ensure that they are applied in order given on commandline
      (AccountAlias
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
      ())
-> [AccountAlias]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
     ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ AccountAlias
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
     ()
forall (m :: * -> *). MonadState Journal m => AccountAlias -> m ()
addAccountAlias ([AccountAlias] -> [AccountAlias]
forall a. [a] -> [a]
reverse ([AccountAlias] -> [AccountAlias])
-> [AccountAlias] -> [AccountAlias]
forall a b. (a -> b) -> a -> b
$ InputOpts -> [AccountAlias]
aliasesFromOpts InputOpts
iopts)
      ErroringJournalParser IO Journal
forall (m :: * -> *). MonadIO m => ErroringJournalParser m Journal
journalp

--- ** parsers
--- *** journal

-- | A journal parser. Accumulates and returns a "ParsedJournal",
-- which should be finalised/validated before use.
--
-- >>> rejp (journalp <* eof) "2015/1/1\n a  0\n"
-- Right (Right Journal (unknown) with 1 transactions, 1 accounts)
--
journalp :: MonadIO m => ErroringJournalParser m ParsedJournal
journalp :: forall (m :: * -> *). MonadIO m => ErroringJournalParser m Journal
journalp = do
  StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     [()]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
addJournalItemP
  StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof
  ErroringJournalParser m Journal
forall s (m :: * -> *). MonadState s m => m s
get

-- | A side-effecting parser; parses any kind of journal item
-- and updates the parse state accordingly.
addJournalItemP :: MonadIO m => ErroringJournalParser m ()
addJournalItemP :: forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
addJournalItemP =
  -- all journal line types can be distinguished by the first
  -- character, can use choice without backtracking
  [StateT
   Journal
   (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
   ()]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [
      StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
directivep
    , JournalParser (ExceptT FinalParseError m) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp          JournalParser (ExceptT FinalParseError m) Transaction
-> (Transaction
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         ())
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall a b.
StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  a
-> (a
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         b)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Journal -> Journal)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Journal -> Journal)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      ())
-> (Transaction -> Journal -> Journal)
-> Transaction
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Journal -> Journal
addTransaction
    , JournalParser (ExceptT FinalParseError m) TransactionModifier
forall (m :: * -> *). JournalParser m TransactionModifier
transactionmodifierp  JournalParser (ExceptT FinalParseError m) TransactionModifier
-> (TransactionModifier
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         ())
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall a b.
StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  a
-> (a
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         b)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Journal -> Journal)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Journal -> Journal)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      ())
-> (TransactionModifier -> Journal -> Journal)
-> TransactionModifier
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransactionModifier -> Journal -> Journal
addTransactionModifier
    , JournalParser (ExceptT FinalParseError m) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp  JournalParser (ExceptT FinalParseError m) PeriodicTransaction
-> (PeriodicTransaction
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         ())
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall a b.
StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  a
-> (a
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         b)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Journal -> Journal)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Journal -> Journal)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      ())
-> (PeriodicTransaction -> Journal -> Journal)
-> PeriodicTransaction
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicTransaction -> Journal -> Journal
addPeriodicTransaction
    , JournalParser (ExceptT FinalParseError m) PriceDirective
forall (m :: * -> *). JournalParser m PriceDirective
marketpricedirectivep JournalParser (ExceptT FinalParseError m) PriceDirective
-> (PriceDirective
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         ())
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall a b.
StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  a
-> (a
    -> StateT
         Journal
         (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
         b)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Journal -> Journal)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Journal -> Journal)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      ())
-> (PriceDirective -> Journal -> Journal)
-> PriceDirective
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PriceDirective -> Journal -> Journal
addPriceDirective
    , StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
forall (m :: * -> *). TextParser m ()
emptyorcommentlinep)
    , StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
forall (m :: * -> *). TextParser m ()
multilinecommentp)
    ] StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
-> [Char]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"transaction or directive"

--- *** directives

-- | Parse any journal directive and update the parse state accordingly.
-- Cf http://hledger.org/hledger.html#directives,
-- http://ledger-cli.org/3.0/doc/ledger3.html#Command-Directives
directivep :: MonadIO m => ErroringJournalParser m ()
directivep :: forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
directivep = (do
  StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  (Token Text)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Maybe (Token Text))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (StateT
   Journal
   (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
   (Token Text)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      (Maybe (Token Text)))
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Token Text)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Maybe (Token Text))
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
oneOf [Char
'!',Char
'@']
  [StateT
   Journal
   (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
   ()]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [
    StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
includedirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
aliasdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endaliasesdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
accountdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
applyaccountdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
applyfixeddirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
applytagdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
assertdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
bucketdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
capturedirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
checkdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
commandlineflagdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
commoditydirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
commodityconversiondirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
decimalmarkdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
defaultyeardirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
defaultcommoditydirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
definedirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endapplyaccountdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endapplyfixeddirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endapplytagdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endapplyyeardirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
endtagdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
evaldirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
exprdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
ignoredpricecommoditydirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
payeedirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
pythondirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
tagdirectivep
   ,StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
forall (m :: * -> *). JournalParser m ()
valuedirectivep
   ]
  ) StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  ()
-> [Char]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"directive"

-- | Parse an include directive. include's argument is an optionally
-- file-format-prefixed file path or glob pattern. In the latter case,
-- the prefix is applied to each matched path. Examples:
-- foo.j, foo/bar.j, timedot:foo/2020*.md
includedirectivep :: MonadIO m => ErroringJournalParser m ()
includedirectivep :: forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
includedirectivep = do
  Tokens Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"include"
  ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
-> ErroringJournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  [Char]
prefixedglob <- Text -> [Char]
T.unpack (Text -> [Char])
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Char]
-> (Token Text -> Bool)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe [Char] -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe [Char]
forall a. Maybe a
Nothing (Token Text -> Token Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
Token Text
'\n') -- don't consume newline yet
  Int
parentoff <- StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
  SourcePos
parentpos <- StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
  let (Maybe [Char]
mprefix,[Char]
glb) = [Char] -> (Maybe [Char], [Char])
splitReaderPrefix [Char]
prefixedglob
  [[Char]]
paths <- Int
-> SourcePos
-> [Char]
-> JournalParser (ExceptT FinalParseError m) [[Char]]
forall (m :: * -> *).
MonadIO m =>
Int -> SourcePos -> [Char] -> JournalParser m [[Char]]
getFilePaths Int
parentoff SourcePos
parentpos [Char]
glb
  let prefixedpaths :: [[Char]]
prefixedpaths = case Maybe [Char]
mprefix of
        Maybe [Char]
Nothing  -> [[Char]]
paths
        Just [Char]
fmt -> ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (([Char]
fmt[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
":")[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++) [[Char]]
paths
  [[Char]]
-> ([Char] -> ErroringJournalParser m ())
-> ErroringJournalParser m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [[Char]]
prefixedpaths (([Char] -> ErroringJournalParser m ())
 -> ErroringJournalParser m ())
-> ([Char] -> ErroringJournalParser m ())
-> ErroringJournalParser m ()
forall a b. (a -> b) -> a -> b
$ SourcePos -> [Char] -> ErroringJournalParser m ()
forall (m :: * -> *).
MonadIO m =>
SourcePos -> [Char] -> ErroringJournalParser m ()
parseChild SourcePos
parentpos
  StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Char
-> ErroringJournalParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Char
StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
newline

  where
    getFilePaths
      :: MonadIO m => Int -> SourcePos -> FilePath -> JournalParser m [FilePath]
    getFilePaths :: forall (m :: * -> *).
MonadIO m =>
Int -> SourcePos -> [Char] -> JournalParser m [[Char]]
getFilePaths Int
parseroff SourcePos
parserpos [Char]
filename = do
        let curdir :: [Char]
curdir = [Char] -> [Char]
takeDirectory (SourcePos -> [Char]
sourceName SourcePos
parserpos)
        [Char]
filename' <- ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m [Char]
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char])
-> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> IO [Char]
expandHomePath [Char]
filename
                         IO [Char] -> [Char] -> ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *) a.
MonadIO m =>
IO a -> [Char] -> TextParser m a
`orRethrowIOError` (SourcePos -> [Char]
forall a. Show a => a -> [Char]
show SourcePos
parserpos [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" locating " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
filename)
        -- Compiling filename as a glob pattern works even if it is a literal
        Pattern
fileglob <- case CompOptions -> [Char] -> Either [Char] Pattern
tryCompileWith CompOptions
compDefault{errorRecovery=False} [Char]
filename' of
            Right Pattern
x -> Pattern
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Pattern
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Pattern
x
            Left [Char]
e -> HledgerParseErrorData
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Pattern
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Pattern)
-> HledgerParseErrorData
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Pattern
forall a b. (a -> b) -> a -> b
$
                        Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
parseroff ([Char] -> HledgerParseErrorData)
-> [Char] -> HledgerParseErrorData
forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid glob pattern: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
e
        -- Get all matching files in the current working directory, sorting in
        -- lexicographic order to simulate the output of 'ls'.
        [[Char]]
filepaths <- IO [[Char]] -> JournalParser m [[Char]]
forall a.
IO a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Char]] -> JournalParser m [[Char]])
-> IO [[Char]] -> JournalParser m [[Char]]
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [[Char]]
forall a. Ord a => [a] -> [a]
sort ([[Char]] -> [[Char]]) -> IO [[Char]] -> IO [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Pattern -> [Char] -> IO [[Char]]
globDir1 Pattern
fileglob [Char]
curdir
        if (Bool -> Bool
not (Bool -> Bool) -> ([[Char]] -> Bool) -> [[Char]] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [[Char]]
filepaths
            then [[Char]] -> JournalParser m [[Char]]
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [[Char]]
filepaths
            else HledgerParseErrorData -> JournalParser m [[Char]]
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m [[Char]])
-> HledgerParseErrorData -> JournalParser m [[Char]]
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
parseroff ([Char] -> HledgerParseErrorData)
-> [Char] -> HledgerParseErrorData
forall a b. (a -> b) -> a -> b
$
                   [Char]
"No existing files match pattern: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
filename

    parseChild :: MonadIO m => SourcePos -> PrefixedFilePath -> ErroringJournalParser m ()
    parseChild :: forall (m :: * -> *).
MonadIO m =>
SourcePos -> [Char] -> ErroringJournalParser m ()
parseChild SourcePos
parentpos [Char]
prefixedpath = do
      let (Maybe [Char]
_mprefix,[Char]
filepath) = [Char] -> (Maybe [Char], [Char])
splitReaderPrefix [Char]
prefixedpath

      Journal
parentj <- StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Journal
forall s (m :: * -> *). MonadState s m => m s
get
      let parentfilestack :: [[Char]]
parentfilestack = Journal -> [[Char]]
jincludefilestack Journal
parentj
      Bool -> ErroringJournalParser m () -> ErroringJournalParser m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Char]
filepath [Char] -> [[Char]] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [[Char]]
parentfilestack) (ErroringJournalParser m () -> ErroringJournalParser m ())
-> ErroringJournalParser m () -> ErroringJournalParser m ()
forall a b. (a -> b) -> a -> b
$
        [Char] -> ErroringJournalParser m ()
forall a.
[Char]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
Fail.fail ([Char]
"Cyclic include: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
filepath)

      Text
childInput <-
        Int
-> [Char]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
forall a. Int -> [Char] -> a -> a
traceOrLogAt Int
6 ([Char]
"parseChild: "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char] -> [Char]
takeFileName [Char]
filepath) (StateT
   Journal
   (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
   Text
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      Text)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
forall a b. (a -> b) -> a -> b
$
        ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m) Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT
   HledgerParseErrorData Text (ExceptT FinalParseError m) Text
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
      Text)
-> ParsecT
     HledgerParseErrorData Text (ExceptT FinalParseError m) Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Text
forall a b. (a -> b) -> a -> b
$ [Char] -> IO Text
readFilePortably [Char]
filepath
          IO Text
-> [Char]
-> ParsecT
     HledgerParseErrorData Text (ExceptT FinalParseError m) Text
forall (m :: * -> *) a.
MonadIO m =>
IO a -> [Char] -> TextParser m a
`orRethrowIOError` (SourcePos -> [Char]
forall a. Show a => a -> [Char]
show SourcePos
parentpos [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" reading " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
filepath)
      let initChildj :: Journal
initChildj = [Char] -> Journal -> Journal
newJournalWithParseStateFrom [Char]
filepath Journal
parentj

      -- Choose a reader/parser based on the file path prefix or file extension,
      -- defaulting to JournalReader. Duplicating readJournal a bit here.
      let r :: Reader m
r = Reader m -> Maybe (Reader m) -> Reader m
forall a. a -> Maybe a -> a
fromMaybe Reader m
forall (m :: * -> *). MonadIO m => Reader m
reader (Maybe (Reader m) -> Reader m) -> Maybe (Reader m) -> Reader m
forall a b. (a -> b) -> a -> b
$ Maybe [Char] -> Maybe [Char] -> Maybe (Reader m)
forall (m :: * -> *).
MonadIO m =>
Maybe [Char] -> Maybe [Char] -> Maybe (Reader m)
findReader Maybe [Char]
forall a. Maybe a
Nothing ([Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
prefixedpath)
          parser :: StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Journal
parser = Reader m
-> MonadIO m =>
   StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Journal
forall (m :: * -> *).
Reader m -> MonadIO m => ErroringJournalParser m Journal
rParser Reader m
r
      [Char] -> [Char] -> ErroringJournalParser m ()
forall (m :: * -> *) a. (MonadIO m, Show a) => [Char] -> a -> m ()
dbg6IO [Char]
"parseChild: trying reader" (Reader m -> [Char]
forall (m :: * -> *). Reader m -> [Char]
rFormat Reader m
r)

      -- Parse the file (of whichever format) to a Journal, with file path and source text attached.
      Journal
updatedChildj <- ([Char], Text) -> Journal -> Journal
journalAddFile ([Char]
filepath, Text
childInput) (Journal -> Journal)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Journal
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Journal
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                        StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Journal
-> Journal
-> [Char]
-> Text
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     Journal
forall (m :: * -> *) st a.
Monad m =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  a
-> st
-> [Char]
-> Text
-> StateT
     st
     (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
     a
parseIncludeFile StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m))
  Journal
parser Journal
initChildj [Char]
filepath Text
childInput

      -- Merge this child journal into the parent journal
      -- (with debug logging for troubleshooting account display order).
      -- The parent journal is the second argument to journalConcat; this means
      -- its parse state is kept, and its lists are appended to child's (which
      -- ultimately produces the right list order, because parent's and child's
      -- lists are in reverse order at this stage. Cf #1909).
      let
        parentj' :: Journal
parentj' =
          [Char] -> Journal -> Journal
dbgJournalAcctDeclOrder ([Char]
"parseChild: child " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
childfilename [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" acct decls: ") Journal
updatedChildj
          Journal -> Journal -> Journal
`journalConcat`
          [Char] -> Journal -> Journal
dbgJournalAcctDeclOrder ([Char]
"parseChild: parent " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
parentfilename [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" acct decls: ") Journal
parentj

          where
            childfilename :: [Char]
childfilename = [Char] -> [Char]
takeFileName [Char]
filepath
            parentfilename :: [Char]
parentfilename = [Char] -> ([Char] -> [Char]) -> Maybe [Char] -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"(unknown)" [Char] -> [Char]
takeFileName (Maybe [Char] -> [Char]) -> Maybe [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[Char]] -> Maybe [Char]
forall a. [a] -> Maybe a
headMay ([[Char]] -> Maybe [Char]) -> [[Char]] -> Maybe [Char]
forall a b. (a -> b) -> a -> b
$ Journal -> [[Char]]
jincludefilestack Journal
parentj  -- XXX more accurate than journalFilePath for some reason

      -- Update the parse state.
      Journal -> ErroringJournalParser m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put Journal
parentj'

    newJournalWithParseStateFrom :: FilePath -> Journal -> Journal
    newJournalWithParseStateFrom :: [Char] -> Journal -> Journal
newJournalWithParseStateFrom [Char]
filepath Journal
j = Journal
nulljournal{
      jparsedefaultyear      = jparsedefaultyear j
      ,jparsedefaultcommodity = jparsedefaultcommodity j
      ,jparseparentaccounts   = jparseparentaccounts j
      ,jparsedecimalmark      = jparsedecimalmark j
      ,jparsealiases          = jparsealiases j
      ,jcommodities           = jcommodities j
      -- ,jparsetransactioncount = jparsetransactioncount j
      ,jparsetimeclockentries = jparsetimeclockentries j
      ,jincludefilestack      = filepath : jincludefilestack j
      }

-- | Lift an IO action into the exception monad, rethrowing any IO
-- error with the given message prepended.
orRethrowIOError :: MonadIO m => IO a -> String -> TextParser m a
orRethrowIOError :: forall (m :: * -> *) a.
MonadIO m =>
IO a -> [Char] -> TextParser m a
orRethrowIOError IO a
io [Char]
msg = do
  Either [Char] a
eResult <- IO (Either [Char] a)
-> ParsecT HledgerParseErrorData Text m (Either [Char] a)
forall a. IO a -> ParsecT HledgerParseErrorData Text m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either [Char] a)
 -> ParsecT HledgerParseErrorData Text m (Either [Char] a))
-> IO (Either [Char] a)
-> ParsecT HledgerParseErrorData Text m (Either [Char] a)
forall a b. (a -> b) -> a -> b
$ (a -> Either [Char] a
forall a b. b -> Either a b
Right (a -> Either [Char] a) -> IO a -> IO (Either [Char] a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO a
io) IO (Either [Char] a)
-> (IOException -> IO (Either [Char] a)) -> IO (Either [Char] a)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`C.catch` \(IOException
e::C.IOException) -> Either [Char] a -> IO (Either [Char] a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either [Char] a -> IO (Either [Char] a))
-> Either [Char] a -> IO (Either [Char] a)
forall a b. (a -> b) -> a -> b
$ [Char] -> Either [Char] a
forall a b. a -> Either a b
Left ([Char] -> Either [Char] a) -> [Char] -> Either [Char] a
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> [Char] -> [Char]
forall r. PrintfType r => [Char] -> r
printf [Char]
"%s:\n%s" [Char]
msg (IOException -> [Char]
forall a. Show a => a -> [Char]
show IOException
e)
  case Either [Char] a
eResult of
    Right a
res -> a -> TextParser m a
forall a. a -> ParsecT HledgerParseErrorData Text m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
res
    Left [Char]
errMsg -> [Char] -> TextParser m a
forall a. [Char] -> ParsecT HledgerParseErrorData Text m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
Fail.fail [Char]
errMsg

-- Parse an account directive, adding its info to the journal's
-- list of account declarations.
accountdirectivep :: JournalParser m ()
accountdirectivep :: forall (m :: * -> *). JournalParser m ()
accountdirectivep = do
  Int
off <- StateT Journal (ParsecT HledgerParseErrorData Text m) Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset -- XXX figure out a more precise position later
  SourcePos
pos <- StateT Journal (ParsecT HledgerParseErrorData Text m) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos

  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"account"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1

  -- the account name, possibly modified by preceding alias or apply account directives
  Text
acct <- (StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> JournalParser m ()
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> JournalParser m ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'(' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'[') JournalParser m () -> [Char] -> JournalParser m ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"account name without brackets") JournalParser m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
          StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *). JournalParser m Text
modifiedaccountnamep

  -- maybe a comment, on this and/or following lines
  (Text
cmt, [Tag]
tags) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp

  -- maybe Ledger-style subdirectives (ignored)
  StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m ()
forall (m :: * -> *) a. MonadPlus m => m a -> m ()
skipMany StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *). JournalParser m [Char]
indentedlinep

  -- an account type may have been set by account type code or a tag;
  -- the latter takes precedence
  let
    metype :: Maybe (Either [Char] AccountType)
metype = Text -> Either [Char] AccountType
parseAccountTypeCode (Text -> Either [Char] AccountType)
-> Maybe Text -> Maybe (Either [Char] AccountType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Tag] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
accountTypeTagName [Tag]
tags

  -- update the journal
  (Text, Text, [Tag], SourcePos) -> JournalParser m ()
forall (m :: * -> *).
(Text, Text, [Tag], SourcePos) -> JournalParser m ()
addAccountDeclaration (Text
acct, Text
cmt, [Tag]
tags, SourcePos
pos)
  Bool -> JournalParser m () -> JournalParser m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Tag] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Tag]
tags) (JournalParser m () -> JournalParser m ())
-> JournalParser m () -> JournalParser m ()
forall a b. (a -> b) -> a -> b
$ Text -> [Tag] -> JournalParser m ()
forall (m :: * -> *). Text -> [Tag] -> JournalParser m ()
addDeclaredAccountTags Text
acct [Tag]
tags
  case Maybe (Either [Char] AccountType)
metype of
    Maybe (Either [Char] AccountType)
Nothing         -> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    Just (Right AccountType
t)  -> Text -> AccountType -> JournalParser m ()
forall (m :: * -> *). Text -> AccountType -> JournalParser m ()
addDeclaredAccountType Text
acct AccountType
t
    Just (Left [Char]
err) -> HledgerParseErrorData -> JournalParser m ()
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m ())
-> HledgerParseErrorData -> JournalParser m ()
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
off [Char]
err

-- The special tag used for declaring account type. XXX change to "class" ?
accountTypeTagName :: Text
accountTypeTagName = Text
"type"

parseAccountTypeCode :: Text -> Either String AccountType
parseAccountTypeCode :: Text -> Either [Char] AccountType
parseAccountTypeCode Text
s =
  case Text -> Text
T.toLower Text
s of
    Text
"asset"      -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Asset
    Text
"a"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Asset
    Text
"liability"  -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Liability
    Text
"l"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Liability
    Text
"equity"     -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Equity
    Text
"e"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Equity
    Text
"revenue"    -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Revenue
    Text
"r"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Revenue
    Text
"expense"    -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Expense
    Text
"x"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Expense
    Text
"cash"       -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Cash
    Text
"c"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Cash
    Text
"conversion" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Conversion
    Text
"v"          -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Conversion
    Text
_            -> [Char] -> Either [Char] AccountType
forall a b. a -> Either a b
Left [Char]
err
  where
    err :: [Char]
err = Text -> [Char]
T.unpack (Text -> [Char]) -> Text -> [Char]
forall a b. (a -> b) -> a -> b
$ Text
"invalid account type code "Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
sText -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
", should be one of " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
            Text -> [Text] -> Text
T.intercalate Text
", " [Text
"A",Text
"L",Text
"E",Text
"R",Text
"X",Text
"C",Text
"V",Text
"Asset",Text
"Liability",Text
"Equity",Text
"Revenue",Text
"Expense",Text
"Cash",Text
"Conversion"]

-- Add an account declaration to the journal, auto-numbering it.
addAccountDeclaration :: (AccountName,Text,[Tag],SourcePos) -> JournalParser m ()
addAccountDeclaration :: forall (m :: * -> *).
(Text, Text, [Tag], SourcePos) -> JournalParser m ()
addAccountDeclaration (Text
a,Text
cmt,[Tag]
tags,SourcePos
pos) = do
  (Journal -> Journal) -> JournalParser m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\Journal
j ->
             let
               decls :: [(Text, AccountDeclarationInfo)]
decls = Journal -> [(Text, AccountDeclarationInfo)]
jdeclaredaccounts Journal
j
               d :: (Text, AccountDeclarationInfo)
d     = (Text
a, AccountDeclarationInfo
nullaccountdeclarationinfo{
                              adicomment          = cmt
                             ,aditags             = tags
                             ,adideclarationorder = length decls + 1  -- gets renumbered when Journals are finalised or merged
                             ,adisourcepos        = pos
                             })
             in
               Journal
j{jdeclaredaccounts = d:decls})

-- Add a payee declaration to the journal.
addPayeeDeclaration :: (Payee,Text,[Tag]) -> JournalParser m ()
addPayeeDeclaration :: forall (m :: * -> *). (Text, Text, [Tag]) -> JournalParser m ()
addPayeeDeclaration (Text
p, Text
cmt, [Tag]
tags) =
  (Journal -> Journal)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\j :: Journal
j@Journal{[(Text, PayeeDeclarationInfo)]
jdeclaredpayees :: [(Text, PayeeDeclarationInfo)]
jdeclaredpayees :: Journal -> [(Text, PayeeDeclarationInfo)]
jdeclaredpayees} -> Journal
j{jdeclaredpayees=d:jdeclaredpayees})
             where
               d :: (Text, PayeeDeclarationInfo)
d = (Text
p
                   ,PayeeDeclarationInfo
nullpayeedeclarationinfo{
                     pdicomment = cmt
                    ,pditags    = tags
                    })

-- Add a tag declaration to the journal.
addTagDeclaration :: (TagName,Text) -> JournalParser m ()
addTagDeclaration :: forall (m :: * -> *). Tag -> JournalParser m ()
addTagDeclaration (Text
t, Text
cmt) =
  (Journal -> Journal)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\j :: Journal
j@Journal{[(Text, TagDeclarationInfo)]
jdeclaredtags :: [(Text, TagDeclarationInfo)]
jdeclaredtags :: Journal -> [(Text, TagDeclarationInfo)]
jdeclaredtags} -> Journal
j{jdeclaredtags=tagandinfo:jdeclaredtags})
  where
    tagandinfo :: (Text, TagDeclarationInfo)
tagandinfo = (Text
t, TagDeclarationInfo
nulltagdeclarationinfo{tdicomment=cmt})

indentedlinep :: JournalParser m String
indentedlinep :: forall (m :: * -> *). JournalParser m [Char]
indentedlinep = ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1 StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ([Char] -> [Char]
rstrip ([Char] -> [Char])
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline)

-- | Parse a one-line or multi-line commodity directive.
--
-- >>> Right _ <- rjp commoditydirectivep "commodity $1.00"
-- >>> Right _ <- rjp commoditydirectivep "commodity $\n  format $1.00"
-- >>> Right _ <- rjp commoditydirectivep "commodity $\n\n" -- a commodity with no format
-- >>> Right _ <- rjp commoditydirectivep "commodity $1.00\n  format $1.00" -- both, what happens ?
commoditydirectivep :: JournalParser m ()
commoditydirectivep :: forall (m :: * -> *). JournalParser m ()
commoditydirectivep = JournalParser m ()
forall (m :: * -> *). JournalParser m ()
commoditydirectiveonelinep JournalParser m () -> JournalParser m () -> JournalParser m ()
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> JournalParser m ()
forall (m :: * -> *). JournalParser m ()
commoditydirectivemultilinep

-- | Parse a one-line commodity directive.
--
-- >>> Right _ <- rjp commoditydirectiveonelinep "commodity $1.00"
-- >>> Right _ <- rjp commoditydirectiveonelinep "commodity $1.00 ; blah\n"
commoditydirectiveonelinep :: JournalParser m ()
commoditydirectiveonelinep :: forall (m :: * -> *). JournalParser m ()
commoditydirectiveonelinep = do
  (Int
off, Amount{Text
acommodity :: Text
acommodity :: Amount -> Text
acommodity,AmountStyle
astyle :: AmountStyle
astyle :: Amount -> AmountStyle
astyle}) <- StateT Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (StateT
   Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount))
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
forall a b. (a -> b) -> a -> b
$ do
    Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"commodity"
    ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
    Int
off <- StateT Journal (ParsecT HledgerParseErrorData Text m) Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
    Amount
amt <- JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
    (Int, Amount)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Int, Amount)
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount))
-> (Int, Amount)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Int, Amount)
forall a b. (a -> b) -> a -> b
$ (Int
off, Amount
amt)
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Text
_ <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
followingcommentp
  let comm :: Commodity
comm = Commodity{csymbol :: Text
csymbol=Text
acommodity, cformat :: Maybe AmountStyle
cformat=AmountStyle -> Maybe AmountStyle
forall a. a -> Maybe a
Just (AmountStyle -> Maybe AmountStyle)
-> AmountStyle -> Maybe AmountStyle
forall a b. (a -> b) -> a -> b
$ [Char] -> AmountStyle -> AmountStyle
forall a. Show a => [Char] -> a -> a
dbg6 [Char]
"style from commodity directive" AmountStyle
astyle}
  if Maybe Char -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Char -> Bool) -> Maybe Char -> Bool
forall a b. (a -> b) -> a -> b
$ AmountStyle -> Maybe Char
asdecimalmark AmountStyle
astyle
  then HledgerParseErrorData -> JournalParser m ()
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m ())
-> HledgerParseErrorData -> JournalParser m ()
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
off [Char]
pleaseincludedecimalpoint
  else (Journal -> Journal) -> JournalParser m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\Journal
j -> Journal
j{jcommodities=M.insert acommodity comm $ jcommodities j})

pleaseincludedecimalpoint :: String
pleaseincludedecimalpoint :: [Char]
pleaseincludedecimalpoint = [Char] -> [Char]
chomp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
unlines [
   [Char]
"Please include a decimal point or decimal comma in commodity directives,"
  ,[Char]
"to help us parse correctly. It may be followed by zero or more decimal digits."
  ,[Char]
"Examples:"
  ,[Char]
"commodity $1000.            ; no thousands mark, decimal period, no decimals"
  ,[Char]
"commodity 1.234,00 ARS      ; period at thousands, decimal comma, 2 decimals"
  ,[Char]
"commodity EUR 1 000,000     ; space at thousands, decimal comma, 3 decimals"
  ,[Char]
"commodity INR1,23,45,678.0  ; comma at thousands/lakhs/crores, decimal period, 1 decimal"
  ]

-- | Parse a multi-line commodity directive, containing 0 or more format subdirectives.
--
-- >>> Right _ <- rjp commoditydirectivemultilinep "commodity $ ; blah \n  format $1.00 ; blah"
commoditydirectivemultilinep :: JournalParser m ()
commoditydirectivemultilinep :: forall (m :: * -> *). JournalParser m ()
commoditydirectivemultilinep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"commodity"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Text
sym <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
commoditysymbolp
  Text
_ <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
followingcommentp
  -- read all subdirectives, saving format subdirectives as Lefts
  [Either AmountStyle [Char]]
subdirectives <- StateT
  Journal
  (ParsecT HledgerParseErrorData Text m)
  (Either AmountStyle [Char])
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     [Either AmountStyle [Char]]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (StateT
   Journal
   (ParsecT HledgerParseErrorData Text m)
   (Either AmountStyle [Char])
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text m)
      [Either AmountStyle [Char]])
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Either AmountStyle [Char])
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     [Either AmountStyle [Char]]
forall a b. (a -> b) -> a -> b
$ StateT
  Journal
  (ParsecT HledgerParseErrorData Text m)
  (Either AmountStyle [Char])
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Either AmountStyle [Char])
forall {b}.
StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
indented (StateT Journal (ParsecT HledgerParseErrorData Text m) AmountStyle
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Either AmountStyle [Char])
forall (m :: * -> *) a b.
Alternative m =>
m a -> m b -> m (Either a b)
eitherP (Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) AmountStyle
forall (m :: * -> *). Text -> JournalParser m AmountStyle
formatdirectivep Text
sym) (ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline))
  let mfmt :: Maybe AmountStyle
mfmt = [AmountStyle] -> Maybe AmountStyle
forall a. [a] -> Maybe a
lastMay ([AmountStyle] -> Maybe AmountStyle)
-> [AmountStyle] -> Maybe AmountStyle
forall a b. (a -> b) -> a -> b
$ [Either AmountStyle [Char]] -> [AmountStyle]
forall a b. [Either a b] -> [a]
lefts [Either AmountStyle [Char]]
subdirectives
  let comm :: Commodity
comm = Commodity{csymbol :: Text
csymbol=Text
sym, cformat :: Maybe AmountStyle
cformat=Maybe AmountStyle
mfmt}
  (Journal -> Journal) -> JournalParser m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\Journal
j -> Journal
j{jcommodities=M.insert sym comm $ jcommodities j})
  where
    indented :: StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
indented = (ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1 JournalParser m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>)

-- | Parse a format (sub)directive, throwing a parse error if its
-- symbol does not match the one given.
formatdirectivep :: CommoditySymbol -> JournalParser m AmountStyle
formatdirectivep :: forall (m :: * -> *). Text -> JournalParser m AmountStyle
formatdirectivep Text
expectedsym = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"format"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Int
off <- StateT Journal (ParsecT HledgerParseErrorData Text m) Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
  Amount{Text
acommodity :: Amount -> Text
acommodity :: Text
acommodity,AmountStyle
astyle :: Amount -> AmountStyle
astyle :: AmountStyle
astyle} <- JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
  Text
_ <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
followingcommentp
  if Text
acommodityText -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
expectedsym
    then
      if Maybe Char -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Char -> Bool) -> Maybe Char -> Bool
forall a b. (a -> b) -> a -> b
$ AmountStyle -> Maybe Char
asdecimalmark AmountStyle
astyle
      then HledgerParseErrorData -> JournalParser m AmountStyle
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m AmountStyle)
-> HledgerParseErrorData -> JournalParser m AmountStyle
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
off [Char]
pleaseincludedecimalpoint
      else AmountStyle -> JournalParser m AmountStyle
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (AmountStyle -> JournalParser m AmountStyle)
-> AmountStyle -> JournalParser m AmountStyle
forall a b. (a -> b) -> a -> b
$ [Char] -> AmountStyle -> AmountStyle
forall a. Show a => [Char] -> a -> a
dbg6 [Char]
"style from format subdirective" AmountStyle
astyle
    else HledgerParseErrorData -> JournalParser m AmountStyle
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m AmountStyle)
-> HledgerParseErrorData -> JournalParser m AmountStyle
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
off ([Char] -> HledgerParseErrorData)
-> [Char] -> HledgerParseErrorData
forall a b. (a -> b) -> a -> b
$
         [Char] -> Text -> Text -> [Char]
forall r. PrintfType r => [Char] -> r
printf [Char]
"commodity directive symbol \"%s\" and format directive symbol \"%s\" should be the same" Text
expectedsym Text
acommodity

-- More Ledger directives, ignore for now:
-- apply fixed, apply tag, assert, bucket, A, capture, check, define, expr
applyfixeddirectivep, endapplyfixeddirectivep, applytagdirectivep, endapplytagdirectivep,
  assertdirectivep, bucketdirectivep, capturedirectivep, checkdirectivep, 
  endapplyyeardirectivep, definedirectivep, exprdirectivep, valuedirectivep,
  evaldirectivep, pythondirectivep, commandlineflagdirectivep
  :: JournalParser m ()
applyfixeddirectivep :: forall (m :: * -> *). JournalParser m ()
applyfixeddirectivep    = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"apply fixed" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
endapplyfixeddirectivep :: forall (m :: * -> *). JournalParser m ()
endapplyfixeddirectivep = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"end apply fixed" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
applytagdirectivep :: forall (m :: * -> *). JournalParser m ()
applytagdirectivep      = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"apply tag" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
endapplytagdirectivep :: forall (m :: * -> *). JournalParser m ()
endapplytagdirectivep   = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"end apply tag" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
endapplyyeardirectivep :: forall (m :: * -> *). JournalParser m ()
endapplyyeardirectivep  = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"end apply year" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
assertdirectivep :: forall (m :: * -> *). JournalParser m ()
assertdirectivep        = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"assert"  StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
bucketdirectivep :: forall (m :: * -> *). JournalParser m ()
bucketdirectivep        = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"A " StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"bucket " StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
capturedirectivep :: forall (m :: * -> *). JournalParser m ()
capturedirectivep       = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"capture" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkdirectivep :: forall (m :: * -> *). JournalParser m ()
checkdirectivep         = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"check"   StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
definedirectivep :: forall (m :: * -> *). JournalParser m ()
definedirectivep        = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"define"  StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
exprdirectivep :: forall (m :: * -> *). JournalParser m ()
exprdirectivep          = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"expr"    StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
valuedirectivep :: forall (m :: * -> *). JournalParser m ()
valuedirectivep         = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"value"   StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
evaldirectivep :: forall (m :: * -> *). JournalParser m ()
evaldirectivep          = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"eval"   StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
commandlineflagdirectivep :: forall (m :: * -> *). JournalParser m ()
commandlineflagdirectivep = do Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"--" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m () -> JournalParser m ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
pythondirectivep :: forall (m :: * -> *). JournalParser m ()
pythondirectivep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"python" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [[Char]]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) [[Char]])
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [[Char]]
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
indentedline StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
blankline
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  where
    indentedline :: StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
indentedline = ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1 JournalParser m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
    blankline :: StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
blankline = ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces JournalParser m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
StateT Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
newline StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
"" StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"blank line"

keywordp :: String -> JournalParser m ()
keywordp :: forall (m :: * -> *). [Char] -> JournalParser m ()
keywordp = StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT
   Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> ([Char]
    -> StateT
         Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text))
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string (Tokens Text
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text))
-> ([Char] -> Tokens Text)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Tokens Text
forall a. IsString a => [Char] -> a
fromString

spacesp :: JournalParser m ()
spacesp :: forall (m :: * -> *). JournalParser m ()
spacesp = StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT Journal (ParsecT HledgerParseErrorData Text m) ()
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1

-- | Backtracking parser similar to string, but allows varying amount of space between words
keywordsp :: String -> JournalParser m ()
keywordsp :: forall (m :: * -> *). [Char] -> JournalParser m ()
keywordsp = StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (StateT Journal (ParsecT HledgerParseErrorData Text m) ()
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> ([Char]
    -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ ([StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> ([Char]
    -> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()])
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
-> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
forall a. a -> [a] -> [a]
intersperse StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *). JournalParser m ()
spacesp ([StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
 -> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()])
-> ([Char]
    -> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()])
-> [Char]
-> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char]
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> [[Char]]
-> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *). [Char] -> JournalParser m ()
keywordp ([[Char]]
 -> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()])
-> ([Char] -> [[Char]])
-> [Char]
-> [StateT Journal (ParsecT HledgerParseErrorData Text m) ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
words

applyaccountdirectivep :: JournalParser m ()
applyaccountdirectivep :: forall (m :: * -> *). JournalParser m ()
applyaccountdirectivep = do
  [Char] -> JournalParser m ()
forall (m :: * -> *). [Char] -> JournalParser m ()
keywordsp [Char]
"apply account" JournalParser m () -> [Char] -> JournalParser m ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"apply account directive"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Text
parent <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
accountnamep
  StateT Journal (ParsecT HledgerParseErrorData Text m) Char
StateT Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
newline
  Text -> JournalParser m ()
forall (m :: * -> *). Text -> JournalParser m ()
pushParentAccount Text
parent

endapplyaccountdirectivep :: JournalParser m ()
endapplyaccountdirectivep :: forall (m :: * -> *). JournalParser m ()
endapplyaccountdirectivep = do
  [Char] -> JournalParser m ()
forall (m :: * -> *). [Char] -> JournalParser m ()
keywordsp [Char]
"end apply account" JournalParser m () -> [Char] -> JournalParser m ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"end apply account directive"
  JournalParser m ()
forall (m :: * -> *). JournalParser m ()
popParentAccount

aliasdirectivep :: JournalParser m ()
aliasdirectivep :: forall (m :: * -> *). JournalParser m ()
aliasdirectivep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"alias"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  AccountAlias
alias <- ParsecT HledgerParseErrorData Text m AccountAlias
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) AccountAlias
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m AccountAlias
forall (m :: * -> *). TextParser m AccountAlias
accountaliasp
  AccountAlias -> JournalParser m ()
forall (m :: * -> *). MonadState Journal m => AccountAlias -> m ()
addAccountAlias AccountAlias
alias

endaliasesdirectivep :: JournalParser m ()
endaliasesdirectivep :: forall (m :: * -> *). JournalParser m ()
endaliasesdirectivep = do
  [Char] -> JournalParser m ()
forall (m :: * -> *). [Char] -> JournalParser m ()
keywordsp [Char]
"end aliases" JournalParser m () -> [Char] -> JournalParser m ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"end aliases directive"
  JournalParser m ()
forall (m :: * -> *). MonadState Journal m => m ()
clearAccountAliases

tagdirectivep :: JournalParser m ()
tagdirectivep :: forall (m :: * -> *). JournalParser m ()
tagdirectivep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"tag" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"tag directive"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Text
tagname <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Text
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Text)
-> ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text m [Char]
-> ParsecT HledgerParseErrorData Text m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text m Char
-> ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT HledgerParseErrorData Text m Char
forall (m :: * -> *). TextParser m Char
nonspace
  (Text
comment, [Tag]
_) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp
  StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m ()
forall (m :: * -> *) a. MonadPlus m => m a -> m ()
skipMany StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *). JournalParser m [Char]
indentedlinep
  Tag -> JournalParser m ()
forall (m :: * -> *). Tag -> JournalParser m ()
addTagDeclaration (Text
tagname,Text
comment)
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- end tag or end apply tag
endtagdirectivep :: JournalParser m ()
endtagdirectivep :: forall (m :: * -> *). JournalParser m ()
endtagdirectivep = (do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"end"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (StateT Journal (ParsecT HledgerParseErrorData Text m) ()
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Maybe ()))
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) (Maybe ())
forall a b. (a -> b) -> a -> b
$ Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"apply" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall a b.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"tag"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol
  () -> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  ) StateT Journal (ParsecT HledgerParseErrorData Text m) ()
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"end tag or end apply tag directive"

payeedirectivep :: JournalParser m ()
payeedirectivep :: forall (m :: * -> *). JournalParser m ()
payeedirectivep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"payee" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"payee directive"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Text
payee <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Text
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Text)
-> ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall a.
ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
doublequotedtextp ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall a.
ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
noncommenttext1p)
  (Text
comment, [Tag]
tags) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp
  StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
-> JournalParser m ()
forall (m :: * -> *) a. MonadPlus m => m a -> m ()
skipMany StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *). JournalParser m [Char]
indentedlinep
  (Text, Text, [Tag]) -> JournalParser m ()
forall (m :: * -> *). (Text, Text, [Tag]) -> JournalParser m ()
addPayeeDeclaration (Text
payee, Text
comment, [Tag]
tags)
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

defaultyeardirectivep :: JournalParser m ()
defaultyeardirectivep :: forall (m :: * -> *). JournalParser m ()
defaultyeardirectivep = do
  (Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"Y" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"year" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"apply year") StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"default year"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Year -> JournalParser m ()
forall (m :: * -> *). Year -> JournalParser m ()
setYear (Year -> JournalParser m ())
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Year
-> JournalParser m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT HledgerParseErrorData Text m Year
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Year
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Year
forall (m :: * -> *). TextParser m Year
yearp

defaultcommoditydirectivep :: JournalParser m ()
defaultcommoditydirectivep :: forall (m :: * -> *). JournalParser m ()
defaultcommoditydirectivep = do
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'D' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"default commodity"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Int
off <- StateT Journal (ParsecT HledgerParseErrorData Text m) Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
  Amount{Text
acommodity :: Amount -> Text
acommodity :: Text
acommodity,AmountStyle
astyle :: Amount -> AmountStyle
astyle :: AmountStyle
astyle} <- JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
  ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  if Maybe Char -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Char -> Bool) -> Maybe Char -> Bool
forall a b. (a -> b) -> a -> b
$ AmountStyle -> Maybe Char
asdecimalmark AmountStyle
astyle
  then HledgerParseErrorData -> JournalParser m ()
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> JournalParser m ())
-> HledgerParseErrorData -> JournalParser m ()
forall a b. (a -> b) -> a -> b
$ Int -> [Char] -> HledgerParseErrorData
parseErrorAt Int
off [Char]
pleaseincludedecimalpoint
  else (Text, AmountStyle) -> JournalParser m ()
forall (m :: * -> *). (Text, AmountStyle) -> JournalParser m ()
setDefaultCommodityAndStyle (Text
acommodity, AmountStyle
astyle)

marketpricedirectivep :: JournalParser m PriceDirective
marketpricedirectivep :: forall (m :: * -> *). JournalParser m PriceDirective
marketpricedirectivep = do
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'P' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"market price"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Day
date <- StateT Journal (ParsecT HledgerParseErrorData Text m) Day
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (do {LocalTime Day
d TimeOfDay
_ <- JournalParser m LocalTime
forall (m :: * -> *). JournalParser m LocalTime
datetimep; Day -> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Day
d}) StateT Journal (ParsecT HledgerParseErrorData Text m) Day
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
forall (m :: * -> *). JournalParser m Day
datep -- a time is ignored
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Text
symbol <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
commoditysymbolp
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Amount
price <- JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
  ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  PriceDirective -> JournalParser m PriceDirective
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (PriceDirective -> JournalParser m PriceDirective)
-> PriceDirective -> JournalParser m PriceDirective
forall a b. (a -> b) -> a -> b
$ Day -> Text -> Amount -> PriceDirective
PriceDirective Day
date Text
symbol Amount
price

ignoredpricecommoditydirectivep :: JournalParser m ()
ignoredpricecommoditydirectivep :: forall (m :: * -> *). JournalParser m ()
ignoredpricecommoditydirectivep = do
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'N' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"ignored-price commodity"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
commoditysymbolp
  ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

commodityconversiondirectivep :: JournalParser m ()
commodityconversiondirectivep :: forall (m :: * -> *). JournalParser m ()
commodityconversiondirectivep = do
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'C' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"commodity conversion"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'='
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  JournalParser m Amount
forall (m :: * -> *). JournalParser m Amount
amountp
  ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Read a valid decimal mark from the decimal-mark directive e.g
--
-- decimal-mark ,
decimalmarkdirectivep :: JournalParser m ()
decimalmarkdirectivep :: forall (m :: * -> *). JournalParser m ()
decimalmarkdirectivep = do
  Tokens Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
"decimal-mark" StateT Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Tokens Text)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"decimal mark"
  ParsecT HledgerParseErrorData Text m () -> JournalParser m ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
  Char
mark <- (Token Text -> Bool)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
isDecimalMark
  (Journal -> Journal) -> JournalParser m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' ((Journal -> Journal) -> JournalParser m ())
-> (Journal -> Journal) -> JournalParser m ()
forall a b. (a -> b) -> a -> b
$ \Journal
j -> Journal
j{jparsedecimalmark=Just mark}
  ParsecT HledgerParseErrorData Text m [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Char]
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m [Char]
forall (m :: * -> *). TextParser m [Char]
restofline
  () -> JournalParser m ()
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

--- *** transactions

-- | Parse a transaction modifier (auto postings) rule.
transactionmodifierp :: JournalParser m TransactionModifier
transactionmodifierp :: forall (m :: * -> *). JournalParser m TransactionModifier
transactionmodifierp = do
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'=' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"modifier transaction"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
  Text
querytxt <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Text
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Text)
-> ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
descriptionp
  (Text
_comment, [Tag]
_tags) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp   -- TODO apply these to modified txns ?
  [TMPostingRule]
postingrules <- Maybe Year -> JournalParser m [TMPostingRule]
forall (m :: * -> *). Maybe Year -> JournalParser m [TMPostingRule]
tmpostingrulesp Maybe Year
forall a. Maybe a
Nothing
  TransactionModifier -> JournalParser m TransactionModifier
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (TransactionModifier -> JournalParser m TransactionModifier)
-> TransactionModifier -> JournalParser m TransactionModifier
forall a b. (a -> b) -> a -> b
$ Text -> [TMPostingRule] -> TransactionModifier
TransactionModifier Text
querytxt [TMPostingRule]
postingrules

-- | Parse a periodic transaction rule.
--
-- This reuses periodexprp which parses period expressions on the command line.
-- This is awkward because periodexprp supports relative and partial dates,
-- which we don't really need here, and it doesn't support the notion of a
-- default year set by a Y directive, which we do need to consider here.
-- We resolve it as follows: in periodic transactions' period expressions,
-- if there is a default year Y in effect, partial/relative dates are calculated
-- relative to Y/1/1. If not, they are calculated related to today as usual.
periodictransactionp :: MonadIO m => JournalParser m PeriodicTransaction
periodictransactionp :: forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp = do
  SourcePos
startpos <- StateT Journal (ParsecT HledgerParseErrorData Text m) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos

  -- first line
  Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'~' StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"periodic transaction"
  ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m ()
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) ())
-> ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces

  -- if there's a default year in effect, use Y/1/1 as base for partial/relative dates
  Day
today <- IO Day -> StateT Journal (ParsecT HledgerParseErrorData Text m) Day
forall a.
IO a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Day
getCurrentDay
  Maybe Year
mdefaultyear <- JournalParser m (Maybe Year)
forall (m :: * -> *). JournalParser m (Maybe Year)
getYear
  let refdate :: Day
refdate = case Maybe Year
mdefaultyear of
                  Maybe Year
Nothing -> Day
today
                  Just Year
y  -> Year -> Int -> Int -> Day
fromGregorian Year
y Int
1 Int
1
  SourceExcerpt
periodExcerpt <- ParsecT HledgerParseErrorData Text m SourceExcerpt
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) SourceExcerpt
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m SourceExcerpt
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) SourceExcerpt)
-> ParsecT HledgerParseErrorData Text m SourceExcerpt
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) SourceExcerpt
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m SourceExcerpt
forall (m :: * -> *) a.
MonadParsec HledgerParseErrorData Text m =>
m a -> m SourceExcerpt
excerpt_ (ParsecT HledgerParseErrorData Text m Text
 -> ParsecT HledgerParseErrorData Text m SourceExcerpt)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m SourceExcerpt
forall a b. (a -> b) -> a -> b
$
                    (Char -> Bool) -> ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). (Char -> Bool) -> TextParser m Text
singlespacedtextsatisfying1p (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
';' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n')
  let periodtxt :: Text
periodtxt = Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ SourceExcerpt -> Text
getExcerptText SourceExcerpt
periodExcerpt

  -- first parsing with 'singlespacedtextp', then "re-parsing" with
  -- 'periodexprp' saves 'periodexprp' from having to respect the single-
  -- and double-space parsing rules
  (Interval
interval, DateSpan
spn) <- ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Interval, DateSpan)
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text m)
      (Interval, DateSpan))
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$ SourceExcerpt
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
forall (m :: * -> *) a.
Monad m =>
SourceExcerpt
-> ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
reparseExcerpt SourceExcerpt
periodExcerpt (ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
 -> ParsecT HledgerParseErrorData Text m (Interval, DateSpan))
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$ do
    (Interval, DateSpan)
pexp <- Day -> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
forall (m :: * -> *). Day -> TextParser m (Interval, DateSpan)
periodexprp Day
refdate
    ParsecT HledgerParseErrorData Text m ()
-> ParsecT HledgerParseErrorData Text m ()
-> ParsecT HledgerParseErrorData Text m ()
forall a.
ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) ParsecT HledgerParseErrorData Text m ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof (ParsecT HledgerParseErrorData Text m ()
 -> ParsecT HledgerParseErrorData Text m ())
-> ParsecT HledgerParseErrorData Text m ()
-> ParsecT HledgerParseErrorData Text m ()
forall a b. (a -> b) -> a -> b
$ do
      Int
offset1 <- ParsecT HledgerParseErrorData Text m Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
      ParsecT HledgerParseErrorData Text m (Tokens Text)
-> ParsecT HledgerParseErrorData Text m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT HledgerParseErrorData Text m (Tokens Text)
forall e s (m :: * -> *). MonadParsec e s m => m (Tokens s)
takeRest
      Int
offset2 <- ParsecT HledgerParseErrorData Text m Int
forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
      HledgerParseErrorData -> ParsecT HledgerParseErrorData Text m ()
forall e s (m :: * -> *) a. MonadParsec e s m => e -> m a
customFailure (HledgerParseErrorData -> ParsecT HledgerParseErrorData Text m ())
-> HledgerParseErrorData -> ParsecT HledgerParseErrorData Text m ()
forall a b. (a -> b) -> a -> b
$ Int -> Int -> [Char] -> HledgerParseErrorData
parseErrorAtRegion Int
offset1 Int
offset2 ([Char] -> HledgerParseErrorData)
-> [Char] -> HledgerParseErrorData
forall a b. (a -> b) -> a -> b
$
           [Char]
"remainder of period expression cannot be parsed"
        [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"\nperhaps you need to terminate the period expression with a double space?"
        [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"\na double space is required between period expression and description/comment"
    (Interval, DateSpan)
-> ParsecT HledgerParseErrorData Text m (Interval, DateSpan)
forall a. a -> ParsecT HledgerParseErrorData Text m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Interval, DateSpan)
pexp

  Status
status <- ParsecT HledgerParseErrorData Text m Status
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Status
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Status
forall (m :: * -> *). TextParser m Status
statusp StateT Journal (ParsecT HledgerParseErrorData Text m) Status
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Status
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"cleared status"
  Text
code <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
codep StateT Journal (ParsecT HledgerParseErrorData Text m) Text
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"transaction code"
  Text
description <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Text
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Text)
-> ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
descriptionp
  (Text
comment, [Tag]
tags) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp
  -- next lines; use same year determined above
  [Posting]
postings <- Maybe Year -> JournalParser m [Posting]
forall (m :: * -> *). Maybe Year -> JournalParser m [Posting]
postingsp (Year -> Maybe Year
forall a. a -> Maybe a
Just (Year -> Maybe Year) -> Year -> Maybe Year
forall a b. (a -> b) -> a -> b
$ (Year, Int, Int) -> Year
forall {a} {b} {c}. (a, b, c) -> a
first3 ((Year, Int, Int) -> Year) -> (Year, Int, Int) -> Year
forall a b. (a -> b) -> a -> b
$ Day -> (Year, Int, Int)
toGregorian Day
refdate)

  SourcePos
endpos <- StateT Journal (ParsecT HledgerParseErrorData Text m) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
  let sourcepos :: (SourcePos, SourcePos)
sourcepos = (SourcePos
startpos, SourcePos
endpos)

  PeriodicTransaction -> JournalParser m PeriodicTransaction
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (PeriodicTransaction -> JournalParser m PeriodicTransaction)
-> PeriodicTransaction -> JournalParser m PeriodicTransaction
forall a b. (a -> b) -> a -> b
$ PeriodicTransaction
nullperiodictransaction{
     ptperiodexpr=periodtxt
    ,ptinterval=interval
    ,ptspan=spn
    ,ptsourcepos=sourcepos
    ,ptstatus=status
    ,ptcode=code
    ,ptdescription=description
    ,ptcomment=comment
    ,pttags=tags
    ,ptpostings=postings
    }

-- | Parse a (possibly unbalanced) transaction.
transactionp :: JournalParser m Transaction
transactionp :: forall (m :: * -> *). JournalParser m Transaction
transactionp = do
  -- dbgparse 0 "transactionp"
  SourcePos
startpos <- StateT Journal (ParsecT HledgerParseErrorData Text m) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
  Day
date <- JournalParser m Day
forall (m :: * -> *). JournalParser m Day
datep JournalParser m Day -> [Char] -> JournalParser m Day
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"transaction"
  Maybe Day
edate <- JournalParser m Day
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Maybe Day)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT HledgerParseErrorData Text m Day -> JournalParser m Day
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Day -> JournalParser m Day)
-> ParsecT HledgerParseErrorData Text m Day -> JournalParser m Day
forall a b. (a -> b) -> a -> b
$ Day -> ParsecT HledgerParseErrorData Text m Day
forall (m :: * -> *). Day -> TextParser m Day
secondarydatep Day
date) StateT Journal (ParsecT HledgerParseErrorData Text m) (Maybe Day)
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Maybe Day)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"secondary date"
  StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (ParsecT HledgerParseErrorData Text m Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Char
forall s (m :: * -> *).
(Stream s, Char ~ Token s) =>
ParsecT HledgerParseErrorData s m Char
spacenonewline StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
StateT Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
newline) StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"whitespace or newline"
  Status
status <- ParsecT HledgerParseErrorData Text m Status
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Status
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Status
forall (m :: * -> *). TextParser m Status
statusp StateT Journal (ParsecT HledgerParseErrorData Text m) Status
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Status
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"cleared status"
  Text
code <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
codep StateT Journal (ParsecT HledgerParseErrorData Text m) Text
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"transaction code"
  Text
description <- ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT HledgerParseErrorData Text m Text
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Text)
-> ParsecT HledgerParseErrorData Text m Text
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text m Text
forall (m :: * -> *). TextParser m Text
descriptionp
  (Text
comment, [Tag]
tags) <- ParsecT HledgerParseErrorData Text m (Text, [Tag])
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Text, [Tag])
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m (Text, [Tag])
forall (m :: * -> *). TextParser m (Text, [Tag])
transactioncommentp
  let year :: Year
year = (Year, Int, Int) -> Year
forall {a} {b} {c}. (a, b, c) -> a
first3 ((Year, Int, Int) -> Year) -> (Year, Int, Int) -> Year
forall a b. (a -> b) -> a -> b
$ Day -> (Year, Int, Int)
toGregorian Day
date
  [Posting]
postings <- Maybe Year -> JournalParser m [Posting]
forall (m :: * -> *). Maybe Year -> JournalParser m [Posting]
postingsp (Year -> Maybe Year
forall a. a -> Maybe a
Just Year
year)
  SourcePos
endpos <- StateT Journal (ParsecT HledgerParseErrorData Text m) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
  let sourcepos :: (SourcePos, SourcePos)
sourcepos = (SourcePos
startpos, SourcePos
endpos)
  Transaction -> JournalParser m Transaction
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Transaction -> JournalParser m Transaction)
-> Transaction -> JournalParser m Transaction
forall a b. (a -> b) -> a -> b
$ Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ Year
-> Text
-> (SourcePos, SourcePos)
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction Year
0 Text
"" (SourcePos, SourcePos)
sourcepos Day
date Maybe Day
edate Status
status Text
code Text
description Text
comment [Tag]
tags [Posting]
postings

--- *** postings

-- Parse the following whitespace-beginning lines as postings, posting
-- tags, and/or comments (inferring year, if needed, from the given date).
postingsp :: Maybe Year -> JournalParser m [Posting]
postingsp :: forall (m :: * -> *). Maybe Year -> JournalParser m [Posting]
postingsp Maybe Year
mTransactionYear = StateT Journal (ParsecT HledgerParseErrorData Text m) Posting
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Posting]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
mTransactionYear) StateT Journal (ParsecT HledgerParseErrorData Text m) [Posting]
-> [Char]
-> StateT Journal (ParsecT HledgerParseErrorData Text m) [Posting]
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"postings"

-- linebeginningwithspaces :: JournalParser m String
-- linebeginningwithspaces = do
--   sp <- lift skipNonNewlineSpaces1
--   c <- nonspace
--   cs <- lift restofline
--   return $ sp ++ (c:cs) ++ "\n"

postingp :: Maybe Year -> JournalParser m Posting
postingp :: forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp = ((Posting, Bool) -> Posting)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Posting
forall a b.
(a -> b)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Posting, Bool) -> Posting
forall a b. (a, b) -> a
fst (StateT
   Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Posting)
-> (Maybe Year
    -> StateT
         Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool))
-> Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Posting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> Maybe Year
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
forall (m :: * -> *).
Bool -> Maybe Year -> JournalParser m (Posting, Bool)
postingphelper Bool
False

-- Parse the following whitespace-beginning lines as transaction posting rules, posting
-- tags, and/or comments (inferring year, if needed, from the given date).
tmpostingrulesp :: Maybe Year -> JournalParser m [TMPostingRule]
tmpostingrulesp :: forall (m :: * -> *). Maybe Year -> JournalParser m [TMPostingRule]
tmpostingrulesp Maybe Year
mTransactionYear = StateT Journal (ParsecT HledgerParseErrorData Text m) TMPostingRule
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) [TMPostingRule]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Maybe Year
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) TMPostingRule
forall (m :: * -> *). Maybe Year -> JournalParser m TMPostingRule
tmpostingrulep Maybe Year
mTransactionYear) StateT
  Journal (ParsecT HledgerParseErrorData Text m) [TMPostingRule]
-> [Char]
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) [TMPostingRule]
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"posting rules"

tmpostingrulep :: Maybe Year -> JournalParser m TMPostingRule
tmpostingrulep :: forall (m :: * -> *). Maybe Year -> JournalParser m TMPostingRule
tmpostingrulep = ((Posting, Bool) -> TMPostingRule)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) TMPostingRule
forall a b.
(a -> b)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Posting -> Bool -> TMPostingRule)
-> (Posting, Bool) -> TMPostingRule
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Posting -> Bool -> TMPostingRule
TMPostingRule) (StateT
   Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) TMPostingRule)
-> (Maybe Year
    -> StateT
         Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool))
-> Maybe Year
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) TMPostingRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> Maybe Year
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Posting, Bool)
forall (m :: * -> *).
Bool -> Maybe Year -> JournalParser m (Posting, Bool)
postingphelper Bool
True

-- Parse a Posting, and return a flag with whether a multiplier has been detected.
-- The multiplier is used in TMPostingRules.
postingphelper :: Bool -> Maybe Year -> JournalParser m (Posting, Bool)
postingphelper :: forall (m :: * -> *).
Bool -> Maybe Year -> JournalParser m (Posting, Bool)
postingphelper Bool
isPostingRule Maybe Year
mTransactionYear = do
    -- lift $ dbgparse 0 "postingp"
    (Status
status, Text
account) <- StateT
  Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
forall a.
StateT Journal (ParsecT HledgerParseErrorData Text m) a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (StateT
   Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Status, Text))
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
forall a b. (a -> b) -> a -> b
$ do
      ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
      Status
status <- ParsecT HledgerParseErrorData Text m Status
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Status
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m Status
forall (m :: * -> *). TextParser m Status
statusp
      ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
      Text
account <- JournalParser m Text
forall (m :: * -> *). JournalParser m Text
modifiedaccountnamep
      (Status, Text)
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Status, Text)
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
status, Text
account)
    let (PostingType
ptype, Text
account') = (Text -> PostingType
accountNamePostingType Text
account, Text -> Text
textUnbracket Text
account)
    ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
    Bool
mult <- if Bool
isPostingRule then StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
multiplierp else Bool -> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
    Maybe Amount
amt <- StateT Journal (ParsecT HledgerParseErrorData Text m) Amount
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Maybe Amount)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (StateT Journal (ParsecT HledgerParseErrorData Text m) Amount
 -> StateT
      Journal (ParsecT HledgerParseErrorData Text m) (Maybe Amount))
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Amount
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Maybe Amount)
forall a b. (a -> b) -> a -> b
$ Bool
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Amount
forall (m :: * -> *). Bool -> JournalParser m Amount
amountp' Bool
mult
    ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
    Maybe BalanceAssertion
massertion <- StateT
  Journal (ParsecT HledgerParseErrorData Text m) BalanceAssertion
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Maybe BalanceAssertion)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional StateT
  Journal (ParsecT HledgerParseErrorData Text m) BalanceAssertion
forall (m :: * -> *). JournalParser m BalanceAssertion
balanceassertionp
    ParsecT HledgerParseErrorData Text m ()
-> StateT Journal (ParsecT HledgerParseErrorData Text m) ()
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text m ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces
    (Text
comment,[Tag]
tags,Maybe Day
mdate,Maybe Day
mdate2) <- ParsecT
  HledgerParseErrorData Text m (Text, [Tag], Maybe Day, Maybe Day)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Text, [Tag], Maybe Day, Maybe Day)
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ParsecT
   HledgerParseErrorData Text m (Text, [Tag], Maybe Day, Maybe Day)
 -> StateT
      Journal
      (ParsecT HledgerParseErrorData Text m)
      (Text, [Tag], Maybe Day, Maybe Day))
-> ParsecT
     HledgerParseErrorData Text m (Text, [Tag], Maybe Day, Maybe Day)
-> StateT
     Journal
     (ParsecT HledgerParseErrorData Text m)
     (Text, [Tag], Maybe Day, Maybe Day)
forall a b. (a -> b) -> a -> b
$ Maybe Year
-> ParsecT
     HledgerParseErrorData Text m (Text, [Tag], Maybe Day, Maybe Day)
forall (m :: * -> *).
Maybe Year -> TextParser m (Text, [Tag], Maybe Day, Maybe Day)
postingcommentp Maybe Year
mTransactionYear
    let p :: Posting
p = Posting
posting
            { pdate=mdate
            , pdate2=mdate2
            , pstatus=status
            , paccount=account'
            , pamount=maybe missingmixedamt mixedAmount amt
            , pcomment=comment
            , ptype=ptype
            , ptags=tags
            , pbalanceassertion=massertion
            }
    (Posting, Bool) -> JournalParser m (Posting, Bool)
forall a.
a -> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Posting
p, Bool
mult)
  where
    multiplierp :: StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
multiplierp = Bool
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Bool
False (StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
 -> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool)
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
forall a b. (a -> b) -> a -> b
$ Bool
True Bool
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Char
-> StateT Journal (ParsecT HledgerParseErrorData Text m) Bool
forall a b.
a
-> StateT Journal (ParsecT HledgerParseErrorData Text m) b
-> StateT Journal (ParsecT HledgerParseErrorData Text m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text
-> StateT
     Journal (ParsecT HledgerParseErrorData Text m) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'*'

--- ** tests

tests_JournalReader :: TestTree
tests_JournalReader = [Char] -> [TestTree] -> TestTree
testGroup [Char]
"JournalReader" [

   let p :: JournalParser IO Text
p = ParsecT HledgerParseErrorData Text IO Text -> JournalParser IO Text
forall (m :: * -> *) a. Monad m => m a -> StateT Journal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ParsecT HledgerParseErrorData Text IO Text
forall (m :: * -> *). TextParser m Text
accountnamep :: JournalParser IO AccountName in
   [Char] -> [TestTree] -> TestTree
testGroup [Char]
"accountnamep" [
     [Char] -> Assertion -> TestTree
testCase [Char]
"basic" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ JournalParser IO Text -> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse JournalParser IO Text
p Text
"a:b:c"
    -- ,testCase "empty inner component" $ assertParseError p "a::c" ""  -- TODO
    -- ,testCase "empty leading component" $ assertParseError p ":b:c" "x"
    -- ,testCase "empty trailing component" $ assertParseError p "a:b:" "x"
    ]

  -- "Parse a date in YYYY/MM/DD format.
  -- Hyphen (-) and period (.) are also allowed as separators.
  -- The year may be omitted if a default year has been set.
  -- Leading zeroes may be omitted."
  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"datep" [
     [Char] -> Assertion -> TestTree
testCase [Char]
"YYYY/MM/DD" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text -> Day -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
"2018/01/01" (Year -> Int -> Int -> Day
fromGregorian Year
2018 Int
1 Int
1)
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"YYYY-MM-DD" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
"2018-01-01"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"YYYY.MM.DD" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
"2018.01.01"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"yearless date with no default year" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text -> [Char] -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> [Char] -> Assertion
assertParseError StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
"1/1" [Char]
"current year is unknown"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"yearless date with default year" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
      let s :: Text
s = Text
"1/1"
      Either HledgerParseErrors Day
ep <- Journal
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text
-> IO (Either HledgerParseErrors Day)
forall (m :: * -> *) st a.
Monad m =>
st
-> StateT st (ParsecT HledgerParseErrorData Text m) a
-> Text
-> m (Either HledgerParseErrors a)
parseWithState Journal
nulljournal{jparsedefaultyear=Just 2018} StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
s
      (HledgerParseErrors -> Assertion)
-> (Day -> Assertion) -> Either HledgerParseErrors Day -> Assertion
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Assertion
forall a. HasCallStack => [Char] -> IO a
assertFailure ([Char] -> Assertion)
-> (HledgerParseErrors -> [Char])
-> HledgerParseErrors
-> Assertion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char]
"parse error at "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++) ([Char] -> [Char])
-> (HledgerParseErrors -> [Char]) -> HledgerParseErrors -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HledgerParseErrors -> [Char]
customErrorBundlePretty) (Assertion -> Day -> Assertion
forall a b. a -> b -> a
const (Assertion -> Day -> Assertion) -> Assertion -> Day -> Assertion
forall a b. (a -> b) -> a -> b
$ () -> Assertion
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Either HledgerParseErrors Day
ep
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"no leading zero" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) Day
forall (m :: * -> *). JournalParser m Day
datep Text
"2018/1/1"
    ]
  ,[Char] -> Assertion -> TestTree
testCase [Char]
"datetimep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
     let
       good :: Text -> Assertion
good  = StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
forall (m :: * -> *). JournalParser m LocalTime
datetimep
       bad :: Text -> Assertion
bad Text
t = StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
-> Text -> [Char] -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> [Char] -> Assertion
assertParseError StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
forall (m :: * -> *). JournalParser m LocalTime
datetimep Text
t [Char]
""
     Text -> Assertion
good Text
"2011/1/1 00:00"
     Text -> Assertion
good Text
"2011/1/1 23:59:59"
     Text -> Assertion
bad Text
"2011/1/1"
     Text -> Assertion
bad Text
"2011/1/1 24:00:00"
     Text -> Assertion
bad Text
"2011/1/1 00:60:00"
     Text -> Assertion
bad Text
"2011/1/1 00:00:60"
     Text -> Assertion
bad Text
"2011/1/1 3:5:7"
     -- timezone is parsed but ignored
     let t :: LocalTime
t = Day -> TimeOfDay -> LocalTime
LocalTime (Year -> Int -> Int -> Day
fromGregorian Year
2018 Int
1 Int
1) (Int -> Int -> Pico -> TimeOfDay
TimeOfDay Int
0 Int
0 Pico
0)
     StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
-> Text -> LocalTime -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
forall (m :: * -> *). JournalParser m LocalTime
datetimep Text
"2018/1/1 00:00-0800" LocalTime
t
     StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
-> Text -> LocalTime -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT Journal (ParsecT HledgerParseErrorData Text IO) LocalTime
forall (m :: * -> *). JournalParser m LocalTime
datetimep Text
"2018/1/1 00:00+1234" LocalTime
t

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"periodictransactionp" [

    [Char] -> Assertion -> TestTree
testCase [Char]
"more period text in comment after one space" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
-> Text -> PeriodicTransaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp
      Text
"~ monthly from 2018/6 ;In 2019 we will change this\n"
      PeriodicTransaction
nullperiodictransaction {
         ptperiodexpr  = "monthly from 2018/6"
        ,ptinterval    = Months 1
        ,ptspan        = DateSpan (Just $ Flex $ fromGregorian 2018 6 1) Nothing
        ,ptsourcepos   = (SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 2) (mkPos 1))
        ,ptdescription = ""
        ,ptcomment     = "In 2019 we will change this\n"
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"more period text in description after two spaces" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
-> Text -> PeriodicTransaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp
      Text
"~ monthly from 2018/6   In 2019 we will change this\n"
      PeriodicTransaction
nullperiodictransaction {
         ptperiodexpr  = "monthly from 2018/6"
        ,ptinterval    = Months 1
        ,ptspan        = DateSpan (Just $ Flex $ fromGregorian 2018 6 1) Nothing
        ,ptsourcepos   = (SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 2) (mkPos 1))
        ,ptdescription = "In 2019 we will change this"
        ,ptcomment     = ""
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"Next year in description" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
-> Text -> PeriodicTransaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp
      Text
"~ monthly  Next year blah blah\n"
      PeriodicTransaction
nullperiodictransaction {
         ptperiodexpr  = "monthly"
        ,ptinterval    = Months 1
        ,ptspan        = DateSpan Nothing Nothing
        ,ptsourcepos   = (SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 2) (mkPos 1))
        ,ptdescription = "Next year blah blah"
        ,ptcomment     = ""
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"Just date, no description" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
-> Text -> PeriodicTransaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp
      Text
"~ 2019-01-04\n"
      PeriodicTransaction
nullperiodictransaction {
         ptperiodexpr  = "2019-01-04"
        ,ptinterval    = NoInterval
        ,ptspan        = DateSpan (Just $ Exact $ fromGregorian 2019 1 4) (Just $ Exact $ fromGregorian 2019 1 5)
        ,ptsourcepos   = (SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 2) (mkPos 1))
        ,ptdescription = ""
        ,ptcomment     = ""
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"Just date, no description + empty transaction comment" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PeriodicTransaction
forall (m :: * -> *).
MonadIO m =>
JournalParser m PeriodicTransaction
periodictransactionp
      Text
"~ 2019-01-04\n  ;\n  a  1\n  b\n"

    ]

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"postingp" [
     [Char] -> Assertion -> TestTree
testCase [Char]
"basic" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Posting -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing)
      Text
"  expenses:food:dining  $10.00   ; a: a a \n   ; b: b b \n"
      Posting
posting{
        paccount="expenses:food:dining",
        pamount=mixedAmount (usd 10),
        pcomment="a: a a\nb: b b\n",
        ptags=[("a","a a"), ("b","b b")]
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"posting dates" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Posting -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing)
      Text
" a  1. ; date:2012/11/28, date2=2012/11/29,b:b\n"
      Posting
nullposting{
         paccount="a"
        ,pamount=mixedAmount (num 1)
        ,pcomment="date:2012/11/28, date2=2012/11/29,b:b\n"
        ,ptags=[("date", "2012/11/28"), ("date2=2012/11/29,b", "b")] -- TODO tag name parsed too greedily
        ,pdate=Just $ fromGregorian 2012 11 28
        ,pdate2=Nothing  -- Just $ fromGregorian 2012 11 29
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"posting dates bracket syntax" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Posting -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing)
      Text
" a  1. ; [2012/11/28=2012/11/29]\n"
      Posting
nullposting{
         paccount="a"
        ,pamount=mixedAmount (num 1)
        ,pcomment="[2012/11/28=2012/11/29]\n"
        ,ptags=[]
        ,pdate= Just $ fromGregorian 2012 11 28
        ,pdate2=Just $ fromGregorian 2012 11 29
        }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"quoted commodity symbol with digits" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1 \"DE123\"\n"

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"only lot price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A {1B}\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"fixed lot price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A {=1B}\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"total lot price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A {{1B}}\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"fixed total lot price, and spaces" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A {{  =  1B }}\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"lot price before transaction price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A {1B} @ 1B\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"lot price after transaction price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A @ 1B {1B}\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"lot price after balance assertion not allowed" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> [Char] -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> [Char] -> Assertion
assertParseError (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A @ 1B = 1A {1B}\n" [Char]
"unexpected '{'"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"only lot date" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A [2000-01-01]\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"transaction price, lot price, lot date" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A @ 1B {1B} [2000-01-01]\n"
    ,[Char] -> Assertion -> TestTree
testCase [Char]
"lot date, lot price, transaction price" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  1A [2000-01-01] {1B} @ 1B\n"

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"balance assertion over entire contents of account" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse (Maybe Year
-> StateT Journal (ParsecT HledgerParseErrorData Text IO) Posting
forall (m :: * -> *). Maybe Year -> JournalParser m Posting
postingp Maybe Year
forall a. Maybe a
Nothing) Text
"  a  $1 == $1\n"
    ]

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"transactionmodifierp" [

    [Char] -> Assertion -> TestTree
testCase [Char]
"basic" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) TransactionModifier
-> Text -> TransactionModifier -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) TransactionModifier
forall (m :: * -> *). JournalParser m TransactionModifier
transactionmodifierp
      Text
"= (some value expr)\n some:postings  1.\n"
      TransactionModifier
nulltransactionmodifier {
        tmquerytxt = "(some value expr)"
       ,tmpostingrules = [TMPostingRule nullposting{paccount="some:postings", pamount=mixedAmount (num 1)} False]
      }
    ]

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"transactionp" [

     [Char] -> Assertion -> TestTree
testCase [Char]
"just a date" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
-> Text -> Transaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp Text
"2015/1/1\n" Transaction
nulltransaction{tdate=fromGregorian 2015 1 1}

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"more complex" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
-> Text -> Transaction -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp
      ([Text] -> Text
T.unlines [
        Text
"2012/05/14=2012/05/15 (code) desc  ; tcomment1",
        Text
"    ; tcomment2",
        Text
"    ; ttag1: val1",
        Text
"    * a         $1.00  ; pcomment1",
        Text
"    ; pcomment2",
        Text
"    ; ptag1: val1",
        Text
"    ; ptag2: val2"
        ])
      Transaction
nulltransaction{
        tsourcepos=(SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 8) (mkPos 1)),  -- 8 because there are 7 lines
        tprecedingcomment="",
        tdate=fromGregorian 2012 5 14,
        tdate2=Just $ fromGregorian 2012 5 15,
        tstatus=Unmarked,
        tcode="code",
        tdescription="desc",
        tcomment="tcomment1\ntcomment2\nttag1: val1\n",
        ttags=[("ttag1","val1")],
        tpostings=[
          nullposting{
            pdate=Nothing,
            pstatus=Cleared,
            paccount="a",
            pamount=mixedAmount (usd 1),
            pcomment="pcomment1\npcomment2\nptag1: val1\nptag2: val2\n",
            ptype=RegularPosting,
            ptags=[("ptag1","val1"),("ptag2","val2")],
            ptransaction=Nothing
            }
          ]
      }

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"parses a well-formed transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
      HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. Either a b -> Bool
isRight (Either Any (Either HledgerParseErrors Transaction) -> Bool)
-> Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. (a -> b) -> a -> b
$ JournalParser (Either Any) Transaction
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
rjp JournalParser (Either Any) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp (Text -> Either Any (Either HledgerParseErrors Transaction))
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines
        [Text
"2007/01/28 coopportunity"
        ,Text
"    expenses:food:groceries                   $47.18"
        ,Text
"    assets:checking                          $-47.18"
        ,Text
""
        ]

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"does not parse a following comment as part of the description" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
      StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
-> Text -> (Transaction -> Text) -> Text -> Assertion
forall b st a.
(HasCallStack, Eq b, Show b, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> (a -> b) -> b -> Assertion
assertParseEqOn StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp Text
"2009/1/1 a ;comment\n b 1\n" Transaction -> Text
tdescription Text
"a"

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"parses a following whitespace line" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
      HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. Either a b -> Bool
isRight (Either Any (Either HledgerParseErrors Transaction) -> Bool)
-> Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. (a -> b) -> a -> b
$ JournalParser (Either Any) Transaction
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
rjp JournalParser (Either Any) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp (Text -> Either Any (Either HledgerParseErrors Transaction))
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines
        [Text
"2012/1/1"
        ,Text
"  a  1"
        ,Text
"  b"
        ,Text
" "
        ]

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"parses an empty transaction comment following whitespace line" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
      HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. Either a b -> Bool
isRight (Either Any (Either HledgerParseErrors Transaction) -> Bool)
-> Either Any (Either HledgerParseErrors Transaction) -> Bool
forall a b. (a -> b) -> a -> b
$ JournalParser (Either Any) Transaction
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall (m :: * -> *) a.
Monad m =>
JournalParser m a -> Text -> m (Either HledgerParseErrors a)
rjp JournalParser (Either Any) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp (Text -> Either Any (Either HledgerParseErrors Transaction))
-> Text -> Either Any (Either HledgerParseErrors Transaction)
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines
        [Text
"2012/1/1"
        ,Text
"  ;"
        ,Text
"  a  1"
        ,Text
"  b"
        ,Text
" "
        ]

    ,[Char] -> Assertion -> TestTree
testCase [Char]
"comments everywhere, two postings parsed" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
      StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
-> Text -> (Transaction -> Int) -> Int -> Assertion
forall b st a.
(HasCallStack, Eq b, Show b, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> (a -> b) -> b -> Assertion
assertParseEqOn StateT Journal (ParsecT HledgerParseErrorData Text IO) Transaction
forall (m :: * -> *). JournalParser m Transaction
transactionp
        ([Text] -> Text
T.unlines
          [Text
"2009/1/1 x  ; transaction comment"
          ,Text
" a  1  ; posting 1 comment"
          ,Text
" ; posting 1 comment 2"
          ,Text
" b"
          ,Text
" ; posting 2 comment"
          ])
        ([Posting] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Posting] -> Int)
-> (Transaction -> [Posting]) -> Transaction -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings)
        Int
2

    ]

  -- directives

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"directivep" [
    [Char] -> Assertion -> TestTree
testCase [Char]
"supports !" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
        StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
-> Text -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  a
-> Text -> Assertion
assertParseE StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
directivep Text
"!account a\n"
        StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
-> Text -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  a
-> Text -> Assertion
assertParseE StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
directivep Text
"!D 1.0\n"
     ]

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"accountdirectivep" [
       [Char] -> Assertion -> TestTree
testCase [Char]
"with-comment"       (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
accountdirectivep Text
"account a:b  ; a comment\n"
      ,[Char] -> Assertion -> TestTree
testCase [Char]
"does-not-support-!" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> [Char] -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> [Char] -> Assertion
assertParseError StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
accountdirectivep Text
"!account a:b\n" [Char]
""
      ,[Char] -> Assertion -> TestTree
testCase [Char]
"account-type-code"  (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
accountdirectivep Text
"account a:b  ; type:A\n"
      ,[Char] -> Assertion -> TestTree
testCase [Char]
"account-type-tag"   (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text
-> (Journal -> [(Text, AccountDeclarationInfo)])
-> [(Text, AccountDeclarationInfo)]
-> Assertion
forall b st a.
(HasCallStack, Eq b, Show b, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> (st -> b) -> b -> Assertion
assertParseStateOn StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
accountdirectivep Text
"account a:b  ; type:asset\n"
        Journal -> [(Text, AccountDeclarationInfo)]
jdeclaredaccounts
        [(Text
"a:b", AccountDeclarationInfo{adicomment :: Text
adicomment          = Text
"type:asset\n"
                                       ,aditags :: [Tag]
aditags             = [(Text
"type",Text
"asset")]
                                       ,adideclarationorder :: Int
adideclarationorder = Int
1
                                       ,adisourcepos :: SourcePos
adisourcepos        = (SourcePos, SourcePos) -> SourcePos
forall a b. (a, b) -> a
fst (SourcePos, SourcePos)
nullsourcepos
                                       })
        ]
      ]

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"commodityconversiondirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
     StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
commodityconversiondirectivep Text
"C 1h = $50.00\n"

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"defaultcommoditydirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
      StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
defaultcommoditydirectivep Text
"D $1,000.0\n"
      StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> [Char] -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> [Char] -> Assertion
assertParseError StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
defaultcommoditydirectivep Text
"D $1000\n" [Char]
"Please include a decimal point or decimal comma"

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"defaultyeardirectivep" [
      [Char] -> Assertion -> TestTree
testCase [Char]
"1000" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
defaultyeardirectivep Text
"Y 1000" -- XXX no \n like the others
     -- ,testCase "999" $ assertParseError defaultyeardirectivep "Y 999" "bad year number"
     ,[Char] -> Assertion -> TestTree
testCase [Char]
"12345" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
defaultyeardirectivep Text
"Y 12345"
     ]

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"ignoredpricecommoditydirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
     StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
ignoredpricecommoditydirectivep Text
"N $\n"

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"includedirectivep" [
      [Char] -> Assertion -> TestTree
testCase [Char]
"include" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
-> Text -> [Char] -> Assertion
forall st a.
(Default st, Eq a, Show a, HasCallStack) =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  a
-> Text -> [Char] -> Assertion
assertParseErrorE StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
includedirectivep Text
"include nosuchfile\n" [Char]
"No existing files match pattern: nosuchfile"
     ,[Char] -> Assertion -> TestTree
testCase [Char]
"glob" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
-> Text -> [Char] -> Assertion
forall st a.
(Default st, Eq a, Show a, HasCallStack) =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  a
-> Text -> [Char] -> Assertion
assertParseErrorE StateT
  Journal
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  ()
forall (m :: * -> *). MonadIO m => ErroringJournalParser m ()
includedirectivep Text
"include nosuchfile*\n" [Char]
"No existing files match pattern: nosuchfile*"
     ]

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"marketpricedirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PriceDirective
-> Text -> PriceDirective -> Assertion
forall a st.
(HasCallStack, Eq a, Show a, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> a -> Assertion
assertParseEq StateT
  Journal (ParsecT HledgerParseErrorData Text IO) PriceDirective
forall (m :: * -> *). JournalParser m PriceDirective
marketpricedirectivep
    Text
"P 2017/01/30 BTC $922.83\n"
    PriceDirective{
      pddate :: Day
pddate      = Year -> Int -> Int -> Day
fromGregorian Year
2017 Int
1 Int
30,
      pdcommodity :: Text
pdcommodity = Text
"BTC",
      pdamount :: Amount
pdamount    = DecimalRaw Year -> Amount
usd DecimalRaw Year
922.83
      }

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"payeedirectivep" [
        [Char] -> Assertion -> TestTree
testCase [Char]
"simple"             (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
payeedirectivep Text
"payee foo\n"
       ,[Char] -> Assertion -> TestTree
testCase [Char]
"with-comment"       (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
payeedirectivep Text
"payee foo ; comment\n"
       ,[Char] -> Assertion -> TestTree
testCase [Char]
"double-quoted"      (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
payeedirectivep Text
"payee \"a b\"\n"
       ,[Char] -> Assertion -> TestTree
testCase [Char]
"empty        "      (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
payeedirectivep Text
"payee \"\"\n"
       ]

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"tagdirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
     StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
tagdirectivep Text
"tag foo \n"

  ,[Char] -> Assertion -> TestTree
testCase [Char]
"endtagdirectivep" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
      StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
endtagdirectivep Text
"end tag \n"
      StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
-> Text -> Assertion
forall st a.
(HasCallStack, Default st) =>
StateT st (ParsecT HledgerParseErrorData Text IO) a
-> Text -> Assertion
assertParse StateT Journal (ParsecT HledgerParseErrorData Text IO) ()
forall (m :: * -> *). JournalParser m ()
endtagdirectivep Text
"end apply tag \n"

  ,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"journalp" [
    [Char] -> Assertion -> TestTree
testCase [Char]
"empty file" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ ErroringJournalParser IO Journal -> Text -> Journal -> Assertion
forall st a.
(Default st, Eq a, Show a, HasCallStack) =>
StateT
  st
  (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO))
  a
-> Text -> a -> Assertion
assertParseEqE ErroringJournalParser IO Journal
forall (m :: * -> *). MonadIO m => ErroringJournalParser m Journal
journalp Text
"" Journal
nulljournal
    ]

   -- these are defined here rather than in Common so they can use journalp
  ,[Char] -> Assertion -> TestTree
testCase [Char]
"parseAndFinaliseJournal" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
      Either [Char] Journal
ej <- ExceptT [Char] IO Journal -> IO (Either [Char] Journal)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT [Char] IO Journal -> IO (Either [Char] Journal))
-> ExceptT [Char] IO Journal -> IO (Either [Char] Journal)
forall a b. (a -> b) -> a -> b
$ ErroringJournalParser IO Journal
-> InputOpts -> [Char] -> Text -> ExceptT [Char] IO Journal
parseAndFinaliseJournal ErroringJournalParser IO Journal
forall (m :: * -> *). MonadIO m => ErroringJournalParser m Journal
journalp InputOpts
definputopts [Char]
"" Text
"2019-1-1\n"
      let Right Journal
j = Either [Char] Journal
ej
      [Char] -> [[Char]] -> [[Char]] -> Assertion
forall a.
(Eq a, Show a, HasCallStack) =>
[Char] -> a -> a -> Assertion
assertEqual [Char]
"" [[Char]
""] ([[Char]] -> Assertion) -> [[Char]] -> Assertion
forall a b. (a -> b) -> a -> b
$ Journal -> [[Char]]
journalFilePaths Journal
j

  ]