Skip to content
Snippets Groups Projects
Unverified Commit 088590bf authored by Oleg Grenrus's avatar Oleg Grenrus Committed by GitHub
Browse files

Merge pull request #176 from haskell/alternative-many

Alternative.many = many; Alternative.some = many1
parents cda16b0c b15fcc1c
No related branches found
No related tags found
No related merge requests found
### 3.1.17.0
- Move `many1 :: ParsecT s u m a -> ParsecT s u m [a]` to `Text.Parsec.Prim`.
Drop `Stream` constraint requirement.
- Implement `Alternative.many/some` using `Text.Parsec.Prim.many/many1`,
instead of default implementation.
### 3.1.16.0
- Add `tokens'` and `string'` combinators which don't consume the prefix.
......
cabal-version: 1.12
name: parsec
version: 3.1.16.1
version: 3.1.17.0
synopsis: Monadic parser combinators
description: Parsec is designed from scratch as an industrial-strength parser
......
......@@ -106,24 +106,6 @@ skipMany p = scan
scan = do{ p; scan } <|> return ()
-}
-- | @many1 p@ applies the parser @p@ /one/ or more times. Returns a
-- list of the returned values of @p@.
--
-- > word = many1 letter
many1 :: (Stream s m t) => ParsecT s u m a -> ParsecT s u m [a]
{-# INLINABLE many1 #-}
many1 p = do{ x <- p; xs <- many p; return (x:xs) }
{-
many p = scan id
where
scan f = do{ x <- p
; scan (\tail -> f (x:tail))
}
<|> return (f [])
-}
-- | @sepBy p sep@ parses /zero/ or more occurrences of @p@, separated
-- by @sep@. Returns a list of values returned by @p@.
--
......
......@@ -61,6 +61,7 @@ module Text.Parsec.Prim
, many
, skipMany
, manyAccum
, many1
, runPT
, runP
, runParserT
......@@ -270,6 +271,9 @@ instance Applicative.Alternative (ParsecT s u m) where
empty = mzero
(<|>) = mplus
many = many
some = many1
instance Monad (ParsecT s u m) where
return = Applicative.pure
p >>= f = parserBind p f
......@@ -715,6 +719,15 @@ many p
= do xs <- manyAccum (:) p
return (reverse xs)
-- | @many1 p@ applies the parser @p@ /one/ or more times. Returns a
-- list of the returned values of @p@.
--
-- > word = many1 letter
many1 :: ParsecT s u m a -> ParsecT s u m [a]
{-# INLINABLE many1 #-}
many1 p = do{ x <- p; xs <- many p; return (x:xs) }
-- | @skipMany p@ applies the parser @p@ /zero/ or more times, skipping
-- its result.
--
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment