[Haskell-cafe] Derived type definition

Miguel Mitrofanov miguelimo38 at yandex.ru
Mon Nov 22 16:46:21 EST 2010


Sure, it's possible with TypeFamilies. The following compiles OK:

{-# LANGUAGE TypeFamilies #-}
module TypeCalc where
data Rec a r = Rec a r
data RecNil = RecNil
data Wrapper a = Wrapper a
class TypeList t where
   type Wrapped t
   i :: t -> Wrapped t
instance TypeList RecNil where
   type Wrapped RecNil = RecNil
   i RecNil = RecNil
instance TypeList r => TypeList (Rec a r) where
   type Wrapped (Rec a r) = Rec (Wrapper a) (Wrapped r)
   i (Rec a r) = Rec (Wrapper a) (i r)
type TTest = Rec Int (Rec String RecNil)
type TTestWrapped = Rec (Wrapper Int) (Rec (Wrapper String) RecNil)
a :: TTest
a = Rec 1 (Rec "a" RecNil)
f :: TTestWrapped -> (Int, String)
f (Rec (Wrapper n) (Rec (Wrapper s) RecNil)) = (n, s)
r = f (i a) -- so, "i a" is of the type TTestWrapped.


On 22 Nov 2010, at 23:43, kg wrote:

> Hi,
> 
> I've tried to simplify as much as possible my problem. Finally, I think I can resume it like that:
> 
> Suppose these following data types :
> data Rec a r = Rec a r
> data RecNil = RecNil
> data Wrapper a = Wrapper a
> 
> Then, we can build the following type:
> type TTest = Rec Int (Rec String RecNil)
> or this type:
> type TTestWrapped = Rec (Wrapper Int) (Rec (Wrapper String) RecNil)
> 
> Is it possible to build TTestWrapped from TTest ?
> 
> 
> Thx in advance,
> Antoine.
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 



More information about the Haskell-Cafe mailing list