hledger-lib-1.26: A reusable library providing the core functionality of hledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Utils.Parse

Synopsis

Documentation

type SimpleStringParser a = Parsec HledgerParseErrorData String a Source #

A parser of string to some type.

type SimpleTextParser = Parsec HledgerParseErrorData Text Source #

A parser of strict text to some type.

type TextParser m a = ParsecT HledgerParseErrorData Text m a Source #

A parser of text that runs in some monad.

SourcePos

data SourcePos #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos 

Fields

Instances

Instances details
Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type #

ToJSON SourcePos Source # 
Instance details

Defined in Hledger.Data.Json

FromJSON SourcePos Source # 
Instance details

Defined in Hledger.Data.Json

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnf :: SourcePos -> () #

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.2.1-62eI0Z3uYkJ6m0SHZxexcc" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos))))

mkPos :: Int -> Pos #

Construction of Pos from Int. The function throws InvalidPosException when given a non-positive argument.

Since: megaparsec-6.0.0

unPos :: Pos -> Int #

Extract Int from Pos.

Since: megaparsec-6.0.0

initialPos :: FilePath -> SourcePos #

Construct initial position (line 1, column 1) given name of source file.

sourcePosPretty :: SourcePos -> String #

Pretty-print a SourcePos.

Since: megaparsec-5.0.0

sourcePosPairPretty :: (SourcePos, SourcePos) -> String Source #

Render a pair of source positions in human-readable form, only displaying the range of lines.

choice' :: [TextParser m a] -> TextParser m a Source #

Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.

choiceInState :: [StateT s (ParsecT HledgerParseErrorData Text m) a] -> StateT s (ParsecT HledgerParseErrorData Text m) a Source #

Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.

surroundedBy :: Applicative m => m openclose -> m a -> m a Source #

runTextParser :: TextParser Identity a -> Text -> Either HledgerParseErrors a Source #

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

rtp :: TextParser Identity a -> Text -> Either HledgerParseErrors a Source #

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

parseWithState :: Monad m => st -> StateT st (ParsecT HledgerParseErrorData Text m) a -> Text -> m (Either HledgerParseErrors a) Source #

Run a stateful parser with some initial state on a text. See also: runTextParser, runJournalParser.

parseWithState' :: Stream s => st -> StateT st (ParsecT e s Identity) a -> s -> Either (ParseErrorBundle s e) a Source #

fromparse :: (Show t, Show (Token t), Show e) => Either (ParseErrorBundle t e) a -> a Source #

parseerror :: (Show t, Show (Token t), Show e) => ParseErrorBundle t e -> a Source #

re-exports

data HledgerParseErrorData Source #

Custom error data for hledger parsers. Specialised for a Text parse stream.

Instances

Instances details
Eq HledgerParseErrorData Source # 
Instance details

Defined in Text.Megaparsec.Custom

Ord HledgerParseErrorData Source # 
Instance details

Defined in Text.Megaparsec.Custom

Show HledgerParseErrorData Source # 
Instance details

Defined in Text.Megaparsec.Custom

ShowErrorComponent HledgerParseErrorData Source # 
Instance details

Defined in Text.Megaparsec.Custom

Ord (ParseError Text HledgerParseErrorData) Source # 
Instance details

Defined in Text.Megaparsec.Custom