[Haskell-cafe] Re: Sorting Types

John Creighton johns243a at gmail.com
Tue Apr 27 10:20:08 EDT 2010


> 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,
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100427/a8f4a6f4/attachment.html


More information about the Haskell-Cafe mailing list