ConstraintKinds and default associated empty constraints

Simon Peyton-Jones simonpj at microsoft.com
Fri Dec 23 16:17:35 CET 2011


Right now it seems it is either * or Constraint depending on context.

Correct.  Tuple bracket are used for both types and Constraints, and we have to decide which from context.

            As I understand you, fixing this seems to indicate that () could have any 'a -> Constraint' kind as well.

No.  () has kind * or Constraint, depending on context, never a -> Constraint.
Similarly (,) has kind * -> * -> * or Constraint -> Constraint -> Constraint, depending on context.

Imaging that there are two sorts of parens, one for types and one for constraints.  We figure out which is intended from context.

S

From: Edward Kmett [mailto:ekmett at gmail.com]
Sent: 23 December 2011 15:05
To: Simon Peyton-Jones
Cc: Bas van Dijk; glasgow-haskell-users at haskell.org
Subject: Re: ConstraintKinds and default associated empty constraints

Fair enough.

So if I understand you correctly, () is becoming more overloaded as to its kind?

Right now it seems it is either * or Constraint depending on context.

As I understand you, fixing this seems to indicate that () could have any 'a -> Constraint' kind as well.

This raises similar questions about (,) and how to build 'a -> Constraint' products nicely.

Sent from my iPad

On Dec 23, 2011, at 4:42 AM, Simon Peyton-Jones <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
it’s a bug.  I’m fixing it.

Simon

From: glasgow-haskell-users-bounces at haskell.org<mailto:glasgow-haskell-users-bounces at haskell.org> [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Edward Kmett
Sent: 22 December 2011 17:03
To: Bas van Dijk
Cc: glasgow-haskell-users at haskell.org<mailto:glasgow-haskell-users at haskell.org>
Subject: Re: ConstraintKinds and default associated empty constraints

On Wed, Dec 21, 2011 at 6:45 PM, Bas van Dijk <v.dijk.bas at gmail.com<mailto:v.dijk.bas at gmail.com>> wrote:
I'm playing a bit with the new ConstraintKinds feature in GHC
7.4.1-rc1. I'm trying to give the Functor class an associated
constraint so that we can make Set an instance of Functor. The
following code works but I wonder if the trick with: class Empty a;
instance Empty a, is the recommended way to do this:

{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-}

import GHC.Prim (Constraint)

import Prelude hiding (Functor, fmap)

import           Data.Set (Set)
import qualified Data.Set as S (map, fromList)

class Functor f where
    type C f :: * -> Constraint
    type C f = Empty

    fmap :: (C f a, C f b) => (a -> b) -> f a -> f b

class Empty a; instance Empty a

instance Functor Set where
    type C Set = Ord
    fmap = S.map

instance Functor [] where
    fmap = map

testList = fmap (+1) [1,2,3]
testSet  = fmap (+1) (S.fromList [1,2,3])

Cheers and thanks for a great new feature!

Bas

This is the same solution I wound up with in

https://github.com/ekmett/constraints

Adding an argument to the family would work but is somewhat unsatisfying as it mucks with polymorphic recursive use of the dictionary, and with placing constraints on constraints, so I prefer to keep as few arguments as possible.

You can go farther with Functor by using polymorphic kinds and indexing the source and destination Category as well as the class of objects in the category.

I should probably write up what I've done with this, but doing so lets you have real product and coproduct Category instances, which were previously not possible (a fact which in part drove me to write all the semigroupoid code i have on hackage.

-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20111223/e4a19406/attachment-0001.htm>


More information about the Glasgow-haskell-users mailing list