
Hi Oleg, I like the polymorphic list indexed by Ints... there do seem to be a couple of differences between this and the list indexed by natural numbers. The list indexed by integers cannot determine the type of the return value through induction on the class... in other words it cannot determine the return type of the lookup function until runtime: you can see this in the class instance for 'tke'
instance (TH a (a,b), TH W b) => TH W (a,b) where tke (W 0) th@(h,t) f = f h th tke (W n) (h,t) f = tke (W$ n-1) t f
On the other hand indexing by natural numbers allows the compiler to know the return type (and avoid the use of existentials) because it is determined at compile time... you can see this because the recursion termination is done by the type signatures in the instance not the pattern guards of the function. instance Relation r => RIndex Zero (a `RCons` r) a where rIndex Zero (x `RCons` _) = x instance RIndex Idx r b => RIndex Idx (a `RCons` r) b where rIndex (Suc n) (_ `RCons` xs) = rIndex n xs It looks like most of this stuff has been done before... but I don't think there is any of it in the ghc libraries. I needed this code for a real application, and could not find anything suitable so I rolled my own. What do people think - is there a case for getting this stuff in the libs, should we write a functional pearl? does anyone have any comments about the code I posted, or how it could be improved? To finish, here are some new definitions for map,zip and unzip class Relation r => RMap t r where rMap :: t -> r -> r instance RMap t RNil where rMap _ RNil = RNil instance (RMapFn t a,RMap t r) => RMap t (a `RCons` r) where rMap t (x `RCons` xs) = rMapFn t x `RCons` rMap t xs class RMapFn t a where rMapFn :: t -> a -> a data RMapId = RMapId instance RMapFn RMapId a where rMapFn RMapId a = a class (Relation r1,Relation r2,Relation r3) => RZip r1 r2 r3 | r1 r2 -> r3 where rZip :: r1 -> r2 -> r3 instance RZip RNil RNil RNil where rZip _ _ = RNil instance RZip r1 r2 r3 => RZip (a `RCons` r1) (b `RCons` r2) ((a,b) `RCons` r3) where rZip (x `RCons` xs) (y `RCons` ys) = (x,y) `RCons` rZip xs ys class (Relation r1,Relation r2,Relation r3) => RUnZip r1 r2 r3 | r1 -> r2 r3 where rUnZip :: r1 -> (r2,r3) instance RUnZip RNil RNil RNil where rUnZip _ = (RNil,RNil) instance RUnZip r1 r2 r3 => RUnZip ((a,b) `RCons` r1) (a `RCons` r2) (b `RCons` r3) where rUnZip ((x,y) `RCons` xys) = (x `RCons` xs,y `RCons` ys) where (xs,ys) = rUnZip xys and finally a lookup that indexes by the left type of a pair and returns the right type & value stored in a polymorphic list: class Relation r => RLookup r l v | r l -> v where rLookup :: r -> l -> v instance Relation r => RLookup ((l,v) `RCons` r) l v where rLookup ((_,v) `RCons` _) _ = v instance RLookup r l v => RLookup ((l',v') `RCons` r) l v where rLookup (_ `RCons` r) l = rLookup r l Regards, Keean Schupke.

MR K P SCHUPKE wrote:
Hi Oleg, I like the polymorphic list indexed by Ints... there do seem to be a couple of differences between this and the list indexed by natural numbers.
...
Agreed with these differences. Another difference: it is initially a heterogeneous set rather than list! (Because the instance TH a (a, x) is for "found", and the overlapping instance TH a (b,c) is for proceeding with the rest of the set if a and b are not the same.) Of course, you could readily store lists of a's rather than a's, and always use [a] as access type rather than a. This deviation looks as follows: instance (Show a) => TH a ([a],x) where ... alter x (xs,y) = (x:xs,y) So a heteregeneous list would be modelled as a type-indexed set of homogeneous lists. That's pretty close. Still cool and simple. Ralf
participants (2)
-
MR K P SCHUPKE
-
Ralf Laemmel