
Perhaps. However, given that `pure` and `return` shouldn't differ, and
#13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:1 bgamari]: that the "`Monad` of no `return`" was seriously considered, it's not clear to me whether it matters enough to change it. The moment `pure /= return` you have bigger problems. It matters in the following code: {{{#!hs {-# Language TypeApplications, ScopedTypeVariables, InstanceSigs, RankNTypes, DeriveFunctor, GeneralizedNewtypeDeriving #-} import Control.Monad import Data.Coerce -- As in Control.Applicative newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a } deriving (Monad) instance Monad m => Functor (WrappedMonad m) where fmap :: (a -> b) -> (WrappedMonad m a -> WrappedMonad m b) fmap f (WrapMonad v) = WrapMonad (liftM f v) instance Monad m => Applicative (WrappedMonad m) where pure :: a -> WrappedMonad m a pure = WrapMonad . pure (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v) -- Definition defining `Applicative' roundtripping through `WrappedMonad' data V3 a = V3 a a a deriving (Functor, Show) instance Applicative V3 where pure :: forall a. a -> V3 a pure = coerce (pure @(WrappedMonad V3) @a) (<*>) :: forall a b. V3 (a -> b) -> V3 a -> V3 b (<*>) = coerce ((<*>) @(WrappedMonad V3) @a @b) instance Monad V3 where return :: a -> V3 a return a = V3 a a a (>>=) :: V3 a -> (a -> V3 b) -> V3 b V3 a b c >>= f = V3 a' b' c' where V3 a' _ _ = f a V3 _ b' _ = f b V3 _ _ c' = f c }}} If we try to run `pure @V3 'a'` it loops.. but replace `pure = WrapMonad . pure` by `pure = WrapMonad . return` and it works as expected. but comment `Control.Applicative` out and un-comment the definition of `WrapMonad` (th -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13876#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler