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

Safe HaskellNone
LanguageHaskell2010

Hledger.Read.Common

Contents

Description

File reading/parsing utilities used by multiple readers, and a good amount of the parsers for journal format, to avoid import cycles when JournalReader imports other readers.

Some of these might belong in Hledger.Read.JournalReader or Hledger.Read.

Synopsis

Documentation

data Reader m Source #

A hledger journal reader is a triple of storage format name, a detector of that format, and a parser from that format to Journal. The type variable m appears here so that rParserr can hold a journal parser, which depends on it.

Instances
Show (Reader m) Source # 
Instance details

Defined in Hledger.Read.Common

Methods

showsPrec :: Int -> Reader m -> ShowS #

show :: Reader m -> String #

showList :: [Reader m] -> ShowS #

data InputOpts Source #

Various options to use when reading journal files. Similar to CliOptions.inputflags, simplifies the journal-reading functions.

Constructors

InputOpts 

Fields

Instances
Data InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputOpts -> c InputOpts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputOpts #

toConstr :: InputOpts -> Constr #

dataTypeOf :: InputOpts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputOpts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputOpts) #

gmapT :: (forall b. Data b => b -> b) -> InputOpts -> InputOpts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputOpts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputOpts -> r #

gmapQ :: (forall d. Data d => d -> u) -> InputOpts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InputOpts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

Show InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Default InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Methods

def :: InputOpts #

parsing utilities

runTextParser :: TextParser Identity a -> Text -> Either (ParseErrorBundle Text CustomErr) a Source #

Run a text parser in the identity monad. See also: parseWithState.

rtp :: TextParser Identity a -> Text -> Either (ParseErrorBundle Text CustomErr) a Source #

Run a text parser in the identity monad. See also: parseWithState.

runJournalParser :: Monad m => JournalParser m a -> Text -> m (Either (ParseErrorBundle Text CustomErr) a) Source #

Run a journal parser in some monad. See also: parseWithState.

rjp :: Monad m => JournalParser m a -> Text -> m (Either (ParseErrorBundle Text CustomErr) a) Source #

Run a journal parser in some monad. See also: parseWithState.

runErroringJournalParser :: Monad m => ErroringJournalParser m a -> Text -> m (Either FinalParseError (Either (ParseErrorBundle Text CustomErr) a)) Source #

Run an erroring journal parser in some monad. See also: parseWithState.

rejp :: Monad m => ErroringJournalParser m a -> Text -> m (Either FinalParseError (Either (ParseErrorBundle Text CustomErr) a)) Source #

Run an erroring journal parser in some monad. See also: parseWithState.

journalSourcePos :: SourcePos -> SourcePos -> GenericSourcePos Source #

Construct a generic start & end line parse position from start and end megaparsec SourcePos's.

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

Given a parser to ParsedJournal, input options, file path and content: run the parser on the content, and finalise the result to get a Journal; or throw an error.

parseAndFinaliseJournal' :: JournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal Source #

Like parseAndFinaliseJournal but takes a (non-Erroring) JournalParser. Used for timeclock/timedot. TODO: get rid of this, use parseAndFinaliseJournal instead

finaliseJournal :: InputOpts -> FilePath -> Text -> Journal -> ExceptT String IO Journal Source #

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.

getDefaultAmountStyle :: JournalParser m (Maybe AmountStyle) Source #

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.

getAmountStyle :: CommoditySymbol -> JournalParser m (Maybe AmountStyle) Source #

Lookup currency-specific amount style.

Returns AmountStyle used in commodity directive within current journal prior to current position or in its parents files.

parsers

transaction bits

dates

datep :: JournalParser m Day Source #

Parse a date in YYYY-MM-DD format. Slash (/) 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 :: JournalParser m LocalTime Source #

Parse a date and time in YYYY-MM-DD HH:MM[:SS][+-ZZZZ] format. Slash (/) 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).

account names

modifiedaccountnamep :: JournalParser m AccountName Source #

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

accountnamep :: TextParser m AccountName Source #

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.

amounts

spaceandamountormissingp :: JournalParser 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 :: JournalParser 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 :: Maybe AmountStyle -> 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.

fromRawNumber :: RawNumber -> Maybe Int -> Either String (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) Source #

Interpret a raw number as a decimal number.

Returns: - the decimal number - the precision (number of digits after the decimal point) - the decimal point character, if any - the digit group style, if any (digit group character and sizes of digit groups)

rawnumberp :: TextParser m (Either AmbiguousNumber RawNumber) Source #

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)

comments

emptyorcommentlinep :: TextParser m () Source #

A blank or comment line in journal format: a line that's empty or containing only whitespace or whose first non-whitespace character is semicolon, hash, or star.

followingcommentp :: TextParser m Text Source #

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"

transactioncommentp :: TextParser m (Text, [Tag]) Source #

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 preceded by leading whitespace.

200011 ; 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.

postingcommentp :: Maybe Year -> TextParser m (Text, [Tag], Maybe Day, Maybe Day) Source #

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 preceded by leading whitespace.

200011 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:34, [=56]" Right ("a:b, date:34, [=56]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:34=56" Right ("date:34=56n",[("date","34=56")],Just 2000-03-04,Nothing)

bracketed dates

bracketeddatetagsp :: Maybe Year -> TextParser 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.

>>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/2=3/4]"
Right [("date",2016-01-02),("date2",2016-03-04)]
>>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[1]"
Left ...not a bracketed date...
>>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/32]"
Left ...1:2:...well-formed but invalid date: 2016/1/32...
>>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[1/31]"
Left ...1:2:...partial date 1/31 found, but the current year is unknown...
>>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]"
Left ...1:13:...expecting month or day...

misc

singlespacedtextp :: TextParser m Text Source #

Parse any text beginning with a non-whitespace character, until a double space or the end of input. TODO including characters which normally start a comment (;#) - exclude those ?

singlespacedtextsatisfyingp :: (Char -> Bool) -> TextParser m Text Source #

Similar to singlespacedtextp, except that the text must only contain characters satisfying the given predicate.

singlespacep :: TextParser m () Source #

Parse one non-newline whitespace character that is not followed by another one.

tests