
[Moving to Haskell-cafe from http://www.haskell.org/pipermail/glasgow-haskell-users/2004-March/006390.htm... http://www.haskell.org/pipermail/glasgow-haskell-users/2004-March/006393.htm... I hope y'all don't mind the move: the discussion of polymorphic lists is of general interest and is not limited to GHC. Besides, they serve coffee in here, albeit virtually. However, they charge for it virtually, too.] Keean Schupke wrote:
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
I concur wholeheartedly. I have expressed the same sentiment: http://www.haskell.org/pipermail/haskell/2003-August/012493.html http://www.haskell.org/pipermail/haskell/2003-June/011939.html The reason the previous message implemented indexing by true Int is because Ralf Laemmel specifically asked for it (plus it is much harder to do). Keean Schupke wrote:
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?
It is indeed a very good question. Just for the sake of it, here's a little bit simplified version of your example. Labels are done differently.
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Foo where
data Z = Z data S a = S a
class Nat a where n2n:: a-> Int instance Nat Z where n2n _ = 0 instance (Nat a) => Nat (S a) where n2n _ = 1 + n2n (undefined::a)
-- keyed access class (Nat n) => MLookup n a r where mLookup :: r -> n -> a instance MLookup Z a (a,r) where mLookup r _ = fst r instance MLookup n a r => MLookup (S n) a (a,r) where mLookup (_,xs) _ = mLookup xs (undefined::n) instance MLookup n a r => MLookup n a (b,r) where mLookup (_,xs) n = mLookup xs n
-- Positional access class (Nat n) => MIndex n a r | n r -> a where midx:: r -> n -> a instance MIndex Z a (a,r) where midx (x,_) _ = x instance (MIndex n a r) => MIndex (S n) a (b,r) where midx (_,xs) _ = midx xs (undefined::n)
The example now reads
newtype Name a = Name a deriving Show newtype Size a = Size a deriving Show newtype Weight a = Weight a deriving Show
infixr 5 &+ (&+) = (,) test = (Name "Box") &+ (Size (3::Int)) &+ (Weight (1.1::Float)) &+ (Name "AnotherBox") &+ (Size (42::Int)) &+ (Weight (24.09::Float)) &+ ()
Note that at run-time, (Name "Box") is the same as "Box". Name is a compile-time-only label that incurs no run-time overhead. So, the essence is the same -- a polymorphic associative list where keys are ephemeral (have no run-time representation). "mLookup r n" finds the n-th association in this list of a type a. In the present representation, labels and values are specified together. There is no need for a type declaration for test. The compiler will figure it out. The name and the size of the first box *Foo> mLookup test Z::(Name String) Name "Box" *Foo> mLookup test Z::(Size Int) Size 3 and of the second one *Foo> mLookup test (S Z)::(Name String) Name "AnotherBox" *Foo> mLookup test (S Z)::(Size Int) Size 42 We can also access the element of the array by their absolute position: *Foo> midx test Z Name "Box" *Foo> midx test (S Z) Size 3 *Foo> midx test (S (S (S Z))) Name "AnotherBox" Decimal types for indices (rather than unary, as above) would make for a nicer interface. We can easily write a right fold
class MFoldr a r where mfoldr :: (a -> b -> b) -> b -> r -> b instance (MFoldr a r) => MFoldr a (a,r) where mfoldr f z r = f (fst r) $ mfoldr f z (snd r) instance MFoldr a () where mfoldr f z r = z instance MFoldr a r => MFoldr a (b,r) where mfoldr f z r = mfoldr f z (snd r)
and find out how many names are in our list *Foo> mfoldr (\ (Name (a::String)) n -> n + 1) 0 test 2 and the total sizes of our boxes *Foo> mfoldr (\ (Size s) a -> a + s) (0::Int) test 45 Incidentally, this polymorphic array may be a model of an extensible record with row polymorphism and even polymorphic labels. Yet another record proposal.