[GHC] #8268: Local annotations ignored in ambiguity check

#8268: Local annotations ignored in ambiguity check -------------------------------------+------------------------------------- Reporter: maxs | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 7.7 checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects Architecture: Unknown/Multiple | valid program Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------+------------------------------------- The following program type checks correctly in GHC 7.6.3 but fails in 7.7 (2013 09 04). {{{ {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances, GADTs, OverlappingInstances, ScopedTypeVariables, TypeFamilies, TypeOperators #-} module Test where newtype Exp t = Exp (Exp t) type family EltRepr a :: * type instance EltRepr () = () data TupleType a where UnitTuple :: TupleType () class (Show a) => Elt a where eltType :: {-dummy-} a -> TupleType (EltRepr a) instance Elt () where eltType _ = UnitTuple instance (Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (a, b) where type Plain (a, b) = (Plain a, Plain b) lift (x, y) = tup2 (lift x, lift y) tup2 :: (Elt a, Elt b) => (Exp a, Exp b) -> Exp (a, b) tup2 (x1, x2) = undefined -- Exp $ Tuple (NilTup `SnocTup` x1 `SnocTup` x2) class Lift c e where type Plain e lift :: e -> c (Plain e) class Lift c e => Unlift c e where unlift :: c (Plain e) -> e fst :: forall f a b. Unlift f (f a, f b) => f (Plain (f a), Plain (f b)) -> f a fst e = let (x, _:: f b) = unlift e in x }}} The error {{{ Test.hs:34:8: Could not deduce (Plain (f b0) ~ Plain (f b)) from the context (Unlift f (f a, f b)) bound by the type signature for Test.fst :: Unlift f (f a, f b) => f (Plain (f a), Plain (f b)) -> f a at Test.hs:34:8-79 NB: ‛Plain’ is a type function, and may not be injective The type variable ‛b0’ is ambiguous Expected type: f (Plain (f a), Plain (f b)) -> f a Actual type: f (Plain (f a), Plain (f b0)) -> f a In the ambiguity check for: forall (f :: * -> *) a b. Unlift f (f a, f b) => f (Plain (f a), Plain (f b)) -> f a In the type signature for ‛Test.fst’: Test.fst :: forall f a b. Unlift f (f a, f b) => f (Plain (f a), Plain (f b)) -> f a }}} GHC 7.7 reports: {{{ Actual type: f (Plain (f a), Plain (f b0)) -> f a }}} which is incorrect due to the type annotation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8268 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8268: Local annotations ignored in ambiguity check ----------------------------------------------+---------------------------- Reporter: maxs | Owner: Type: bug | Status: closed Priority: highest | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: I'm afraid the error is quite right: `fst`'s type is ambiguous. Suppose we accepted its type. Then we said: {{{ fst2 :: forall f a b. Unlift f (f a, f b) => f (Plain (f a), Plain (f b)) -> f a fst2 = fst }}} The type sig for `fst2` is identical to `fst`, and `fst2 = fst`, so obviously it should typecheck. But it won't for the reason specified: there is no way to fix `b` in the call to `fst` inside `fst2`, because it only appears under a type function. In a more general context you'll find `fst` very hard to call. Does that make sense? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8268#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8268: Local annotations ignored in ambiguity check ----------------------------------------------+---------------------------- Reporter: maxs | Owner: Type: bug | Status: closed Priority: highest | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Comment (by maxs): Replying to [comment:1 simonpj]: Excellent. Yeah, thanks for that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8268#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC