hledger-lib-1.3: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Read.Common

Description

Some common parsers and helpers used by several readers. Some of these might belong in Hledger.Read.JournalReader or Hledger.Read.

Synopsis

Documentation

 

runTextParser :: TextParser Identity a -> Text -> Either (ParseError Char Dec) a Source #

Run a string parser with no state in the identity monad.

rtp :: TextParser Identity a -> Text -> Either (ParseError Char Dec) a Source #

Run a string parser with no state in the identity monad.

runJournalParser :: Monad m => TextParser m a -> Text -> m (Either (ParseError Char Dec) a) Source #

Run a journal parser with a null journal-parsing state.

rjp :: Monad m => TextParser m a -> Text -> m (Either (ParseError Char Dec) a) Source #

Run a journal parser with a null journal-parsing state.

runErroringJournalParser :: Monad m => ErroringJournalParser m a -> Text -> m (Either String a) Source #

Run an error-raising journal parser with a null journal-parsing state.

rejp :: Monad m => ErroringJournalParser m a -> Text -> m (Either String a) Source #

Run an error-raising journal parser with a null journal-parsing state.

parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> Bool -> FilePath -> Text -> ExceptT String IO Journal Source #

Given a megaparsec ParsedJournal parser, balance assertion flag, file path and file content: parse and post-process a Journal, or give an error.

parserErrorAt :: Monad m => SourcePos -> String -> ErroringJournalParser m a Source #

Terminate parsing entirely, returning the given error message with the given parse position prepended.

datep :: JournalStateParser m Day Source #

Parse a date in YYYYMMDD 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.

datetimep :: JournalStateParser m LocalTime Source #

Parse a date and time in YYYYMMDD 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).

modifiedaccountnamep :: JournalStateParser m AccountName Source #

> parsewith twoorthreepartdatestringp "2016/01/2"

Right "2016012" twoorthreepartdatestringp = do n1 <- some digitChar c <- datesepchar n2 <- some digitChar mn3 optional $ char c> some digitChar return $ n1 ++ c:n2 ++ maybe "" (c:) mn3

Parse an account name, then apply any parent account prefix and/or account aliases currently in effect.

accountnamep :: TextParser m AccountName Source #

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.)

spaceandamountormissingp :: Monad m => JournalStateParser m MixedAmount Source #

Parse whitespace then an amount, with an optional left or right currency symbol and optional price, or return the special "missing" marker amount.

amountp :: Monad m => JournalStateParser m Amount Source #

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.

amountp' :: String -> Amount Source #

Parse an amount from a string, or get an error.

mamountp' :: String -> MixedAmount Source #

Parse a mixed amount from a string, or get an error.

numberp :: TextParser m (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) Source #

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.

followingcommentp :: JournalStateParser m Text Source #

Parse a possibly multi-line comment following a semicolon.

followingcommentandtagsp :: MonadIO m => Maybe Day -> ErroringJournalParser m (Text, [Tag], Maybe Day, Maybe Day) Source #

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 andor 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/4n ; second line" Left ...1:22...partial date 3/4 found, but the current 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:34=56" Right ("date:34=56n",[("date","34=56")],Just 2000-03-04,Nothing)

commentTags :: Text -> [Tag] Source #

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","111"),("date","11"),("date2","111"),("date2","11"),("date","11"),("date2","111"),("date","1"),("date2","11/1")]
>>> commentTags "\na b:, \nd:e, f"
[("b",""),("d","e")]

tagsp :: Parser [Tag] Source #

Parse all tags found in a string.

nontagp :: Parser String Source #

Parse everything up till the first tag.

>>> rtp nontagp "\na b:, \nd:e, f"
Right "\na "

tagp :: Parser Tag Source #

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).

>>> rtp tagp "a:b b , c AuxDate: 4/2"
Right ("a","b b")

tagnamep :: Parser Text Source #

>>> rtp tagnamep "a:"
Right "a"

postingdatesp :: Monad m => Maybe Day -> ErroringJournalParser m [(TagName, Day)] Source #

Parse all posting dates found in a string. Posting dates can be expressed with datedate2 tags andor bracketed dates. The dates are parsed fully to give useful errors. Missing years can be inferred only if a default date is provided.

datetagp :: Monad m => Maybe Day -> ErroringJournalParser m (TagName, Day) Source #

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 ...1:9...partial date 3/4 found, but the current year is unknown...

bracketeddatetagsp :: Monad m => Maybe Day -> ErroringJournalParser m [(TagName, Day)] Source #

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 ...1:11:...bad date: 2016/1/32...
>>> rejp (bracketeddatetagsp Nothing) "[1/31]"
Left ...1:6:...partial date 1/31 found, but the current year is unknown...
>>> rejp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]"
Left ...1:15:...bad date, different separators...