DataKinds and type class instances

跟風遠走 提交于 2019-12-10 13:53:33

问题


The following example is a boiled-down version of my real-life problem. It seems to be in some way similar to Retrieving information from DataKinds constrained existential types, but I could not quite get the answers I was seeking.

Suppose we have a finite, promoted DataKind K with types A and B, and a poly-kinded Proxy data-type to generate terms with types of kind *.

{-# LANGUAGE DataKinds, PolyKinds, GADTs, FlexibleInstances, FlexibleContexts #-}

data K = A | B

data Proxy :: k -> * where Proxy :: Proxy k

Now I want to write Show-instances for every type Proxy a where a is of kind K, which are exactly two:

instance Show (Proxy A) where show Proxy = "A"
instance Show (Proxy B) where show Proxy = "B"

But to use the Show-instance, I have to explicitly provide the context, even if the kind is restricted to K:

test :: Show (Proxy a) => Proxy (a :: K) -> String
test p = show p

My goal is to get rid of the type-class constraint. This may seem unimportant, but in my real application, this has major implications.

I could also define a single, but more general Show-instance like this:

instance Show (Proxy (a :: K)) where show p = "?"

This actually allows me to drop the constraint, but the new problem is to differentiate between the two types A and B.

So, is there a way to eat my cake and have it too? That is, not having to provide a type-class constraint in the type of test (kind annotations are fine, though), and still having two different show implementations (e.g. by differentiating the types somehow)?

Actually, it would also be okay to drop the entire type class, if I could simply associate the respective types (A, B) with their specific values (here: "A", "B") in a context where I just have the type information. I have no idea how to do this, though.

I would be very thankful for any provided insights.


回答1:


No, this is not possible. In a context where you have "just the type information", at run-time, you really have no information. Type information is erased. So even for closed kinds, where it is in principle possible to show that given the type in question, you can always come up with a dictionary, you still need the class constraint. The class constraint ensures that at compile time, when GHC knows the type, it can select the appropriate instance to pass along. At run-time, the information which type it is is lost, and there's no chance to do the same. Writing a "one size fits all" instance does indeed work, because then the exact type does not matter for the choice anymore.

I don't know the full picture, but it may be possible to work around this by explicitly bundling up either the class dictionary or the string itself with the value you are passing around ...




回答2:


You can add another class.

class Kish (k :: K) where
  toK :: proxy k -> K

instance Kish A where
  toK _ = A

instance Kish B where
  toK _ = B

instance Kish k => Show (Proxy k) where
  showsPrec n _ = case toK (Proxy :: Proxy k) of
    A -> ...
    B -> ...

Now you'll still be stuck with a context, but it's a more general one that might well be useful for other things too.

If it turns out that you tend to need to distinguish the proxies a lot, then you should switch to a GADT that you can just inspect as needed instead of using a proxy.




回答3:


Knowing that:

  1. a is of kind K
  2. the only types of kind K are A and B
  3. Show (Proxy A) holds
  4. Show (Proxy B) holds

is sufficient to prove that Show (Proxy a) holds. But a type class isn't just a proposition that we need to prove true to use with our type, it also provides implementations. To actually use show (x :: Proxy a) we need to not just prove that an implementation for Show (Proxy a) exists, we need to actually know which one it is.

Haskell type variables (without constraints) are parametric: there's no way to be fully polymorphic in a, and also be able to inspect a to provide different behaviour for A and B. The "different behaviour" you want is about as "close to parametric" as you can possibly be without actually being parametric, since it's just the selection of a different instance for each type when you know there is one for each type. But it's still something that breaks the contract of what test :: forall (a :: K). Proxy a -> String means.

Type class constraints allow your code to be non-parametric in the constrained type variables, in as much as you can use the type class' mapping from types to implementations to switch how your code behaves based on the type it's invoked at. So test :: forall (a :: K). Show (Proxy a) => Proxy a -> String works. (In terms of the actual implementation, the same ultimate caller who gets to choose the type a also provides the Show (Proxy a) instance for the code generated from your function to use).

You can use your instance Show (Proxy (a :: K)) idea; now your function that is parametric in a type a :: K can still use show (x :: Proxy a) because there is one instance that works for all a :: K. But the instance itself runs into the same problem; the implementation of show in the instance is parametric in a, and so can't inspect it in anyway in order to return a different string based on the type.

You can use something like dfeuer's answer, where Kish exploits the non-parametricity of constrained type variables to basically allow you to inspect the type at runtime; the instance dictionary passed along to satisfy the Kish a constraint basically is a run time record of which type was chosen for the variable a (in a roundabout way). Pushing this idea further gets you all the way to Typeable. But you still need some sort of constraint to make your code non-parametric in a.

You can also use a type that is explicitly a runtime representation of the choice of A or B (as opposed to Proxy, which is an empty value at runtime and only provides a compile-time representation of the choice), something like:

{-# LANGUAGE DataKinds, GADTs, KindSignatures, StandaloneDeriving #-}

data K = A | B

data KProxy (a :: K)
  where KA :: KProxy A
        KB :: KProxy B

deriving instance Show (KProxy a)

test :: KProxy a -> String
test = show

(Note here I can not only implement Show (Kproxy a), I can actually derive it, although it does require standalone deriving)

This is using a GADT KProxy to allow test to be non-parametric in a, essentially doing the same job as the Kish constraint from dfeuer's answer but avoiding the need to add an extra constraint to your type signatures. In an earlier version of this post I stated that test was able to do this while remaining "just" parametric in a, which was incorrect.

Of course now to pass a proxy you have to actually write KA or KB. That's no bother where you were having to write Proxy :: Proxy A to actually choose the type (which is often the case with proxies, given that you usually only use them to fix a type that otherwise would be ambiguous). But where it would have been unambiguous anyway the compiler will catch you if you're inconsistent with the rest of the call, but you can't write just one symbol like Proxy and have the compiler infer the correct meaning. You can address that with a type class:

class KProxyable (a :: K)
  where kproxy :: KProxy a

instance KProxyable A
  where kproxy = KA

instance KProxyable B
  where kproxy = KB

Then you can use KA instead of Proxy :: Proxy A, and kproxy instead of letting the compiler infer the type of a bare Proxy. Stupid example time:

foo :: KProxy a -> KProxy a -> String
foo kx ky = show kx ++ " " ++ show ky

GHCI:

λ foo KA kproxy
"KA KA"

Note I'm not actually needing to have a KProxyable constraint anywhere; I use kproxy at a point where the type is known. This still has to "come in from the top", though (exactly as the instance dictionary satisfying your Show (Proxy a) constraint would); there's no way to have a function parametric in a type a :: K come up with the relevant KProxy a on its own.

Because it's the correspondence between the constructors and the type that makes this work, I don't believe you can make a generic proxy in this style the way you can with the empty-at-runtime Proxy. TemplateHaskell could certainly generate such proxy types for you though; I think the concept of singletons is the general idea here, and so the https://hackage.haskell.org/package/singletons probably provides what you need, but I'm not very familiar with how to actually use that package.



来源:https://stackoverflow.com/questions/32408110/datakinds-and-type-class-instances

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!