[GHC] #11347: No skolem info: b_azg[sk]

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 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 was testing this code, which is from our ICFP paper on Coercible: {{{#!hs {-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances, AllowAmbiguousTypes #-} newtype Id1 a = MkId1 a newtype Id2 a = MkId2 (Id1 a) deriving (UnsafeCast b) type family Discern a b type instance Discern (Id1 a) b = a type instance Discern (Id2 a) b = b class UnsafeCast to from where unsafe :: from -> Discern from to instance UnsafeCast b (Id1 a) where unsafe (MkId1 x) = x unsafeCoerce :: a -> b unsafeCoerce x = unsafe (MkId2 (MkId1 x)) }}} without `AllowAmbiguousTypes` I get {{{ UnsafeCast.hs:11:3: error: Couldn't match type ‘Discern from to0’ with ‘Discern from to’ NB: ‘Discern’ is a type function, and may not be injective The type variable ‘to0’ is ambiguous Expected type: from -> Discern from to Actual type: from -> Discern from to0 In the ambiguity check for the type signature for ‘unsafe’: unsafe :: forall to from. UnsafeCast to from => from -> Discern from to To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: unsafe :: forall to from. UnsafeCast to from => from -> Discern from to In the class declaration for ‘UnsafeCast’ }}} (is that a bug? I feel like it could be, but I’m intimidated by the error message). So I put in the suggested pragma, and now I get {{{ UnsafeCast.hs:4:41: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20151111 for x86_64-unknown-linux): No skolem info: b_azg[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is GHC-almost-HEAD (changeset:2f6e87/ghc). I’ll start a rebuild with head and see what has changed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10946, #10045 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * related: => #10946, #10045 Comment: Other tickets with this error message: #10946, #10045 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10946, #10045 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Still in todays’s HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk]
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #10946, #10045 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10946, #10045 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk]
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_fail/T11347
Blocked By: | Blocking:
Related Tickets: #10946, #10045 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by simonpj):
* testcase: => typecheck/should_fail/T11347
* status: new => merge
Comment:
Done. I put the wrong ticket number in the commit, but this is it
{{{
commit 02c1c5735aff0cce2b04a6b3e4732d62bb0a4f3c
Author: Simon Peyton Jones
---------------------------------------------------------------
02c1c5735aff0cce2b04a6b3e4732d62bb0a4f3c compiler/typecheck/TcDeriv.hs | 23 +++++++++++++++------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 11 +++++++++- .../tests/deriving/should_compile/T10561.stderr | 8 +++++--- testsuite/tests/deriving/should_fail/T7148.stderr | 24 +++++++++++++--------- .../tests/typecheck/should_fail/T11347.stderr | 13 ++++++++++-- }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T11347 Blocked By: | Blocking: Related Tickets: #10946, #10045 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11347: No skolem info: b_azg[sk] -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T11347 Blocked By: | Blocking: Related Tickets: #10946, #10045 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11347#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC