Is it possible to enforce a type constraint on a class instance for a higher-kinded type?

人盡茶涼 提交于 2021-01-27 15:00:19

问题


I have a type defined like this:

newtype PrimeSet a = P Integer
    deriving Eq

I have also defined a function which converts a prime set to a list, given that its type parameter is an Integral.

toList :: Integral a => PrimeSet a -> [a]

I now what to give PrimeSet a Foldable instance, so this was my first attempt (after importing fold from Data.Foldable):

instance Foldable PrimeSet where
    foldMap f = fold . map f . toList

This didn't work, however, and the compiler told me that it Could not deduce (Integral a) arising from a use of ‘toList’. My understanding of this message is that toList requires its argument to be an Integral a => PrimeSet a type, but this isn't necessarily the case in the Foldable instance.

The message also said that a possible fix would be to add Integral a to the context of the type signature for my foldMap implementation, but of course I was then told that I'm not allowed to provide my own type definitons for class methods unless I use InstanceSigs, so I tried that but that didn't seem to work either.

So my question is this: is it possible to add a type constraint to a class instance if the type parameter of the type I'm writing the class instance for is hidden - or, to reiterate, can I do something like this?

instance (Integral a) => Foldable (PrimeSet a) where

(This of course doesn't work because PrimeSet a has the kind * whereas Foldable requires * -> *)


回答1:


No, this is not possible. The whole point of higher-kinded types is to work over any parameter type. Whereas PrimeSet isn't really parametric at all – basically, it's always PrimeSet Integer. Why do you have that a parameter at all?

There is however a different class for types that are “kinda containers”, but not for arbitrary types: MonoTraversable, or actually MonoFoldable in this case.

{-# LANGUAGE FlexibleInstances, TypeFamilies #-}

import Data.MonoTraversable

type instance Element (PrimeSet a) = a
-- or, if `PrimeSet` is not parameterised,
-- type instance Element PrimeSet = Integer

instance (Integral a) => MonoFoldable (PrimeSet a) where
  otoList = YourImplementation.toList

An alternative would be that you do use parameterised types, functors in fact, but not in the normal Hask category of all Haskell types but only in the subcategory whose types areis Integer. I have such a class in my constrained-categories package. But, especially for this type you have, this really doesn't seem to make any sense.




回答2:


You can use a GADT to constrain the parameter type:

{-# LANGUAGE GADTs #-}

data PrimeSet a where
    PrimeSet :: Integral a => Integer -> PrimeSet a

instance Foldable PrimeSet where
    foldr f b (PrimeSet x) = f (fromInteger x) b

You could generalise a little with ConstraintKinds (and the monofoldable class):

data Monomorphic f c a where
    Monomorphic :: c a => f -> Monomorphic f c a

instance (item ~ Item f, MonoFoldable f) => Foldable (Monomorphic f ((~) item)) where
    foldr f b (Monomorphic xs) = ofoldr f b xs

data PrimeSet = PrimeSet Integer

instance Foldable (Monomorphic PrimeSet Integral) where
    foldr f b (Monomorphic (PrimeSet i)) = f (fromInteger i) b


来源:https://stackoverflow.com/questions/55750523/is-it-possible-to-enforce-a-type-constraint-on-a-class-instance-for-a-higher-kin

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