text-lips-0.1.0.1: Monadic parsing combinator library with attention to locations

Safe HaskellNone
LanguageHaskell98

Text.Lips

Description

Monadic parsing combinator library with attention to locations.

Synopsis

Documentation

data ParsedLines Source #

Lines of text consumed by a parser (fully or partially).

Constructors

ParsedLines 

Fields

data Parser α Source #

Opaque parser type.

Instances

Monad Parser Source # 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

CharParsing Parser Source # 
Parsing Parser Source # 

Methods

try :: Parser a -> Parser a #

(<?>) :: Parser a -> String -> Parser a #

skipMany :: Parser a -> Parser () #

skipSome :: Parser a -> Parser () #

unexpected :: String -> Parser a #

eof :: Parser () #

notFollowedBy :: Show a => Parser a -> Parser () #

ResetLineParsing Parser Source # 
LocParsing Parser Source # 
(~) * α String => IsString (Parser α) Source # 

Methods

fromString :: String -> Parser α #

type ParserLoc Parser Source # 

data ParserResult α Source #

Parser result.

Constructors

ParserSuccess 

Fields

ParserFailure 

Fields

Instances

data ParserStep α Source #

Parser continuation.

startParser :: Parser α -> ParserStep α Source #

Start a parser.

startParserAtLine :: Word -> Text -> Parser α -> ParserStep α Source #

Start a parser on a specific line number and provide it with a first chunk of the input.

starveParser :: ParserStep α -> ParserResult α Source #

Feed a parser continuation with empty input.

parseText :: Text -> Parser α -> ParserResult α Source #

Run a parser on a text.

class CharParsing p => LocParsing p where Source #

Parsers that provide location information.

Minimal complete definition

located, spanned

Associated Types

type ParserLoc p Source #

Parser location type.

Methods

location :: p (ParserLoc p) Source #

The current location.

location :: (MonadTrans t, Monad m, LocParsing m, p ~ t m, ParserLoc p ~ ParserLoc m) => p (ParserLoc p) Source #

The current location.

located :: p α -> p (Located (ParserLoc p) α) Source #

Attach the starting location to the parsed value.

spanned :: p α -> p (Located (Span (ParserLoc p)) α) Source #

Attach the spanned location to the parsed value.

Instances

LocParsing Parser Source # 
(MonadPlus p, LocParsing p) => LocParsing (StateT s p) Source # 

Associated Types

type ParserLoc (StateT s p :: * -> *) :: * Source #

Methods

location :: StateT s p (ParserLoc (StateT s p)) Source #

located :: StateT s p α -> StateT s p (Located (ParserLoc (StateT s p)) α) Source #

spanned :: StateT s p α -> StateT s p (Located (Span (ParserLoc (StateT s p))) α) Source #

(MonadPlus p, LocParsing p) => LocParsing (StateT s p) Source # 

Associated Types

type ParserLoc (StateT s p :: * -> *) :: * Source #

Methods

location :: StateT s p (ParserLoc (StateT s p)) Source #

located :: StateT s p α -> StateT s p (Located (ParserLoc (StateT s p)) α) Source #

spanned :: StateT s p α -> StateT s p (Located (Span (ParserLoc (StateT s p))) α) Source #

(Monoid w, MonadPlus p, LocParsing p) => LocParsing (WriterT w p) Source # 

Associated Types

type ParserLoc (WriterT w p :: * -> *) :: * Source #

Methods

location :: WriterT w p (ParserLoc (WriterT w p)) Source #

located :: WriterT w p α -> WriterT w p (Located (ParserLoc (WriterT w p)) α) Source #

spanned :: WriterT w p α -> WriterT w p (Located (Span (ParserLoc (WriterT w p))) α) Source #

(Monoid w, MonadPlus p, LocParsing p) => LocParsing (WriterT w p) Source # 

Associated Types

type ParserLoc (WriterT w p :: * -> *) :: * Source #

Methods

location :: WriterT w p (ParserLoc (WriterT w p)) Source #

located :: WriterT w p α -> WriterT w p (Located (ParserLoc (WriterT w p)) α) Source #

spanned :: WriterT w p α -> WriterT w p (Located (Span (ParserLoc (WriterT w p))) α) Source #

(MonadPlus p, LocParsing p) => LocParsing (IdentityT * p) Source # 

Associated Types

type ParserLoc (IdentityT * p :: * -> *) :: * Source #

(MonadPlus p, LocParsing p) => LocParsing (ReaderT * r p) Source # 

Associated Types

type ParserLoc (ReaderT * r p :: * -> *) :: * Source #

Methods

location :: ReaderT * r p (ParserLoc (ReaderT * r p)) Source #

located :: ReaderT * r p α -> ReaderT * r p (Located (ParserLoc (ReaderT * r p)) α) Source #

spanned :: ReaderT * r p α -> ReaderT * r p (Located (Span (ParserLoc (ReaderT * r p))) α) Source #

(Monoid w, MonadPlus p, LocParsing p) => LocParsing (RWST r w s p) Source # 

Associated Types

type ParserLoc (RWST r w s p :: * -> *) :: * Source #

Methods

location :: RWST r w s p (ParserLoc (RWST r w s p)) Source #

located :: RWST r w s p α -> RWST r w s p (Located (ParserLoc (RWST r w s p)) α) Source #

spanned :: RWST r w s p α -> RWST r w s p (Located (Span (ParserLoc (RWST r w s p))) α) Source #

(Monoid w, MonadPlus p, LocParsing p) => LocParsing (RWST r w s p) Source # 

Associated Types

type ParserLoc (RWST r w s p :: * -> *) :: * Source #

Methods

location :: RWST r w s p (ParserLoc (RWST r w s p)) Source #

located :: RWST r w s p α -> RWST r w s p (Located (ParserLoc (RWST r w s p)) α) Source #

spanned :: RWST r w s p α -> RWST r w s p (Located (Span (ParserLoc (RWST r w s p))) α) Source #

class LocParsing p => ResetLineParsing p where Source #

Parsers with resettable line numbers.

Methods

resetLineNr :: Word -> p (Seq Text) Source #

Reset the current line number and return the text lines fully consumed by the parser so far.

resetLineNr :: (MonadTrans t, Monad m, ResetLineParsing m, p ~ t m) => Word -> p (Seq Text) Source #

Reset the current line number and return the text lines fully consumed by the parser so far.