
#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