2016-04-23 21:27:39 +03:00
--- * doc
2016-04-28 23:23:20 +03:00
-- Lines beginning "--- *" are collapsible orgstruct nodes. Emacs users,
2016-04-23 03:43:16 +03:00
-- (add-hook 'haskell-mode-hook
2016-04-23 21:27:39 +03:00
-- (lambda () (set-variable 'orgstruct-heading-prefix-regexp "--- " t))
2016-04-23 03:43:16 +03:00
-- 'orgstruct-mode)
2016-04-28 23:23:20 +03:00
-- and press TAB on nodes to expand/collapse.
2016-04-23 03:43:16 +03:00
2008-10-01 04:29:58 +04:00
{- |
2008-10-03 06:28:58 +04:00
2012-03-24 22:08:11 +04:00
A reader for hledger's journal file format
( < http :// hledger . org / MANUAL . 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 :
2007-03-12 10:40:33 +03:00
2008-10-01 05:40:32 +04:00
@
2012-03-24 22:08:11 +04:00
2012 \/ 3 \/ 24 gift
expenses : gifts $ 10
assets : cash
2008-10-01 05:40:32 +04:00
@
2008-10-01 04:29:58 +04:00
2007-02-09 04:23:12 +03:00
- }
2007-07-04 16:05:54 +04:00
2016-04-23 21:27:39 +03:00
--- * module
2016-04-23 03:43:16 +03:00
-- {-# OPTIONS_GHC -F -pgmF htfpp #-}
2016-04-23 21:27:39 +03:00
2016-04-28 23:23:20 +03:00
{- # LANGUAGE CPP, RecordWildCards, NoMonoLocalBinds, ScopedTypeVariables, FlexibleContexts, TupleSections # -}
2016-04-23 03:43:16 +03:00
2010-11-15 10:01:46 +03:00
module Hledger.Read.JournalReader (
2016-04-23 21:27:39 +03:00
2016-04-28 23:23:20 +03:00
--- * exports
2012-03-24 22:08:11 +04:00
-- * Reader
reader ,
2016-04-23 03:43:16 +03:00
-- * Parsing utils
2015-06-29 02:20:28 +03:00
genericSourcePos ,
2016-04-23 03:43:16 +03:00
parseAndFinaliseJournal ,
-- * Parsers used elsewhere
2012-03-24 22:08:11 +04:00
getParentAccount ,
2015-10-17 21:51:45 +03:00
journalp ,
directivep ,
defaultyeardirectivep ,
marketpricedirectivep ,
2014-02-06 06:55:38 +04:00
datetimep ,
2016-02-20 02:14:25 +03:00
datep ,
2014-02-06 06:55:38 +04:00
codep ,
accountnamep ,
2015-09-25 03:23:52 +03:00
modifiedaccountnamep ,
2014-02-06 01:02:24 +04:00
postingp ,
2012-11-20 01:20:10 +04:00
amountp ,
amountp' ,
2012-11-20 03:17:55 +04:00
mamountp' ,
2014-02-06 06:55:38 +04:00
numberp ,
2015-05-16 21:51:35 +03:00
statusp ,
2014-02-27 23:47:36 +04:00
emptyorcommentlinep ,
2015-05-14 22:50:32 +03:00
followingcommentp ,
accountaliasp
2012-03-24 22:08:11 +04:00
-- * Tests
2015-06-11 20:13:27 +03:00
, tests_Hledger_Read_JournalReader
# ifdef TESTS
2012-12-06 04:28:23 +04:00
-- disabled by default, HTF not available on windows
, htf_thisModulesTests
, htf_Hledger_Read_JournalReader_importedTests
# endif
2010-05-31 05:15:18 +04:00
)
2010-03-13 02:46:20 +03:00
where
2016-04-23 21:27:39 +03:00
--- * imports
2015-04-23 10:39:29 +03:00
import Prelude ( )
import Prelude.Compat hiding ( readFile )
2012-03-30 01:19:35 +04:00
import qualified Control.Exception as C
2015-04-23 10:39:29 +03:00
import Control.Monad.Compat
2015-04-29 17:08:12 +03:00
import Control.Monad.Except ( ExceptT ( .. ) , liftIO , runExceptT , throwError , catchError )
2011-05-28 08:11:44 +04:00
import Data.Char ( isNumber )
2016-04-28 23:23:20 +03:00
import Data.Functor.Identity
2015-04-23 10:39:29 +03:00
import Data.List.Compat
2010-09-04 03:22:58 +04:00
import Data.List.Split ( wordsBy )
2011-05-28 08:11:44 +04:00
import Data.Maybe
import Data.Time.Calendar
import Data.Time.LocalTime
2016-04-28 23:23:20 +03:00
import Safe
2015-06-11 20:13:27 +03:00
import Test.HUnit
2012-12-06 04:28:23 +04:00
# ifdef TESTS
import Test.Framework
import Text.Parsec.Error
# endif
2014-11-03 08:52:12 +03:00
import Text.Parsec hiding ( parse )
2011-05-28 08:11:44 +04:00
import Text.Printf
2012-03-24 22:08:11 +04:00
import System.FilePath
import System.Time ( getClockTime )
2010-11-15 10:18:35 +03:00
import Hledger.Data
2011-05-28 08:11:44 +04:00
import Hledger.Utils
2010-03-13 02:46:20 +03:00
2016-04-23 21:27:39 +03:00
--- * reader
2010-03-13 02:46:20 +03:00
2010-06-25 18:56:48 +04:00
reader :: Reader
reader = Reader format detect parse
format :: String
format = " journal "
2014-05-10 04:55:32 +04:00
-- | Does the given file path and data look like it might be hledger's journal format ?
2010-06-25 18:56:48 +04:00
detect :: FilePath -> String -> Bool
2014-05-10 04:55:32 +04:00
detect f s
2016-02-20 10:02:10 +03:00
| f /= " - " = takeExtension f ` elem ` [ '.' : format , " .j " ] -- from a known file name: yes if the extension is this format's name or .j
| otherwise = regexMatches " (^| \ n )[0-9]+.* \ n [ \ t ]+ " s -- from stdin: yes if we can see something that looks like a journal entry (digits in column 0 with the next line indented)
2010-06-25 18:56:48 +04:00
2010-05-30 23:11:58 +04:00
-- | Parse and post-process a "Journal" from hledger's journal file
2010-05-31 05:15:18 +04:00
-- format, or give an error.
2015-03-29 17:53:23 +03:00
parse :: Maybe FilePath -> Bool -> FilePath -> String -> ExceptT String IO Journal
2015-10-17 22:09:03 +03:00
parse _ = parseAndFinaliseJournal journalp
2010-03-13 02:46:20 +03:00
2016-04-23 21:27:39 +03:00
--- * parsing utils
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
-- | A parser of strings with generic user state, monad and return type.
type StringParser u m a = ParsecT String u m a
-- | A string parser with journal-parsing state.
type JournalParser m a = StringParser JournalContext m a
-- | A journal parser that runs in IO and can throw an error mid-parse.
type ErroringJournalParser a = JournalParser ( ExceptT String IO ) a
-- | Run a string parser with no state in the identity monad.
runStringParser , rsp :: StringParser () Identity a -> String -> Either ParseError a
runStringParser p s = runIdentity $ runParserT p () " " s
rsp = runStringParser
-- | Run a journal parser with a null journal-parsing state.
runJournalParser , rjp :: Monad m => JournalParser m a -> String -> m ( Either ParseError a )
runJournalParser p s = runParserT p nullctx " " s
rjp = runJournalParser
-- | Run an error-raising journal parser with a null journal-parsing state.
runErroringJournalParser , rejp :: ErroringJournalParser a -> String -> IO ( Either String a )
runErroringJournalParser p s = runExceptT $ runJournalParser p s >>= either ( throwError . show ) return
rejp = runErroringJournalParser
2015-06-29 02:20:28 +03:00
genericSourcePos :: SourcePos -> GenericSourcePos
genericSourcePos p = GenericSourcePos ( sourceName p ) ( sourceLine p ) ( sourceColumn p )
2015-10-13 21:49:51 +03:00
-- | Flatten a list of JournalUpdate's (journal-transforming
-- monadic actions which can do IO or raise an exception) into a
-- single equivalent action.
2012-03-24 22:08:11 +04:00
combineJournalUpdates :: [ JournalUpdate ] -> JournalUpdate
2015-10-13 21:54:15 +03:00
combineJournalUpdates us = foldl' ( flip ( . ) ) id <$> sequence us
2015-09-27 05:01:27 +03:00
-- XXX may be contributing to excessive stack use
2015-10-13 21:49:51 +03:00
2015-09-27 05:01:27 +03:00
-- cf http://neilmitchell.blogspot.co.uk/2015/09/detecting-space-leaks.html
-- $ ./devprof +RTS -K576K -xc
2016-04-23 03:43:16 +03:00
-- Exception (reporting due to +RTS -xc): (THUNK_STATIC), stack trace:
2015-09-27 05:01:27 +03:00
-- Hledger.Read.JournalReader.combineJournalUpdates.\,
-- called from Hledger.Read.JournalReader.combineJournalUpdates,
-- called from Hledger.Read.JournalReader.fixedlotprice,
-- called from Hledger.Read.JournalReader.partialbalanceassertion,
-- called from Hledger.Read.JournalReader.getDefaultCommodityAndStyle,
-- called from Hledger.Read.JournalReader.priceamount,
-- called from Hledger.Read.JournalReader.nosymbolamount,
-- called from Hledger.Read.JournalReader.numberp,
-- called from Hledger.Read.JournalReader.rightsymbolamount,
-- called from Hledger.Read.JournalReader.simplecommoditysymbol,
-- called from Hledger.Read.JournalReader.quotedcommoditysymbol,
-- called from Hledger.Read.JournalReader.commoditysymbol,
-- called from Hledger.Read.JournalReader.signp,
-- called from Hledger.Read.JournalReader.leftsymbolamount,
-- called from Hledger.Read.JournalReader.amountp,
-- called from Hledger.Read.JournalReader.spaceandamountormissing,
-- called from Hledger.Read.JournalReader.accountnamep.singlespace,
-- called from Hledger.Utils.Parse.nonspace,
-- called from Hledger.Read.JournalReader.accountnamep,
-- called from Hledger.Read.JournalReader.getAccountAliases,
-- called from Hledger.Read.JournalReader.getParentAccount,
-- called from Hledger.Read.JournalReader.modifiedaccountnamep,
-- called from Hledger.Read.JournalReader.postingp,
-- called from Hledger.Read.JournalReader.postings,
-- called from Hledger.Read.JournalReader.commentStartingWith,
-- called from Hledger.Read.JournalReader.semicoloncomment,
-- called from Hledger.Read.JournalReader.followingcommentp,
-- called from Hledger.Read.JournalReader.descriptionp,
-- called from Hledger.Read.JournalReader.codep,
-- called from Hledger.Read.JournalReader.statusp,
-- called from Hledger.Utils.Parse.spacenonewline,
-- called from Hledger.Read.JournalReader.secondarydatep,
-- called from Hledger.Data.Dates.datesepchar,
-- called from Hledger.Read.JournalReader.datep,
-- called from Hledger.Read.JournalReader.transaction,
-- called from Hledger.Utils.Parse.choice',
-- called from Hledger.Read.JournalReader.directive,
-- called from Hledger.Read.JournalReader.emptyorcommentlinep,
-- called from Hledger.Read.JournalReader.multilinecommentp,
-- called from Hledger.Read.JournalReader.journal.journalItem,
-- called from Hledger.Read.JournalReader.journal,
-- called from Hledger.Read.JournalReader.parseJournalWith,
-- called from Hledger.Read.readJournal.tryReaders.firstSuccessOrBestError,
-- called from Hledger.Read.readJournal.tryReaders,
-- called from Hledger.Read.readJournal,
-- called from Main.main,
-- called from Main.CAF
-- Stack space overflow: current size 33568 bytes.
2012-03-24 22:08:11 +04:00
-- | Given a JournalUpdate-generating parsec parser, file path and data string,
-- parse and post-process a Journal so that it's ready to use, or give an error.
2015-10-17 22:09:03 +03:00
parseAndFinaliseJournal ::
2016-04-28 23:23:20 +03:00
( ErroringJournalParser ( JournalUpdate , JournalContext ) )
2015-10-17 22:09:03 +03:00
-> Bool -> FilePath -> String -> ExceptT String IO Journal
parseAndFinaliseJournal parser assrt f s = do
2012-03-24 22:08:11 +04:00
tc <- liftIO getClockTime
tl <- liftIO getCurrentLocalTime
y <- liftIO getCurrentYear
2015-10-17 22:09:03 +03:00
r <- runParserT parser nullctx { ctxYear = Just y } f s
2014-11-03 08:52:12 +03:00
case r of
2012-03-24 22:08:11 +04:00
Right ( updates , ctx ) -> do
2015-10-17 22:09:03 +03:00
j <- ap updates ( return nulljournal )
2014-07-02 05:26:37 +04:00
case journalFinalise tc tl f s ctx assrt j of
2012-03-24 22:08:11 +04:00
Right j' -> return j'
Left estr -> throwError estr
Left e -> throwError $ show e
2016-04-28 23:23:20 +03:00
setYear :: Monad m => Integer -> JournalParser m ()
2014-11-03 08:52:12 +03:00
setYear y = modifyState ( \ ctx -> ctx { ctxYear = Just y } )
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
getYear :: Monad m => JournalParser m ( Maybe Integer )
2012-03-24 22:08:11 +04:00
getYear = liftM ctxYear getState
2016-04-28 23:23:20 +03:00
setDefaultCommodityAndStyle :: Monad m => ( Commodity , AmountStyle ) -> JournalParser m ()
2014-11-03 08:52:12 +03:00
setDefaultCommodityAndStyle cs = modifyState ( \ ctx -> ctx { ctxDefaultCommodityAndStyle = Just cs } )
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
getDefaultCommodityAndStyle :: Monad m => JournalParser m ( Maybe ( Commodity , AmountStyle ) )
2014-07-02 22:23:30 +04:00
getDefaultCommodityAndStyle = ctxDefaultCommodityAndStyle ` fmap ` getState
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
pushAccount :: Monad m => String -> JournalParser m ()
2016-04-04 20:18:59 +03:00
pushAccount acct = modifyState addAccount
where addAccount ctx0 = ctx0 { ctxAccounts = acct : ctxAccounts ctx0 }
2016-04-28 23:23:20 +03:00
pushParentAccount :: Monad m => String -> JournalParser m ()
2014-11-03 08:52:12 +03:00
pushParentAccount parent = modifyState addParentAccount
2016-04-04 20:18:59 +03:00
where addParentAccount ctx0 = ctx0 { ctxParentAccount = parent : ctxParentAccount ctx0 }
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
popParentAccount :: Monad m => JournalParser m ()
2012-03-24 22:08:11 +04:00
popParentAccount = do ctx0 <- getState
2016-04-04 20:18:59 +03:00
case ctxParentAccount ctx0 of
[] -> unexpected " End of apply account block with no beginning "
( _ : rest ) -> setState $ ctx0 { ctxParentAccount = rest }
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
getParentAccount :: Monad m => JournalParser m String
2016-04-04 20:18:59 +03:00
getParentAccount = liftM ( concatAccountNames . reverse . ctxParentAccount ) getState
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
addAccountAlias :: Monad m => AccountAlias -> JournalParser m ()
2014-11-03 08:52:12 +03:00
addAccountAlias a = modifyState ( \ ( ctx @ Ctx { .. } ) -> ctx { ctxAliases = a : ctxAliases } )
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
getAccountAliases :: Monad m => JournalParser m [ AccountAlias ]
2012-03-24 22:08:11 +04:00
getAccountAliases = liftM ctxAliases getState
2016-04-28 23:23:20 +03:00
clearAccountAliases :: Monad m => JournalParser m ()
2014-11-03 08:52:12 +03:00
clearAccountAliases = modifyState ( \ ( ctx @ Ctx { .. } ) -> ctx { ctxAliases = [] } )
2012-03-24 22:08:11 +04:00
2016-04-28 23:23:20 +03:00
getIndex :: Monad m => JournalParser m Integer
2015-10-30 06:12:46 +03:00
getIndex = liftM ctxTransactionIndex getState
2016-04-28 23:23:20 +03:00
setIndex :: Monad m => Integer -> JournalParser m ()
2015-10-30 06:12:46 +03:00
setIndex i = modifyState ( \ ctx -> ctx { ctxTransactionIndex = i } )
2016-04-23 21:27:39 +03:00
--- * parsers
--- ** journal
2012-03-24 22:08:11 +04:00
2010-03-13 04:16:59 +03:00
-- | Top-level journal parser. Returns a single composite, I/O performing,
2010-11-15 10:18:35 +03:00
-- error-raising "JournalUpdate" (and final "JournalContext") which can be
-- applied to an empty journal to get the final result.
2016-04-28 23:23:20 +03:00
journalp :: ErroringJournalParser ( JournalUpdate , JournalContext )
2015-10-17 21:51:45 +03:00
journalp = do
2010-11-13 18:03:40 +03:00
journalupdates <- many journalItem
eof
finalctx <- getState
2012-03-24 22:08:11 +04:00
return $ ( combineJournalUpdates journalupdates , finalctx )
2014-09-11 00:07:53 +04:00
where
2010-07-13 10:30:06 +04:00
-- As all journal line types can be distinguished by the first
2010-03-13 02:46:20 +03:00
-- character, excepting transactions versus empty (blank or
-- comment-only) lines, can use choice w/o try
2015-10-17 21:51:45 +03:00
journalItem = choice [ directivep
, liftM ( return . addTransaction ) transactionp
, liftM ( return . addModifierTransaction ) modifiertransactionp
, liftM ( return . addPeriodicTransaction ) periodictransactionp
, liftM ( return . addMarketPrice ) marketpricedirectivep
2014-02-27 23:47:36 +04:00
, emptyorcommentlinep >> return ( return id )
2014-10-26 21:19:42 +03:00
, multilinecommentp >> return ( return id )
2011-08-04 11:49:10 +04:00
] <?> " journal transaction or directive "
2010-09-23 03:02:19 +04:00
2016-04-23 21:27:39 +03:00
--- ** directives
2016-04-23 03:43:16 +03:00
2012-05-09 19:34:05 +04:00
-- cf http://ledger-cli.org/3.0/doc/ledger3.html#Command-Directives
2016-04-28 23:23:20 +03:00
directivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
directivep = do
2011-08-03 03:28:53 +04:00
optional $ char '!'
choice' [
2015-10-17 21:51:45 +03:00
includedirectivep
, aliasdirectivep
, endaliasesdirectivep
, accountdirectivep
2016-04-04 20:18:59 +03:00
, applyaccountdirectivep
, endapplyaccountdirectivep
2015-10-17 21:51:45 +03:00
, tagdirectivep
, endtagdirectivep
, defaultyeardirectivep
, defaultcommoditydirectivep
, commodityconversiondirectivep
, ignoredpricecommoditydirectivep
2011-08-03 03:28:53 +04:00
]
<?> " directive "
2010-03-13 02:46:20 +03:00
2016-04-28 23:23:20 +03:00
includedirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
includedirectivep = do
2011-08-04 11:49:10 +04:00
string " include "
2010-09-23 01:52:04 +04:00
many1 spacenonewline
filename <- restofline
outerState <- getState
outerPos <- getPosition
2012-05-30 12:36:01 +04:00
let curdir = takeDirectory ( sourceName outerPos )
2015-03-29 17:53:23 +03:00
let ( u :: ExceptT String IO ( Journal -> Journal , JournalContext ) ) = do
2014-11-03 08:52:12 +03:00
filepath <- expandPath curdir filename
txt <- readFileOrError outerPos filepath
let inIncluded = show outerPos ++ " in included file " ++ show filename ++ " : \ n "
2015-10-17 21:51:45 +03:00
r <- runParserT journalp outerState filepath txt
2016-02-20 10:02:10 +03:00
2014-11-03 08:52:12 +03:00
case r of
Right ( ju , ctx ) -> do
u <- combineJournalUpdates [ return $ journalAddFile ( filepath , txt )
, ju
] ` catchError ` ( throwError . ( inIncluded ++ ) )
return ( u , ctx )
Left err -> throwError $ inIncluded ++ show err
where readFileOrError pos fp =
2015-03-29 17:53:23 +03:00
ExceptT $ liftM Right ( readFile' fp ) ` C . catch `
2012-03-30 01:19:35 +04:00
\ e -> return $ Left $ printf " %s reading %s: \ n %s " ( show pos ) fp ( show ( e :: C . IOException ) )
2015-03-29 17:53:23 +03:00
r <- liftIO $ runExceptT u
2014-11-03 08:52:12 +03:00
case r of
Left err -> return $ throwError err
2015-03-29 17:53:23 +03:00
Right ( ju , _finalparsectx ) -> return $ ExceptT $ return $ Right ju
2010-03-13 02:46:20 +03:00
2011-08-04 11:49:10 +04:00
journalAddFile :: ( FilePath , String ) -> Journal -> Journal
journalAddFile f j @ Journal { files = fs } = j { files = fs ++ [ f ] }
2014-11-03 09:00:02 +03:00
-- NOTE: first encountered file to left, to avoid a reverse
2011-08-04 11:49:10 +04:00
2016-04-28 23:23:20 +03:00
accountdirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
accountdirectivep = do
2016-04-04 20:18:59 +03:00
string " account "
many1 spacenonewline
acct <- accountnamep
newline
let indentedline = many1 spacenonewline >> restofline
many indentedline
pushAccount acct
return $ ExceptT $ return $ Right id
2016-04-28 23:23:20 +03:00
applyaccountdirectivep :: ErroringJournalParser JournalUpdate
2016-04-04 20:18:59 +03:00
applyaccountdirectivep = do
string " apply " >> many1 spacenonewline >> string " account "
2011-08-04 11:49:10 +04:00
many1 spacenonewline
2014-02-06 06:55:38 +04:00
parent <- accountnamep
2011-08-04 11:49:10 +04:00
newline
pushParentAccount parent
2015-03-29 17:53:23 +03:00
return $ ExceptT $ return $ Right id
2010-03-13 02:46:20 +03:00
2016-04-28 23:23:20 +03:00
endapplyaccountdirectivep :: ErroringJournalParser JournalUpdate
2016-04-04 20:18:59 +03:00
endapplyaccountdirectivep = do
string " end " >> many1 spacenonewline >> string " apply " >> many1 spacenonewline >> string " account "
2011-08-04 11:49:10 +04:00
popParentAccount
2015-03-29 17:53:23 +03:00
return $ ExceptT $ return $ Right id
2010-03-13 02:46:20 +03:00
2016-04-28 23:23:20 +03:00
aliasdirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
aliasdirectivep = do
2011-08-04 12:45:18 +04:00
string " alias "
many1 spacenonewline
2015-05-14 22:50:32 +03:00
alias <- accountaliasp
addAccountAlias alias
2011-08-04 12:45:18 +04:00
return $ return id
2016-04-28 23:23:20 +03:00
accountaliasp :: Monad m => StringParser u m AccountAlias
2015-05-14 22:50:32 +03:00
accountaliasp = regexaliasp <|> basicaliasp
2016-04-28 23:23:20 +03:00
basicaliasp :: Monad m => StringParser u m AccountAlias
2015-05-14 22:50:32 +03:00
basicaliasp = do
-- pdbg 0 "basicaliasp"
old <- rstrip <$> ( many1 $ noneOf " = " )
char '='
many spacenonewline
new <- rstrip <$> anyChar ` manyTill ` eolof -- don't require a final newline, good for cli options
return $ BasicAlias old new
2016-04-28 23:23:20 +03:00
regexaliasp :: Monad m => StringParser u m AccountAlias
2015-05-14 22:50:32 +03:00
regexaliasp = do
-- pdbg 0 "regexaliasp"
char '/'
re <- many1 $ noneOf " / \ n \ r " -- paranoid: don't try to read past line end
char '/'
many spacenonewline
char '='
many spacenonewline
repl <- rstrip <$> anyChar ` manyTill ` eolof
return $ RegexAlias re repl
2016-04-28 23:23:20 +03:00
endaliasesdirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
endaliasesdirectivep = do
2011-08-04 12:45:18 +04:00
string " end aliases "
clearAccountAliases
return ( return id )
2016-04-28 23:23:20 +03:00
tagdirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
tagdirectivep = do
2011-08-04 11:49:10 +04:00
string " tag " <?> " tag directive "
many1 spacenonewline
_ <- many1 nonspace
restofline
return $ return id
2007-02-09 04:23:12 +03:00
2016-04-28 23:23:20 +03:00
endtagdirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
endtagdirectivep = do
2011-08-04 11:49:10 +04:00
( string " end tag " <|> string " pop " ) <?> " end tag or pop directive "
restofline
return $ return id
2016-04-28 23:23:20 +03:00
defaultyeardirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
defaultyeardirectivep = do
2011-08-04 11:49:10 +04:00
char 'Y' <?> " default year "
2007-02-09 04:23:12 +03:00
many spacenonewline
2011-08-04 11:49:10 +04:00
y <- many1 digit
let y' = read y
failIfInvalidYear y
setYear y'
return $ return id
2016-04-28 23:23:20 +03:00
defaultcommoditydirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
defaultcommoditydirectivep = do
2011-08-04 11:49:10 +04:00
char 'D' <?> " default commodity "
many1 spacenonewline
2012-11-20 03:17:55 +04:00
Amount { .. } <- amountp
2014-07-02 22:23:30 +04:00
setDefaultCommodityAndStyle ( acommodity , astyle )
2011-08-04 11:49:10 +04:00
restofline
return $ return id
2007-02-09 04:23:12 +03:00
2016-04-28 23:23:20 +03:00
marketpricedirectivep :: ErroringJournalParser MarketPrice
2015-10-17 21:51:45 +03:00
marketpricedirectivep = do
2015-08-10 02:20:02 +03:00
char 'P' <?> " market price "
2008-12-16 13:54:20 +03:00
many spacenonewline
2014-08-08 18:27:32 +04:00
date <- try ( do { LocalTime d _ <- datetimep ; return d } ) <|> datep -- a time is ignored
2009-11-26 00:21:49 +03:00
many1 spacenonewline
2015-10-17 21:51:45 +03:00
symbol <- commoditysymbolp
2008-12-16 13:54:20 +03:00
many spacenonewline
2012-11-20 01:20:10 +04:00
price <- amountp
2008-12-16 13:54:20 +03:00
restofline
2015-08-10 02:20:02 +03:00
return $ MarketPrice date symbol price
2008-12-16 13:54:20 +03:00
2016-04-28 23:23:20 +03:00
ignoredpricecommoditydirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
ignoredpricecommoditydirectivep = do
2010-03-13 01:52:57 +03:00
char 'N' <?> " ignored-price commodity "
many1 spacenonewline
2015-10-17 21:51:45 +03:00
commoditysymbolp
2010-03-13 01:52:57 +03:00
restofline
return $ return id
2016-04-28 23:23:20 +03:00
commodityconversiondirectivep :: ErroringJournalParser JournalUpdate
2015-10-17 21:51:45 +03:00
commodityconversiondirectivep = do
2010-03-13 04:10:10 +03:00
char 'C' <?> " commodity conversion "
many1 spacenonewline
2012-11-20 01:20:10 +04:00
amountp
2010-03-13 04:10:10 +03:00
many spacenonewline
char '='
many spacenonewline
2012-11-20 01:20:10 +04:00
amountp
2010-03-13 04:10:10 +03:00
restofline
return $ return id
2016-04-23 21:27:39 +03:00
--- ** transactions
2016-04-23 03:43:16 +03:00
2016-04-28 23:23:20 +03:00
modifiertransactionp :: ErroringJournalParser ModifierTransaction
2015-10-17 21:51:45 +03:00
modifiertransactionp = do
2011-08-04 11:49:10 +04:00
char '=' <?> " modifier transaction "
2009-01-23 02:42:34 +03:00
many spacenonewline
2011-08-04 11:49:10 +04:00
valueexpr <- restofline
2016-04-28 23:23:20 +03:00
postings <- postingsp Nothing
2011-08-04 11:49:10 +04:00
return $ ModifierTransaction valueexpr postings
2009-01-23 02:42:34 +03:00
2016-04-28 23:23:20 +03:00
periodictransactionp :: ErroringJournalParser PeriodicTransaction
2015-10-17 21:51:45 +03:00
periodictransactionp = do
2011-08-04 11:49:10 +04:00
char '~' <?> " periodic transaction "
many spacenonewline
periodexpr <- restofline
2016-04-28 23:23:20 +03:00
postings <- postingsp Nothing
2011-08-04 11:49:10 +04:00
return $ PeriodicTransaction periodexpr postings
2010-11-13 02:54:21 +03:00
2012-05-15 05:49:05 +04:00
-- | Parse a (possibly unbalanced) transaction.
2016-04-28 23:23:20 +03:00
transactionp :: ErroringJournalParser Transaction
2015-10-17 21:51:45 +03:00
transactionp = do
-- ptrace "transactionp"
2015-06-29 02:20:28 +03:00
sourcepos <- genericSourcePos <$> getPosition
2014-08-08 18:27:32 +04:00
date <- datep <?> " transaction "
edate <- optionMaybe ( secondarydatep date ) <?> " secondary date "
2014-09-06 20:20:22 +04:00
lookAhead ( spacenonewline <|> newline ) <?> " whitespace or newline "
2015-05-16 21:51:35 +03:00
status <- statusp <?> " cleared status "
2014-02-06 06:55:38 +04:00
code <- codep <?> " transaction code "
2012-12-06 04:28:23 +04:00
description <- descriptionp >>= return . strip
2014-02-27 23:47:36 +04:00
comment <- try followingcommentp <|> ( newline >> return " " )
2016-04-28 23:23:20 +03:00
let tags = commentTags comment
postings <- postingsp ( Just date )
2015-10-30 20:41:42 +03:00
i' <- ( + 1 ) <$> getIndex
setIndex i'
return $ txnTieKnot $ Transaction i' sourcepos date edate status code description comment tags postings " "
2007-02-09 04:23:12 +03:00
2012-12-06 04:28:23 +04:00
# ifdef TESTS
2015-10-17 21:51:45 +03:00
test_transactionp = do
2012-05-15 05:49:05 +04:00
let s ` gives ` t = do
2015-10-17 21:51:45 +03:00
let p = parseWithCtx nullctx transactionp s
2012-12-06 04:28:23 +04:00
assertBool $ isRight p
2012-05-15 05:49:05 +04:00
let Right t2 = p
2012-12-06 04:28:23 +04:00
-- same f = assertEqual (f t) (f t2)
assertEqual ( tdate t ) ( tdate t2 )
2012-12-06 08:43:41 +04:00
assertEqual ( tdate2 t ) ( tdate2 t2 )
2012-12-06 04:28:23 +04:00
assertEqual ( tstatus t ) ( tstatus t2 )
assertEqual ( tcode t ) ( tcode t2 )
assertEqual ( tdescription t ) ( tdescription t2 )
assertEqual ( tcomment t ) ( tcomment t2 )
assertEqual ( ttags t ) ( ttags t2 )
assertEqual ( tpreceding_comment_lines t ) ( tpreceding_comment_lines t2 )
assertEqual ( show $ tpostings t ) ( show $ tpostings t2 )
2014-09-11 00:07:53 +04:00
-- "0000/01/01\n\n" `gives` nulltransaction
2012-05-15 05:49:05 +04:00
unlines [
" 2012/05/14=2012/05/15 (code) desc ; tcomment1 " ,
" ; tcomment2 " ,
" ; ttag1: val1 " ,
" * a $1.00 ; pcomment1 " ,
" ; pcomment2 " ,
" ; ptag1: val1 " ,
" ; ptag2: val2 "
]
` gives `
nulltransaction {
tdate = parsedate " 2012/05/14 " ,
2012-12-06 08:43:41 +04:00
tdate2 = Just $ parsedate " 2012/05/15 " ,
2015-05-16 21:51:35 +03:00
tstatus = Uncleared ,
2012-05-15 05:49:05 +04:00
tcode = " code " ,
tdescription = " desc " ,
2012-12-06 04:28:23 +04:00
tcomment = " tcomment1 \ n tcomment2 \ n ttag1: val1 \ n " ,
2012-05-28 02:59:06 +04:00
ttags = [ ( " ttag1 " , " val1 " ) ] ,
2012-05-15 05:49:05 +04:00
tpostings = [
nullposting {
2015-05-16 21:51:35 +03:00
pstatus = Cleared ,
2012-05-15 05:49:05 +04:00
paccount = " a " ,
2012-11-20 01:20:10 +04:00
pamount = Mixed [ usd 1 ] ,
2012-12-06 04:28:23 +04:00
pcomment = " pcomment1 \ n pcomment2 \ n ptag1: val1 \ n ptag2: val2 \ n " ,
2012-05-15 05:49:05 +04:00
ptype = RegularPosting ,
2012-05-28 02:59:06 +04:00
ptags = [ ( " ptag1 " , " val1 " ) , ( " ptag2 " , " val2 " ) ] ,
2012-05-15 05:49:05 +04:00
ptransaction = Nothing
}
] ,
tpreceding_comment_lines = " "
}
2015-06-11 20:13:27 +03:00
unlines [
" 2015/1/1 " ,
]
` gives `
nulltransaction {
tdate = parsedate " 2015/01/01 " ,
}
2012-05-15 05:49:05 +04:00
2015-10-17 21:51:45 +03:00
assertRight $ parseWithCtx nullctx transactionp $ unlines
2012-12-06 04:28:23 +04:00
[ " 2007/01/28 coopportunity "
, " expenses:food:groceries $47.18 "
, " assets:checking $-47.18 "
, " "
]
2015-10-17 21:51:45 +03:00
-- transactionp should not parse just a date
assertLeft $ parseWithCtx nullctx transactionp " 2009/1/1 \ n "
2012-12-06 04:28:23 +04:00
2015-10-17 21:51:45 +03:00
-- transactionp should not parse just a date and description
assertLeft $ parseWithCtx nullctx transactionp " 2009/1/1 a \ n "
2012-12-06 04:28:23 +04:00
2015-10-17 21:51:45 +03:00
-- transactionp should not parse a following comment as part of the description
let p = parseWithCtx nullctx transactionp " 2009/1/1 a ;comment \ n b 1 \ n "
2012-12-06 04:28:23 +04:00
assertRight p
assertEqual " a " ( let Right p' = p in tdescription p' )
-- parse transaction with following whitespace line
2015-10-17 21:51:45 +03:00
assertRight $ parseWithCtx nullctx transactionp $ unlines
2012-12-06 04:28:23 +04:00
[ " 2012/1/1 "
2012-05-27 22:14:20 +04:00
, " a 1 "
, " b "
, " "
]
2014-09-11 00:07:53 +04:00
2015-10-17 21:51:45 +03:00
let p = parseWithCtx nullctx transactionp $ unlines
2012-12-06 04:28:23 +04:00
[ " 2009/1/1 x ; transaction comment "
, " a 1 ; posting 1 comment "
, " ; posting 1 comment 2 "
, " b "
, " ; posting 2 comment "
]
assertRight p
assertEqual 2 ( let Right t = p in length $ tpostings t )
2014-09-11 00:07:53 +04:00
# endif
2012-05-15 05:49:05 +04:00
2016-04-28 23:23:20 +03:00
statusp :: Monad m => JournalParser m ClearedStatus
2016-04-23 03:43:16 +03:00
statusp =
choice'
[ many spacenonewline >> char '*' >> return Cleared
, many spacenonewline >> char '!' >> return Pending
, return Uncleared
]
<?> " cleared status "
2016-04-28 23:23:20 +03:00
codep :: Monad m => JournalParser m String
2016-04-23 03:43:16 +03:00
codep = try ( do { many1 spacenonewline ; char '(' <?> " codep " ; code <- anyChar ` manyTill ` char ')' ; return code } ) <|> return " "
descriptionp = many ( noneOf " ; \ n " )
2016-04-23 21:27:39 +03:00
--- ** dates
2016-04-23 03:43:16 +03:00
2015-04-28 23:50:58 +03:00
-- | 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.
2016-04-28 23:23:20 +03:00
datep :: Monad m => JournalParser m Day
2014-08-08 18:27:32 +04:00
datep = do
2010-09-04 03:22:58 +04:00
-- hacky: try to ensure precise errors for invalid dates
-- XXX reported error position is not too good
2015-06-29 02:20:28 +03:00
-- pos <- genericSourcePos <$> getPosition
2015-10-04 21:41:01 +03:00
datestr <- do
c <- digit
cs <- many $ choice' [ digit , datesepchar ]
return $ c : cs
2014-08-08 18:27:59 +04:00
let sepchars = nub $ sort $ filter ( ` elem ` datesepchars ) datestr
when ( length sepchars /= 1 ) $ fail $ " bad date, different separators used: " ++ datestr
2010-09-04 03:22:58 +04:00
let dateparts = wordsBy ( ` elem ` datesepchars ) datestr
2011-04-22 17:55:42 +04:00
currentyear <- getYear
2011-05-31 23:49:37 +04:00
[ y , m , d ] <- case ( dateparts , currentyear ) of
( [ m , d ] , Just y ) -> return [ show y , m , d ]
( [ _ , _ ] , Nothing ) -> fail $ " partial date " ++ datestr ++ " found, but the current year is unknown "
( [ y , m , d ] , _ ) -> return [ y , m , d ]
_ -> fail $ " bad date: " ++ datestr
let maybedate = fromGregorianValid ( read y ) ( read m ) ( read d )
2011-04-22 17:55:42 +04:00
case maybedate of
Nothing -> fail $ " bad date: " ++ datestr
Just date -> return date
2010-09-04 03:22:58 +04:00
<?> " full or partial date "
2008-11-11 15:34:05 +03:00
2015-04-28 23:50:58 +03:00
-- | Parse a date and time in YYYY/MM/DD HH:MM[:SS][+-ZZZZ] format.
-- Hyphen (-) and period (.) are also allowed as date separators.
-- The year may be omitted if a default year has been set.
-- Seconds are optional.
-- The timezone is optional and ignored (the time is always interpreted as a local time).
-- Leading zeroes may be omitted (except in a timezone).
2016-04-28 23:23:20 +03:00
datetimep :: Monad m => JournalParser m LocalTime
2014-02-06 06:55:38 +04:00
datetimep = do
2014-08-08 18:27:32 +04:00
day <- datep
2009-12-08 02:29:19 +03:00
many1 spacenonewline
2008-11-11 15:34:05 +03:00
h <- many1 digit
2011-06-01 02:45:54 +04:00
let h' = read h
guard $ h' >= 0 && h' <= 23
2008-11-11 15:34:05 +03:00
char ':'
m <- many1 digit
2011-06-01 02:45:54 +04:00
let m' = read m
guard $ m' >= 0 && m' <= 59
2011-06-01 05:50:04 +04:00
s <- optionMaybe $ char ':' >> many1 digit
2011-06-01 02:45:54 +04:00
let s' = case s of Just sstr -> read sstr
2011-06-01 05:50:04 +04:00
Nothing -> 0
2011-06-01 02:45:54 +04:00
guard $ s' >= 0 && s' <= 59
2011-06-01 05:50:04 +04:00
{- tz < - -}
optionMaybe $ do
plusminus <- oneOf " -+ "
d1 <- digit
d2 <- digit
d3 <- digit
d4 <- digit
return $ plusminus : d1 : d2 : d3 : d4 : " "
-- ltz <- liftIO $ getCurrentTimeZone
-- let tz' = maybe ltz (fromMaybe ltz . parseTime defaultTimeLocale "%z") tz
-- return $ localTimeToUTC tz' $ LocalTime day $ TimeOfDay h' m' (fromIntegral s')
return $ LocalTime day $ TimeOfDay h' m' ( fromIntegral s' )
2007-02-09 04:23:12 +03:00
2016-04-28 23:23:20 +03:00
secondarydatep :: Monad m => Day -> JournalParser m Day
2014-08-08 18:27:32 +04:00
secondarydatep primarydate = do
2009-12-12 06:03:41 +03:00
char '='
2012-12-06 08:43:41 +04:00
-- kludgy way to use primary date for default year
2010-02-04 00:19:01 +03:00
let withDefaultYear d p = do
y <- getYear
let ( y' , _ , _ ) = toGregorian d in setYear y'
r <- p
when ( isJust y ) $ setYear $ fromJust y
return r
2014-08-08 18:27:32 +04:00
edate <- withDefaultYear primarydate datep
2010-04-16 00:44:04 +04:00
return edate
2009-11-26 00:21:49 +03:00
2016-04-28 23:23:20 +03:00
-- |
-- >> parsewith twoorthreepartdatestringp "2016/01/2"
-- Right "2016/01/2"
-- twoorthreepartdatestringp = do
-- n1 <- many1 digit
-- c <- datesepchar
-- n2 <- many1 digit
-- mn3 <- optionMaybe $ char c >> many1 digit
-- return $ n1 ++ c:n2 ++ maybe "" (c:) mn3
2016-04-23 21:27:39 +03:00
--- ** postings
2007-02-09 04:23:12 +03:00
2016-04-28 23:23:20 +03:00
-- Parse the following whitespace-beginning lines as postings, posting
-- tags, and/or comments (inferring year, if needed, from the given date).
postingsp :: Maybe Day -> ErroringJournalParser [ Posting ]
postingsp mdate = many ( try $ postingp mdate ) <?> " postings "
2014-09-11 00:07:53 +04:00
2016-04-28 23:23:20 +03:00
-- linebeginningwithspaces :: Monad m => JournalParser m String
2012-05-14 22:52:22 +04:00
-- linebeginningwithspaces = do
-- sp <- many1 spacenonewline
-- c <- nonspace
-- cs <- restofline
-- return $ sp ++ (c:cs) ++ "\n"
2007-02-09 04:23:12 +03:00
2016-04-28 23:23:20 +03:00
postingp :: Maybe Day -> ErroringJournalParser Posting
postingp mtdate = do
-- pdbg 0 "postingp"
2009-05-25 21:28:41 +04:00
many1 spacenonewline
2015-05-16 21:51:35 +03:00
status <- statusp
2010-11-13 23:20:04 +03:00
many spacenonewline
2015-09-25 03:23:52 +03:00
account <- modifiedaccountnamep
2011-08-03 03:29:13 +04:00
let ( ptype , account' ) = ( accountNamePostingType account , unbracket account )
2015-10-17 21:51:45 +03:00
amount <- spaceandamountormissingp
massertion <- partialbalanceassertionp
_ <- fixedlotpricep
2008-10-16 10:00:46 +04:00
many spacenonewline
2016-04-28 23:23:20 +03:00
( comment , tags , mdate , mdate2 ) <-
try ( followingcommentandtagsp mtdate ) <|> ( newline >> return ( " " , [] , Nothing , Nothing ) )
2014-11-03 08:52:12 +03:00
return posting
2016-04-28 23:23:20 +03:00
{ pdate = mdate
, pdate2 = mdate2
2014-11-03 08:52:12 +03:00
, pstatus = status
, paccount = account'
, pamount = amount
, pcomment = comment
, ptype = ptype
, ptags = tags
, pbalanceassertion = massertion
}
2012-12-06 04:28:23 +04:00
# ifdef TESTS
test_postingp = do
let s ` gives ` ep = do
2016-04-28 23:23:20 +03:00
let parse = parseWithCtx nullctx ( postingp Nothing ) s
2014-09-11 00:07:53 +04:00
assertBool -- "postingp parser"
2012-12-06 04:28:23 +04:00
$ isRight parse
let Right ap = parse
same f = assertEqual ( f ep ) ( f ap )
same pdate
2012-05-15 05:49:05 +04:00
same pstatus
same paccount
same pamount
same pcomment
same ptype
2012-05-28 02:59:06 +04:00
same ptags
2012-05-15 05:49:05 +04:00
same ptransaction
2012-12-06 04:28:23 +04:00
" expenses:food:dining $10.00 ; a: a a \ n ; b: b b \ n " ` gives `
posting { paccount = " expenses:food:dining " , pamount = Mixed [ usd 10 ] , pcomment = " a: a a \ n b: b b \ n " , ptags = [ ( " a " , " a a " ) , ( " b " , " b b " ) ] }
2014-09-11 00:07:53 +04:00
" a 1 ; [2012/11/28] \ n " ` gives `
2012-12-06 04:28:23 +04:00
( " a " ` post ` num 1 ) { pcomment = " [2012/11/28] \ n "
, ptags = [ ( " date " , " 2012/11/28 " ) ]
, pdate = parsedateM " 2012/11/28 " }
2014-09-11 00:07:53 +04:00
" a 1 ; a:a, [=2012/11/28] \ n " ` gives `
2012-12-06 04:28:23 +04:00
( " a " ` post ` num 1 ) { pcomment = " a:a, [=2012/11/28] \ n "
, ptags = [ ( " a " , " a " ) , ( " date2 " , " 2012/11/28 " ) ]
, pdate = Nothing }
2014-09-11 00:07:53 +04:00
" a 1 ; a:a \ n ; [2012/11/28=2012/11/29],b:b \ n " ` gives `
2012-12-06 04:28:23 +04:00
( " a " ` post ` num 1 ) { pcomment = " a:a \ n [2012/11/28=2012/11/29],b:b \ n "
, ptags = [ ( " a " , " a " ) , ( " date " , " 2012/11/28 " ) , ( " date2 " , " 2012/11/29 " ) , ( " b " , " b " ) ]
, pdate = parsedateM " 2012/11/28 " }
2014-09-11 00:07:53 +04:00
2012-12-06 04:28:23 +04:00
assertBool -- "postingp parses a quoted commodity with numbers"
2016-04-28 23:23:20 +03:00
( isRight $ parseWithCtx nullctx ( postingp Nothing ) " a 1 \ " DE123 \ " \ n " )
2012-12-06 04:28:23 +04:00
-- ,"postingp parses balance assertions and fixed lot prices" ~: do
2016-04-28 23:23:20 +03:00
assertBool ( isRight $ parseWithCtx nullctx ( postingp Nothing ) " a 1 \ " DE123 \ " =$1 { =2.2 EUR} \ n " )
2012-12-06 04:28:23 +04:00
2013-05-29 03:18:15 +04:00
-- let parse = parseWithCtx nullctx postingp " a\n ;next-line comment\n"
-- assertRight parse
-- let Right p = parse
-- assertEqual "next-line comment\n" (pcomment p)
-- assertEqual (Just nullmixedamt) (pbalanceassertion p)
2014-09-11 00:07:53 +04:00
# endif
2012-05-15 05:49:05 +04:00
2016-04-23 21:27:39 +03:00
--- ** account names
2016-04-23 03:43:16 +03:00
2012-05-09 19:34:05 +04:00
-- | Parse an account name, then apply any parent account prefix and/or account aliases currently in effect.
2016-04-28 23:23:20 +03:00
modifiedaccountnamep :: Monad m => JournalParser m AccountName
2015-09-25 03:23:52 +03:00
modifiedaccountnamep = do
parent <- getParentAccount
2011-08-04 12:45:18 +04:00
aliases <- getAccountAliases
2015-09-25 03:23:52 +03:00
a <- accountnamep
return $
accountNameApplyAliases aliases $
2015-09-27 04:54:46 +03:00
-- XXX accountNameApplyAliasesMemo ? doesn't seem to make a difference
2015-09-25 03:23:52 +03:00
joinAccountNames parent
a
2008-12-08 10:21:33 +03:00
2015-04-28 23:50:58 +03:00
-- | Parse an account name. Account names start with a non-space, may
-- have single spaces inside them, and are terminated by two or more
-- spaces (or end of input). Also they have one or more components of
-- at least one character, separated by the account separator char.
-- (This parser will also consume one following space, if present.)
2016-04-28 23:23:20 +03:00
accountnamep :: Monad m => StringParser u m AccountName
2014-02-06 06:55:38 +04:00
accountnamep = do
2015-04-28 23:50:58 +03:00
a <- do
c <- nonspace
cs <- striptrailingspace <$> many ( nonspace <|> singlespace )
return $ c : cs
when ( accountNameFromComponents ( accountNameComponents a ) /= a )
( fail $ " account name seems ill-formed: " ++ a )
return a
2014-09-11 00:07:53 +04:00
where
2008-10-03 13:47:50 +04:00
singlespace = try ( do { spacenonewline ; do { notFollowedBy spacenonewline ; return ' ' } } )
2015-04-28 23:50:58 +03:00
striptrailingspace " " = " "
striptrailingspace s = if last s == ' ' then init s else s
2007-02-09 04:23:12 +03:00
2009-05-25 21:28:41 +04:00
-- accountnamechar = notFollowedBy (oneOf "()[]") >> nonspace
-- <?> "account name character (non-bracket, non-parenthesis, non-whitespace)"
2008-10-16 10:00:46 +04:00
2016-04-23 21:27:39 +03:00
--- ** amounts
2016-04-23 03:43:16 +03:00
2012-05-09 19:34:05 +04:00
-- | Parse whitespace then an amount, with an optional left or right
-- currency symbol and optional price, or return the special
2012-05-15 05:51:14 +04:00
-- "missing" marker amount.
2016-04-28 23:23:20 +03:00
spaceandamountormissingp :: Monad m => JournalParser m MixedAmount
2015-10-17 21:51:45 +03:00
spaceandamountormissingp =
2008-10-13 01:52:48 +04:00
try ( do
many1 spacenonewline
2012-11-20 03:17:55 +04:00
( Mixed . ( : [] ) ) ` fmap ` amountp <|> return missingmixedamt
2012-05-27 22:14:20 +04:00
) <|> return missingmixedamt
2008-10-13 01:52:48 +04:00
2012-12-06 04:28:23 +04:00
# ifdef TESTS
assertParseEqual' :: ( Show a , Eq a ) => ( Either ParseError a ) -> a -> Assertion
assertParseEqual' parse expected = either ( assertFailure . show ) ( ` is' ` expected ) parse
is' :: ( Eq a , Show a ) => a -> a -> Assertion
a ` is' ` e = assertEqual e a
2015-10-17 21:51:45 +03:00
test_spaceandamountormissingp = do
assertParseEqual' ( parseWithCtx nullctx spaceandamountormissingp " $47.18 " ) ( Mixed [ usd 47.18 ] )
assertParseEqual' ( parseWithCtx nullctx spaceandamountormissingp " $47.18 " ) missingmixedamt
assertParseEqual' ( parseWithCtx nullctx spaceandamountormissingp " " ) missingmixedamt
assertParseEqual' ( parseWithCtx nullctx spaceandamountormissingp " " ) missingmixedamt
2014-09-11 00:07:53 +04:00
# endif
2012-05-09 19:34:05 +04:00
2012-11-20 03:17:55 +04:00
-- | Parse a single-commodity amount, with optional symbol on the left or
-- right, optional unit or total price, and optional (ignored)
-- ledger-style balance assertion or fixed lot price declaration.
2016-04-28 23:23:20 +03:00
amountp :: Monad m => JournalParser m Amount
2015-10-17 21:51:45 +03:00
amountp = try leftsymbolamountp <|> try rightsymbolamountp <|> nosymbolamountp
2012-11-20 01:20:10 +04:00
2012-12-06 04:28:23 +04:00
# ifdef TESTS
test_amountp = do
assertParseEqual' ( parseWithCtx nullctx amountp " $47.18 " ) ( usd 47.18 )
assertParseEqual' ( parseWithCtx nullctx amountp " $1. " ) ( usd 1 ` withPrecision ` 0 )
-- ,"amount with unit price" ~: do
assertParseEqual'
2012-11-20 01:20:10 +04:00
( parseWithCtx nullctx amountp " $10 @ €0.5 " )
2012-11-20 03:17:55 +04:00
( usd 10 ` withPrecision ` 0 ` at ` ( eur 0.5 ` withPrecision ` 1 ) )
2012-12-06 04:28:23 +04:00
-- ,"amount with total price" ~: do
assertParseEqual'
2012-11-20 01:20:10 +04:00
( parseWithCtx nullctx amountp " $10 @@ €5 " )
2012-11-20 03:17:55 +04:00
( usd 10 ` withPrecision ` 0 @@ ( eur 5 ` withPrecision ` 0 ) )
2014-09-11 00:07:53 +04:00
# endif
2008-11-22 19:26:01 +03:00
2012-11-20 03:17:55 +04:00
-- | Parse an amount from a string, or get an error.
amountp' :: String -> Amount
2014-11-03 08:52:12 +03:00
amountp' s =
2014-11-04 06:35:25 +03:00
case runParser ( amountp <* eof ) nullctx " " s of
2014-11-03 08:52:12 +03:00
Right t -> t
2016-04-28 23:23:20 +03:00
Left err -> error ' $ s h o w e r r - - X X X s h o u l d t h r o w E r r o r
2012-05-27 22:14:20 +04:00
2012-11-20 03:17:55 +04:00
-- | Parse a mixed amount from a string, or get an error.
mamountp' :: String -> MixedAmount
2014-07-28 17:32:09 +04:00
mamountp' = Mixed . ( : [] ) . amountp'
2012-11-20 03:17:55 +04:00
2016-04-28 23:23:20 +03:00
signp :: Monad m => JournalParser m String
2014-04-30 22:21:01 +04:00
signp = do
sign <- optionMaybe $ oneOf " +- "
return $ case sign of Just '-' -> " - "
_ -> " "
2016-04-28 23:23:20 +03:00
leftsymbolamountp :: Monad m => JournalParser m Amount
2015-10-17 21:51:45 +03:00
leftsymbolamountp = do
2014-04-30 22:21:01 +04:00
sign <- signp
2015-10-17 21:51:45 +03:00
c <- commoditysymbolp
2008-10-13 01:52:48 +04:00
sp <- many spacenonewline
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
( q , prec , mdec , mgrps ) <- numberp
let s = amountstyle { ascommodityside = L , ascommodityspaced = not $ null sp , asprecision = prec , asdecimalpoint = mdec , asdigitgroups = mgrps }
2015-10-17 21:51:45 +03:00
p <- priceamountp
2014-04-30 22:28:47 +04:00
let applysign = if sign == " - " then negate else id
2012-11-20 03:17:55 +04:00
return $ applysign $ Amount c q p s
2008-10-13 01:52:48 +04:00
<?> " left-symbol amount "
2016-04-28 23:23:20 +03:00
rightsymbolamountp :: Monad m => JournalParser m Amount
2015-10-17 21:51:45 +03:00
rightsymbolamountp = do
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
( q , prec , mdec , mgrps ) <- numberp
2008-10-13 01:52:48 +04:00
sp <- many spacenonewline
2015-10-17 21:51:45 +03:00
c <- commoditysymbolp
p <- priceamountp
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
let s = amountstyle { ascommodityside = R , ascommodityspaced = not $ null sp , asprecision = prec , asdecimalpoint = mdec , asdigitgroups = mgrps }
2012-11-20 03:17:55 +04:00
return $ Amount c q p s
2008-10-13 01:52:48 +04:00
<?> " right-symbol amount "
2016-04-28 23:23:20 +03:00
nosymbolamountp :: Monad m => JournalParser m Amount
2015-10-17 21:51:45 +03:00
nosymbolamountp = do
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
( q , prec , mdec , mgrps ) <- numberp
2015-10-17 21:51:45 +03:00
p <- priceamountp
2014-07-02 22:23:30 +04:00
-- apply the most recently seen default commodity and style to this commodityless amount
defcs <- getDefaultCommodityAndStyle
2012-11-20 01:20:10 +04:00
let ( c , s ) = case defcs of
2014-03-27 04:25:59 +04:00
Just ( defc , defs ) -> ( defc , defs { asprecision = max ( asprecision defs ) prec } )
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
Nothing -> ( " " , amountstyle { asprecision = prec , asdecimalpoint = mdec , asdigitgroups = mgrps } )
2012-11-20 03:17:55 +04:00
return $ Amount c q p s
2008-10-13 01:52:48 +04:00
<?> " no-symbol amount "
2016-04-28 23:23:20 +03:00
commoditysymbolp :: Monad m => JournalParser m String
2015-10-17 21:51:45 +03:00
commoditysymbolp = ( quotedcommoditysymbolp <|> simplecommoditysymbolp ) <?> " commodity symbol "
2010-04-06 00:55:57 +04:00
2016-04-28 23:23:20 +03:00
quotedcommoditysymbolp :: Monad m => JournalParser m String
2015-10-17 21:51:45 +03:00
quotedcommoditysymbolp = do
2010-04-06 00:55:57 +04:00
char '"'
2010-05-27 05:31:50 +04:00
s <- many1 $ noneOf " ; \ n \ " "
2010-04-06 00:55:57 +04:00
char '"'
return s
2008-10-15 03:14:31 +04:00
2016-04-28 23:23:20 +03:00
simplecommoditysymbolp :: Monad m => JournalParser m String
2015-10-17 21:51:45 +03:00
simplecommoditysymbolp = many1 ( noneOf nonsimplecommoditychars )
2010-05-27 05:31:50 +04:00
2016-04-28 23:23:20 +03:00
priceamountp :: Monad m => JournalParser m Price
2015-10-17 21:51:45 +03:00
priceamountp =
2008-11-22 19:26:01 +03:00
try ( do
many spacenonewline
char '@'
2011-01-15 05:04:53 +03:00
try ( do
char '@'
many spacenonewline
2012-11-20 01:20:10 +04:00
a <- amountp -- XXX can parse more prices ad infinitum, shouldn't
2012-11-20 02:39:08 +04:00
return $ TotalPrice a )
2011-01-15 05:04:53 +03:00
<|> ( do
many spacenonewline
2012-11-20 01:20:10 +04:00
a <- amountp -- XXX can parse more prices ad infinitum, shouldn't
2012-11-20 02:39:08 +04:00
return $ UnitPrice a ) )
<|> return NoPrice
2008-11-22 19:26:01 +03:00
2016-04-28 23:23:20 +03:00
partialbalanceassertionp :: Monad m => JournalParser m ( Maybe MixedAmount )
2015-10-17 21:51:45 +03:00
partialbalanceassertionp =
2012-11-02 20:50:36 +04:00
try ( do
many spacenonewline
char '='
many spacenonewline
2012-11-20 01:20:10 +04:00
a <- amountp -- XXX should restrict to a simple amount
2013-05-29 03:18:15 +04:00
return $ Just $ Mixed [ a ] )
2012-11-02 20:50:36 +04:00
<|> return Nothing
2016-04-28 23:23:20 +03:00
-- balanceassertion :: Monad m => JournalParser m (Maybe MixedAmount)
2014-07-18 02:23:03 +04:00
-- balanceassertion =
-- try (do
-- many spacenonewline
-- string "=="
-- many spacenonewline
-- a <- amountp -- XXX should restrict to a simple amount
-- return $ Just $ Mixed [a])
-- <|> return Nothing
2012-11-17 06:40:27 +04:00
-- http://ledger-cli.org/3.0/doc/ledger3.html#Fixing-Lot-Prices
2016-04-28 23:23:20 +03:00
fixedlotpricep :: Monad m => JournalParser m ( Maybe Amount )
2015-10-17 21:51:45 +03:00
fixedlotpricep =
2012-11-17 06:40:27 +04:00
try ( do
many spacenonewline
char '{'
many spacenonewline
char '='
many spacenonewline
2012-11-20 01:20:10 +04:00
a <- amountp -- XXX should restrict to a simple amount
2012-11-17 06:40:27 +04:00
many spacenonewline
char '}'
return $ Just a )
<|> return Nothing
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- | Parse a string representation of a number for its value and display
-- attributes.
2014-09-11 00:07:53 +04:00
--
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- Some international number formats are accepted, eg either period or comma
-- may be used for the decimal point, and the other of these may be used for
-- separating digit groups in the integer part. See
-- http://en.wikipedia.org/wiki/Decimal_separator for more examples.
2014-09-11 00:07:53 +04:00
--
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- This returns: the parsed numeric value, the precision (number of digits
-- seen following the decimal point), the decimal point character used if any,
-- and the digit group style if any.
2014-09-11 00:07:53 +04:00
--
2016-04-28 23:23:20 +03:00
numberp :: Monad m => JournalParser m ( Quantity , Int , Maybe Char , Maybe DigitGroupStyle )
2014-02-06 06:55:38 +04:00
numberp = do
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- a number is an optional sign followed by a sequence of digits possibly
-- interspersed with periods, commas, or both
-- ptrace "numberp"
2014-04-30 22:21:01 +04:00
sign <- signp
2011-01-19 15:32:18 +03:00
parts <- many1 $ choice' [ many1 digit , many1 $ char ',' , many1 $ char '.' ]
2015-05-14 22:49:17 +03:00
dbg8 " numberp parsed " ( sign , parts ) ` seq ` return ()
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- check the number is well-formed and identify the decimal point and digit
-- group separator characters used, if any
let ( numparts , puncparts ) = partition numeric parts
( ok , mdecimalpoint , mseparator ) =
case ( numparts , puncparts ) of
( [] , _ ) -> ( False , Nothing , Nothing ) -- no digits, not ok
( _ , [] ) -> ( True , Nothing , Nothing ) -- digits with no punctuation, ok
( _ , [ [ d ] ] ) -> ( True , Just d , Nothing ) -- just a single punctuation of length 1, assume it's a decimal point
( _ , [ _ ] ) -> ( False , Nothing , Nothing ) -- a single punctuation of some other length, not ok
( _ , _ : _ : _ ) -> -- two or more punctuations
let ( s : ss , d ) = ( init puncparts , last puncparts ) -- the leftmost is a separator and the rightmost may be a decimal point
in if ( any ( ( /= 1 ) . length ) puncparts -- adjacent punctuation chars, not ok
|| any ( s /= ) ss -- separator chars vary, not ok
|| head parts == s ) -- number begins with a separator char, not ok
then ( False , Nothing , Nothing )
else if s == d
then ( True , Nothing , Just $ head s ) -- just one kind of punctuation - must be separators
else ( True , Just $ head d , Just $ head s ) -- separator(s) and a decimal point
2011-01-19 15:32:18 +03:00
when ( not ok ) ( fail $ " number seems ill-formed: " ++ concat parts )
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
-- get the digit group sizes and digit group style if any
let ( intparts' , fracparts' ) = span ( ( /= mdecimalpoint ) . Just . head ) parts
2011-01-19 15:32:18 +03:00
( intparts , fracpart ) = ( filter numeric intparts' , filter numeric fracparts' )
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
groupsizes = reverse $ case map length intparts of
( a : b : cs ) | a < b -> b : cs
gs -> gs
mgrps = maybe Nothing ( Just . ( ` DigitGroups ` groupsizes ) ) $ mseparator
-- put the parts back together without digit group separators, get the precision and parse the value
let int = concat $ " " : intparts
2011-01-19 15:32:18 +03:00
frac = concat $ " " : fracpart
precision = length frac
int' = if null int then " 0 " else int
frac' = if null frac then " 0 " else frac
2014-04-30 22:21:01 +04:00
quantity = read $ sign ++ int' ++ " . " ++ frac' -- this read should never fail
2008-10-15 03:14:31 +04:00
2015-05-14 22:49:17 +03:00
return $ dbg8 " numberp quantity,precision,mdecimalpoint,mgrps " ( quantity , precision , mdecimalpoint , mgrps )
look harder for decimal point & digit groups (fixes #196)
Amount display styles have been reworked a bit; they are now calculated
after journal parsing, not during it. This allows the fix for #196:
we now search through the amounts until a decimal point is detected,
instead of just looking at the first one; likewise for digit groups.
Digit groups are now implemented with a better type.
Digit group size detection has been improved a little:
1000,000 now gives group sizes [3,4,4,...], not [3,3,...], and
10,000 gives groups sizes [3,3,...] not [3,2,2,..].
(To get [3,2,2,...] you'd use eg 00,00,000.)
There are still some old (or new ?) issues; I don't think we handle
inconsistent decimal points & digit groups too well. But for now all
tests pass.
2014-07-03 10:26:16 +04:00
<?> " numberp "
where
numeric = isNumber . headDef '_'
2014-09-11 00:07:53 +04:00
2015-06-11 20:13:27 +03:00
-- test_numberp = do
-- let s `is` n = assertParseEqual (parseWithCtx nullctx numberp s) n
-- assertFails = assertBool . isLeft . parseWithCtx nullctx numberp
-- assertFails ""
-- "0" `is` (0, 0, '.', ',', [])
-- "1" `is` (1, 0, '.', ',', [])
-- "1.1" `is` (1.1, 1, '.', ',', [])
-- "1,000.1" `is` (1000.1, 1, '.', ',', [3])
-- "1.00.000,1" `is` (100000.1, 1, ',', '.', [3,2])
-- "1,000,000" `is` (1000000, 0, '.', ',', [3,3])
-- "1." `is` (1, 0, '.', ',', [])
-- "1," `is` (1, 0, ',', '.', [])
-- ".1" `is` (0.1, 1, '.', ',', [])
-- ",1" `is` (0.1, 1, ',', '.', [])
-- assertFails "1,000.000,1"
-- assertFails "1.000,000.1"
-- assertFails "1,000.000.1"
-- assertFails "1,,1"
-- assertFails "1..1"
-- assertFails ".1,"
-- assertFails ",1."
2011-01-19 15:32:18 +03:00
2016-04-23 21:27:39 +03:00
--- ** comments
2010-03-11 20:16:03 +03:00
2016-04-28 23:23:20 +03:00
multilinecommentp :: Monad m => JournalParser m ()
2014-10-26 21:19:42 +03:00
multilinecommentp = do
2015-05-09 23:25:31 +03:00
string " comment " >> many spacenonewline >> newline
2014-10-26 21:19:42 +03:00
go
where
2015-10-08 02:41:49 +03:00
go = try ( eof <|> ( string " end comment " >> newline >> return () ) )
2014-10-26 21:19:42 +03:00
<|> ( anyLine >> go )
anyLine = anyChar ` manyTill ` newline
2016-04-28 23:23:20 +03:00
emptyorcommentlinep :: Monad m => JournalParser m ()
2014-02-27 23:47:36 +04:00
emptyorcommentlinep = do
2015-10-17 21:51:45 +03:00
many spacenonewline >> ( commentp <|> ( many spacenonewline >> newline >> return " " ) )
2014-02-27 23:47:36 +04:00
return ()
2016-04-28 23:23:20 +03:00
-- | Parse a possibly multi-line comment following a semicolon.
followingcommentp :: Monad m => JournalParser m String
2014-02-27 23:47:36 +04:00
followingcommentp =
-- ptrace "followingcommentp"
2015-10-17 21:51:45 +03:00
do samelinecomment <- many spacenonewline >> ( try semicoloncommentp <|> ( newline >> return " " ) )
newlinecomments <- many ( try ( many1 spacenonewline >> semicoloncommentp ) )
2013-09-10 21:32:49 +04:00
return $ unlines $ samelinecomment : newlinecomments
2016-04-28 23:23:20 +03:00
-- | Parse a possibly multi-line comment following a semicolon, and
-- any tags and/or posting dates within it. Posting dates can be
-- expressed with "date"/"date2" tags and/or bracketed dates. The
-- dates are parsed in full here so that errors are reported in the
-- right position. Missing years can be inferred if a default date is
-- provided.
--
-- >>> rejp (followingcommentandtagsp (Just $ fromGregorian 2000 1 2)) "; a:b, date:3/4, [=5/6]"
-- Right ("a:b, date:3/4, [=5/6]\n",[("a","b"),("date","3/4")],Just 2000-03-04,Just 2000-05-06)
--
-- Year unspecified and no default provided -> unknown year error, at correct position:
-- >>> rejp (followingcommentandtagsp Nothing) " ; xxx date:3/4\n ; second line"
-- Left ...line 1, column 22...year is unknown...
--
-- Date tag value contains trailing text - forgot the comma, confused:
-- the syntaxes ? We'll accept the leading date anyway
-- >>> rejp (followingcommentandtagsp (Just $ fromGregorian 2000 1 2)) "; date:3/4=5/6"
-- Right ("date:3/4=5/6\n",[("date","3/4=5/6")],Just 2000-03-04,Nothing)
--
followingcommentandtagsp :: Maybe Day -> ErroringJournalParser ( String , [ Tag ] , Maybe Day , Maybe Day )
followingcommentandtagsp mdefdate = do
-- pdbg 0 "followingcommentandtagsp"
-- Parse a single or multi-line comment, starting on this line or the next one.
-- Save the starting position and preserve all whitespace for the subsequent re-parsing,
-- to get good error positions.
startpos <- getPosition
commentandwhitespace <- do
let semicoloncommentp' = ( : ) <$> char ';' <*> anyChar ` manyTill ` eolof
sp1 <- many spacenonewline
l1 <- try semicoloncommentp' <|> ( newline >> return " " )
ls <- many $ try ( ( ++ ) <$> many1 spacenonewline <*> semicoloncommentp' )
return $ unlines $ ( sp1 ++ l1 ) : ls
let comment = unlines $ map ( lstrip . dropWhile ( == ';' ) . strip ) $ lines commentandwhitespace
-- pdbg 0 $ "commentws:"++show commentandwhitespace
-- pdbg 0 $ "comment:"++show comment
-- Reparse the comment for any tags.
tags <- case runStringParser ( setPosition startpos >> tagsp ) commentandwhitespace of
Right ts -> return ts
Left e -> throwError $ show e
-- pdbg 0 $ "tags: "++show tags
-- Reparse the comment for any posting dates. Use the transaction date for defaults, if provided.
epdates <- liftIO $ rejp ( setPosition startpos >> postingdatesp mdefdate ) commentandwhitespace
pdates <- case epdates of
Right ds -> return ds
Left e -> throwError e
-- pdbg 0 $ "pdates: "++show pdates
let mdate = headMay $ map snd $ filter ( ( == " date " ) . fst ) pdates
mdate2 = headMay $ map snd $ filter ( ( == " date2 " ) . fst ) pdates
return ( comment , tags , mdate , mdate2 )
commentp :: Monad m => JournalParser m String
2015-10-17 21:51:45 +03:00
commentp = commentStartingWithp commentchars
2014-12-28 01:35:05 +03:00
commentchars :: [ Char ]
commentchars = " #;* "
2014-02-27 23:47:36 +04:00
2016-04-28 23:23:20 +03:00
semicoloncommentp :: Monad m => JournalParser m String
2015-10-17 21:51:45 +03:00
semicoloncommentp = commentStartingWithp " ; "
2014-02-27 23:47:36 +04:00
2016-04-28 23:23:20 +03:00
commentStartingWithp :: Monad m => String -> JournalParser m String
2015-10-17 21:51:45 +03:00
commentStartingWithp cs = do
2014-02-27 23:47:36 +04:00
-- ptrace "commentStartingWith"
oneOf cs
2013-09-10 21:32:49 +04:00
many spacenonewline
2012-12-06 04:28:23 +04:00
l <- anyChar ` manyTill ` eolof
2012-05-15 05:49:05 +04:00
optional newline
2012-12-06 04:28:23 +04:00
return l
2016-04-23 21:27:39 +03:00
--- ** tags
2016-04-23 03:43:16 +03:00
2016-04-28 23:23:20 +03:00
-- | Extract any tags (name:value ended by comma or newline) embedded in a string.
--
-- >>> commentTags "a b:, c:c d:d, e"
-- [("b",""),("c","c d:d")]
--
-- >>> commentTags "a [1/1/1] [1/1] [1], [=1/1/1] [=1/1] [=1] [1/1=1/1/1] [1=1/1/1] b:c"
-- [("b","c")]
--
-- --[("date","1/1/1"),("date","1/1"),("date2","1/1/1"),("date2","1/1"),("date","1/1"),("date2","1/1/1"),("date","1"),("date2","1/1/1")]
--
-- >>> commentTags "\na b:, \nd:e, f"
-- [("b",""),("d","e")]
--
commentTags :: String -> [ Tag ]
commentTags s =
case runStringParser tagsp s of
Right r -> r
Left _ -> [] -- shouldn't happen
-- | Parse all tags found in a string.
tagsp :: StringParser u Identity [ Tag ]
tagsp = do
-- pdbg 0 $ "tagsp"
many ( try ( nontagp >> tagp ) )
-- | Parse everything up till the first tag.
--
-- >>> rsp nontagp "\na b:, \nd:e, f"
-- Right "\na "
nontagp :: StringParser u Identity String
nontagp = do
-- pdbg 0 "nontagp"
-- anyChar `manyTill` (lookAhead (try (tagorbracketeddatetagsp Nothing >> return ()) <|> eof))
anyChar ` manyTill ` ( lookAhead ( try ( tagp >> return () ) <|> eof ) )
-- XXX costly ?
-- | Tags begin with a colon-suffixed tag name (a word beginning with
-- a letter) and are followed by a tag value (any text up to a comma
-- or newline, whitespace-stripped).
--
-- >>> rsp tagp "a:b b , c AuxDate: 4/2"
-- Right ("a","b b")
--
tagp :: Monad m => StringParser u m Tag
2015-10-17 21:51:45 +03:00
tagp = do
2016-04-28 23:23:20 +03:00
-- pdbg 0 "tagp"
2015-10-17 21:51:45 +03:00
n <- tagnamep
v <- tagvaluep
2012-12-06 04:28:23 +04:00
return ( n , v )
2016-04-28 23:23:20 +03:00
-- |
-- >>> rsp tagnamep "a:"
-- Right "a"
tagnamep :: Monad m => StringParser u m String
2015-10-17 21:51:45 +03:00
tagnamep = do
2016-04-28 23:23:20 +03:00
-- pdbg 0 "tagnamep"
many1 ( noneOf " : \ t \ n " ) <* char ':'
2012-12-06 04:28:23 +04:00
2016-04-28 23:23:20 +03:00
tagvaluep :: Monad m => StringParser u m String
2015-10-17 21:51:45 +03:00
tagvaluep = do
2012-12-06 04:28:23 +04:00
-- ptrace "tagvalue"
2016-04-28 23:23:20 +03:00
v <- anyChar ` manyTill ` ( ( try ( char ',' ) >> return () ) <|> eolof )
2012-12-06 04:28:23 +04:00
return $ strip $ reverse $ dropWhile ( == ',' ) $ reverse $ strip v
2016-04-28 23:23:20 +03:00
--- ** posting dates
2014-09-11 00:07:53 +04:00
2016-04-28 23:23:20 +03:00
-- | Parse all posting dates found in a string. Posting dates can be
-- expressed with date/date2 tags and/or bracketed dates. The dates
-- are parsed fully to give useful errors. Missing years can be
-- inferred only if a default date is provided.
--
postingdatesp :: Maybe Day -> ErroringJournalParser [ ( TagName , Day ) ]
postingdatesp mdefdate = do
-- pdbg 0 $ "postingdatesp"
let p = ( datetagp mdefdate >>= return . ( : [] ) ) <|> bracketeddatetagsp mdefdate
nonp =
many ( notFollowedBy p >> anyChar )
-- anyChar `manyTill` (lookAhead (try (p >> return ()) <|> eof))
concat <$> ( many $ try ( nonp >> p ) )
--- ** date tags
-- | Date tags are tags with name "date" or "date2". Their value is
-- parsed as a date, using the provided default date if any for
-- inferring a missing year if needed. Any error in date parsing is
-- reported and terminates parsing.
--
-- >>> rejp (datetagp Nothing) "date: 2000/1/2 "
-- Right ("date",2000-01-02)
--
-- >>> rejp (datetagp (Just $ fromGregorian 2001 2 3)) "date2:3/4"
-- Right ("date2",2001-03-04)
--
-- >>> rejp (datetagp Nothing) "date: 3/4"
-- Left ...line 1, column 9...year is unknown...
--
datetagp :: Maybe Day -> ErroringJournalParser ( TagName , Day )
datetagp mdefdate = do
-- pdbg 0 "datetagp"
string " date "
n <- maybe " " id <$> optionMaybe ( string " 2 " )
char ':'
startpos <- getPosition
v <- tagvaluep
-- re-parse value as a date.
ctx <- getState
ep <- parseWithCtx
ctx { ctxYear = first3 . toGregorian <$> mdefdate }
-- The value extends to a comma, newline, or end of file.
-- It seems like ignoring any extra stuff following a date
-- gives better errors here.
( do
setPosition startpos
datep ) -- <* eof)
v
case ep
of Left e -> throwError $ show e
Right d -> return ( " date " ++ n , d )
--- ** bracketed dates
-- tagorbracketeddatetagsp :: Monad m => Maybe Day -> StringParser u m [Tag]
-- tagorbracketeddatetagsp mdefdate =
-- bracketeddatetagsp mdefdate <|> ((:[]) <$> tagp)
-- | Parse Ledger-style bracketed posting dates ([DATE=DATE2]), as
-- "date" and/or "date2" tags. Anything that looks like an attempt at
-- this (a square-bracketed sequence of 0123456789/-.= containing at
-- least one digit and one date separator) is also parsed, and will
-- throw an appropriate error.
--
-- The dates are parsed in full here so that errors are reported in
-- the right position. A missing year in DATE can be inferred if a
-- default date is provided. A missing year in DATE2 will be inferred
-- from DATE.
--
-- >>> rejp (bracketeddatetagsp Nothing) "[2016/1/2=3/4]"
-- Right [("date",2016-01-02),("date2",2016-03-04)]
--
-- >>> rejp (bracketeddatetagsp Nothing) "[1]"
-- Left ...not a bracketed date...
--
-- >>> rejp (bracketeddatetagsp Nothing) "[2016/1/32]"
-- Left ...line 1, column 11...bad date...
--
-- >>> rejp (bracketeddatetagsp Nothing) "[1/31]"
-- Left ...line 1, column 6...year is unknown...
--
-- >>> rejp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]"
-- Left ...line 1, column 15...bad date, different separators...
--
bracketeddatetagsp :: Maybe Day -> ErroringJournalParser [ ( TagName , Day ) ]
bracketeddatetagsp mdefdate = do
-- pdbg 0 "bracketeddatetagsp"
char '['
startpos <- getPosition
let digits = " 0123456789 "
s <- many1 ( oneOf $ '=' : digits ++ datesepchars )
char ']'
unless ( any ( ` elem ` s ) digits && any ( ` elem ` datesepchars ) s ) $
parserFail " not a bracketed date "
-- looks sufficiently like a bracketed date, now we
-- re-parse as dates and throw any errors
ctx <- getState
ep <- parseWithCtx
ctx { ctxYear = first3 . toGregorian <$> mdefdate }
( do
setPosition startpos
md1 <- optionMaybe datep
maybe ( return () ) ( setYear . first3 . toGregorian ) md1
md2 <- optionMaybe $ char '=' >> datep
eof
return ( md1 , md2 )
)
s
case ep
of Left e -> throwError $ show e
Right ( md1 , md2 ) -> return $ catMaybes $
[ maybe Nothing ( Just . ( " date " , ) ) md1 , maybe Nothing ( Just . ( " date2 " , ) ) md2 ]
--- * more tests
2016-04-23 03:43:16 +03:00
2015-06-11 20:13:27 +03:00
tests_Hledger_Read_JournalReader = TestList $ concat [
-- test_numberp
]
2012-12-06 04:28:23 +04:00
{- old hunit tests
2015-06-11 20:13:27 +03:00
tests_Hledger_Read_JournalReader = TestList $ concat [
2014-02-06 06:55:38 +04:00
test_numberp ,
2012-12-06 04:28:23 +04:00
test_amountp ,
2015-10-17 21:51:45 +03:00
test_spaceandamountormissingp ,
2012-12-06 04:28:23 +04:00
test_tagcomment ,
test_inlinecomment ,
2014-02-27 23:47:36 +04:00
test_comments ,
2012-12-06 04:28:23 +04:00
test_ledgerDateSyntaxToTags ,
test_postingp ,
2015-10-17 21:51:45 +03:00
test_transactionp ,
2012-05-15 05:49:05 +04:00
[
2015-10-17 21:51:45 +03:00
" modifiertransactionp " ~: do
assertParse ( parseWithCtx nullctx modifiertransactionp " = (some value expr) \ n some:postings 1 \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " periodictransactionp " ~: do
assertParse ( parseWithCtx nullctx periodictransactionp " ~ (some period expr) \ n some:postings 1 \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " directivep " ~: do
assertParse ( parseWithCtx nullctx directivep " !include /some/file.x \ n " )
assertParse ( parseWithCtx nullctx directivep " account some:account \ n " )
assertParse ( parseWithCtx nullctx ( directivep >> directivep ) " !account a \ n end \ n " )
2010-03-13 04:10:10 +03:00
2014-02-27 23:47:36 +04:00
, " comment " ~: do
assertParse ( parseWithCtx nullctx comment " ; some comment \ n " )
assertParse ( parseWithCtx nullctx comment " \ t ; x \ n " )
assertParse ( parseWithCtx nullctx comment " #x " )
2010-03-13 04:10:10 +03:00
2014-08-08 18:27:32 +04:00
, " datep " ~: do
assertParse ( parseWithCtx nullctx datep " 2011/1/1 " )
assertParseFailure ( parseWithCtx nullctx datep " 1/1 " )
assertParse ( parseWithCtx nullctx { ctxYear = Just 2011 } datep " 1/1 " )
2011-05-31 23:49:37 +04:00
2014-02-06 06:55:38 +04:00
, " datetimep " ~: do
let p = do { t <- datetimep ; eof ; return t }
2011-06-01 05:50:04 +04:00
bad = assertParseFailure . parseWithCtx nullctx p
good = assertParse . parseWithCtx nullctx p
bad " 2011/1/1 "
bad " 2011/1/1 24:00:00 "
bad " 2011/1/1 00:60:00 "
bad " 2011/1/1 00:00:60 "
good " 2011/1/1 00:00 "
good " 2011/1/1 23:59:59 "
good " 2011/1/1 3:5:7 "
-- timezone is parsed but ignored
let startofday = LocalTime ( fromGregorian 2011 1 1 ) ( TimeOfDay 0 0 ( fromIntegral 0 ) )
assertParseEqual ( parseWithCtx nullctx p " 2011/1/1 00:00-0800 " ) startofday
assertParseEqual ( parseWithCtx nullctx p " 2011/1/1 00:00+1234 " ) startofday
2011-06-01 02:45:54 +04:00
2015-10-17 21:51:45 +03:00
, " defaultyeardirectivep " ~: do
assertParse ( parseWithCtx nullctx defaultyeardirectivep " Y 2010 \ n " )
assertParse ( parseWithCtx nullctx defaultyeardirectivep " Y 10001 \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " marketpricedirectivep " ~:
assertParseEqual ( parseWithCtx nullctx marketpricedirectivep " P 2004/05/01 XYZ $55.00 \ n " ) ( MarketPrice ( parsedate " 2004/05/01 " ) " XYZ " $ usd 55 )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " ignoredpricecommoditydirectivep " ~: do
assertParse ( parseWithCtx nullctx ignoredpricecommoditydirectivep " N $ \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " defaultcommoditydirectivep " ~: do
assertParse ( parseWithCtx nullctx defaultcommoditydirectivep " D $1,000.0 \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " commodityconversiondirectivep " ~: do
assertParse ( parseWithCtx nullctx commodityconversiondirectivep " C 1h = $50.00 \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " tagdirectivep " ~: do
assertParse ( parseWithCtx nullctx tagdirectivep " tag foo \ n " )
2010-03-13 04:10:10 +03:00
2015-10-17 21:51:45 +03:00
, " endtagdirectivep " ~: do
assertParse ( parseWithCtx nullctx endtagdirectivep " end tag \ n " )
assertParse ( parseWithCtx nullctx endtagdirectivep " pop \ n " )
2010-03-13 04:10:10 +03:00
2014-02-06 06:55:38 +04:00
, " accountnamep " ~: do
assertBool " accountnamep parses a normal account name " ( isRight $ parsewith accountnamep " a:b:c " )
assertBool " accountnamep rejects an empty inner component " ( isLeft $ parsewith accountnamep " a::c " )
assertBool " accountnamep rejects an empty leading component " ( isLeft $ parsewith accountnamep " :b:c " )
assertBool " accountnamep rejects an empty trailing component " ( isLeft $ parsewith accountnamep " a:b: " )
2010-03-11 20:16:03 +03:00
2015-10-17 21:51:45 +03:00
, " leftsymbolamountp " ~: do
assertParseEqual ( parseWithCtx nullctx leftsymbolamountp " $1 " ) ( usd 1 ` withPrecision ` 0 )
assertParseEqual ( parseWithCtx nullctx leftsymbolamountp " $-1 " ) ( usd ( - 1 ) ` withPrecision ` 0 )
assertParseEqual ( parseWithCtx nullctx leftsymbolamountp " -$1 " ) ( usd ( - 1 ) ` withPrecision ` 0 )
2010-05-27 03:44:08 +04:00
2012-05-27 22:14:20 +04:00
, " amount " ~: do
2012-11-20 03:17:55 +04:00
let -- | compare a parse result with an expected amount, showing the debug representation for clarity
assertAmountParse parseresult amount =
( either ( const " parse error " ) showAmountDebug parseresult ) ~?= ( showAmountDebug amount )
assertAmountParse ( parseWithCtx nullctx amountp " 1 @ $2 " )
2012-11-20 06:22:20 +04:00
( num 1 ` withPrecision ` 0 ` at ` ( usd 2 ` withPrecision ` 0 ) )
2012-05-27 22:14:20 +04:00
2012-05-09 19:34:05 +04:00
] ]
2012-12-06 04:28:23 +04:00
- }