parsely-0.1ContentsIndex
Text.ParserCombinators.Parsely.Class
Description
It will help in using this library if you are familiar with Parsec. (The best way to become familiar with Parsec is to read the source. See also http://www.cs.uu.nl/people/daan/parsec.html)
Synopsis
(<|>) :: Parsely m => m a -> m a -> m a
class (Functor m, MonadPlus m) => Parsely m where
(<?>) :: m a -> String -> m a
unexpected :: String -> m a
many :: m a -> m [a]
skipMany :: m a -> m ()
class Parsely m => ParselyTry m where
try :: m a -> m a
class ParselyTry m => MonadParsec m tok pos | m -> tok, m -> pos where
token :: (tok -> String) -> (tok -> pos) -> (tok -> Maybe a) -> m a
tokenPrim :: (tok -> String) -> (pos -> tok -> [tok] -> pos) -> (tok -> Maybe a) -> m a
tokens :: Eq tok => ([tok] -> String) -> (pos -> [tok] -> pos) -> [tok] -> m [tok]
lookAhead :: m a -> m a
Documentation
(<|>) :: Parsely m => m a -> m a -> m a
This is just a type-restricted version of mplus (as in Parsec)
class (Functor m, MonadPlus m) => Parsely m where
Methods
(<?>) :: m a -> String -> m a
Give a name to a parser (used in error messages, hopefully)
unexpected :: String -> m a
This parser didn't expect that input. Try other branch of <|>? Nearly the same as mzero, but mzero may produce a less informative message in case of error.
many :: m a -> m [a]
Run given parser as many times as possible, returning results. In the typeclass because Parsec needs them as primitives to avoid stack overflow. (XXX how will we preserve space properties with monad transformers?)
skipMany :: m a -> m ()
Run given parser as many times as possible, discarding results. Here for the same reason as many.
show/hide Instances
class Parsely m => ParselyTry m where
Methods
try :: m a -> m a
If argument fails consuming input, act as if it wasn't consumed. (I.e. put it back)
show/hide Instances
class ParselyTry m => MonadParsec m tok pos | m -> tok, m -> pos where
Methods
token :: (tok -> String) -> (tok -> pos) -> (tok -> Maybe a) -> m a
tokenPrim :: (tok -> String) -> (pos -> tok -> [tok] -> pos) -> (tok -> Maybe a) -> m a
tokens :: Eq tok => ([tok] -> String) -> (pos -> [tok] -> pos) -> [tok] -> m [tok]
lookAhead :: m a -> m a
show/hide Instances
MonadParsec (GenParser tok st) tok SourcePos
MonadParsec m tok pos => MonadParsec (ReaderT r m) tok pos
MonadParsec m tok pos => MonadParsec (StateT r m) tok pos
(MonadParsec m tok pos, Monoid w) => MonadParsec (WriterT w m) tok pos
Produced by Haddock version 0.8