[GHC] #15344: ApplicativeDo seems to prevent the fail method from being used

GHC ghc-devs at haskell.org
Wed Jul 4 23:53:59 UTC 2018


#15344: ApplicativeDo seems to prevent the fail method from being used
-------------------------------------+-------------------------------------
           Reporter:  kccqzy         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.2.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:
-------------------------------------+-------------------------------------
 I am not sure if this is intended, but I came across this issue when
 debugging a runtime exception. It seems like an incomplete pattern match
 in a do-block with ApplicativeDo enabled will not use the fail method.

 If I have a module like this

 {{{#!hs
 {-# LANGUAGE ApplicativeDo #-}
 {-# OPTIONS_ghc -ddump-simpl #-}
 module M where

 f :: Maybe (Maybe Int) -> Maybe Int -> Maybe Int
 f mgs mid = do
   _ <- mid
   (Just moi) <- mgs
   pure (moi + 42)

 main :: IO ()
 main = print (f (Just Nothing) (Just 2))

 }}}

 This will result in a runtime exception:

 {{{
 Just *** Exception: repro.hs:(6,13)-(9,17): Non-exhaustive patterns in
 lambda
 }}}

 But if I remove the ApplicativeDo extension, this code works as normal,
 producing Nothing as the output.

 On a theoretical level I understand why this is happening, but I still
 find it quite unexpected, especially since the documentation at
 https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html
 #things-to-watch-out-for claims that

 > Your code should just work as before when ApplicativeDo is enabled,
 provided you use conventional Applicative instances.

 If this is not a defect in GHC itself, I'd say it is a defect in
 documentation in not pointing out this gotcha.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15344>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list