[GHC] #13511: ApplicativeDo incorrectly requiring Monad
GHC
ghc-devs at haskell.org
Sun Apr 2 11:31:06 UTC 2017
#13511: ApplicativeDo incorrectly requiring Monad
-------------------------------------+-------------------------------------
Reporter: mnislaih | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
We ran into this bug in production, this is a simplified reproduction. The
following program will not type check, requiring an unnecessary Monad
instance:
{{{
{-# LANGUAGE ApplicativeDo, GeneralizedNewtypeDeriving #-}
import Data.Functor.Identity
import Data.Monoid
newtype A x = A (Identity x) deriving (Functor, Applicative)
shouldWork :: A ()
shouldWork = do
a <- pure ()
b <- pure ()
let ab = a <> b
return ab
}}}
{{{
pepe:~/code/snippets$ ghci ApplicativeDoBug.hs
GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( ApplicativeDoBug.hs, interpreted )
ApplicativeDoBug.hs:10:14: error:
• No instance for (Monad A) arising from a do statement
• In the expression:
do { a <- pure ();
b <- pure ();
let ab = a <> b;
return ab }
In an equation for ‘shouldWork’:
shouldWork
= do { a <- pure ();
b <- pure ();
let ab = ...;
return ab }
Failed, modules loaded: none.
}}}
There is a simple workaround, which worked for us in production:
{{{
workaround :: A ()
workaround = do
a <- pure ()
b <- pure ()
return $
let ab = a <> b
in ab
}}}
I asked in #ghc and it seems this is not yet fixed in HEAD.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13511>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list