[Haskell-cafe] A question about type families conflicting instances

Darryn reid.darryn at gmail.com
Wed Nov 22 02:18:52 UTC 2023


Sir/Madam, 

I have familiarity with Haskell and have recently returned to using it on a small project, and have just taken a crack at using type families for the first time. I've used functional dependencies more in the past. My example below is a greatly simplified version of what I'm trying to do; for context, the overall purpose is a clean representation of logical forms across languages for abstract case analysis for theorem-proving for certain multimodal logics. The idea represented here is a unified representation for sentential forms and labelled sentential forms. The instance for the latter would be defined in terms of the instance for the former, but to keep it as simple as possible, the snippet here just has a separate (nonsense) implementation of three functions f1,f2,f3 that represent the pattern. 

I understand that that I'm running into overlapping instances but am unsure about how to correct it, and I couldn't find anything to address this in a search of the haskell-cafe archive (which is not to say that it isn't there, just that I couldn't find and/or recognise it). I'm sure it will be a simple matter to point me in the right direction here for people with more experience. 

Thank you to anyone in advance who can help; I do really appreciate it. 

-------------------------------------------------------------------------------
{-# LANGUAGE TypeFamilies, TypeFamilyDependencies, MultiParamTypeClasses, FlexibleInstances #-} 
-- A simplified model for sentences.
data S a =   SA a (S a)
           | SB a (S a)
           | SC String
          deriving (Eq, Show)

-- A simplified model for what will be abstract case analysis:
data Form a b =   FA a b
                | FB
          deriving (Eq, Show)

-- A simplified a model for the case analysis class:
class (F a ~ b) => Formable a b where
    type F a = t | t -> a
    f1 :: b -> Form a b
    f2 :: b -> b
    f3 :: b -> Bool

-- Simple test instance of Formable for S:
instance Formable a (S a) where
    type F a = S a
    f1 (SA a y) = FA a y
    f1 (SB a y) = FA a y
    f1 (SC x)   = FB
    f2 (SA a y) = SA a y
    f2 (SB a y) = SA a y
    f2 (SC x)   = SC "nothing"
    f3 (SA a y) = False
    f3 (SB a y) = False
    f3 (SC _)   = True

-- Some test instances all work fine:
-- > f1 (SA "a" (SB "b" (SC "c")))
-- > f2 (SA "a" (SB "b" (SC "c")))
-- > f3 (SA "a" (SB "b" (SC "c")))

-- A model of a wrapper for sentences to iadd integer labels:
data W a = W Int (S a)
        deriving (Eq, Show)

-- Test instance modelling an instance for labelled sentences:
instance Formable a (W a) where
    type F a = W a
    f1 (W k (SA a y)) = FA a (W k y)
    f1 (W k (SB a y)) = FA a (W k y)
    f1 (W k (SC x))   = FB
    f2 (W k x)        = W (1+k) x
    f3 (W k (SA a y)) = False
    f3 (W k (SB a y)) = False
    f3 (W k (SC _))   = True
    -- Intend to re-implement f1,f2,f3 in terms of the instance for S once
    -- I can convince GHC to let both instances stand. 
------------------------------------------------------------------------------- 

Everything is dandy if either of the two instances, for S and for W, are provided, but GHC is not at all impressed with the idea of having both.  GHCi reports the following error.
Test.hs:29:10: error:
    Conflicting family instance declarations:
      F a = S a -- Defined at Test.hs:29:10
      F a = W a -- Defined at Test.hs:51:10 

Regards,
D.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20231122/60522f62/attachment.html>


More information about the Haskell-Cafe mailing list