0

I want to write a class like this:

class C c where
    op :: c -> c -> Bool

class A b => B b where
    func :: C c => b -> c -- ^ type 'c' is random(forall). 
    func2 :: b -> b -> Bool
    func2 x y = func b `op` func c

Here, c is a type restricted by C and this restriction will be used in func2. But this cannot be compiler. Type c is not a real type. I try to add forall or using TypeFamilies, but none of them can do this. TypeFamilies looks good, but it cannot use with restriction in funcion definition like C c => b -> c or `type X x :: C * => *.

Must I use (A b, C c) => B b c to define this class? I have another class using with B like B b => D d b. If adding a param for class B, the D class needs one more param as well. In fact, Seq a will be used with class D, which cannot match D d b.

EDIT: one more description.

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Main where

type Ta = (Integer, Integer)
newtype Tb t = Tb { tb :: [t] } deriving Show

class Eq a => A a where
    a1f :: Ord b => a -> b
    a2f :: a -> a -> Bool
    a2f x y = a1f x >= a1f y

instance A Ta where
    a1f (_, y) = y

class A a => B b a where
    op :: b a -> b a

instance B Tb Ta where
    op x = x

main :: IO ()
main = putStrLn $ show $ op $ (Tb [(1, 1)] :: Tb Ta)

Compiler will complain with the line a2f :: b -> Bool:

    • Could not deduce (Ord a0) arising from a use of ‘>=’
      from the context: A a
        bound by the class declaration for ‘A’ at test.hs:10:15
      The type variable ‘a0’ is ambiguous
      These potential instances exist:
        instance Ord Ordering -- Defined in ‘GHC.Classes’
        instance Ord Integer
          -- Defined in ‘integer-gmp-1.0.2.0:GHC.Integer.Type’
        instance Ord a => Ord (Maybe a) -- Defined in ‘GHC.Maybe’
        ...plus 22 others
        ...plus four instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In the expression: a1f x >= a1f y
      In an equation for ‘a2f’: a2f x y = a1f x >= a1f y

EDIT2: Use type families

...
class Eq a => A a where
    type AT a :: *
    a1f :: Ord (AT a) => a -> AT a
    a2f :: a -> a -> Bool
    a2f x y = a1f x >= a2f y

instance A Ta where
    type AT Ta = Integer
    a1f (_, y) = y
...

It will show error with:

    • Could not deduce (Ord (AT a)) arising from a use of ‘>=’
      from the context: A a
        bound by the class declaration for ‘A’ at test.hs:10:15
    • In the expression: a1f x >= a1f y
      In an equation for ‘a2f’: a2f x y = a1f x >= a1f y
Vonfry
  • 365
  • 2
  • 16
  • `forall` does not mean random. It means [the caller chooses](https://stackoverflow.com/a/42821578/791604). In this case, the caller is `func2`, and you have to tell it how to choose. Can you say a bit more about what you're trying to accomplish, so we can give better advice on how to fix this? There are a couple (contradictory) ways forward, and it's not clear which will be best for you. – Daniel Wagner Sep 23 '19 at 12:30
  • @DanielWagner My whole program has many lines and it is only an exercise for my other course. I have added an example in the question which is the minimized problem what I have. Would you like to give me some advice? – Vonfry Sep 23 '19 at 13:27
  • You don't need to show us your whole program to explain what you're trying to accomplish, but you do need to talk about the computation you want to achieve, and why you believe that leads you inexorably to needing to have a typeclass of this shape to achieve that computation. – Daniel Wagner Sep 24 '19 at 15:22

2 Answers2

1

In your code as it stands, the problem is simply that c in func b `op` func c is ambiguous. That's not really much of a problem: just pin down the choice with a local signature. E.g.

func2 x y = func x `op` (func y :: Int)

But this may not be what you really want. Should c really be a type parameter of the func class, or of the entire instance? In the latter case, a MPTC would be the right approach.

{-# LANGUAGE MultiParamTypeClasses, AllowAmbiguousTypes, TypeApplications #-}

class ∀ b c . (A b, C c) => B b c where
  func :: b -> c
  func2 :: b -> b -> Bool
  func2 x y = func @b @c b `op` func c

Or if for each instance, only one c makes sense, then you want a type family or fundep.

{-# LANGUAGE TypeFamilies #-}

class A b => B b where
  type Ct b :: *
  func :: b -> Ct b
  func2 :: b -> b -> Bool
  func2 x y = func b `op` func c
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Sorry for my incomplete description and I have add an example what I want. The `op` in `func2` is defined in a typeclass. If I use typefamilies, the constrain is miss and `op` cannot be matched. – Vonfry Sep 23 '19 at 13:24
1

The smallest fix to your type families code that lets it compile is to move the demand for an Ord constraint from where it is produced to where it is consumed:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstrainedClassMethods #-}

type Ta = (Integer, Integer)

class Eq a => A a where
    type AT a :: *
    a1f :: a -> AT a
    a2f :: Ord (AT a) => a -> a -> Bool
    a2f x y = a1f x >= a1f y

instance A Ta where
    type AT Ta = Integer
    a1f (_, y) = y

If you'd like to only demand Ord (AT a) when the default implementation is used, you can use DefaultSignatures (and eliminate ConstrainedClassMethods):

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}

type Ta = (Integer, Integer)

class Eq a => A a where
    type AT a :: *
    a1f :: a -> AT a
    a2f :: a -> a -> Bool
    default a2f :: Ord (AT a) => a -> a -> Bool
    a2f x y = a1f x >= a1f y

instance A Ta where
    type AT Ta = Integer
    a1f (_, y) = y

However, this typeclass structure is exceeding strange and unidiomatic. (Some red flags it raises as I read it: What is that Eq constraint doing there? Why is there a class with just one instance? Why is a2f inside the class instead of outside? Why isn't a1f simply a non-class-polymorphic function? Why should we believe there is just one canonical selection function for each type?)

I'd like to reiterate that you should tell us more about what goal you are trying to achieve with this, rather than talking about your proposed typeclasses for achieving that goal. Much about this architecture screams "beginner trying to use typeclasses the way OO languages use classes", which is going to be an ongoing source of impedance mismatches and papercuts for you. I strongly suspect you simply shouldn't be defining a new typeclass at all.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • Thank for your advice. I have searched a lot about 'what is type class' and think that it is not needed here for me, just coding a data struct with some functions and not defining type class. – Vonfry Sep 25 '19 at 02:25