[GHC] #11010: Untouchable type, pattern synonyms
 
            #11010: Untouchable type, pattern synonyms ------------------------------------+--------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Linux Architecture: x86 | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ------------------------------------+--------------------------------- GHC panicked while experimenting {{{#!hs {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-} module Test where data Expr a where Fun :: String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun str f x = Fun str f x pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int pattern Suc n <- IntFun _ _ n where Suc n = IntFun "suc" (+ 1) n }}} {{{ % ghc Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) Test.hs:12:18: Couldn't match expected type ‘Int’ with actual type ‘a1’ ‘a1’ is untouchable inside the constraints (a ~ Int) bound by the type signature for Suc :: Expr a -> Expr Int at Test.hs:12:9-11ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for i386-unknown-linux): No skolem info: a1_anA[ssk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms ---------------------------------+------------------------------ Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+------------------------------ Description changed by Iceland_jack: Old description:
GHC panicked while experimenting
{{{#!hs {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-}
module Test where
data Expr a where Fun :: String -> (a -> b) -> (Expr a -> Expr b)
pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun str f x = Fun str f x
pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int pattern Suc n <- IntFun _ _ n where Suc n = IntFun "suc" (+ 1) n }}}
{{{ % ghc Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o )
Test.hs:12:18: Couldn't match expected type ‘Int’ with actual type ‘a1’ ‘a1’ is untouchable inside the constraints (a ~ Int) bound by the type signature for Suc :: Expr a -> Expr Int at Test.hs:12:9-11ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for i386-unknown-linux): No skolem info: a1_anA[ssk]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
New description: GHC panicked while experimenting {{{#!hs {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-} module Test where data Expr a where Fun :: String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun str f x = Fun str f x pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int pattern Suc n <- IntFun _ _ n where Suc n = IntFun "suc" (+ 1) n }}} {{{ % ghc Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) Test.hs:12:18: Couldn't match expected type ‘Int’ with actual type ‘a1’ ‘a1’ is untouchable inside the constraints (a ~ Int) bound by the type signature for Suc :: Expr a -> Expr Int at Test.hs:12:9-11ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for i386-unknown-linux): No skolem info: a1_anA[ssk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms ---------------------------------+------------------------------ Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+------------------------------ Description changed by Iceland_jack: Old description:
GHC panicked while experimenting
{{{#!hs {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-}
module Test where
data Expr a where Fun :: String -> (a -> b) -> (Expr a -> Expr b)
pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun str f x = Fun str f x
pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int pattern Suc n <- IntFun _ _ n where Suc n = IntFun "suc" (+ 1) n }}}
{{{ % ghc Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o )
Test.hs:12:18: Couldn't match expected type ‘Int’ with actual type ‘a1’ ‘a1’ is untouchable inside the constraints (a ~ Int) bound by the type signature for Suc :: Expr a -> Expr Int at Test.hs:12:9-11ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for i386-unknown-linux): No skolem info: a1_anA[ssk]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
New description: GHC panicked while experimenting {{{#!hs {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-} module Test where data Expr a where Fun :: String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr b) pattern IntFun str f x = Fun str f x -- Alternative syntax for pattern synonyms: -- pattern -- Suc :: () => (a ~ Int) => Expr a -> Expr Int -- Suc n <- IntFun _ _ n where -- Suc n = IntFun "suc" (+ 1) n pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int pattern Suc n <- IntFun _ _ n where Suc n = IntFun "suc" (+ 1) n }}} {{{ % ghc Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) Test.hs:12:18: Couldn't match expected type ‘Int’ with actual type ‘a1’ ‘a1’ is untouchable inside the constraints (a ~ Int) bound by the type signature for Suc :: Expr a -> Expr Int at Test.hs:12:9-11ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for i386-unknown-linux): No skolem info: a1_anA[ssk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms ---------------------------------+------------------------------ Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+------------------------------ Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms ---------------------------------+------------------------------ Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+------------------------------ Comment (by simonpj): The signatures are plain wrong. See comment:5 of #10928. In both signatures, the response should be 'a' is not in scope in the constraint `(a ~ Int)`. It's in the "required" position but mentions an existential variable. I think we should reverse the provided/required order, as descried in #10928, and do it for 8.0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms ---------------------------------+------------------------------ Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+------------------------------ Comment (by simonpj): In [changeset:"04b0a73a2a418e1ca9c282ab3f2b4fe216911fdd/ghc" 04b0a73/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="04b0a73a2a418e1ca9c282ab3f2b4fe216911fdd" Pattern synonyms: swap provided/required This patch swaps the order of provided and required constraints in a pattern signature, so it now goes pattern P :: req => prov => t1 -> ... tn -> res_ty See the long discussion in Trac #10928. I think I have found all the places, but I could have missed something particularly in comments. There is a Haddock changes; so a submodule update. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #11010: Untouchable type, pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: | patsyn/should_fail/T11010 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => patsyn/should_fail/T11010 * status: new => closed * resolution: => fixed Comment: Now we get {{{ T11010.hs:8:1: error: The 'required' context ‘a ~ Int’ mentions existential type variable ‘a’ T11010.hs:16:1: error: The 'required' context ‘a ~ Int’ mentions existential type variable ‘a’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11010#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
- 
                 GHC GHC