[Haskell-cafe] newbie question about "Functional dependencies conflict between instance declarations:".....

Erik Hesselink hesselink at gmail.com
Fri Jul 5 14:55:43 CEST 2013


The constraint on an instance never influences which instance is
selected. So as far as instance selection goes, 'instance Foo x' and
'instance C x => Foo x' are the same. The constraint is only checked
after the instance is selected.

Erik

On Fri, Jul 5, 2013 at 2:43 PM, Nicholls, Mark <nicholls.mark at vimn.com> wrote:
> Hello,
>
>
>
> I largely don’t know what I’m doing or even trying to do, it is a voyage
> into the unknown….but….if I go…
>
>
>
>> {-# LANGUAGE MultiParamTypeClasses #-}
>
>> {-# LANGUAGE FunctionalDependencies #-}
>
>> {-# LANGUAGE FlexibleInstances #-}
>
>> {-# LANGUAGE UndecidableInstances #-}
>
>
>
>> class Foo x y | x -> y, y -> x
>
>> instance Foo Integer Integer
>
>
>
> That seems to work….and my head seems to say…your created some sort of
> binary relation between 2 types…and made <Integer,Integer> a member of it…
>
>
>
> Something like that anyway….
>
>
>
> Then I go….
>
>
>
>> data Bar
>
>
>
>> instance Foo Bar x
>
>
>
> Error!....but I’m think I understand this….I can’t claim that <Bar,x> is a
> member of Foo and <Integer,Integer> is member of Foo and preserve my
> functional dependencies, because <Bar,Integer> is now a member of Foo..
>
>
>
> Bad programmer…….
>
>
>
>
>
> So how I naively go….
>
>
>
>
>
>> class NotAnInteger a
>
>
>
>> instance (NotAnInteger x) => Foo Bar x
>
>
>
> I haven’t declared integer to be “NotAnInteger”….so (in a closed
> world)….this would seem to exclude the contradiction….but…
>
>
>
>
>
> Functional dependencies conflict between instance declarations:
>
>       instance Foo Integer Integer -- Defined at liam1.lhs:7:12
>
>       instance NotAnInteger x => Foo Bar x -- Defined at liam1.lhs:13:12
>
>
>
> So
>
> i)                    I clearly don’t understand something about the type
> system.
>
> ii)                   I don’t know how to restrict type variables in
> instance declarations….i.e. how do I use the notion of “Foo” across
> different combinations of types, without them colliding.
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
> CONFIDENTIALITY NOTICE
>
> This e-mail (and any attached files) is confidential and protected by
> copyright (and other intellectual property rights). If you are not the
> intended recipient please e-mail the sender and then delete the email and
> any attached files immediately. Any further use or dissemination is
> prohibited.
>
> While MTV Networks Europe has taken steps to ensure that this email and any
> attachments are virus free, it is your responsibility to ensure that this
> message and any attachments are virus free and do not affect your systems /
> data.
>
> Communicating by email is not 100% secure and carries risks such as delay,
> data corruption, non-delivery, wrongful interception and unauthorised
> amendment. If you communicate with us by e-mail, you acknowledge and assume
> these risks, and you agree to take appropriate measures to minimise these
> risks when e-mailing us.
>
> MTV Networks International, MTV Networks UK & Ireland, Greenhouse,
> Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
> International, Be Viacom, Viacom International Media Networks and VIMN and
> Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
> Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks
> Europe Inc.  Address for service in Great Britain is 17-29 Hawley Crescent,
> London, NW1 8TT.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list