[GHC] #7812: Ambiguity check too eager with unconstrained type variable

#7812: Ambiguity check too eager with unconstrained type variable -----------------------------+---------------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.7 | Keywords: AmbiguityCheck Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Consider the following code: {{{ {-# LANGUAGE TypeFamilies, DataKinds, GADTs #-} type family F (b :: Bool) a type instance F False a = a type instance F True a = Int data SBool :: Bool -> * where SFalse :: SBool False STrue :: SBool True foo :: SBool b -> [F b a] foo _ = [] }}} GHC 7.6.1 compiles this code without a problem, and both {{{foo STrue}}} and {{{foo SFalse}}} are well typed and evaluate to {{{[]}}}. HEAD (even after yesterday's ambiguity patch for #7804) does not compile this code, complaining about ambiguity. Here is the error: {{{ Couldn't match type ‛F b a0’ with ‛F b a’ NB: ‛F’ is a type function, and may not be injective The type variable ‛a0’ is ambiguous Expected type: SBool b -> [F b a] Actual type: SBool b -> [F b a0] In the ambiguity check for: forall (b :: Bool) a. SBool b -> [F b a] In the type signature for ‛foo’: foo :: SBool b -> [F b a] }}} This is admittedly a weird corner case, but it's one I've run into in real(ish) code. On first glance, the type variable {{{a}}} really is ambiguous in the type signature for {{{foo}}}. But, it turns out that this is a benign ambiguity, because the variable is either ignored or, after type family simplification, appears in an inferrable location within the type. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7812 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7812: Ambiguity check too eager with unconstrained type variable ----------------------------------------+----------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: AmbiguityCheck | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------------+----------------------------------- Changes (by simonpj): * difficulty: => Unknown Comment: Unlike #7804, this one is by design. Suppose you said {{{ bar :: SBool b -> [F b a] bar = foo }}} You'd expect that to work, right? Same type signature! But it doesn't, even in 7.6: {{{ T7812.hs:17:7: Couldn't match type `F b a' with `F b a0' NB: `F' is a type function, and may not be injective The type variable `a0' is ambiguous Possible fix: add a type signature that fixes these type variable(s) Expected type: SBool b -> [F b a] Actual type: SBool b -> [F b a0] In the expression: foo In an equation for `bar': bar = foo }}} People complained about this, especially when they got an inferred type, tried to add it as a type signature, and had the program rejected. Your example is deeply strange too; if you put a singleton list you might well be stuck. And you could just make your type signature polymorphic in the list {{{ foo :: SBool b -> [c] }}} In short, I can't see how to help here. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7812#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7812: Ambiguity check too eager with unconstrained type variable ----------------------------------------+----------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: AmbiguityCheck | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------------+----------------------------------- Comment(by goldfire): I understand the motivation for disallowing my code, but perhaps I have a compelling enough use case to counter that argument. I'm experimenting with heterogeneous lists, using the HList library as a high-level design spec, but I'm avoiding any use of functional dependencies in my code. The HList library defines {{{hMapOut}}}, a function to map a hetero list to a plain old regular list. Because the function involved in the map must work with a variety of types of input (because the source list is hetero), HList uses a symbol to represent the function and defines instances of a class (which I call {{{Applicable}}}) to define the operation of the function at different types. {{{ class Applicable (f :: *) (x :: *) where type Apply f x :: * apply :: f -> x -> Apply f x -- example to aid understanding of Applicable; otherwise, Id is unused here data Id = Id instance Applicable Id x where type Apply Id x = x apply Id x = x }}} Here is my definition of hetero lists: {{{ data HList :: [*] -> * where HNil :: HList '[] HCons :: h -> HList t -> HList (h ': t) }}} How can we define {{{hMapOut}}}? Provided we are mapping over a non-empty list, we can simply use the {{{Apply}}} associated type family on, say, the first type in the list to find the resultant type. But, what should we do on an empty list? Ideally, we want the type of {{{hMapOut f HNil}}} to be {{{[a]}}} for any {{{a}}}. But, it is necessary to define {{{hMapOut}}} to use a type family in its return type, and thus the return type of {{{hMapOut}}} looks like the return type of {{{foo}}}, above -- it mentions a type variable that is not mentioned anywhere else in the type. Here are my definitions, which work well under GHC 7.6.1: {{{ type family MapOut (f :: *) (list :: [*]) (a :: *) :: * type instance MapOut f '[] a = a type instance MapOut f (h ': t) a = Apply f h type family MapOuttable (f :: *) (list :: [*]) :: Constraint type instance MapOuttable f '[] = () type instance MapOuttable f '[elt] = Applicable f elt type instance MapOuttable f (h1 ': h2 ': t) = (Applicable f h1, Apply f h1 ~ Apply f h2, MapOuttable f (h2 ': t)) data Proxy a = P hMapOutP :: MapOuttable f list => Proxy a -> f -> HList list -> [MapOut f list a] hMapOutP _ _ HNil = [] hMapOutP _ f (HCons elt HNil) = [apply f elt] hMapOutP p f (HCons h t@(HCons _ _)) = apply f h : hMapOutP p f t hMapOut :: forall f list a. MapOuttable f list => f -> HList list -> [MapOut f list a] hMapOut = hMapOutP (P :: Proxy a) }}} Unsurprisingly, my {{{hMapOutP}}} function needs a {{{Proxy}}} argument, because it is recursive and needs to make sure that the result type is consistent across recursive calls. But, the toplevel {{{hMapOut}}} function does not need a proxy, and it works as desired, allowing {{{a}}} to be inferred for an empty list. An alternate design for this would have each function symbol (like {{{Id}}}) to declare a ''default'' type, just for this scenario. Then, we would have an escape hatch for the empty list. But, that won't always be possible. Consider a symbol {{{Widen}}} that maps both {{{Int}}}s and {{{Integer}}}s to {{{Integer}}}s and maps both {{{Float}}}s and {{{Double}}}s to {{{Double}}}s. This seems like a logical enough operation, and yet it would resist a default type. I think a reasonable person could look at all of this and say "Well, yes, but it's all quite a strange corner case and not something we need to support". I couldn't strongly disagree with such a statement. But, I don't see another way, without functional dependencies, of getting this behavior. One possible way to support this code would be to have a new language flag (ugh) to disable the new ambiguity check. That would restore the GHC 7.6.1 behavior and would suffice for my needs. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7812#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7812: Ambiguity check too eager with unconstrained type variable --------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: invalid | Keywords: AmbiguityCheck Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: I have figured out a suitable workaround. Instead of using a type family application in a return type, just have the function return {{{[result]}}}. Then, use a type family to optionally create an equality constraint for {{{result}}}. {{{ type family MapOuttable (f :: *) (list :: [*]) (result :: *) :: Constraint type instance MapOuttable f '[] result = () type instance MapOuttable f '[elt] result = (Applicable f elt, result ~ Apply f elt) type instance MapOuttable f (h1 ': h2 ': t) result = ( Applicable f h1 , Apply f h1 ~ Apply f h2 , MapOuttable f (h2 ': t) result , result ~ Apply f h1 ) hMapOut :: MapOuttable f list a => f -> HList list -> [a] hMapOut _ HNil = [] hMapOut f (HCons elt HNil) = [apply f elt] hMapOut f (HCons h t@(HCons _ _)) = apply f h : hMapOut f t }}} Given this workaround -- which should always be available in the case I'm thinking of -- I will close the ticket. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7812#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC