[Haskell-cafe] type-level programming support library

Edward Kmett ekmett at gmail.com
Mon Mar 30 15:22:38 EDT 2009


Thats a bit farther down the rabbit hole than the concern in question,
though certainly related.

 An example of what you could write with polymorphic kinds, inventing a
notation for polymorphic kind variables using 'x to denote a polymorphic
kind x, which could subtitute in for a kind k = * | ** | k -> k | ...

type Id (f :: 'k) = f
type Const (a :: 'a) (b :: 'b) = a

data True
data False

type family If c (x :: 'k) (y :: 'k) :: 'k
type instance If True x y = x
type instance If False x y = y

then you could safely apply Id and If types of different kinds.

class Container x where
    type Elem x :: *
    type SearchOffersMultipleResults x :: *
    search :: x -> SearchResult x

 type SearchResult x =  (If (SearchOffersMultipleResults x) [] Maybe) (Elem
x)

instance Container (SomeContainer a) where
    type Elem (SomeContainer a) = a
     type SearchOffersMultipleResults (SomeContainer a) = True

I suppose once down this slippery slope you might consider classes that are
parameterized on types with polymorphic kinds as well, but I definitely
wouldn't start there. ;)

-Edward

On Mon, Mar 30, 2009 at 2:54 PM, John Van Enk <vanenkj at gmail.com> wrote:

> I suppose having a good description of what I'd like to do might help: I'd
> like to be able to make an N-Tuple an instance of a type class.
>
> class Foo a where
>     ....
>
> instance Foo (,) where
>     ....
>
> instance Foo (,,) where
>     ....
> The different kindedness of (,) and (,,) prevent this from working.
>
> /jve
>
>
> On Mon, Mar 30, 2009 at 2:00 PM, Martijn van Steenbergen <
> martijn at van.steenbergen.nl> wrote:
>
>> John Van Enk wrote:
>>
>>>  > Haskell not having 'polymorphic kinds'.
>>>  Is there a good description of why Haskell doesn't have polymorphic
>>> kinds?
>>>
>>
>> IANA expert but polymorphic kinds belong to a set of reasonably new
>> influences (e.g. from dependently typed programming languages and generic
>> programming) and they haven't been 1) polished enough to be a widely
>> accepted standard or 2) simply haven't been implemented yet (low priority,
>> etc).
>>
>> Besides that, I sometimes see polymorphic kinds in GHC error messages, so
>> I suspect that at least parts of GHC already support them.
>>
>> Martijn.
>>
>>
>
>
> --
> /jve
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090330/ab29bdb2/attachment-0001.htm


More information about the Haskell-Cafe mailing list