[Haskell-cafe] Could not deduce ... using functional dependencies with GHC7

JP Moresmau jpmoresmau at gmail.com
Fri Mar 18 13:35:22 CET 2011


These are GHC types, but here is a self-contained example:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances #-}

data Id=Id String

data Result id =ResultId Id
    | ResultGen id

data Sig id=IdSig Id
    | SigGen id

class Search id a | a -> id where
  search :: a -> Result id

instance Search Id Id where
  search i = ResultId i

instance (Search id id) => Search id (Sig id) where
  search (SigGen g)   = search g
  search (IdSig i)    = search i

The last line fails. I don't understand why this doesn't compile.
Thanks,

JP

On Fri, Mar 18, 2011 at 12:56 PM, Dimitrios Vytiniotis
<dimitris at microsoft.com> wrote:
> Hi, can you elaborate a bit? What is Id and what is (Sig id) and IdSig in your
> example?  Can you reproduce an example that you believe should compile but doesn't?
>
> thanks
> d-
>
> -----Original Message-----
> From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of JP Moresmau
> Sent: 16 March 2011 21:46
> To: Haskell Cafe
> Subject: [Haskell-cafe] Could not deduce ... using functional dependencies with GHC7
>
> Hello, when moving to GHC7 a body of code that I'm not immensely familiar with, I got an error compiling with GHC 7.0.2. Can somebody kindly explain to me what it means and how to get around it?
> This is in the scion code base so is using some GHC types.
>
> I have a class with a functional dependency (I think :-p):
> class Search id a | a -> id where
>  search :: (SrcSpan -> Bool) -> SrcSpan -> a -> SearchResults id
>
> And some instances, notably:
> instance Search Id Id where
>  search _ _ i = only (FoundId i)
>
> And the error occurs on another instance:
> instance (Search id id) => Search id (Sig id) where
>  search p s (IdSig i)       = search p s i
>  ... other cases here, that work
>
> The error is:
>
> Could not deduce (id ~ Id)
>    from the context (Search id id)
>      bound by the instance declaration
>      at lib\Scion\Inspect\Find.hs:477:10-45
>      `id' is a rigid type variable bound by
>           the instance declaration at lib\Scion\Inspect\Find.hs:477:18
>    When using functional dependencies to combine
>      Search Id Id,
>        arising from the dependency `a -> id'
>        in the instance declaration at lib\Scion\Inspect\Find.hs:183:10
>      Search id Id,
>        arising from a use of `search'
>        at lib\Scion\Inspect\Find.hs:479:32-37
>    In the expression: search p s i
>    In an equation for `search': search p s (IdSig i) = search p s i
>
> If I replace the call to search with the actual implementation of search for Id, it compiles, so at some level the code "makes sense".
> I much prefer when error messages end with "Possible fix:..."!
>
> Thanks!
>
> --
> JP Moresmau
> http://jpmoresmau.blogspot.com/
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
JP Moresmau
http://jpmoresmau.blogspot.com/



More information about the Haskell-Cafe mailing list