JeanJouX
JeanJouX

Reputation: 2741

How to embed Multiple parameter types in a single type container with a class constraint?

I would like to create a Haskell class which perform operations on multiples data types. For an example, I would like to add a value on all elements of a Map structure and retrieve a new Map.

To do that I created a class and instances with 3 types using the MultiParamTypeClasses and FlexibleInstances pragma :

class OPER a b c where
  add::  a -> b ->  c
 
instance OPER (Maybe Double) (Maybe Double) (Maybe Double)  where
  add (Just a) (Just b) = Just (a + b)
  add _ _ = Nothing

instance OPER (Map.Map Int (Maybe Double)) (Maybe Double) (Map.Map Int (Maybe Double)) where
  add ma mbdlb = Map.map (\mbi -> add mbi mbdlb ) ma

It work fine and give me what I want :

main = do
  print $ (add (Just (3.5::Double)) (Just (9.7::Double)) :: (Maybe Double))
  print $ (add (Map.fromList [(1,Just 3.4),(2,Just 9.4),(3::Int,Just (9.7::Double)),(4,Just 4.8)]) (Just (9.7::Double)) :: (Map.Map Int (Maybe Double)))


Just 13.2
fromList [(1,Just 13.1),(2,Just 19.1),(3,Just 19.4),(4,Just 14.5)]

Now, I would like to embed all possibles types in an AnyData type. I created the following :

data AnyData = forall s . (Show s, Eq s) => DAT s 

and the instances :

instance Show AnyData where
  show (DAT a) = "DAT "++show a

instance OPER AnyData AnyData AnyData  where
  add (DAT a) (DAT b) =  DAT (add a b)

But when I try to compile, I get the message :

        • Could not deduce (OPER s s1 s0) arising from a use of ‘add’
          from the context: (Show s, Eq s)
            bound by a pattern with constructor:
                       DAT :: forall s. (Show s, Eq s) => s -> AnyData,
                     in an equation for ‘add’
            at testMultiFun_test5.hs:40:8-12
          or from: (Show s1, Eq s1)
            bound by a pattern with constructor:
                       DAT :: forall s. (Show s, Eq s) => s -> AnyData,
                     in an equation for ‘add’
            at testMultiFun_test5.hs:40:16-20
          The type variable ‘s0’ is ambiguous
          Relevant bindings include
            b :: s1 (bound at testMultiFun_test5.hs:40:20)
            a :: s (bound at testMultiFun_test5.hs:40:12)
        • In the first argument of ‘DAT’, namely ‘(add a b)’
          In the expression: DAT (add a b)
          In an equation for ‘add’: add (DAT a) (DAT b) = DAT (add a b)
       |
    40 |   add (DAT a) (DAT b) =  DAT (add a b)
       |                               ^^^^^^^  

I tried to modify my AnyData type declaration with :

data AnyData = forall s . (OPER s s s, Show s, Eq s) => DAT s 

or

data AnyData = forall s s1 s2 . (OPER s s1 s2) => DAT s 

with the AllowAmbiguousTypes Pragma.

and more simply :

data AnyData = forall s . DAT s 

but I always have the same kind of message.

• No instance for (OPER s s1 s0) arising from a use of ‘add’
        • In the first argument of ‘DAT’, namely ‘(add a b)’
          In the expression: DAT (add a b)
          In an equation for ‘add’: add (DAT a) (DAT b) = DAT (add a b)
       |
    43 |   add (DAT a) (DAT b) =  DAT (add a b)
       |     

As far as I understand, the compiler doesn't understand that there can be different types to my add function when I use it with AnyData and can't resolve the inference of types.

Is there a solution to embed all the types usable with my OPER class in a single type (to make a list of results) ?

Are there other ways of doing this? with GADTs or type families ?

Upvotes: 1

Views: 90

Answers (1)

Short answer

Add a type parameter to AnyData and may be use GADTs for less constraints in instance declarations.

Type parameter for AnyData

All the code here and below works with GHC, version 8.8.4, also using compiler switch -Wall.

