parsec-free-3.1.11.7: Parsec API encoded as a deeply-embedded DSL, for debugging and analysis
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Parsec.Prim

Synopsis

Documentation

unexpected :: Stream s m t => String -> ParsecT s u m a Source #

runParsecT :: ParsecT s u m a -> ParsecDSL s u m a Source #

mkPT :: Monad m => (State s u -> m (Consumed (m (Reply s u a)))) -> ParsecT s u m a #

Low-level creation of the ParsecT type. You really shouldn't have to do this.

type Parsec s u = ParsecT s u Identity Source #

data Consumed a #

Constructors

Consumed a 
Empty !a 

Instances

Instances details
Functor Consumed 
Instance details

Defined in Text.Parsec.Prim

Methods

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

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

data Reply s u a #

Constructors

Ok a !(State s u) ParseError 
Error ParseError 

Instances

Instances details
Functor (Reply s u) 
Instance details

Defined in Text.Parsec.Prim

Methods

fmap :: (a -> b) -> Reply s u a -> Reply s u b #

(<$) :: a -> Reply s u b -> Reply s u a #

data State s u #

Constructors

State 

Fields

parsecMap :: (a -> b) -> ParsecT s u m a -> ParsecT s u m b Source #

parserReturn :: a -> ParsecT s u m a Source #

parserBind :: ParsecT s u m a -> (a -> ParsecT s u m b) -> ParsecT s u m b Source #

mergeErrorReply :: ParseError -> Reply s u a -> Reply s u a #

parserPlus :: ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a Source #

(<?>) :: ParsecT s u m a -> String -> ParsecT s u m a infix 0 Source #

(<|>) :: ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a infixr 1 Source #

label :: ParsecT s u m a -> String -> ParsecT s u m a Source #

A synonym for <?>, but as a function instead of an operator.

labels :: ParsecT s u m a -> [String] -> ParsecT s u m a Source #

lookAhead :: Stream s m t => ParsecT s u m a -> ParsecT s u m a Source #

class Monad m => Stream s (m :: Type -> Type) t | s -> t where #

An instance of Stream has stream type s, underlying monad m and token type t determined by the stream

Some rough guidelines for a "correct" instance of Stream:

  • unfoldM uncons gives the [t] corresponding to the stream
  • A Stream instance is responsible for maintaining the "position within the stream" in the stream state s. This is trivial unless you are using the monad in a non-trivial way.

Methods

uncons :: s -> m (Maybe (t, s)) #

Instances

Instances details
Monad m => Stream ByteString m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: ByteString -> m (Maybe (Char, ByteString)) #

Monad m => Stream ByteString m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: ByteString -> m (Maybe (Char, ByteString)) #

Monad m => Stream Text m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: Text -> m (Maybe (Char, Text)) #

Monad m => Stream Text m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: Text -> m (Maybe (Char, Text)) #

Monad m => Stream [tok] m tok 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: [tok] -> m (Maybe (tok, [tok])) #

tokens :: (Monad m, Stream s m t, Eq t) => ([t] -> String) -> (SourcePos -> [t] -> SourcePos) -> [t] -> ParsecT s u m [t] Source #

try :: ParsecT s u m a -> ParsecT s u m a Source #

token Source #

Arguments

:: Stream s Identity t 
=> (t -> String)

Token pretty-printing function.

-> (t -> SourcePos)

Computes the position of a token.

-> (t -> Maybe a)

Matching function for the token to parse.

-> Parsec s u a 

tokenPrim Source #

Arguments

:: Stream s m t 
=> (t -> String)

Token pretty-printing function.

-> (SourcePos -> t -> s -> SourcePos)

Next position calculating function.

-> (t -> Maybe a)

Matching function for the token to parse.

-> ParsecT s u m a 

tokenPrimEx :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> Maybe (SourcePos -> t -> s -> u -> u) -> (t -> Maybe a) -> ParsecT s u m a Source #

many :: ParsecT s u m a -> ParsecT s u m [a] Source #

skipMany :: ParsecT s u m a -> ParsecT s u m () Source #

manyAccum :: (a -> [a] -> [a]) -> ParsecT s u m a -> ParsecT s u m [a] Source #

runPT :: (Monad m, Show t, Stream s m t) => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) Source #

runPTLog :: (MonadIO m, MonadReader LogType m, Show t, Stream s m t) => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) Source #

runP :: (Show t, Stream s Identity t) => Parsec s u a -> u -> SourceName -> s -> Either ParseError a Source #

runParserT :: (Show t, Stream s m t) => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) Source #

runParserTLog :: (MonadIO m, MonadReader LogType m, Show t, Stream s m t) => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) Source #

runParser :: (Show t, Stream s Identity t) => Parsec s u a -> u -> SourceName -> s -> Either ParseError a Source #

parse :: (Show t, Stream s Identity t) => Parsec s () a -> SourceName -> s -> Either ParseError a Source #

parseTest :: (Show t, Stream s Identity t, Show a) => Parsec s () a -> s -> IO () Source #

parseTestLog Source #

Arguments

:: (Show t, Stream s (ReaderT LogType IO) t, Show a) 
=> Bool

If True, display every parse, not just the interesting ones

-> ParsecT s () (ReaderT LogType IO) a 
-> s 
-> IO () 

getPosition :: forall (m :: Type -> Type) s u. Monad m => ParsecT s u m SourcePos #

Returns the current source position. See also SourcePos.

getInput :: forall (m :: Type -> Type) s u. Monad m => ParsecT s u m s #

Returns the current input

setPosition :: forall (m :: Type -> Type) s u. Monad m => SourcePos -> ParsecT s u m () #

setPosition pos sets the current source position to pos.

setInput :: forall (m :: Type -> Type) s u. Monad m => s -> ParsecT s u m () #

setInput input continues parsing with input. The getInput and setInput functions can for example be used to deal with #include files.

getParserState :: Monad m => ParsecT s u m (State s u) Source #

Returns the full parser state as a State record.

setParserState :: Monad m => State s u -> ParsecT s u m (State s u) Source #

setParserState st set the full parser state to st.

updateParserState :: Monad m => (State s u -> State s u) -> ParsecT s u m (State s u) Source #

updateParserState f applies function f to the parser state.

getState :: Monad m => ParsecT s u m u Source #

Returns the current user state.

putState :: Monad m => u -> ParsecT s u m () Source #

putState st set the user state to st.

modifyState :: Monad m => (u -> u) -> ParsecT s u m () Source #

modifyState f applies function f to the user state. Suppose that we want to count identifiers in a source, we could use the user state as:

 expr  = do{ x <- identifier
           ; modifyState (+1)
           ; return (Id x)
           }

setState :: Monad m => u -> ParsecT s u m () Source #

An alias for putState for backwards compatibility.

updateState :: Monad m => (u -> u) -> ParsecT s u m () Source #

An alias for modifyState for backwards compatibility.