[GHC] #12666: ApplicativeDo fails to sequence actions

GHC ghc-devs at haskell.org
Wed Oct 5 19:24:18 UTC 2016


#12666: ApplicativeDo fails to sequence actions
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.0.2
          Component:  Compiler       |           Version:  8.0.1
  (Type checker)                     |
           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:
-------------------------------------+-------------------------------------
 Consider the following,
 {{{#!hs
 {-# LANGUAGE ApplicativeDo #-}
 module Fail where

 data P a = P

 instance Functor (P) where
     fmap _ P = P

 instance Applicative (P) where
     P <*> P = P
     pure _ = P


 action :: P Int
 action = P

 works :: P (Int, Int)
 works = do
     a <- action
     b <- action
     return (a,b)

 thisWorks :: P Int
 thisWorks = action *> action

 -- It seems like this should be equivalent to thisWorks.
 shouldThisWork :: P Int
 shouldThisWork = do
     action
     action
 }}}

 It seems to me that `thisWorks` and `shouldThisWork` are equivalent, yet
 the latter fails to typecheck. It seems that `ApplicativeDo` fails to
 catch this the fact that the result of the first `action` is unbound and
 therefore can be sequenced with `*>`.

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


More information about the ghc-tickets mailing list