Skip to content

Commit

Permalink
Define ‘Semigroup’ and ‘Monoid’ for ‘ParsecT’
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Apr 29, 2017
1 parent 16a3e7f commit 376db59
Show file tree
Hide file tree
Showing 4 changed files with 29 additions and 4 deletions.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Expand Up @@ -9,6 +9,8 @@
* Added the `getNextTokenPosition`, which returns position where the next
token in the stream begins.

* Defined `Semigroup` and `Monoid` instances of `ParsecT`.

* Dropped support for GHC 7.6.

* Added an `ErrorComponent` instance for `()`.
Expand Down
12 changes: 12 additions & 0 deletions Text/Megaparsec/Prim.hs
Expand Up @@ -365,6 +365,18 @@ newtype ParsecT e s m a = ParsecT
-> (ParseError (Token s) e -> State s -> m b) -- empty-error
-> m b }

instance (ErrorComponent e, Stream s, Semigroup a)
=> Semigroup (ParsecT e s m a) where
(<>) = A.liftA2 (<>)
{-# INLINE (<>) #-}

instance (ErrorComponent e, Stream s, Monoid a)
=> Monoid (ParsecT e s m a) where
mempty = pure mempty
{-# INLINE mempty #-}
mappend = A.liftA2 mappend
{-# INLINE mappend #-}

instance Functor (ParsecT e s m) where
fmap = pMap

Expand Down
4 changes: 0 additions & 4 deletions megaparsec.cabal
Expand Up @@ -96,10 +96,6 @@ library
, Text.Megaparsec.Text.Lazy
if flag(dev)
ghc-options: -Wall -Werror
if impl(ghc >= 8.0)
ghc-options: -Wcompat
ghc-options: -Wnoncanonical-monadfail-instances
ghc-options: -Wnoncanonical-monoid-instances
else
ghc-options: -O2 -Wall
default-language: Haskell2010
Expand Down
15 changes: 15 additions & 0 deletions tests/Text/Megaparsec/PrimSpec.hs
Expand Up @@ -216,6 +216,21 @@ spec = do
st = st' { stateInput = h : stateInput st' }
runParser' p st `shouldBe` (st, (Right . Just . spanStart) h)

describe "ParsecT Semigroup instance" $
it "the associative operation works" $
property $ \a b -> do
let p = pure [a] G.<> pure [b]
prs p "" `shouldParse` ([a,b] :: [Int])

describe "ParsecT Monoid instance" $ do
it "mempty works" $ do
let p = mempty
prs p "" `shouldParse` ([] :: [Int])
it "mappend works" $
property $ \a b -> do
let p = pure [a] `mappend` pure [b]
prs p "" `shouldParse` ([a,b] :: [Int])

describe "ParsecT Functor instance" $ do
it "obeys identity law" $
property $ \n ->
Expand Down

0 comments on commit 376db59

Please sign in to comment.