Skip to content

Commit

Permalink
doc: documentation for gigaparsec module
Browse files Browse the repository at this point in the history
  • Loading branch information
j-mie6 committed Feb 6, 2024
1 parent a29ee0e commit 4044a86
Show file tree
Hide file tree
Showing 2 changed files with 156 additions and 16 deletions.
140 changes: 126 additions & 14 deletions src/Text/Gigaparsec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,6 @@ Stability : stable
This object contains the core combinators and parser type: all parsers will require something from
within!
TODO: what is inside it?
@since 0.1.0.0
-}
module Text.Gigaparsec (
Expand Down Expand Up @@ -110,7 +108,7 @@ Similar to @Either@, this type represents whether a parser has failed or not.
This is chosen instead of @Either@ to be more specific about the naming.
-}
type Result :: * -> * -> *
data Result e a = Success a | Failure e deriving stock (Show, Eq, Generic)
data Result e a = Success a | Failure e deriving stock (Show, Eq, Generic) -- TODO: monad?

Check warning on line 111 in src/Text/Gigaparsec.hs

View workflow job for this annotation

GitHub Actions / GHC latest, Cabal latest

Missing role annotation:

{-|
A fold for the 'Result' type.
Expand Down Expand Up @@ -249,10 +247,8 @@ For instance, keywords are normally only considered keywords if they are not
part of some larger valid identifier (i.e. the keyword \"if\" should not parse
successfully given \"ifp\"). This can be accomplished as follows:
@
keyword :: String -> Parsec ()
keyword kw = atomic $ string kw *> notFollowedBy letterOrDigit
@
> keyword :: String -> Parsec ()
> keyword kw = atomic $ string kw *> notFollowedBy letterOrDigit
@since 0.1.0.0
-}
Expand All @@ -264,7 +260,7 @@ notFollowedBy (Parsec p) = Parsec $ \st ok bad ->
(\_ _ -> ok () st)

-- eof is usually `notFollowedBy item`, but this requires annoying cyclic dependencies on Char
{- This parser only succeeds at the end of the input.
{-| This parser only succeeds at the end of the input.
Equivalent to `notFollowedBy(item)`.
Expand Down Expand Up @@ -293,26 +289,111 @@ successfully returned. It has no other effect on the state of the parser.
unit :: Parsec ()
unit = pure ()

{-|
This combinator, pronounced "zip", first parses this parser then parses @q@: if both succeed the result of this
parser is paired with the result of @q@.
First, this parser is ran, yielding @x@ on success, then @q@ is ran, yielding @y@ on success. If both
are successful then @(x, y)@ is returned. If either fail then the entire combinator fails.
==== __Examples__
>>> p = char 'a' <~> char 'b'
>>> parse p "ab"
Success ('a', 'b')
>>> parse p "b"
Failure ..
>>> parse p "a"
Failure ..
-}
infixl 4 <~>
(<~>) :: Parsec a -> Parsec b -> Parsec (a, b)
(<~>) = liftA2 (,)

{-|
This combinator, pronounced "as", replaces the result of this parser, ignoring the old result.
Similar to @(<$>)@, except the old result of this parser is not required to
compute the new result. This is useful when the result is a constant value (or function!).
Functionally the same as @p *> pure x@ or @const x <$> p@.
/In @parsley@, this combinator is known as @#>@ or @as@/.
==== __Examples__
>>> parse (string "true" $> true) "true"
Success true
-}
infixl 4 $>
($>) :: Parsec a -> b -> Parsec b
($>) = flip (<$)

{-|
This combinator, pronounced "cons", first parses this parser then parses @ps@: if both succeed the result of this
parser is prepended onto the result of @ps@.
First, this parser is ran, yielding @x@ on success, then @ps@ is ran, yielding @xs@ on success. If both
are successful then @x : xs@ is returned. If either fail then the entire combinator fails.
==== __Examples__
> some p = p <:> many(p)
-}
infixl 4 <:>
(<:>) :: Parsec a -> Parsec [a] -> Parsec [a]
(<:>) = liftA2 (:)

infixl 3 <+>
{-|
This combinator, pronounced "sum", wraps this parser's result in @Left@ if it succeeds, and parses @q@ if it failed __without__ consuming input,
wrapping the result in @Right@.
If this parser is successful, then its result is wrapped up using @Left@ and no further action is taken.
Otherwise, if this parser fails __without__ consuming input, then @q@ is parsed instead and its result is
wrapped up using @Right@. If this parser fails having consumed input, this combinator fails.
This is functionally equivalent to @Left <$> p <|> Right <$> q@.
The reason for this behaviour is that it prevents space leaks and improves error messages. If this behaviour
is not desired, use @atomic p@ to rollback any input consumed on failure.
==== __Examples__
>>> p = string "abc" <+> char "xyz"
>>> parse p "abc"
Success (Left "abc")
>>> parse p "xyz"
Success (Right "xyz")
>>> parse p "ab"
Failure .. -- first parser consumed an 'a'!
-}
(<+>) :: Parsec a -> Parsec b -> Parsec (Either a b)
p <+> q = Left <$> p <|> Right <$> q

manyl :: (b -> a -> b) -> b -> Parsec a -> Parsec b
{-|
This combinator will parse this parser __zero__ or more times combining the results with the function @f@ and base value @k@ from the left.
This parser will continue to be parsed until it fails having __not consumed__ input.
All of the results generated by the successful parses are then combined in a left-to-right
fashion using the function @f@: the left-most value provided to @f@ is the value @k@.
If this parser does fail at any point having consumed input, this combinator will fail.
-}
manyl :: (b -> a -> b) -- ^ function to apply to each value produced by this parser, starting at the left.
-> b -- ^ the initial value to feed into the reduction
-> Parsec a
-> Parsec b -- ^ a parser which parses this parser many times and folds the results together with @f@ and @k@ left-associatively.
manyl f k = _repl f (pure k)

somel :: (b -> a -> b) -> b -> Parsec a -> Parsec b
{-|
This combinator will parse this parser __one__ or more times combining the results with the function @f@ and base value @k@ from the left.
This parser will continue to be parsed until it fails having __not consumed__ input.
All of the results generated by the successful parses are then combined in a left-to-right
fashion using the function @f@: the left-most value provided to @f@ is the value @k@.
If this parser does fail at any point having consumed input, this combinator will fail.
==== __Examples__
> natural = somel (\x d -> x * 10 + digitToInt d) 0 digit
-}
somel :: (b -> a -> b) -- ^ function to apply to each value produced by this parser, starting at the left.
-> b -- ^ the initial value to feed into the reduction
-> Parsec a
-> Parsec b -- ^ a parser which parses this parser some times and folds the results together with @f@ and @k@ left-associatively.
somel f k p = _repl f (f k <$> p) p

{-|
Expand Down Expand Up @@ -362,17 +443,48 @@ _repl :: (b -> a -> b) -> Parsec b -> Parsec a -> Parsec b
_repl f k p = k <**> manyr (\x next !acc -> next (f acc x)) id p

-- should these be implemented with branch? probably not.
{-
{-|
This combinator filters the result of this parser using a given predicate, succeeding only if the predicate returns @True@.
First, parse this parser. If it succeeds then take its result @x@ and apply it to the predicate @pred@. If @pred x@ is
true, then return @x@. Otherwise, the combinator fails.
==== __Examples__
>>> keywords = Set.fromList ["if", "then", "else"]
>>> identifier = filterS (\v -> not (Set.member v keywords)) (some letter)
>>> parse identifier "hello"
Success "hello"
>>> parse identifier "if"
Failure ..
@since 0.2.2.0
-}
filterS :: (a -> Bool) -> Parsec a -> Parsec a
filterS :: (a -> Bool) -- ^ the predicate that is tested against the parser result.
-> Parsec a -- ^ the parser to filter, @p@.
-> Parsec a -- ^ a parser that returns the result of @p@ if it passes the predicate.
filterS = filterSWith vanillaGen

-- this is called mapFilter in Scala... there is no collect counterpart
{-
{-|
This combinator applies a function @f@ to the result of this parser: if it returns a
@Just y@, @y@ is returned, otherwise the parser fails.
First, parse this parser. If it succeeds, apply the function @f@ to the result @x@. If
@f x@ returns @Just y@, return @y@. If @f x@ returns @Nothing@, or this parser failed
then this combinator fails. Is a more efficient way of performing a @filterS@ and @fmap@
at the same time.
==== __Examples__
>>> int = ...
>>> safeDiv = mapMaybeS (\(x, y) -> if y /= 0 then Just (div x y) else Nothing) (int <~> (char ' ' *> int))
>>> parse safeDiv "7 0"
Failure .. -- y cannot be 0!
>>> parse safeDiv "10 2"
Success 5
@since 0.2.2.0
-}
mapMaybeS :: (a -> Maybe b) -> Parsec a -> Parsec b
mapMaybeS :: (a -> Maybe b) -- ^ the function used to both filter the result of this parser and transform it.
-> Parsec a -- ^ the parser to filter, @p@.
-> Parsec b -- ^ a parser that returns the result of @p@ applied to @f@, if it yields a value.
mapMaybeS = mapMaybeSWith vanillaGen
32 changes: 30 additions & 2 deletions src/Text/Gigaparsec/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -154,12 +154,40 @@ instance Alternative Parsec where
{-# INLINE many #-}
{-# INLINE some #-}

{-|
This combinator will parse this parser __zero__ or more times combining the results with the function @f@ and base value @k@ from the right.
This parser will continue to be parsed until it fails having __not consumed__ input.
All of the results generated by the successful parses are then combined in a right-to-left
fashion using the function @f@: the right-most value provided to @f@ is the value @k@.
If this parser does fail at any point having consumed input, this combinator will fail.
==== __Examples__
> many = manyr (:) []
-}
{-# INLINE manyr #-}
manyr :: (a -> b -> b) -> b -> Parsec a -> Parsec b
manyr :: (a -> b -> b) -- ^ function to apply to each value produced by this parser, starting at the right.
-> b -- ^ value to use when this parser no longer succeeds.
-> Parsec a
-> Parsec b -- ^ a parser which parses this parser many times and folds the results together with @f@ and @k@ right-associatively.
manyr f k p = let go = liftA2 f p go <|> pure k in go

{-|
This combinator will parse this parser __one__ or more times combining the results with the function @f@ and base value @k@ from the right.
This parser will continue to be parsed until it fails having __not consumed__ input.
All of the results generated by the successful parses are then combined in a right-to-left
fashion using the function @f@: the right-most value provided to @f@ is the value @k@.
If this parser does fail at any point having consumed input, this combinator will fail.
==== __Examples__
> some = somer (:) []
-}
{-# INLINE somer #-}
somer :: (a -> b -> b) -> b -> Parsec a -> Parsec b
somer :: (a -> b -> b) -- ^ function to apply to each value produced by this parser, starting at the right.
-> b -- ^ value to use when this parser no longer succeeds.
-> Parsec a
-> Parsec b -- ^ a parser which parses this parser some times and folds the results together with @f@ and @k@ right-associatively.
somer f k p = liftA2 f p (manyr f k p)

instance Semigroup m => Semigroup (Parsec m) where
Expand Down

0 comments on commit 4044a86

Please sign in to comment.