[GHC] #12666: ApplicativeDo fails to sequence actions

#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

#12666: ApplicativeDo fails to sequence actions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonmar -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12666#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12666: ApplicativeDo fails to sequence actions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | 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: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -37,1 +37,1 @@ - catch this the fact that the result of the first `action` is unbound and + catch the fact that the result of the first `action` is not bound and New description: 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 the fact that the result of the first `action` is not bound and therefore can be sequenced with `*>`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12666#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12666: ApplicativeDo fails to sequence actions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | 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: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => duplicate Comment: I'm going to merge this into #10892 because it's basically the same thing - we don't handle `ExprStmt` in `ApplicativeDo` right now. I was a bit lazy and skipped this when I implemented `ApplicativeDo` because I didn't need it, sorry! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12666#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12666: ApplicativeDo fails to sequence actions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | 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: | -------------------------------------+------------------------------------- Changes (by simonmar): * priority: normal => high -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12666#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC