[GHC] #12820: Regression around pattern synonyms and higher-rank types

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC 8.0.1 accepts, but HEAD rejects: {{{#!hs {-# LANGUAGE PatternSynonyms, RankNTypes, ViewPatterns #-} module Bug where pattern P :: (forall a. a -> a) -> String pattern P x <- (\ _ -> id -> x) }}} (Sidenote: kudos to the parser on figuring out my view pattern.) HEAD gives this error: {{{ Bug.hs:6:30: error: • Couldn't match expected type ‘forall a. a -> a’ with actual type ‘a0 -> a0’ • In the declaration for pattern synonym ‘P’ • Relevant bindings include x :: a0 -> a0 (bound at Bug.hs:6:30) }}} The code looks correct to me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): What makes you say it's correct? Consier {{{ f :: String -> Int f ( (\_ -> id) -> (x :: forall a. a->a) ) = 3 }}} This too is rejected with {{{ T12820.hs:10:20: error: * Couldn't match expected type `a0 -> a0' with actual type `forall a. a -> a' * When checking that the pattern signature: forall a. a -> a fits the type of its context: a0 -> a0 In the pattern: x :: forall a. a -> a In the pattern: (\ _ -> id) -> (x :: forall a. a -> a) }}} Suppose we are inferring the type of `f -> p`. W could either * Infer the type of `f`, and use that to check the type of pattern `p`, or * Infer the type of `p`, and use that to check the type of `f` (actually it only fixes teh result type of `f` but still. We use the first alternative, but perhpas the second makes more sense. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Fair enough. But the problem persists even with a type signature on the pattern: {{{ pattern P x <- (((\ _ -> id) :: forall b c. b -> c -> c) -> x) }}} Interestingly, adding the type signature fails in GHC 8.0.1 as well as HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. Works ok if you put the forall after the arrow {{{ pattern P x <- (((\ _ -> id) :: forall b. b -> forall c. c -> c) -> x) }}} Reason: we infer the type of `f`, and then try to decompose and arrow, instantiating if necessary. But we don't re-generalise. I suppose we could but this is a pretty exotic corner and it's not keeping me awake at night. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire Comment: Maybe this ''is'' what kept me awake last night. Or maybe it was my cat who felt the need to lovingly stroke my face roughly hourly. Until she was banished to the kitchen. No, I'm not overly bothered by this. But it is subtly wrong, according to any bidirectional accounting of a type system that accommodates view patterns and has principal types. I'll put this in my queue. At the bottom. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12820: Regression around pattern synonyms and higher-rank types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This regression was introduced somewhere between commit 45bfd1a65978ee282d8d2cc1ddb7e3e5f4cd4717 (Refactor typechecking of pattern bindings) and 9417e57983dbcf7f500cca16163b11d1abb699e6 (Refactor occurrence-check logic). (I'm 90% sure it's 45bfd1a65978ee282d8d2cc1ddb7e3e5f4cd4717, but I can't say with certainty because that commit was in the middle of a slew of commits which didn't compile correctly until 9417e57983dbcf7f500cca16163b11d1abb699e6.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12820#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC