[Haskell-cafe] Re: Sorting Types

Robert Greayer robgreayer at gmail.com
Tue Apr 27 11:23:10 EDT 2010


On Tue, Apr 27, 2010 at 10:20 AM, John Creighton <johns243a at gmail.com> wrote:
>
>> I was wondering if it is possible to sort types in hakell and if so what
>> language extension I should use. Not sure if
>> this is possible but here is my attempt:
>>
>> (I'm aware I don't need so many pragmas
>>
>> {-# LANGUAGE GADTs #-}
>> {-# LANGUAGE TypeFamilies #-}
>> {-# LANGUAGE UndecidableInstances #-}
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> {-# LANGUAGE FlexibleInstances #-}
>> {-# LANGUAGE TypeSynonymInstances #-}
>> data Z=Z deriving (Show)
>> data S i=S i deriving (Show)
>> data family N a
>> type family Add n m
>> type instance Add Z m = m
>> type instance Add m Z = m
>> type instance Add (S n) (S m) = S (S (Add n m))
>> --14
>> type family LT a b
>> data Cat=Cat
>> data Dog=Dog
>> data Fish=Fish
>> type family Sort a --19
>> data And a b=And a b
>>
>> type instance LT Dog Z = Cat
>> type instance LT Fish Z = Dog
>> type instance LT a (S i) = LT (LT a Z) i
>> type instance Sort (And a (LT a i))=And (LT a i) a
>>
>> I get the following error:
>>
>>   Illegal type synonym family application in instance: And a (LT a i)
>>   In the type synonym instance declaration for 'Sort'
>> Failed, modules loaded: none,
>>
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

It's certainly possible.  There's a sample on the haskell wiki using
functional dependencies:

http://www.haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort

This could be translated to type families.  Your instance:

type instance Sort (And a (LT a i))=And (LT a i) a

is illegal because you are using a type function (LT) in the instance head.


More information about the Haskell-Cafe mailing list