hledger/hledger-lib/Hledger/Read/Common.hs

1371 lines
51 KiB
Haskell
Raw Normal View History

--- * doc
-- Lines beginning "--- *" are collapsible orgstruct nodes. Emacs users,
-- (add-hook 'haskell-mode-hook
-- (lambda () (set-variable 'orgstruct-heading-prefix-regexp "--- " t))
-- 'orgstruct-mode)
-- and press TAB on nodes to expand/collapse.
{-|
2016-05-19 02:37:31 +03:00
Some common parsers and helpers used by several readers.
Some of these might belong in Hledger.Read.JournalReader or Hledger.Read.
-}
--- * module
{-# LANGUAGE CPP, BangPatterns, DeriveDataTypeable, RecordWildCards, NamedFieldPuns, NoMonoLocalBinds, ScopedTypeVariables, FlexibleContexts, TupleSections, OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PackageImports #-}
module Hledger.Read.Common (
Reader (..),
InputOpts (..),
definputopts,
rawOptsToInputOpts,
-- * parsing utilities
runTextParser,
rtp,
runJournalParser,
rjp,
runErroringJournalParser,
rejp,
genericSourcePos,
journalSourcePos,
parseAndFinaliseJournal,
parseAndFinaliseJournal',
finaliseJournal,
setYear,
getYear,
setDefaultCommodityAndStyle,
getDefaultCommodityAndStyle,
getDefaultAmountStyle,
getAmountStyle,
journal: account directives can declare account types Previously you had to use one of the standard english account names (assets, liabilities..) for top-level accounts, if you wanted to use the bs/bse/cf/is commands. Now, account directives can specify which of the big five categories an account belongs to - asset, liability, equity, revenue or expense - by writing one of the letters A, L, E, R or X two or more spaces after the account name (where the numeric account code used to be). This might change. Some thoughts influencing the current syntax: - easy to type and read - does not require multiple lines - does not depend on any particular account numbering scheme - allows more types later if needed - still anglocentric, but only a little - could be treated as syntactic sugar for account tags later - seems to be compatible with (ignored by) current Ledger The current design permits unlimited account type declarations anywhere in the account tree. So you could declare a liability account somewhere under assets, and maybe a revenue account under that, and another asset account even further down. In such cases you start to see oddities like accounts appearing in multiple places in a tree-mode report. In theory the reports will still behave reasonably, but this has not been tested too hard. In any case this is clearly too much freedom. I have left it this way, for now, in case it helps with: - modelling contra accounts ? - multiple files. I suspect the extra expressiveness may come in handy when combining multiple files with account type declarations, rewriting account names, apply parent accounts etc. If we only allowed type declarations on top-level accounts, or only allowed a single account of each type, complications seem likely.
2018-09-27 04:34:48 +03:00
addDeclaredAccountType,
pushParentAccount,
popParentAccount,
getParentAccount,
addAccountAlias,
getAccountAliases,
clearAccountAliases,
journalAddFile,
-- * parsers
-- ** transaction bits
statusp,
codep,
descriptionp,
-- ** dates
datep,
datetimep,
secondarydatep,
-- ** account names
modifiedaccountnamep,
accountnamep,
-- ** amounts
spaceandamountormissingp,
amountp,
amountp',
mamountp',
commoditysymbolp,
priceamountp,
balanceassertionp,
fixedlotpricep,
numberp,
fromRawNumber,
rawnumberp,
-- ** comments
multilinecommentp,
emptyorcommentlinep,
followingcommentp,
transactioncommentp,
postingcommentp,
-- ** bracketed dates
bracketeddatetagsp,
-- ** misc
singlespacedtextp,
singlespacedtextsatisfyingp,
2018-06-18 01:23:41 +03:00
singlespacep,
-- * tests
2018-09-06 23:08:26 +03:00
tests_Common,
)
where
--- * imports
import Prelude ()
import "base-compat-batteries" Prelude.Compat hiding (fail, readFile)
import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail)
import Control.Monad.Except (ExceptT(..), runExceptT, throwError)
import Control.Monad.State.Strict hiding (fail)
import Data.Bifunctor (bimap, second)
import Data.Char
import Data.Data
import Data.Decimal (DecimalRaw (Decimal), Decimal)
import Data.Default
import Data.Functor.Identity
import "base-compat-batteries" Data.List.Compat
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe
import qualified Data.Map as M
import qualified Data.Semigroup as Sem
lib: textification: saved journal source Slightly worse on small files, better on large ones. hledger -f data/100x100x10.journal stats <<ghc: 39305392 bytes, 77 GCs, 196354/268584 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.007 elapsed), 0.014 MUT (0.027 elapsed), 0.011 GC (0.111 elapsed) :ghc>> <<ghc: 39307728 bytes, 77 GCs, 196909/270248 avg/max bytes residency (3 samples), 2M in use, 0.001 INIT (0.010 elapsed), 0.015 MUT (0.028 elapsed), 0.012 GC (0.116 elapsed) :ghc>> hledger -f data/1000x1000x10.journal stats <<ghc: 314285912 bytes, 612 GCs, 2064811/6597608 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.002 elapsed), 0.126 MUT (0.134 elapsed), 0.059 GC (0.069 elapsed) :ghc>> <<ghc: 314271368 bytes, 612 GCs, 2070227/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.137 MUT (0.143 elapsed), 0.059 GC (0.068 elapsed) :ghc>> hledger -f data/10000x1000x10.journal stats <<ghc: 3070033264 bytes, 5965 GCs, 12699294/62962464 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.000 elapsed), 1.245 MUT (1.300 elapsed), 0.498 GC (0.558 elapsed) :ghc>> <<ghc: 3070006752 bytes, 5973 GCs, 12687314/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.257 MUT (1.281 elapsed), 0.496 GC (0.554 elapsed) :ghc>> hledger -f data/100000x1000x10.journal stats <<ghc: 30753465088 bytes, 59763 GCs, 117723618/666643528 avg/max bytes residency (14 samples), 1589M in use, 0.000 INIT (0.002 elapsed), 12.536 MUT (12.793 elapsed), 5.978 GC (7.155 elapsed) :ghc>> <<ghc: 30753367256 bytes, 59811 GCs, 117723236/666627528 avg/max bytes residency (14 samples), 1590M in use, 0.001 INIT (0.012 elapsed), 12.923 MUT (13.169 elapsed), 5.981 GC (6.860 elapsed) :ghc>>
2016-05-24 05:24:39 +03:00
import Data.Text (Text)
lib: textification begins! account names The first of several conversions from String to (strict) Text, hopefully reducing space and time usage. This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1: hledger -f data/100x100x10.journal stats string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>> text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>> text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>> text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>> text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.LocalTime
import System.Time (getClockTime)
import Text.Megaparsec
import Text.Megaparsec.Char
2018-05-23 05:17:51 +03:00
import Text.Megaparsec.Char.Lexer (decimal)
import Text.Megaparsec.Custom
import Hledger.Data
import Hledger.Utils
-- $setup
-- >>> :set -XOverloadedStrings
-- | A hledger journal reader is a triple of storage format name, a
-- detector of that format, and a parser from that format to Journal.
data Reader = Reader {
-- The canonical name of the format handled by this reader
rFormat :: StorageFormat
-- The file extensions recognised as containing this format
,rExtensions :: [String]
-- A text parser for this format, accepting input options, file
-- path for error messages and file contents, producing an exception-raising IO
-- action that returns a journal or error message.
,rParser :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal
-- Experimental readers are never tried automatically.
,rExperimental :: Bool
}
instance Show Reader where show r = rFormat r ++ " reader"
-- $setup
-- | Various options to use when reading journal files.
-- Similar to CliOptions.inputflags, simplifies the journal-reading functions.
data InputOpts = InputOpts {
-- files_ :: [FilePath]
mformat_ :: Maybe StorageFormat -- ^ a file/storage format to try, unless overridden
-- by a filename prefix. Nothing means try all.
,mrules_file_ :: Maybe FilePath -- ^ a conversion rules file to use (when reading CSV)
csv: merge lucamolteni's cassava/custom separators (squashed) (#829) commit 5ba464de761b298e50d57a8b7d14bc28adb30d5d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:54:12 2018 +0200 Fix CI 2 commit f060ae9449f4b61a915b0ed4629fc1ba9b66fb4a Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:30:08 2018 +0200 Fix CI build commit af0719a33b9b72ad244ae80198d881a1f7145e9d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:19:01 2018 +0200 Fix rebase commit 1a24ddfa54dfb4ff1326e1a51005ffa82d3dc3c8 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:25:24 2018 +0200 Fixed some GHC warnings commit 1ac43398a359b5925ef71f53347698f1c6c510ef Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:14:49 2018 +0200 Fix .cabal commit 422456b925d8aa4ab3e869f51e98c2b1c3dcde0a Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:56:20 2018 +0200 Removed to-do list commit 1118b762e4fd15c4fe7ba48ba86676706ea3a5a5 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:53:28 2018 +0200 Better test commit 1146ed0941655668bf7684f18aa15c5f4b9b20c2 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 15:32:28 2018 +0200 Fix parsing commit 4fc2374b2b81802990da30c96756aab54d77399c Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 22:11:11 2018 +0200 Parsing of separator commit f7a61737f1ad4460ba20ca9b2e86eb21468abb33 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:29:23 2018 +0200 Almost separator in options commit ac8841cf3b9c80914bc3271ad9b9ff4ae9ba48a7 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:16:59 2018 +0200 Separator in parseCSV commit 92a8b9f6ba77ea4237f769641e03029ac88542ea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 13:30:41 2018 +0200 separator option commit ec417a81ae625647cf35e61776cdf02bdb2c6aea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 10:45:26 2018 +0200 Removed one qualified import commit 8b2f386c2f780adcd34cff3de7edceacc1d325a7 Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 14:01:12 2018 +0200 Removed string conversions commit a14d0e099e28a286bb81770cfc9cb8f5c7e5cf1f Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 10:23:20 2018 +0200 custom delimiter in cassava commit 694d48e2bc1ada0037b90367c017f3082f68ed45 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:51:54 2018 +0200 Use Text.getContents - remove UTF-8 compatibility library commit a7ada2cc60033ebdd796ca34cc2ec69a4f387843 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:49:34 2018 +0200 todo list commit 58ec47d3987909f6bace50e3e647e30dadd5bf03 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:45:22 2018 +0200 CSV test now has unicode characters commit b7851e94c3f1683b63ec7250a12bcde3b7bed691 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 16:59:39 2018 +0200 Use decode from Text commit 79f59fd28ccaca08fcd718fcd8d00b1c1d65d7e1 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 13:28:57 2018 +0200 Use Text and Lazy Bytestring commit 470c9bcb8dc00669beb4ef0303a1e7d9f7aecc89 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:30:22 2018 +0200 Use megaparsec error commit f978848ba249ef4f67b855bea5d4e549290c205c Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:22:07 2018 +0200 Renamed qualify and remove Parsec commit 152587fde204c43a55798d212e43f37cd3038c2e Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:12:36 2018 +0200 Use cassava mega parsec commit cf281577a3d3a071196484a6fc8485f2ea1f7d67 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 14:01:47 2018 +0200 Removed Data.Vector commit 1272e8e758369d8cc5778029a705b277355a5029 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:16:18 2018 +0200 Removed Parsec ParseError commit ae07f043135a19307fd65b281ade37a74c76acb2 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:06:14 2018 +0200 Type sinonim for ParsecError commit 8e15b253c11bd1c0c35a7641aeb18aa54e0ba9b0 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:16:08 2018 +0200 Replaced with typeclasses commit 1ed46f9c175603611325f3d377004e4b85f29377 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:01:33 2018 +0200 Replaced Text/CSV with Cassava commit 362f4111b5854145703174b976fc7acbd71b8783 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 10:34:37 2018 +0200 Use cassava parsin instead of Text/CSV commit 83e678e371618687cf7c15a4e2cfa67f570b6b64 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 08:22:51 2018 +0200 Text CSV error messages commit f922df71d274beeacab9fb2530b16c97f005cc08 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:45:20 2018 +0200 Better types commit edd130781c84790a53bff2283e6041eb8232e7cf Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:34:59 2018 +0200 Conversion to Text CSV type commit 0799383214483018ad2d977a3c8022414959c2b2 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 16:06:21 2018 +0200 First function with cassava commit e92aeb151ff527b383ff3d0ced7764e81b71af82 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:47:34 2018 +0200 Added cassava as dependency commit 5ea005c558a3939af7e5f0cd735a9b4da931228e Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:18:47 2018 +0200 Better .gitignore for multi idea modules
2018-09-07 20:12:13 +03:00
,separator_ :: Char -- ^ the separator to use (when reading CSV)
,aliases_ :: [String] -- ^ account name aliases to apply
,anon_ :: Bool -- ^ do light anonymisation/obfuscation of the data
,ignore_assertions_ :: Bool -- ^ don't check balance assertions
,new_ :: Bool -- ^ read only new transactions since this file was last read
,new_save_ :: Bool -- ^ save latest new transactions state for next time
,pivot_ :: String -- ^ use the given field's value as the account name
,auto_ :: Bool -- ^ generate automatic postings when journal is parsed
} deriving (Show, Data) --, Typeable)
instance Default InputOpts where def = definputopts
definputopts :: InputOpts
csv: merge lucamolteni's cassava/custom separators (squashed) (#829) commit 5ba464de761b298e50d57a8b7d14bc28adb30d5d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:54:12 2018 +0200 Fix CI 2 commit f060ae9449f4b61a915b0ed4629fc1ba9b66fb4a Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:30:08 2018 +0200 Fix CI build commit af0719a33b9b72ad244ae80198d881a1f7145e9d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:19:01 2018 +0200 Fix rebase commit 1a24ddfa54dfb4ff1326e1a51005ffa82d3dc3c8 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:25:24 2018 +0200 Fixed some GHC warnings commit 1ac43398a359b5925ef71f53347698f1c6c510ef Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:14:49 2018 +0200 Fix .cabal commit 422456b925d8aa4ab3e869f51e98c2b1c3dcde0a Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:56:20 2018 +0200 Removed to-do list commit 1118b762e4fd15c4fe7ba48ba86676706ea3a5a5 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:53:28 2018 +0200 Better test commit 1146ed0941655668bf7684f18aa15c5f4b9b20c2 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 15:32:28 2018 +0200 Fix parsing commit 4fc2374b2b81802990da30c96756aab54d77399c Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 22:11:11 2018 +0200 Parsing of separator commit f7a61737f1ad4460ba20ca9b2e86eb21468abb33 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:29:23 2018 +0200 Almost separator in options commit ac8841cf3b9c80914bc3271ad9b9ff4ae9ba48a7 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:16:59 2018 +0200 Separator in parseCSV commit 92a8b9f6ba77ea4237f769641e03029ac88542ea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 13:30:41 2018 +0200 separator option commit ec417a81ae625647cf35e61776cdf02bdb2c6aea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 10:45:26 2018 +0200 Removed one qualified import commit 8b2f386c2f780adcd34cff3de7edceacc1d325a7 Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 14:01:12 2018 +0200 Removed string conversions commit a14d0e099e28a286bb81770cfc9cb8f5c7e5cf1f Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 10:23:20 2018 +0200 custom delimiter in cassava commit 694d48e2bc1ada0037b90367c017f3082f68ed45 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:51:54 2018 +0200 Use Text.getContents - remove UTF-8 compatibility library commit a7ada2cc60033ebdd796ca34cc2ec69a4f387843 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:49:34 2018 +0200 todo list commit 58ec47d3987909f6bace50e3e647e30dadd5bf03 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:45:22 2018 +0200 CSV test now has unicode characters commit b7851e94c3f1683b63ec7250a12bcde3b7bed691 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 16:59:39 2018 +0200 Use decode from Text commit 79f59fd28ccaca08fcd718fcd8d00b1c1d65d7e1 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 13:28:57 2018 +0200 Use Text and Lazy Bytestring commit 470c9bcb8dc00669beb4ef0303a1e7d9f7aecc89 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:30:22 2018 +0200 Use megaparsec error commit f978848ba249ef4f67b855bea5d4e549290c205c Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:22:07 2018 +0200 Renamed qualify and remove Parsec commit 152587fde204c43a55798d212e43f37cd3038c2e Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:12:36 2018 +0200 Use cassava mega parsec commit cf281577a3d3a071196484a6fc8485f2ea1f7d67 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 14:01:47 2018 +0200 Removed Data.Vector commit 1272e8e758369d8cc5778029a705b277355a5029 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:16:18 2018 +0200 Removed Parsec ParseError commit ae07f043135a19307fd65b281ade37a74c76acb2 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:06:14 2018 +0200 Type sinonim for ParsecError commit 8e15b253c11bd1c0c35a7641aeb18aa54e0ba9b0 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:16:08 2018 +0200 Replaced with typeclasses commit 1ed46f9c175603611325f3d377004e4b85f29377 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:01:33 2018 +0200 Replaced Text/CSV with Cassava commit 362f4111b5854145703174b976fc7acbd71b8783 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 10:34:37 2018 +0200 Use cassava parsin instead of Text/CSV commit 83e678e371618687cf7c15a4e2cfa67f570b6b64 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 08:22:51 2018 +0200 Text CSV error messages commit f922df71d274beeacab9fb2530b16c97f005cc08 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:45:20 2018 +0200 Better types commit edd130781c84790a53bff2283e6041eb8232e7cf Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:34:59 2018 +0200 Conversion to Text CSV type commit 0799383214483018ad2d977a3c8022414959c2b2 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 16:06:21 2018 +0200 First function with cassava commit e92aeb151ff527b383ff3d0ced7764e81b71af82 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:47:34 2018 +0200 Added cassava as dependency commit 5ea005c558a3939af7e5f0cd735a9b4da931228e Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:18:47 2018 +0200 Better .gitignore for multi idea modules
2018-09-07 20:12:13 +03:00
definputopts = InputOpts def def ',' def def def def True def def
rawOptsToInputOpts :: RawOpts -> InputOpts
rawOptsToInputOpts rawopts = InputOpts{
-- files_ = listofstringopt "file" rawopts
mformat_ = Nothing
,mrules_file_ = maybestringopt "rules-file" rawopts
csv: merge lucamolteni's cassava/custom separators (squashed) (#829) commit 5ba464de761b298e50d57a8b7d14bc28adb30d5d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:54:12 2018 +0200 Fix CI 2 commit f060ae9449f4b61a915b0ed4629fc1ba9b66fb4a Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:30:08 2018 +0200 Fix CI build commit af0719a33b9b72ad244ae80198d881a1f7145e9d Author: Luca Molteni <volothamp@gmail.com> Date: Fri Sep 7 17:19:01 2018 +0200 Fix rebase commit 1a24ddfa54dfb4ff1326e1a51005ffa82d3dc3c8 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:25:24 2018 +0200 Fixed some GHC warnings commit 1ac43398a359b5925ef71f53347698f1c6c510ef Author: Luca Molteni <volothamp@gmail.com> Date: Fri Aug 10 16:14:49 2018 +0200 Fix .cabal commit 422456b925d8aa4ab3e869f51e98c2b1c3dcde0a Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:56:20 2018 +0200 Removed to-do list commit 1118b762e4fd15c4fe7ba48ba86676706ea3a5a5 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 22:53:28 2018 +0200 Better test commit 1146ed0941655668bf7684f18aa15c5f4b9b20c2 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jul 1 15:32:28 2018 +0200 Fix parsing commit 4fc2374b2b81802990da30c96756aab54d77399c Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 22:11:11 2018 +0200 Parsing of separator commit f7a61737f1ad4460ba20ca9b2e86eb21468abb33 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:29:23 2018 +0200 Almost separator in options commit ac8841cf3b9c80914bc3271ad9b9ff4ae9ba48a7 Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 14:16:59 2018 +0200 Separator in parseCSV commit 92a8b9f6ba77ea4237f769641e03029ac88542ea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 13:30:41 2018 +0200 separator option commit ec417a81ae625647cf35e61776cdf02bdb2c6aea Author: Luca Molteni <volothamp@gmail.com> Date: Thu Jun 21 10:45:26 2018 +0200 Removed one qualified import commit 8b2f386c2f780adcd34cff3de7edceacc1d325a7 Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 14:01:12 2018 +0200 Removed string conversions commit a14d0e099e28a286bb81770cfc9cb8f5c7e5cf1f Author: Luca Molteni <volothamp@gmail.com> Date: Wed Jun 20 10:23:20 2018 +0200 custom delimiter in cassava commit 694d48e2bc1ada0037b90367c017f3082f68ed45 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:51:54 2018 +0200 Use Text.getContents - remove UTF-8 compatibility library commit a7ada2cc60033ebdd796ca34cc2ec69a4f387843 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:49:34 2018 +0200 todo list commit 58ec47d3987909f6bace50e3e647e30dadd5bf03 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 17:45:22 2018 +0200 CSV test now has unicode characters commit b7851e94c3f1683b63ec7250a12bcde3b7bed691 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 16:59:39 2018 +0200 Use decode from Text commit 79f59fd28ccaca08fcd718fcd8d00b1c1d65d7e1 Author: Luca Molteni <volothamp@gmail.com> Date: Sun Jun 10 13:28:57 2018 +0200 Use Text and Lazy Bytestring commit 470c9bcb8dc00669beb4ef0303a1e7d9f7aecc89 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:30:22 2018 +0200 Use megaparsec error commit f978848ba249ef4f67b855bea5d4e549290c205c Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:22:07 2018 +0200 Renamed qualify and remove Parsec commit 152587fde204c43a55798d212e43f37cd3038c2e Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 15:12:36 2018 +0200 Use cassava mega parsec commit cf281577a3d3a071196484a6fc8485f2ea1f7d67 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 14:01:47 2018 +0200 Removed Data.Vector commit 1272e8e758369d8cc5778029a705b277355a5029 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:16:18 2018 +0200 Removed Parsec ParseError commit ae07f043135a19307fd65b281ade37a74c76acb2 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 12:06:14 2018 +0200 Type sinonim for ParsecError commit 8e15b253c11bd1c0c35a7641aeb18aa54e0ba9b0 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:16:08 2018 +0200 Replaced with typeclasses commit 1ed46f9c175603611325f3d377004e4b85f29377 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 11:01:33 2018 +0200 Replaced Text/CSV with Cassava commit 362f4111b5854145703174b976fc7acbd71b8783 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 10:34:37 2018 +0200 Use cassava parsin instead of Text/CSV commit 83e678e371618687cf7c15a4e2cfa67f570b6b64 Author: Luca Molteni <volothamp@gmail.com> Date: Sat Jun 9 08:22:51 2018 +0200 Text CSV error messages commit f922df71d274beeacab9fb2530b16c97f005cc08 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:45:20 2018 +0200 Better types commit edd130781c84790a53bff2283e6041eb8232e7cf Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 21:34:59 2018 +0200 Conversion to Text CSV type commit 0799383214483018ad2d977a3c8022414959c2b2 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 16:06:21 2018 +0200 First function with cassava commit e92aeb151ff527b383ff3d0ced7764e81b71af82 Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:47:34 2018 +0200 Added cassava as dependency commit 5ea005c558a3939af7e5f0cd735a9b4da931228e Author: Luca Molteni <volothamp@gmail.com> Date: Fri Jun 8 13:18:47 2018 +0200 Better .gitignore for multi idea modules
2018-09-07 20:12:13 +03:00
,separator_ = fromMaybe ',' (maybecharopt "separator" rawopts)
,aliases_ = listofstringopt "alias" rawopts
,anon_ = boolopt "anon" rawopts
,ignore_assertions_ = boolopt "ignore-assertions" rawopts
,new_ = boolopt "new" rawopts
,new_save_ = True
,pivot_ = stringopt "pivot" rawopts
,auto_ = boolopt "auto" rawopts
}
--- * parsing utilities
2018-08-04 18:11:32 +03:00
-- | Run a text parser in the identity monad. See also: parseWithState.
2018-09-30 04:32:08 +03:00
runTextParser, rtp
:: TextParser Identity a -> Text -> Either (ParseErrorBundle Text CustomErr) a
runTextParser p t = runParser p "" t
lib: textification: parse stream 10% more allocation, but 35% lower maximum residency, and slightly quicker. hledger -f data/100x100x10.journal stats <<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>> <<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>> hledger -f data/1000x1000x10.journal stats <<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>> <<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>> hledger -f data/10000x1000x10.journal stats <<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>> <<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>> hledger -f data/100000x1000x10.journal stats <<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>> <<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
rtp = runTextParser
2018-08-04 18:11:32 +03:00
-- | Run a journal parser in some monad. See also: parseWithState.
2018-09-30 04:32:08 +03:00
runJournalParser, rjp
:: Monad m
=> JournalParser m a -> Text -> m (Either (ParseErrorBundle Text CustomErr) a)
2018-05-25 06:18:55 +03:00
runJournalParser p t = runParserT (evalStateT p mempty) "" t
rjp = runJournalParser
-- | Run an erroring journal parser in some monad. See also: parseWithState.
runErroringJournalParser, rejp
:: Monad m
=> ErroringJournalParser m a
-> Text
2018-09-30 04:32:08 +03:00
-> m (Either FinalParseError (Either (ParseErrorBundle Text CustomErr) a))
runErroringJournalParser p t =
runExceptT $ runParserT (evalStateT p mempty) "" t
rejp = runErroringJournalParser
genericSourcePos :: SourcePos -> GenericSourcePos
genericSourcePos p = GenericSourcePos (sourceName p) (fromIntegral . unPos $ sourceLine p) (fromIntegral . unPos $ sourceColumn p)
-- | Construct a generic start & end line parse position from start and end megaparsec SourcePos's.
journalSourcePos :: SourcePos -> SourcePos -> GenericSourcePos
journalSourcePos p p' = JournalSourcePos (sourceName p) (fromIntegral . unPos $ sourceLine p, fromIntegral $ line')
where line'
| (unPos $ sourceColumn p') == 1 = unPos (sourceLine p') - 1
| otherwise = unPos $ sourceLine p' -- might be at end of file withat last new-line
-- | Given a megaparsec ParsedJournal parser, input options, file
-- path and file content: parse and finalise a Journal, or give an error.
parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts
-> FilePath -> Text -> ExceptT String IO Journal
parseAndFinaliseJournal parser iopts f txt = do
y <- liftIO getCurrentYear
let initJournal = nulljournal{ jparsedefaultyear = Just y, jincludefilestack = [f] }
eep <- liftIO $ runExceptT $ runParserT (evalStateT parser initJournal) f txt
-- TODO: urgh.. clean this up somehow
case eep of
Left finalParseError -> throwError $ finalErrorBundlePretty $ attachSource f txt finalParseError
Right ep -> case ep of
Left e -> throwError $ customErrorBundlePretty e
Right pj -> finaliseJournal iopts f txt pj
-- | Like parseAndFinaliseJournal but takes a (non-Erroring) JournalParser.
-- Used for timeclock/timedot.
-- TODO: get rid of this, use parseAndFinaliseJournal instead
parseAndFinaliseJournal' :: JournalParser IO ParsedJournal -> InputOpts
-> FilePath -> Text -> ExceptT String IO Journal
parseAndFinaliseJournal' parser iopts f txt = do
y <- liftIO getCurrentYear
let initJournal = nulljournal
{ jparsedefaultyear = Just y
, jincludefilestack = [f] }
ep <- liftIO $ runParserT (evalStateT parser initJournal) f txt
-- see notes above
case ep of
2018-09-30 04:32:08 +03:00
Left e -> throwError $ customErrorBundlePretty e
Right pj -> finaliseJournal iopts f txt pj
-- | Post-process a Journal that has just been parsed or generated, in this order:
--
-- - apply canonical amount styles,
--
-- - save misc info and reverse transactions into their original parse order,
--
-- - evaluate balance assignments and balance each transaction,
--
-- - apply transaction modifiers (auto postings) if enabled,
--
-- - check balance assertions if enabled.
--
finaliseJournal :: InputOpts -> FilePath -> Text -> Journal -> ExceptT String IO Journal
finaliseJournal iopts f txt pj = do
t <- liftIO getClockTime
-- Infer and apply canonical styles for each commodity (or fail).
-- TODO: since #903's refactoring for hledger 1.12,
-- journalApplyCommodityStyles here is seeing the
-- transactions before they get reversesd to normal order.
case journalApplyCommodityStyles pj of
Left e -> throwError e
Right pj' ->
-- Finalise the parsed journal.
let fj =
if auto_ iopts && (not . null . jtxnmodifiers) pj
then
-- When automatic postings are active, we finalise twice:
-- once before and once after. However, if we are running it
-- twice, we don't check assertions the first time (they might
-- be false pending modifiers) and we don't reorder the second
-- time. If we are only running once, we reorder and follow
-- the options for checking assertions.
--
-- first pass, doing most of the work
(
(journalModifyTransactions <$>) $ -- add auto postings after balancing ? #893b fails
journalBalanceTransactions False $ -- balance transactions without checking assertions
-- journalModifyTransactions <$> -- add auto postings before balancing ? probably #893a, #928, #938 fail
journalReverse $
journalSetLastReadTime t $
journalAddFile (f, txt) $
pj')
-- balance transactions a second time, now just checking balance assertions
>>= (\j ->
journalBalanceTransactions (not $ ignore_assertions_ iopts) $
j)
else
-- automatic postings are not active
journalBalanceTransactions (not $ ignore_assertions_ iopts) $
journalReverse $
journalSetLastReadTime t $
journalAddFile (f, txt) $
pj'
in
case fj of
Left e -> throwError e
Right j -> return j
setYear :: Year -> JournalParser m ()
setYear y = modify' (\j -> j{jparsedefaultyear=Just y})
getYear :: JournalParser m (Maybe Year)
getYear = fmap jparsedefaultyear get
setDefaultCommodityAndStyle :: (CommoditySymbol,AmountStyle) -> JournalParser m ()
setDefaultCommodityAndStyle cs = modify' (\j -> j{jparsedefaultcommodity=Just cs})
getDefaultCommodityAndStyle :: JournalParser m (Maybe (CommoditySymbol,AmountStyle))
getDefaultCommodityAndStyle = jparsedefaultcommodity `fmap` get
-- | Get amount style associated with default currency.
--
-- Returns 'AmountStyle' used to defined by a latest default commodity directive
-- prior to current position within this file or its parents.
getDefaultAmountStyle :: JournalParser m (Maybe AmountStyle)
getDefaultAmountStyle = fmap snd <$> getDefaultCommodityAndStyle
-- | Lookup currency-specific amount style.
--
-- Returns 'AmountStyle' used in commodity directive within current journal
-- prior to current position or in its parents files.
getAmountStyle :: CommoditySymbol -> JournalParser m (Maybe AmountStyle)
getAmountStyle commodity = do
specificStyle <- maybe Nothing cformat . M.lookup commodity . jcommodities <$> get
defaultStyle <- fmap snd <$> getDefaultCommodityAndStyle
let effectiveStyle = listToMaybe $ catMaybes [specificStyle, defaultStyle]
return effectiveStyle
journal: account directives can declare account types Previously you had to use one of the standard english account names (assets, liabilities..) for top-level accounts, if you wanted to use the bs/bse/cf/is commands. Now, account directives can specify which of the big five categories an account belongs to - asset, liability, equity, revenue or expense - by writing one of the letters A, L, E, R or X two or more spaces after the account name (where the numeric account code used to be). This might change. Some thoughts influencing the current syntax: - easy to type and read - does not require multiple lines - does not depend on any particular account numbering scheme - allows more types later if needed - still anglocentric, but only a little - could be treated as syntactic sugar for account tags later - seems to be compatible with (ignored by) current Ledger The current design permits unlimited account type declarations anywhere in the account tree. So you could declare a liability account somewhere under assets, and maybe a revenue account under that, and another asset account even further down. In such cases you start to see oddities like accounts appearing in multiple places in a tree-mode report. In theory the reports will still behave reasonably, but this has not been tested too hard. In any case this is clearly too much freedom. I have left it this way, for now, in case it helps with: - modelling contra accounts ? - multiple files. I suspect the extra expressiveness may come in handy when combining multiple files with account type declarations, rewriting account names, apply parent accounts etc. If we only allowed type declarations on top-level accounts, or only allowed a single account of each type, complications seem likely.
2018-09-27 04:34:48 +03:00
addDeclaredAccountType :: AccountName -> AccountType -> JournalParser m ()
addDeclaredAccountType acct atype =
journal: account directives can declare account types Previously you had to use one of the standard english account names (assets, liabilities..) for top-level accounts, if you wanted to use the bs/bse/cf/is commands. Now, account directives can specify which of the big five categories an account belongs to - asset, liability, equity, revenue or expense - by writing one of the letters A, L, E, R or X two or more spaces after the account name (where the numeric account code used to be). This might change. Some thoughts influencing the current syntax: - easy to type and read - does not require multiple lines - does not depend on any particular account numbering scheme - allows more types later if needed - still anglocentric, but only a little - could be treated as syntactic sugar for account tags later - seems to be compatible with (ignored by) current Ledger The current design permits unlimited account type declarations anywhere in the account tree. So you could declare a liability account somewhere under assets, and maybe a revenue account under that, and another asset account even further down. In such cases you start to see oddities like accounts appearing in multiple places in a tree-mode report. In theory the reports will still behave reasonably, but this has not been tested too hard. In any case this is clearly too much freedom. I have left it this way, for now, in case it helps with: - modelling contra accounts ? - multiple files. I suspect the extra expressiveness may come in handy when combining multiple files with account type declarations, rewriting account names, apply parent accounts etc. If we only allowed type declarations on top-level accounts, or only allowed a single account of each type, complications seem likely.
2018-09-27 04:34:48 +03:00
modify' (\j -> j{jdeclaredaccounttypes = M.insertWith (++) atype [acct] (jdeclaredaccounttypes j)})
pushParentAccount :: AccountName -> JournalParser m ()
pushParentAccount acct = modify' (\j -> j{jparseparentaccounts = acct : jparseparentaccounts j})
popParentAccount :: JournalParser m ()
popParentAccount = do
j <- get
case jparseparentaccounts j of
[] -> unexpected (Tokens ('E' :| "nd of apply account block with no beginning"))
(_:rest) -> put j{jparseparentaccounts=rest}
getParentAccount :: JournalParser m AccountName
getParentAccount = fmap (concatAccountNames . reverse . jparseparentaccounts) get
addAccountAlias :: MonadState Journal m => AccountAlias -> m ()
addAccountAlias a = modify' (\(j@Journal{..}) -> j{jparsealiases=a:jparsealiases})
getAccountAliases :: MonadState Journal m => m [AccountAlias]
getAccountAliases = fmap jparsealiases get
clearAccountAliases :: MonadState Journal m => m ()
clearAccountAliases = modify' (\(j@Journal{..}) -> j{jparsealiases=[]})
-- getTransactionCount :: MonadState Journal m => m Integer
-- getTransactionCount = fmap jparsetransactioncount get
--
-- setTransactionCount :: MonadState Journal m => Integer -> m ()
-- setTransactionCount i = modify' (\j -> j{jparsetransactioncount=i})
--
-- -- | Increment the transaction index by one and return the new value.
-- incrementTransactionCount :: MonadState Journal m => m Integer
-- incrementTransactionCount = do
-- modify' (\j -> j{jparsetransactioncount=jparsetransactioncount j + 1})
-- getTransactionCount
lib: textification: saved journal source Slightly worse on small files, better on large ones. hledger -f data/100x100x10.journal stats <<ghc: 39305392 bytes, 77 GCs, 196354/268584 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.007 elapsed), 0.014 MUT (0.027 elapsed), 0.011 GC (0.111 elapsed) :ghc>> <<ghc: 39307728 bytes, 77 GCs, 196909/270248 avg/max bytes residency (3 samples), 2M in use, 0.001 INIT (0.010 elapsed), 0.015 MUT (0.028 elapsed), 0.012 GC (0.116 elapsed) :ghc>> hledger -f data/1000x1000x10.journal stats <<ghc: 314285912 bytes, 612 GCs, 2064811/6597608 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.002 elapsed), 0.126 MUT (0.134 elapsed), 0.059 GC (0.069 elapsed) :ghc>> <<ghc: 314271368 bytes, 612 GCs, 2070227/6628024 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.137 MUT (0.143 elapsed), 0.059 GC (0.068 elapsed) :ghc>> hledger -f data/10000x1000x10.journal stats <<ghc: 3070033264 bytes, 5965 GCs, 12699294/62962464 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.000 elapsed), 1.245 MUT (1.300 elapsed), 0.498 GC (0.558 elapsed) :ghc>> <<ghc: 3070006752 bytes, 5973 GCs, 12687314/62848920 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.257 MUT (1.281 elapsed), 0.496 GC (0.554 elapsed) :ghc>> hledger -f data/100000x1000x10.journal stats <<ghc: 30753465088 bytes, 59763 GCs, 117723618/666643528 avg/max bytes residency (14 samples), 1589M in use, 0.000 INIT (0.002 elapsed), 12.536 MUT (12.793 elapsed), 5.978 GC (7.155 elapsed) :ghc>> <<ghc: 30753367256 bytes, 59811 GCs, 117723236/666627528 avg/max bytes residency (14 samples), 1590M in use, 0.001 INIT (0.012 elapsed), 12.923 MUT (13.169 elapsed), 5.981 GC (6.860 elapsed) :ghc>>
2016-05-24 05:24:39 +03:00
journalAddFile :: (FilePath,Text) -> Journal -> Journal
journalAddFile f j@Journal{jfiles=fs} = j{jfiles=fs++[f]}
-- append, unlike the other fields, even though we do a final reverse,
-- to compensate for additional reversal due to including/monoid-concatting
--- * parsers
2018-05-24 07:36:19 +03:00
--- ** transaction bits
statusp :: TextParser m Status
statusp =
choice'
[ skipMany spacenonewline >> char '*' >> return Cleared
, skipMany spacenonewline >> char '!' >> return Pending
, return Unmarked
]
codep :: TextParser m Text
codep = option "" $ do
try $ do
skipSome spacenonewline
char '('
code <- takeWhileP Nothing $ \c -> c /= ')' && c /= '\n'
char ')' <?> "closing bracket ')' for transaction code"
pure code
2018-06-06 08:52:28 +03:00
descriptionp :: TextParser m Text
2018-05-24 07:36:19 +03:00
descriptionp = takeWhileP Nothing (not . semicolonOrNewline)
where semicolonOrNewline c = c == ';' || c == '\n'
--- ** dates
-- | 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.
datep :: JournalParser m Day
datep = do
2018-05-24 07:36:19 +03:00
mYear <- getYear
lift $ datep' mYear
datep' :: Maybe Year -> TextParser m Day
2018-05-23 05:17:51 +03:00
datep' mYear = do
2018-09-30 04:32:08 +03:00
startOffset <- getOffset
2018-05-23 05:17:51 +03:00
d1 <- decimal <?> "year or month"
sep <- satisfy isDateSepChar <?> "date separator"
d2 <- decimal <?> "month or day"
2018-09-30 04:32:08 +03:00
fullDate startOffset d1 sep d2 <|> partialDate startOffset mYear d1 sep d2
<?> "full or partial date"
2018-05-23 05:17:51 +03:00
where
2018-09-30 04:32:08 +03:00
fullDate :: Int -> Integer -> Char -> Int -> TextParser m Day
fullDate startOffset year sep1 month = do
2018-05-23 05:17:51 +03:00
sep2 <- satisfy isDateSepChar <?> "date separator"
day <- decimal <?> "day"
2018-09-30 04:32:08 +03:00
endOffset <- getOffset
2018-05-23 05:17:51 +03:00
let dateStr = show year ++ [sep1] ++ show month ++ [sep2] ++ show day
2018-09-30 04:32:08 +03:00
when (sep1 /= sep2) $ customFailure $ parseErrorAtRegion startOffset endOffset $
2018-05-23 05:17:51 +03:00
"invalid date (mixing date separators is not allowed): " ++ dateStr
2018-05-24 07:36:19 +03:00
case fromGregorianValid year month day of
2018-09-30 04:32:08 +03:00
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
2018-06-06 20:15:38 +03:00
"well-formed but invalid date: " ++ dateStr
Just date -> pure $! date
2018-05-23 05:17:51 +03:00
2018-06-06 20:15:38 +03:00
partialDate
2018-09-30 04:32:08 +03:00
:: Int -> Maybe Year -> Integer -> Char -> Int -> TextParser m Day
partialDate startOffset mYear month sep day = do
endOffset <- getOffset
2018-06-06 20:15:38 +03:00
case mYear of
Just year ->
case fromGregorianValid year (fromIntegral month) day of
2018-09-30 04:32:08 +03:00
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
2018-06-06 20:15:38 +03:00
"well-formed but invalid date: " ++ dateStr
Just date -> pure $! date
where dateStr = show year ++ [sep] ++ show month ++ [sep] ++ show day
2018-09-30 04:32:08 +03:00
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
2018-06-06 20:15:38 +03:00
"partial date "++dateStr++" found, but the current year is unknown"
where dateStr = show month ++ [sep] ++ show day
2018-05-23 05:17:51 +03:00
{-# INLINABLE datep' #-}
-- | 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).
datetimep :: JournalParser m LocalTime
datetimep = do
mYear <- getYear
lift $ datetimep' mYear
datetimep' :: Maybe Year -> TextParser m LocalTime
datetimep' mYear = do
day <- datep' mYear
skipSome spacenonewline
time <- timeOfDay
optional timeZone -- ignoring time zones
pure $ LocalTime day time
where
timeOfDay :: TextParser m TimeOfDay
timeOfDay = do
2018-09-30 04:32:08 +03:00
off1 <- getOffset
h' <- twoDigitDecimal <?> "hour"
2018-09-30 04:32:08 +03:00
off2 <- getOffset
unless (h' >= 0 && h' <= 23) $ customFailure $
2018-09-30 04:32:08 +03:00
parseErrorAtRegion off1 off2 "invalid time (bad hour)"
char ':' <?> "':' (hour-minute separator)"
2018-09-30 04:32:08 +03:00
off3 <- getOffset
m' <- twoDigitDecimal <?> "minute"
2018-09-30 04:32:08 +03:00
off4 <- getOffset
unless (m' >= 0 && m' <= 59) $ customFailure $
2018-09-30 04:32:08 +03:00
parseErrorAtRegion off3 off4 "invalid time (bad minute)"
s' <- option 0 $ do
char ':' <?> "':' (minute-second separator)"
2018-09-30 04:32:08 +03:00
off5 <- getOffset
s' <- twoDigitDecimal <?> "second"
2018-09-30 04:32:08 +03:00
off6 <- getOffset
unless (s' >= 0 && s' <= 59) $ customFailure $
2018-09-30 04:32:08 +03:00
parseErrorAtRegion off5 off6 "invalid time (bad second)"
-- we do not support leap seconds
pure s'
pure $ TimeOfDay h' m' (fromIntegral s')
twoDigitDecimal :: TextParser m Int
twoDigitDecimal = do
d1 <- digitToInt <$> digitChar
d2 <- digitToInt <$> (digitChar <?> "a second digit")
pure $ d1*10 + d2
timeZone :: TextParser m String
timeZone = do
plusminus <- satisfy $ \c -> c == '-' || c == '+'
fourDigits <- count 4 (digitChar <?> "a digit (for a time zone)")
pure $ plusminus:fourDigits
2018-05-24 07:36:19 +03:00
secondarydatep :: Day -> TextParser m Day
secondarydatep primaryDate = char '=' *> datep' (Just primaryYear)
where primaryYear = first3 $ toGregorian primaryDate
--- ** account names
-- | Parse an account name (plus one following space if present),
-- then apply any parent account prefix and/or account aliases currently in effect,
-- in that order. (Ie first add the parent account prefix, then rewrite with aliases).
modifiedaccountnamep :: JournalParser m AccountName
modifiedaccountnamep = do
parent <- getParentAccount
aliases <- getAccountAliases
a <- lift accountnamep
return $!
accountNameApplyAliases aliases $
-- XXX accountNameApplyAliasesMemo ? doesn't seem to make a difference (retest that function)
joinAccountNames parent
a
-- | Parse an account name, plus one following space if present.
-- Account names have one or more parts separated by the account separator character,
-- and are terminated by two or more spaces (or end of input).
-- Each part is at least one character long, may have single spaces inside it,
-- and starts with a non-whitespace.
-- Note, this means "{account}", "%^!" and ";comment" are all accepted
-- (parent parsers usually prevent/consume the last).
-- It should have required parts to start with an alphanumeric;
-- for now it remains as-is for backwards compatibility.
accountnamep :: TextParser m AccountName
accountnamep = singlespacedtextp
-- | Parse any text beginning with a non-whitespace character, until a
-- double space or the end of input.
singlespacedtextp :: TextParser m T.Text
singlespacedtextp = singlespacedtextsatisfyingp (const True)
-- | Similar to 'singlespacedtextp', except that the text must only contain
-- characters satisfying the given predicate.
singlespacedtextsatisfyingp :: (Char -> Bool) -> TextParser m T.Text
singlespacedtextsatisfyingp pred = do
firstPart <- partp
otherParts <- many $ try $ singlespacep *> partp
pure $! T.unwords $ firstPart : otherParts
2018-05-22 04:09:47 +03:00
where
partp = takeWhile1P Nothing (\c -> pred c && not (isSpace c))
-- | Parse one non-newline whitespace character that is not followed by another one.
singlespacep :: TextParser m ()
singlespacep = void spacenonewline *> notFollowedBy spacenonewline
--- ** amounts
-- | Parse whitespace then an amount, with an optional left or right
-- currency symbol and optional price, or return the special
-- "missing" marker amount.
2018-06-06 08:52:28 +03:00
spaceandamountormissingp :: JournalParser m MixedAmount
spaceandamountormissingp =
2018-05-24 07:36:19 +03:00
option missingmixedamt $ try $ do
lift $ skipSome spacenonewline
Mixed . (:[]) <$> amountp
-- | 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.
2018-06-06 08:52:28 +03:00
amountp :: JournalParser m Amount
amountp = label "amount" $ do
amount <- amountwithoutpricep
lift $ skipMany spacenonewline
mprice <- priceamountp
pure $ amount { aprice = mprice }
2018-06-06 08:52:28 +03:00
amountwithoutpricep :: JournalParser m Amount
amountwithoutpricep = do
(mult, sign) <- lift $ (,) <$> multiplierp <*> signp
leftsymbolamountp mult sign <|> rightornosymbolamountp mult sign
where
leftsymbolamountp :: Bool -> (Decimal -> Decimal) -> JournalParser m Amount
leftsymbolamountp mult sign = label "amount" $ do
c <- lift commoditysymbolp
suggestedStyle <- getAmountStyle c
commodityspaced <- lift $ skipMany' spacenonewline
sign2 <- lift $ signp
2018-09-30 04:32:08 +03:00
offBeforeNum <- getOffset
ambiguousRawNum <- lift rawnumberp
mExponent <- lift $ optional $ try exponentp
2018-09-30 04:32:08 +03:00
offAfterNum <- getOffset
let numRegion = (offBeforeNum, offAfterNum)
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps}
return $ nullamt{acommodity=c, aquantity=sign (sign2 q), aismultiplier=mult, astyle=s, aprice=Nothing}
rightornosymbolamountp :: Bool -> (Decimal -> Decimal) -> JournalParser m Amount
rightornosymbolamountp mult sign = label "amount" $ do
2018-09-30 04:32:08 +03:00
offBeforeNum <- getOffset
ambiguousRawNum <- lift rawnumberp
mExponent <- lift $ optional $ try exponentp
2018-09-30 04:32:08 +03:00
offAfterNum <- getOffset
let numRegion = (offBeforeNum, offAfterNum)
mSpaceAndCommodity <- lift $ optional $ try $ (,) <$> skipMany' spacenonewline <*> commoditysymbolp
case mSpaceAndCommodity of
-- right symbol amount
Just (commodityspaced, c) -> do
suggestedStyle <- getAmountStyle c
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps}
return $ nullamt{acommodity=c, aquantity=sign q, aismultiplier=mult, astyle=s, aprice=Nothing}
-- no symbol amount
Nothing -> do
suggestedStyle <- getDefaultAmountStyle
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
-- if a default commodity has been set, apply it and its style to this amount
-- (unless it's a multiplier in an automated posting)
defcs <- getDefaultCommodityAndStyle
let (c,s) = case (mult, defcs) of
(False, Just (defc,defs)) -> (defc, defs{asprecision=max (asprecision defs) prec})
_ -> ("", amountstyle{asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps})
return $ nullamt{acommodity=c, aquantity=sign q, aismultiplier=mult, astyle=s, aprice=Nothing}
-- For reducing code duplication. Doesn't parse anything. Has the type
-- of a parser only in order to throw parse errors (for convenience).
interpretNumber
2018-09-30 04:32:08 +03:00
:: (Int, Int) -- offsets
-> Maybe AmountStyle
-> Either AmbiguousNumber RawNumber
-> Maybe Int
-> TextParser m (Quantity, Int, Maybe Char, Maybe DigitGroupStyle)
interpretNumber posRegion suggestedStyle ambiguousNum mExp =
let rawNum = either (disambiguateNumber suggestedStyle) id ambiguousNum
in case fromRawNumber rawNum mExp of
Left errMsg -> customFailure $
uncurry parseErrorAtRegion posRegion errMsg
Right res -> pure res
-- | Parse an amount from a string, or get an error.
amountp' :: String -> Amount
amountp' s =
case runParser (evalStateT (amountp <* eof) mempty) "" (T.pack s) of
lib: textification: parse stream 10% more allocation, but 35% lower maximum residency, and slightly quicker. hledger -f data/100x100x10.journal stats <<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>> <<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>> hledger -f data/1000x1000x10.journal stats <<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>> <<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>> hledger -f data/10000x1000x10.journal stats <<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>> <<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>> hledger -f data/100000x1000x10.journal stats <<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>> <<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
Right amt -> amt
Left err -> error' $ show err -- XXX should throwError
-- | Parse a mixed amount from a string, or get an error.
mamountp' :: String -> MixedAmount
mamountp' = Mixed . (:[]) . amountp'
signp :: Num a => TextParser m (a -> a)
signp = char '-' *> pure negate <|> char '+' *> pure id <|> pure id
multiplierp :: TextParser m Bool
2018-05-24 07:36:19 +03:00
multiplierp = option False $ char '*' *> pure True
-- | This is like skipMany but it returns True if at least one element
-- was skipped. This is helpful if youre just using many to check if
-- the resulting list is empty or not.
skipMany' :: MonadPlus m => m a -> m Bool
skipMany' p = go False
where
go !isNull = do
more <- option False (True <$ p)
if more
then go True
else pure isNull
commoditysymbolp :: TextParser m CommoditySymbol
2018-05-25 05:34:00 +03:00
commoditysymbolp =
quotedcommoditysymbolp <|> simplecommoditysymbolp <?> "commodity symbol"
quotedcommoditysymbolp :: TextParser m CommoditySymbol
quotedcommoditysymbolp =
2018-05-24 07:36:19 +03:00
between (char '"') (char '"') $ takeWhile1P Nothing f
where f c = c /= ';' && c /= '\n' && c /= '\"'
simplecommoditysymbolp :: TextParser m CommoditySymbol
simplecommoditysymbolp = takeWhile1P Nothing (not . isNonsimpleCommodityChar)
priceamountp :: JournalParser m (Maybe AmountPrice)
priceamountp = option Nothing $ do
char '@'
2018-05-25 05:34:00 +03:00
priceConstructor <- char '@' *> pure TotalPrice <|> pure UnitPrice
2018-05-24 07:36:19 +03:00
lift (skipMany spacenonewline)
priceAmount <- amountwithoutpricep <?> "unpriced amount (specifying a price)"
2018-05-24 07:36:19 +03:00
pure $ Just $ priceConstructor priceAmount
balanceassertionp :: JournalParser m BalanceAssertion
balanceassertionp = do
sourcepos <- genericSourcePos <$> lift getSourcePos
char '='
istotal <- fmap isJust $ optional $ try $ char '='
isinclusive <- fmap isJust $ optional $ try $ char '*'
2018-05-24 07:36:19 +03:00
lift (skipMany spacenonewline)
-- this amount can have a price; balance assertions ignore it,
-- but balance assignments will use it
a <- amountp <?> "amount (for a balance assertion or assignment)"
return BalanceAssertion
{ baamount = a
, batotal = istotal
, bainclusive = isinclusive
, baposition = sourcepos
}
-- Parse a Ledger-style fixed lot price: {=PRICE}
-- https://www.ledger-cli.org/3.0/doc/ledger3.html#Fixing-Lot-Prices .
-- Currently we ignore these (hledger's @ PRICE is equivalent),
-- and we don't parse a Ledger-style {PRICE} (equivalent to Ledger's @ PRICE).
2018-06-06 08:52:28 +03:00
fixedlotpricep :: JournalParser m (Maybe Amount)
fixedlotpricep = optional $ do
try $ do
lift (skipMany spacenonewline)
char '{'
2018-05-24 07:36:19 +03:00
lift (skipMany spacenonewline)
char '='
lift (skipMany spacenonewline)
a <- amountwithoutpricep <?> "unpriced amount (for an ignored ledger-style fixed lot price)"
2018-05-24 07:36:19 +03:00
lift (skipMany spacenonewline)
char '}'
return a
-- | Parse a string representation of a number for its value and display
-- attributes.
--
-- 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.
--
-- 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.
--
numberp :: Maybe AmountStyle -> TextParser m (Quantity, Int, Maybe Char, Maybe DigitGroupStyle)
numberp suggestedStyle = label "number" $ do
2017-10-28 21:07:24 +03:00
-- a number is an optional sign followed by a sequence of digits possibly
-- interspersed with periods, commas, or both
2018-07-16 17:28:58 +03:00
-- dbgparse 0 "numberp"
2017-10-28 21:07:24 +03:00
sign <- signp
rawNum <- either (disambiguateNumber suggestedStyle) id <$> rawnumberp
mExp <- optional $ try $ exponentp
dbg8 "numberp suggestedStyle" suggestedStyle `seq` return ()
case dbg8 "numberp quantity,precision,mdecimalpoint,mgrps"
$ fromRawNumber rawNum mExp of
Left errMsg -> Fail.fail errMsg
Right (q, p, d, g) -> pure (sign q, p, d, g)
2017-10-28 21:07:24 +03:00
exponentp :: TextParser m Int
exponentp = char' 'e' *> signp <*> decimal <?> "exponent"
-- | Interpret a raw number as a decimal number.
--
2018-04-21 07:39:06 +03:00
-- Returns:
-- - the decimal number
-- - the precision (number of digits after the decimal point)
2018-04-21 07:39:06 +03:00
-- - the decimal point character, if any
-- - the digit group style, if any (digit group character and sizes of digit groups)
fromRawNumber
:: RawNumber
-> Maybe Int
-> Either String
(Quantity, Int, Maybe Char, Maybe DigitGroupStyle)
fromRawNumber raw mExp = case raw of
NoSeparators digitGrp mDecimals ->
2018-05-27 07:54:31 +03:00
let mDecPt = fmap fst mDecimals
decimalGrp = maybe mempty snd mDecimals
(quantity, precision) =
maybe id applyExp mExp $ toQuantity digitGrp decimalGrp
2018-05-27 07:54:31 +03:00
in Right (quantity, precision, mDecPt, Nothing)
2018-05-27 07:54:31 +03:00
WithSeparators digitSep digitGrps mDecimals -> case mExp of
Nothing ->
2018-05-27 07:54:31 +03:00
let mDecPt = fmap fst mDecimals
decimalGrp = maybe mempty snd mDecimals
digitGroupStyle = DigitGroups digitSep (groupSizes digitGrps)
2018-05-27 07:54:31 +03:00
(quantity, precision) = toQuantity (mconcat digitGrps) decimalGrp
2018-05-27 07:54:31 +03:00
in Right (quantity, precision, mDecPt, Just digitGroupStyle)
Just _ -> Left
"invalid number: mixing digit separators with exponents is not allowed"
where
-- Outputs digit group sizes from least significant to most significant
groupSizes :: [DigitGrp] -> [Int]
groupSizes digitGrps = reverse $ case map digitGroupLength digitGrps of
(a:b:cs) | a < b -> b:cs
gs -> gs
toQuantity :: DigitGrp -> DigitGrp -> (Quantity, Int)
toQuantity preDecimalGrp postDecimalGrp = (quantity, precision)
where
quantity = Decimal (fromIntegral precision)
(digitGroupNumber $ preDecimalGrp <> postDecimalGrp)
precision = digitGroupLength postDecimalGrp
applyExp :: Int -> (Decimal, Int) -> (Decimal, Int)
applyExp exponent (quantity, precision) =
(quantity * 10^^exponent, max 0 (precision - exponent))
disambiguateNumber :: Maybe AmountStyle -> AmbiguousNumber -> RawNumber
disambiguateNumber suggestedStyle (AmbiguousNumber grp1 sep grp2) =
-- If present, use the suggested style to disambiguate;
-- otherwise, assume that the separator is a decimal point where possible.
if isDecimalPointChar sep &&
maybe True (sep `isValidDecimalBy`) suggestedStyle
then NoSeparators grp1 (Just (sep, grp2))
else WithSeparators sep [grp1, grp2] Nothing
where
isValidDecimalBy :: Char -> AmountStyle -> Bool
isValidDecimalBy c = \case
AmountStyle{asdecimalpoint = Just d} -> d == c
AmountStyle{asdigitgroups = Just (DigitGroups g _)} -> g /= c
AmountStyle{asprecision = 0} -> False
_ -> True
-- | Parse and interpret the structure of a number without external hints.
-- Numbers are digit strings, possibly separated into digit groups by one
-- of two types of separators. (1) Numbers may optionally have a decimal
-- mark, which may be either a period or comma. (2) Numbers may
-- optionally contain digit group marks, which must all be either a
-- period, a comma, or a space.
--
-- It is our task to deduce the characters used as decimal mark and
-- digit group mark, based on the allowed syntax. For instance, we
-- make use of the fact that a decimal mark can occur at most once and
-- must be to the right of all digit group marks.
--
-- >>> parseTest rawnumberp "1,234,567.89"
-- Right (WithSeparators ',' ["1","234","567"] (Just ('.',"89")))
-- >>> parseTest rawnumberp "1,000"
-- Left (AmbiguousNumber "1" ',' "000")
-- >>> parseTest rawnumberp "1 000"
-- Right (WithSeparators ' ' ["1","000"] Nothing)
--
rawnumberp :: TextParser m (Either AmbiguousNumber RawNumber)
rawnumberp = label "number" $ do
rawNumber <- fmap Right leadingDecimalPt <|> leadingDigits
-- Guard against mistyped numbers
mExtraDecimalSep <- optional $ lookAhead $ satisfy isDecimalPointChar
when (isJust mExtraDecimalSep) $
Fail.fail "invalid number (invalid use of separator)"
mExtraFragment <- optional $ lookAhead $ try $
2018-09-30 04:32:08 +03:00
char ' ' *> getOffset <* digitChar
case mExtraFragment of
2018-09-30 04:32:08 +03:00
Just off -> customFailure $
parseErrorAt off "invalid number (excessive trailing digits)"
Nothing -> pure ()
return $ dbg8 "rawnumberp" rawNumber
where
leadingDecimalPt :: TextParser m RawNumber
leadingDecimalPt = do
decPt <- satisfy isDecimalPointChar
decGrp <- digitgroupp
pure $ NoSeparators mempty (Just (decPt, decGrp))
leadingDigits :: TextParser m (Either AmbiguousNumber RawNumber)
leadingDigits = do
grp1 <- digitgroupp
withSeparators grp1 <|> fmap Right (trailingDecimalPt grp1)
<|> pure (Right $ NoSeparators grp1 Nothing)
withSeparators :: DigitGrp -> TextParser m (Either AmbiguousNumber RawNumber)
withSeparators grp1 = do
(sep, grp2) <- try $ (,) <$> satisfy isDigitSeparatorChar <*> digitgroupp
grps <- many $ try $ char sep *> digitgroupp
let digitGroups = grp1 : grp2 : grps
fmap Right (withDecimalPt sep digitGroups)
<|> pure (withoutDecimalPt grp1 sep grp2 grps)
withDecimalPt :: Char -> [DigitGrp] -> TextParser m RawNumber
withDecimalPt digitSep digitGroups = do
decPt <- satisfy $ \c -> isDecimalPointChar c && c /= digitSep
decDigitGrp <- option mempty digitgroupp
pure $ WithSeparators digitSep digitGroups (Just (decPt, decDigitGrp))
withoutDecimalPt
:: DigitGrp
-> Char
-> DigitGrp
-> [DigitGrp]
-> Either AmbiguousNumber RawNumber
withoutDecimalPt grp1 sep grp2 grps
| null grps && isDecimalPointChar sep =
Left $ AmbiguousNumber grp1 sep grp2
| otherwise = Right $ WithSeparators sep (grp1:grp2:grps) Nothing
trailingDecimalPt :: DigitGrp -> TextParser m RawNumber
trailingDecimalPt grp1 = do
decPt <- satisfy isDecimalPointChar
pure $ NoSeparators grp1 (Just (decPt, mempty))
isDecimalPointChar :: Char -> Bool
isDecimalPointChar c = c == '.' || c == ','
isDigitSeparatorChar :: Char -> Bool
isDigitSeparatorChar c = isDecimalPointChar c || c == ' '
-- | Some kinds of number literal we might parse.
data RawNumber
= NoSeparators DigitGrp (Maybe (Char, DigitGrp))
-- ^ A number with no digit group marks (eg 100),
-- or with a leading or trailing comma or period
-- which (apparently) we interpret as a decimal mark (like 100. or .100)
| WithSeparators Char [DigitGrp] (Maybe (Char, DigitGrp))
-- ^ A number with identifiable digit group marks
-- (eg 1,000,000 or 1,000.50 or 1 000)
deriving (Show, Eq)
-- | Another kind of number literal: this one contains either a digit
-- group separator or a decimal mark, we're not sure which (eg 1,000 or 100.50).
data AmbiguousNumber = AmbiguousNumber DigitGrp Char DigitGrp
deriving (Show, Eq)
-- | Description of a single digit group in a number literal.
-- "Thousands" is one well known digit grouping, but there are others.
data DigitGrp = DigitGrp {
digitGroupLength :: !Int, -- ^ The number of digits in this group.
digitGroupNumber :: !Integer -- ^ The natural number formed by this group's digits.
} deriving (Eq)
-- | A custom show instance, showing digit groups as the parser saw them.
instance Show DigitGrp where
show (DigitGrp len num)
| len > 0 = "\"" ++ padding ++ numStr ++ "\""
| otherwise = "\"\""
where numStr = show num
padding = replicate (len - length numStr) '0'
instance Sem.Semigroup DigitGrp where
DigitGrp l1 n1 <> DigitGrp l2 n2 = DigitGrp (l1 + l2) (n1 * 10^l2 + n2)
instance Monoid DigitGrp where
mempty = DigitGrp 0 0
mappend = (Sem.<>)
digitgroupp :: TextParser m DigitGrp
digitgroupp = label "digits"
$ makeGroup <$> takeWhile1P (Just "digit") isDigit
where
makeGroup = uncurry DigitGrp . foldl' step (0, 0) . T.unpack
step (!l, !a) c = (l+1, a*10 + fromIntegral (digitToInt c))
--- ** comments
multilinecommentp :: TextParser m ()
2018-05-11 00:23:19 +03:00
multilinecommentp = startComment *> anyLine `skipManyTill` endComment
where
startComment = string "comment" *> trailingSpaces
endComment = eof <|> string "end comment" *> trailingSpaces
trailingSpaces = skipMany spacenonewline <* newline
anyLine = void $ takeWhileP Nothing (\c -> c /= '\n') *> newline
{-# INLINABLE multilinecommentp #-}
emptyorcommentlinep :: TextParser m ()
emptyorcommentlinep = do
skipMany spacenonewline
skiplinecommentp <|> void newline
where
-- A line (file-level) comment can start with a semicolon, hash, or star
-- (allowing org nodes).
skiplinecommentp :: TextParser m ()
skiplinecommentp = do
satisfy $ \c -> c == ';' || c == '#' || c == '*'
void $ takeWhileP Nothing (\c -> c /= '\n')
optional newline
pure ()
{-# INLINABLE emptyorcommentlinep #-}
-- A parser combinator for parsing (possibly multiline) comments
-- following journal items.
--
-- Several journal items may be followed by comments, which begin with
-- semicolons and extend to the end of the line. Such comments may span
-- multiple lines, but comment lines below the journal item must be
-- preceeded by leading whitespace.
--
-- This parser combinator accepts a parser that consumes all input up
-- until the next newline. This parser should extract the "content" from
-- comments. The resulting parser returns this content plus the raw text
-- of the comment itself.
--
-- See followingcommentp for tests.
--
followingcommentp' :: (Monoid a, Show a) => TextParser m a -> TextParser m (Text, a)
followingcommentp' contentp = do
skipMany spacenonewline
-- there can be 0 or 1 sameLine
sameLine <- try headerp *> ((:[]) <$> match' contentp) <|> pure []
_ <- eolof
-- there can be 0 or more nextLines
nextLines <- many $
try (skipSome spacenonewline *> headerp) *> match' contentp <* eolof
let
-- if there's just a next-line comment, insert an empty same-line comment
-- so the next-line comment doesn't get rendered as a same-line comment.
sameLine' | null sameLine && not (null nextLines) = [("",mempty)]
| otherwise = sameLine
(texts, contents) = unzip $ sameLine' ++ nextLines
strippedCommentText = T.unlines $ map T.strip texts
commentContent = mconcat contents
pure (strippedCommentText, commentContent)
where
headerp = char ';' *> skipMany spacenonewline
{-# INLINABLE followingcommentp' #-}
-- | Parse the text of a (possibly multiline) comment following a journal item.
--
-- >>> rtp followingcommentp "" -- no comment
-- Right ""
-- >>> rtp followingcommentp ";" -- just a (empty) same-line comment. newline is added
-- Right "\n"
-- >>> rtp followingcommentp "; \n"
-- Right "\n"
-- >>> rtp followingcommentp ";\n ;\n" -- a same-line and a next-line comment
-- Right "\n\n"
-- >>> rtp followingcommentp "\n ;\n" -- just a next-line comment. Insert an empty same-line comment so the next-line comment doesn't become a same-line comment.
-- Right "\n\n"
--
followingcommentp :: TextParser m Text
followingcommentp =
fst <$> followingcommentp' (void $ takeWhileP Nothing (/= '\n'))
{-# INLINABLE followingcommentp #-}
-- | Parse a transaction comment and extract its tags.
--
-- The first line of a transaction may be followed by comments, which
-- begin with semicolons and extend to the end of the line. Transaction
-- comments may span multiple lines, but comment lines below the
-- transaction must be preceeded by leading whitespace.
--
-- 2000/1/1 ; a transaction comment starting on the same line ...
-- ; extending to the next line
-- account1 $1
-- account2
--
-- Tags are name-value pairs.
--
-- >>> let getTags (_,tags) = tags
-- >>> let parseTags = fmap getTags . rtp transactioncommentp
--
-- >>> parseTags "; name1: val1, name2:all this is value2"
-- Right [("name1","val1"),("name2","all this is value2")]
--
-- A tag's name must be immediately followed by a colon, without
-- separating whitespace. The corresponding value consists of all the text
-- following the colon up until the next colon or newline, stripped of
-- leading and trailing whitespace.
--
transactioncommentp :: TextParser m (Text, [Tag])
transactioncommentp = followingcommentp' commenttagsp
{-# INLINABLE transactioncommentp #-}
commenttagsp :: TextParser m [Tag]
commenttagsp = do
tagName <- fmap (last . T.split isSpace)
$ takeWhileP Nothing (\c -> c /= ':' && c /= '\n')
atColon tagName <|> pure [] -- if not ':', then either '\n' or EOF
where
atColon :: Text -> TextParser m [Tag]
atColon name = char ':' *> do
if T.null name
then commenttagsp
else do
skipMany spacenonewline
val <- tagValue
let tag = (name, val)
(tag:) <$> commenttagsp
tagValue :: TextParser m Text
tagValue = do
val <- T.strip <$> takeWhileP Nothing (\c -> c /= ',' && c /= '\n')
_ <- optional $ char ','
pure val
{-# INLINABLE commenttagsp #-}
-- | Parse a posting comment and extract its tags and dates.
--
-- Postings may be followed by comments, which begin with semicolons and
-- extend to the end of the line. Posting comments may span multiple
-- lines, but comment lines below the posting must be preceeded by
-- leading whitespace.
--
-- 2000/1/1
-- account1 $1 ; a posting comment starting on the same line ...
-- ; extending to the next line
--
-- account2
-- ; a posting comment beginning on the next line
--
-- Tags are name-value pairs.
--
-- >>> let getTags (_,tags,_,_) = tags
-- >>> let parseTags = fmap getTags . rtp (postingcommentp Nothing)
--
-- >>> parseTags "; name1: val1, name2:all this is value2"
-- Right [("name1","val1"),("name2","all this is value2")]
--
-- A tag's name must be immediately followed by a colon, without
-- separating whitespace. The corresponding value consists of all the text
-- following the colon up until the next colon or newline, stripped of
-- leading and trailing whitespace.
--
-- Posting dates may be expressed with "date"/"date2" tags or with
-- bracketed date syntax. Posting dates will inherit their year from the
-- transaction date if the year is not specified. We throw parse errors on
-- invalid dates.
--
-- >>> let getDates (_,_,d1,d2) = (d1, d2)
-- >>> let parseDates = fmap getDates . rtp (postingcommentp (Just 2000))
--
-- >>> parseDates "; date: 1/2, date2: 1999/12/31"
-- Right (Just 2000-01-02,Just 1999-12-31)
-- >>> parseDates "; [1/2=1999/12/31]"
-- Right (Just 2000-01-02,Just 1999-12-31)
--
-- Example: tags, date tags, and bracketed dates
-- >>> rtp (postingcommentp (Just 2000)) "; 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)
--
-- Example: extraction of dates from date tags ignores trailing text
-- >>> rtp (postingcommentp (Just 2000)) "; date:3/4=5/6"
-- Right ("date:3/4=5/6\n",[("date","3/4=5/6")],Just 2000-03-04,Nothing)
--
postingcommentp
:: Maybe Year -> TextParser m (Text, [Tag], Maybe Day, Maybe Day)
postingcommentp mYear = do
(commentText, (tags, dateTags)) <-
followingcommentp' (commenttagsanddatesp mYear)
let mdate = fmap snd $ find ((=="date") .fst) dateTags
mdate2 = fmap snd $ find ((=="date2").fst) dateTags
pure (commentText, tags, mdate, mdate2)
{-# INLINABLE postingcommentp #-}
commenttagsanddatesp
:: Maybe Year -> TextParser m ([Tag], [DateTag])
commenttagsanddatesp mYear = do
(txt, dateTags) <- match $ readUpTo ':'
-- next char is either ':' or '\n' (or EOF)
let tagName = last (T.split isSpace txt)
(fmap.second) (dateTags++) (atColon tagName) <|> pure ([], dateTags) -- if not ':', then either '\n' or EOF
where
readUpTo :: Char -> TextParser m [DateTag]
readUpTo end = do
void $ takeWhileP Nothing (\c -> c /= end && c /= '\n' && c /= '[')
-- if not '[' then ':' or '\n' or EOF
atBracket (readUpTo end) <|> pure []
atBracket :: TextParser m [DateTag] -> TextParser m [DateTag]
atBracket cont = do
-- Uses the fact that bracketed date-tags cannot contain newlines
dateTags <- option [] $ lookAhead (bracketeddatetagsp mYear)
_ <- char '['
dateTags' <- cont
pure $ dateTags ++ dateTags'
atColon :: Text -> TextParser m ([Tag], [DateTag])
atColon name = char ':' *> do
skipMany spacenonewline
(tags, dateTags) <- case name of
"" -> pure ([], [])
"date" -> dateValue name
"date2" -> dateValue name
_ -> tagValue name
_ <- optional $ char ','
bimap (tags++) (dateTags++) <$> commenttagsanddatesp mYear
dateValue :: Text -> TextParser m ([Tag], [DateTag])
dateValue name = do
(txt, (date, dateTags)) <- match' $ do
date <- datep' mYear
dateTags <- readUpTo ','
pure (date, dateTags)
let val = T.strip txt
pure $ ( [(name, val)]
, (name, date) : dateTags )
tagValue :: Text -> TextParser m ([Tag], [DateTag])
tagValue name = do
(txt, dateTags) <- match' $ readUpTo ','
let val = T.strip txt
pure $ ( [(name, val)]
, dateTags )
{-# INLINABLE commenttagsanddatesp #-}
--- ** bracketed dates
-- | 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.
--
2018-09-30 04:32:08 +03:00
-- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/2=3/4]"
-- Right [("date",2016-01-02),("date2",2016-03-04)]
--
2018-09-30 04:32:08 +03:00
-- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[1]"
-- Left ...not a bracketed date...
--
2018-09-30 04:32:08 +03:00
-- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/32]"
-- Left ...1:2:...well-formed but invalid date: 2016/1/32...
--
2018-09-30 04:32:08 +03:00
-- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[1/31]"
-- Left ...1:2:...partial date 1/31 found, but the current year is unknown...
--
2018-09-30 04:32:08 +03:00
-- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]"
2018-05-23 05:17:51 +03:00
-- Left ...1:13:...expecting month or day...
--
bracketeddatetagsp
:: Maybe Year -> TextParser m [(TagName, Day)]
bracketeddatetagsp mYear1 = do
2018-07-16 17:28:58 +03:00
-- dbgparse 0 "bracketeddatetagsp"
try $ do
s <- lookAhead
$ between (char '[') (char ']')
$ takeWhile1P Nothing isBracketedDateChar
unless (T.any isDigit s && T.any isDateSepChar s) $
Fail.fail "not a bracketed date"
-- Looks sufficiently like a bracketed date to commit to parsing a date
between (char '[') (char ']') $ do
md1 <- optional $ datep' mYear1
let mYear2 = fmap readYear md1 <|> mYear1
md2 <- optional $ char '=' *> datep' mYear2
pure $ catMaybes [("date",) <$> md1, ("date2",) <$> md2]
where
readYear = first3 . toGregorian
isBracketedDateChar c = isDigit c || isDateSepChar c || c == '='
{-# INLINABLE bracketeddatetagsp #-}
--- ** helper parsers
-- A version of `match` that is strict in the returned text
match' :: TextParser m a -> TextParser m (Text, a)
match' p = do
(!txt, p) <- match p
pure (txt, p)
2018-06-18 01:23:41 +03:00
2018-08-20 17:07:22 +03:00
--- * tests
2018-09-06 23:08:26 +03:00
tests_Common = tests "Common" [
2018-08-20 17:07:22 +03:00
2019-01-15 23:58:05 +03:00
tests "amountp" [
test "basic" $ expectParseEq amountp "$47.18" (usd 47.18)
2018-08-20 16:43:35 +03:00
,test "ends with decimal mark" $ expectParseEq amountp "$1." (usd 1 `withPrecision` 0)
,test "unit price" $ expectParseEq amountp "$10 @ €0.5"
-- not precise enough:
-- (usd 10 `withPrecision` 0 `at` (eur 0.5 `withPrecision` 1)) -- `withStyle` asdecimalpoint=Just '.'
amount{
acommodity="$"
,aquantity=10 -- need to test internal precision with roundTo ? I think not
,astyle=amountstyle{asprecision=0, asdecimalpoint=Nothing}
,aprice=Just $ UnitPrice $
amount{
acommodity=""
,aquantity=0.5
,astyle=amountstyle{asprecision=1, asdecimalpoint=Just '.'}
}
}
2018-08-20 16:43:35 +03:00
,test "total price" $ expectParseEq amountp "$10 @@ €5"
amount{
acommodity="$"
,aquantity=10
,astyle=amountstyle{asprecision=0, asdecimalpoint=Nothing}
,aprice=Just $ TotalPrice $
amount{
acommodity=""
,aquantity=5
,astyle=amountstyle{asprecision=0, asdecimalpoint=Nothing}
}
}
]
2018-08-20 17:07:22 +03:00
,let p = lift (numberp Nothing) :: JournalParser IO (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) in
tests "numberp" [
test "." $ expectParseEq p "0" (0, 0, Nothing, Nothing)
,test "." $ expectParseEq p "1" (1, 0, Nothing, Nothing)
,test "." $ expectParseEq p "1.1" (1.1, 1, Just '.', Nothing)
,test "." $ expectParseEq p "1,000.1" (1000.1, 1, Just '.', Just $ DigitGroups ',' [3])
,test "." $ expectParseEq p "1.00.000,1" (100000.1, 1, Just ',', Just $ DigitGroups '.' [3,2])
,test "." $ expectParseEq p "1,000,000" (1000000, 0, Nothing, Just $ DigitGroups ',' [3,3]) -- could be simplified to [3]
,test "." $ expectParseEq p "1." (1, 0, Just '.', Nothing)
,test "." $ expectParseEq p "1," (1, 0, Just ',', Nothing)
,test "." $ expectParseEq p ".1" (0.1, 1, Just '.', Nothing)
,test "." $ expectParseEq p ",1" (0.1, 1, Just ',', Nothing)
,test "." $ expectParseError p "" ""
,test "." $ expectParseError p "1,000.000,1" ""
,test "." $ expectParseError p "1.000,000.1" ""
,test "." $ expectParseError p "1,000.000.1" ""
,test "." $ expectParseError p "1,,1" ""
,test "." $ expectParseError p "1..1" ""
,test "." $ expectParseError p ".1," ""
,test "." $ expectParseError p ",1." ""
]
2018-08-20 17:07:22 +03:00
,tests "spaceandamountormissingp" [
test "space and amount" $ expectParseEq spaceandamountormissingp " $47.18" (Mixed [usd 47.18])
,test "empty string" $ expectParseEq spaceandamountormissingp "" missingmixedamt
,_test "just space" $ expectParseEq spaceandamountormissingp " " missingmixedamt -- XXX should it ?
-- ,test "just amount" $ expectParseError spaceandamountormissingp "$47.18" "" -- succeeds, consuming nothing
]
]