{-# LANGUAGE MultiParamTypeClasses #-}

class OPER a b c where
    add :: a -> b -> c

data AnyData s = DAT s

instance Show s => Show (AnyData s) where
    show (DAT a) = "DAT " ++ show a

instance (OPER a a a) => OPER (AnyData a) (AnyData a) (AnyData a) where
    add (DAT x1) (DAT x2) = DAT (add x1 x2)

instance OPER Int Int Int where
    add nA nB = nA + nB

main :: IO ()
main = 
    do
        print ( add ( DAT ( 7 :: Int ) ) ( DAT ( 13 :: Int ) ) :: (AnyData Int) )

GADTs

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}

class OPER a b c where
    add :: a -> b -> c

data AnyData s where
    DAT :: (OPER s s s) => s -> AnyData s

instance Show s => Show (AnyData s) where
    show (DAT a) = "DAT " ++ show a

instance OPER (AnyData s) (AnyData s) (AnyData s) where
    add (DAT x1) (DAT x2) = DAT (add x1 x2)

instance OPER Int Int Int where
    add nA nB = nA + nB

main :: IO ()
main = 
    do
        print ( add ( DAT ( 7 :: Int ) ) ( DAT ( 13 :: Int ) ) :: (AnyData Int) )

The advantage of GADTs is that you do not need to add a constraint to a in the the instance declaration for of OPER (AnyData a) (AnyData a) (AnyData a).

Other trials

I found one more depreciated alternative using a constraint in data type declaration.

The compiler warns: "-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language."

Additionally you have to apply UndecidableInstances to avoid the following error:

    • Variable ‘s’ occurs more often
        in the constraint ‘OPER s s s’
        than in the instance head ‘Show (AnyData s)’
      (Use UndecidableInstances to permit this)
    • In the instance declaration for ‘Show (AnyData s)’
   |
17 | instance (OPER s s s, Show s) => Show (AnyData s) where
   |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

DEPRICATED: Constraint in data type declaration (DatatypeContexts)

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DatatypeContexts #-}
{-# LANGUAGE UndecidableInstances #-}

module X2
    (
        main
    )
    where

class OPER a b c where
    add :: a -> b -> c

data (OPER s s s, Show s) => AnyData s = DAT s

instance (OPER s s s, Show s) => Show (AnyData s) where
    show (DAT a) = "DAT " ++ show a

instance (OPER s s s, Show s) => OPER (AnyData s) (AnyData s) (AnyData s) where
    add (DAT x1) (DAT x2) = DAT (add x1 x2)

instance OPER Int Int Int where
    add nA nB = nA + nB

main :: IO ()
main = 
    do
        print ( add ( DAT ( 7 :: Int ) ) ( DAT ( 13 :: Int ) ) :: (AnyData Int) )

NOTE: When applying add you have to add the the resulting type as well because the compiler cannot deduce (see in the final code line (AnyData Int)).

Final code?

Is this what you wanted to achieve?

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}

import qualified Data.Map as Map

class OPER a b c where
    add :: a -> b -> c

data AnyData s where
    DAT :: (OPER s s s) => s -> AnyData s

instance Show s => Show (AnyData s) where
    show (DAT a) = "DAT " ++ show a

instance OPER (AnyData s) (AnyData s) (AnyData s) where
    add (DAT x1) (DAT x2) = DAT (add x1 x2)

instance OPER Int Int Int where
    add nA nB = nA + nB

instance OPER (Map.Map Int (Maybe Double)) (Maybe Double) (Map.Map Int (Maybe Double)) where
  add ma mbdlb = Map.map (\mbi -> add mbi mbdlb ) ma

instance OPER (Maybe Double) (Maybe Double) (Maybe Double) where
  add (Just dA) (Just dB) = Just (dA + dB)
  add Nothing _ = Nothing
  add _ Nothing = Nothing

main :: IO ()
main = 
    do
        print ( add ( DAT ( 7 :: Int ) ) ( DAT ( 13 :: Int ) ) :: (AnyData Int) )
        print (add (Map.fromList [(1,Just 3.4),(2,Just 9.4),(3::Int,Just (9.7::Double)),(4,Just 4.8)]) (Just (9.7::Double)) :: (Map.Map Int (Maybe Double)))

Output

DAT 20
fromList [(1,Just 13.1),(2,Just 19.1),(3,Just 19.4),(4,Just 14.5)]

Upvotes: 1

Related Questions