Skip to content
Snippets Groups Projects
Commit f636faa7 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Set default-impl of `mapM`/`sequence` methods to `traverse`/`sequenceA`


This is made possible by the AMP, as we don't need the `WrappedMonad`
helper for that anymore.

Approved-by: default avatarEdward Kmett <ekmett@gmail.com>
parent 51aa2fa3
No related branches found
No related tags found
No related merge requests found
...@@ -46,7 +46,7 @@ module Data.Traversable ( ...@@ -46,7 +46,7 @@ module Data.Traversable (
foldMapDefault, foldMapDefault,
) where ) where
import Control.Applicative ( Const(..), WrappedMonad(..) ) import Control.Applicative ( Const(..) )
import Data.Either ( Either(..) ) import Data.Either ( Either(..) )
import Data.Foldable ( Foldable ) import Data.Foldable ( Foldable )
import Data.Functor import Data.Functor
...@@ -157,12 +157,12 @@ class (Functor t, Foldable t) => Traversable t where ...@@ -157,12 +157,12 @@ class (Functor t, Foldable t) => Traversable t where
-- | Map each element of a structure to a monadic action, evaluate -- | Map each element of a structure to a monadic action, evaluate
-- these actions from left to right, and collect the results. -- these actions from left to right, and collect the results.
mapM :: Monad m => (a -> m b) -> t a -> m (t b) mapM :: Monad m => (a -> m b) -> t a -> m (t b)
mapM f = unwrapMonad . traverse (WrapMonad . f) mapM = traverse
-- | Evaluate each monadic action in the structure from left to right, -- | Evaluate each monadic action in the structure from left to right,
-- and collect the results. -- and collect the results.
sequence :: Monad m => t (m a) -> m (t a) sequence :: Monad m => t (m a) -> m (t a)
sequence = mapM id sequence = sequenceA
{-# MINIMAL traverse | sequenceA #-} {-# MINIMAL traverse | sequenceA #-}
-- instances for Prelude types -- instances for Prelude types
......
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