简体   繁体   中英

How do I specifiy class constraints for p in (:+:) f g p? (With :+: from GHC.Generics)

To encode choice between constructors GHC.Generics defines the following type:

data    (:+:) f g p = L1 (f p) | R1 (g p)

The Generic class provides the method from to convert a Generic type to a representation:

from :: a -> Rep a x

To write a function that is type generic, I define a class that works on the representation:

class MyClass r where myFun :: r a -> Maybe Int

Assume I also have a class SomeClass for which I defined the instance:

instance (SomeClass (f p),SomeClass (g p)) => SomeClass ((:+:) f g p) where
  someFun (R1 _) = Just 42

How would I add a SomeClass constraint to an MyClass instance of the Generic sum type? In other words, what is wrong with the following instance:

instance (SomeClass (f p), SomeClass (g p), MyClass f, MyClass g)
      => MyClass ((:+:) f g) where
 myFun (L1 x) = myFun x
 myFun y      = someFun y -- Error: Could not deduce (SomeClass (f a))
                          -- arising from a use of ‘someFun’

A complete example I wrote is:

{-# LANGUAGE TypeOperators, DefaultSignatures, DeriveGeneric, FlexibleContexts, 
             UndecidableInstances, AllowAmbiguousTypes, RankNTypes #-}
module M where
import GHC.Generics

---

class SomeClass a where 
  someFun :: a -> Maybe Int
  default someFun :: (Generic a, MyClass (Rep a)) => a -> Maybe Int
  someFun x = myFun (from x)

instance (SomeClass (f p),SomeClass (g p)) => SomeClass ((:+:) f g p) where
  someFun (R1 _) = Just 42

instance SomeClass Int where
  someFun i  = Just i

---

class MyClass r where 
  myFun :: r a -> Maybe Int

instance (SomeClass a) => MyClass (K1 i a) where
  myFun (K1 x) = someFun x -- This is fine

instance (SomeClass (f p), SomeClass (g p), MyClass f, MyClass g) => MyClass ((:+:) f g) where
  myFun (L1 x) = myFun x
  myFun y      = someFun y -- Error: Could not deduce (SomeClass (f a)) arising from a use of ‘someFun’

If you add a SomeClass a constraint to myFun there's really nothing more to do.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}

import Control.Applicative
import GHC.Generics

class SomeClass a where
    someFun :: a -> Maybe Int

class MyClass f where
    myFun :: SomeClass a => f a -> Maybe Int

    default myFun :: (Generic1 f, MyClass (Rep1 f), SomeClass a) => f a -> Maybe Int
    myFun f = myFun (from1 f)

You can write instances for all of the data types used in generic representations. The most interesting of these is Par1 , which actually uses the SomeClass a constraint to use someFun on an occurrence of the parameter.

-- occurences of the parameter
instance MyClass Par1 where
    myFun (Par1 p) = someFun p

-- recursions of kind *
instance SomeClass a => MyClass (K1 i a) where
    myFun (K1 a) = someFun a

-- recursions of kind * -> *
instance MyClass f => MyClass (Rec1 f) where
    myFun (Rec1 f) = myFun f

-- constructors with no arguments
instance MyClass U1 where
    myFun (U1) = Nothing -- or Just 0 or Just 1 depending on what you're doing

-- constructors with multiple arguments
instance (MyClass f, MyClass g) => MyClass (f :*: g) where
    myFun (f :*: g) = liftA2 (+) (myFun f) (myFun g)  -- or howerever you are going to combine the Maybe Int

-- data types with multiple constructors
instance (MyClass f, MyClass g) => MyClass (f :+: g) where
    myFun (L1 f) = myFun f
    myFun (R1 g) = myFun g

-- metadata
instance (MyClass f) => MyClass (M1 i c f) where
    myFun (M1 f) = myFun f

If you want to support composition of functors, we'll have to be a bit more clever. The obvious definition requires a SomeClass (Maybe Int) instance.

-- composition of functors
instance (MyClass f, MyClass g, Functor f) => MyClass (f :.: g) where
    myFun (Comp1 fg) = myFun $ fmap myFun fg

Deriving SomeClass from MyClass

We'll get SomeClass instances generically reusing MyClass to get them. Since MyClass 's myFun requires a SomeClass instance, we'll need to prove that the parameter Par1 never occurs in a Rep . from' will prove that the parameter is empty.

class SomeClass a where
    someFun :: a -> Maybe Int

    default someFun :: (Generic a, MyClass (Rep a)) => a -> Maybe Int
    someFun a = myFun (from' a)

The Void type from void represents a type that can't logically exist. The following proves that the parameter for a Generic is always empty

-- Prove that the parameter is always empty
from' :: Generic a => a -> Rep a Void
from' = from

To satisfy the SomeClass constraint for myFun we equip Void with a SomeClass instance. We can be sure someFun :: Void -> Maybe Int is never called because there's no value of type Void to pass to it.

instance SomeClass Void where
    someFun = absurd

Now we can derive an instance for SomeClass (Maybe Int) assuming we have a SomeClass Int instance.

-- The following instances are needed for the composition of functors
instance SomeClass Int where
    someFun = Just

instance SomeClass a => SomeClass (Maybe a)

Deriving SomeClass

You don't need to reuse MyClass with Void to derive SomeClass instances. Instead you can define another class for things that have a myFun regardless of what the parameter is.

class GSomeClass f where
    gsomeFun :: f a -> Maybe Int

You'd write GSomeClass instances for everything except Par1 and Rec1 and use GSomeClass to derive SomeClass instances. The Generic instances never use the parameter, not even for types like Maybe a ; instead each occurrence of the parameter a appears as a K1 iap .

class SomeClass a where
    someFun :: a -> Maybe Int

    default someFun :: (Generic a, GSomeClass (Rep a)) => a -> Maybe Int
    someFun a = gsomeFun (from a)

There's no way in Haskell currently to write constraints of the kind forall p. SomeClass (fp) => forall p. SomeClass (fp) => which is what you are trying to do in the type

(SomeClass (f p), SomeClass (g p), MyClass f, MyClass g) => MyClass ((:+:) f g)

There is a trick to capture those constraints with a second type class. You could write a second class FSomeClass f that represents forall p. SomeClass (fp) forall p. SomeClass (fp) . If SomeClass is simple, you can just reproduce the fields of the dictionary for SomeClass in the dictionary for FSomeClass , using fa in place of a everywhere.

class FSomeClass f where
    fsomeFun :: f a -> Maybe Int

If SomeClass is more complicated, or if you need to provide a real SomeClass instance to code that depends on it, you can instead capture the entire SomeClass dictionary in a GADT . Dict captures a dictionary for any constraint.

{-# LANGUAGE GADTs #-}
{-# LANGUAGE ConstraintKinds #-}

data Dict c where
    Dict :: c => Dict c

With Dict s we can write a class that says that, for every a , fa has a SomeClass instance trapped in a Dict .

class FSomeClass f where
    someDict :: p0 a -> p1 f -> Dict (SomeClass (f a))
    --          |       |       ^ there's a SomeClass (f a) instance
    --          |       ^ for this f
    --          ^ for any a 

To get to the SomeClass (fa) instance you'd pattern match on the dictionary.

SomeClass and FSomeClass instances

We'll make SomeClass (fp) instances for all the types from GHC.Generics and FSomeClass f instances that demonstrate that p can vary over all types.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}

For Par1 , there's nothing we can do with the parameter p , since it can vary over all types. Our only other option is to provide no SomeClass (Par1 p) instance. For Par1 , K1 , and U1 the SomeClass instances have no constraints and the FSomeClass instance just captures the SomeClass dictionary.

instance SomeClass (Par1 p) where
    someFun (Par1 p) = Nothing -- You can't do anything with the p; you know nothing about it.

instance FSomeClass Par1 where
    someDict _ _ = Dict

instance SomeClass a => SomeClass (K1 i a p) where
    someFun (K1 a) = someFun a

instance SomeClass a => FSomeClass (K1 i a) where
    someDict _ _ = Dict

instance SomeClass (U1 p) where
    someFun (U1) = Nothing -- or Just 0 or Just 1 depending on what you're doing

instance FSomeClass U1 where
    someDict _ _ = Dict

The SomeClass instances for M1 and Rec1 require a SomeClass (fp) => constraint. Before we can construct a Dict for eg SomeClass (Rec1 fp) we have to introduce a dictionary for SomeClass (fp) . We get the dictionary from SomeClass (fp) from the FSomeClass instance for f and pattern match on its Dict .

instance SomeClass (f p) => SomeClass (Rec1 f p) where
    someFun (Rec1 f) = someFun f

instance (FSomeClass f) => FSomeClass (Rec1 f) where
    someDict pa _ = case someDict pa (Proxy :: Proxy f) of Dict -> Dict

instance SomeClass (f p) => SomeClass (M1 i c f p) where
    someFun (M1 f) = someFun f

instance (FSomeClass f) => FSomeClass (M1 i c f) where
    someDict pa _ = case someDict pa (Proxy :: Proxy f) of Dict -> Dict

For products and sums there are two constraints on the SomeClass instances, so we get and pattern match on two dictionaries. We'd handle composition of functors the same way, but I'm skipping it for brevity.

instance (SomeClass (f p), SomeClass (g p)) => SomeClass ((f :*: g) p) where
    someFun (f :*: g) = liftA2 (+) (someFun f) (someFun g)   -- or howerever you are going to combine the Maybe Int

instance (FSomeClass f, FSomeClass g) => FSomeClass (f :*: g) where
    someDict pa _ = case someDict pa (Proxy :: Proxy f) of
                       Dict -> case someDict pa (Proxy :: Proxy g) of
                           Dict -> Dict

instance (SomeClass (f p), SomeClass (g p)) => SomeClass ((f :+: g) p)  where
    someFun (L1 f) = someFun f
    someFun (R1 g) = someFun g

instance (FSomeClass f, FSomeClass g) => FSomeClass (f :+: g) where
    someDict pa _ = case someDict pa (Proxy :: Proxy f) of
                       Dict -> case someDict pa (Proxy :: Proxy g) of
                           Dict -> Dict

Using FSomeClass

With your original MyClass

class MyClass f where
    myFun :: f a -> Maybe Int

We'll write an instance for :+: . We'll take your original signature and replace SomeClass (fp) with FSomeClass f .

instance (SomeClass (f p), SomeClass (g p), MyClass f, MyClass g) => MyClass ((:+:) f g)
instance (FSomeClass f,    FSomeClass g   , MyClass f, MyClass g) => MyClass ((:+:) f g)

The branch for R1 literally uses someFun .

instance (FSomeClass f, FSomeClass g, MyClass f, MyClass g) => MyClass (f :+: g) where
    myFun (L1 f) = myFun f
    myFun (R1 g) = case someDict g (Proxy :: Proxy g) of
                       Dict -> someFun g

I cannot recommend writing instances for :+: that are not associative. If you want to treat the first constructor differently, you should guarantee that later constructors won't be treated in the same way as the first constructor. A datatype

data MySum = A | B | C

Has more than one possible representation. Taking liberties with metadata, the two possible representations for MySum are

 A :+: (B :+: C)
(A :+: B) :+: C

The constructors' representations could be either of

L1 A      | R1 (L1 B) | R1 (L1 C)
L1 (L1 A) | L1 (R1 B) | R1     C

The technical post webpages of this site follow the CC BY-SA 4.0 protocol. If you need to reprint, please indicate the site URL or the original address.Any question please contact:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM