| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
ParseLib.Abstract.Core
Description
Synopsis
- newtype Parser s r = Parser ([s] -> ([(r, [s])], DifferenceList (ParseError [s])))
- anySymbol :: HasCallStack => Parser s s
- satisfy :: HasCallStack => (s -> Bool) -> Parser s s
- empty :: Alternative f => f a
- failp :: HasCallStack => Parser s a
- succeed :: a -> Parser s a
- pure :: Applicative f => a -> f a
- (<|>) :: Alternative f => f a -> f a -> f a
- (<<|>) :: Parser s a -> Parser s a -> Parser s a
- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (>>=) :: Monad m => m a -> (a -> m b) -> m b
- look :: Parser s [s]
- parseAndTrace :: (ErrorsPretty s, Ord s) => Config -> Parser s a -> [s] -> [(a, [s])]
- parseWithConfig :: Ord s => Config -> Parser s a -> [s] -> Either (ParseErrorBundle [s]) (NonEmpty (a, [s]))
- parse :: (ErrorsPretty s, Ord s) => Parser s a -> [s] -> [(a, [s])]
The type of parsers
An input string is mapped to a list of successful parses.
For each succesful parse, we return the result of type r,
and the remaining input string. The input must be a list of
symbols.
Constructors
| Parser ([s] -> ([(r, [s])], DifferenceList (ParseError [s]))) |
Elementary parsers
anySymbol :: HasCallStack => Parser s s Source #
Parses any single symbol.
satisfy :: HasCallStack => (s -> Bool) -> Parser s s Source #
Takes a predicate and returns a parser that parses a single symbol satisfying that predicate.
empty :: Alternative f => f a #
The identity of <|>
failp :: HasCallStack => Parser s a Source #
Same as empty; provided for compatibility with the lecture notes.
pure :: Applicative f => a -> f a #
Lift a value.
Parser combinators
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation
(<<|>) :: Parser s a -> Parser s a -> Parser s a infixr 3 Source #
Biased choice. If the left hand side parser succeeds, the right hand side is not considered. Use with care!
(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
Example
Used in combination with (, <$>)( can be used to build a record.<*>)
>>>data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>produceFoo :: Applicative f => f Foo
>>>produceBar :: Applicative f => f Bar>>>produceBaz :: Applicative f => f Baz
>>>mkState :: Applicative f => f MyState>>>mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap.
The name of this operator is an allusion to $.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $ is function application, <$> is function
application lifted over a Functor.
Examples
Convert from a to a Maybe Int using Maybe
Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an
Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "17"
Double each element of a list:
>>>(*2) <$> [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>even <$> (2,2)(2,True)
(>>=) :: Monad m => m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
'as ' can be understood as the >>= bsdo expression
do a <- as bs a
Lookahead
Running parsers
parseAndTrace :: (ErrorsPretty s, Ord s) => Config -> Parser s a -> [s] -> [(a, [s])] Source #
Runs a parser on a given string printing error messages to standard error (stderr).
The ErrorsPretty constraint is automatically fulfilled by Show
instances. But if you see the following GHC error, you usually need to
add an ( constraint to your function and ErrorsPretty s)import
ParseLib.Error (.ErrorsPretty)
Overlapping instances for ErrorsPretty s arising from a use of ‘parseAndTrace’
ErrorsPretty is not defined in this package but in
uu-tc-error-error. We
did this so you can switch back and forth between this library and
uu-tc without the need to
remove ErrorsPretty constraints from your code. Just permanently keep
uu-tc-error-error
in your .cabal file. It does not conflict with
uu-tc because there are
no module name collisions.
parseWithConfig :: Ord s => Config -> Parser s a -> [s] -> Either (ParseErrorBundle [s]) (NonEmpty (a, [s])) Source #
Runs a parser on a given string. Pretty print the error information
with errorBundlePrettyImproved.
parse :: (ErrorsPretty s, Ord s) => Parser s a -> [s] -> [(a, [s])] Source #
Runs a parser on a given string printing error messages to standard error (stderr).
Notice that, when using parse, you might need to add Ord and
ErrorsPretty constraints to your own functions and ensure your own
data types are deriving (.Ord, Show)
The ErrorsPretty constraint is automatically fulfilled by Show
instances. But if you see the following GHC error, you usually need to
add an ( constraint to your function and ErrorsPretty s)import
ParseLib.Error (.ErrorsPretty)
Overlapping instances for ErrorsPretty s arising from a use of ‘parse’
ErrorsPretty is not defined in this package but in
uu-tc-error-error. We
did this so you can switch back and forth between this library and
uu-tc without the need to
remove ErrorsPretty constraints from your code. Just permanently keep
uu-tc-error-error
in your .cabal file. It does not conflict with
uu-tc because there are
no module name collisions.