Hello,

I am experimenting with type-level HList based programming.

The Apply class:

   class Apply f a r | f a -> r where
     apply :: f -> a -> r
     apply = undefined  -- In case we use Apply for
                                -- type-level computations only

   -- Normal function application

   instance Apply (x -> y) x y where
     apply f x = f x

makes it seem like it should be possible to hMap:

   class HMap f l l' | f l -> l'
   where
     hMap :: f -> l -> l'

   instance HMap f HNil HNil
   where
     hMap f HNil = HNil

   instance (
             Apply f x y,
             HMap f xs ys
                )
        => HMap f (HCons x xs) (HCons y ys)
   where
     hMap f (HCons x xs) = HCons (apply f x) (hMap f xs)

a (term-level) polymorphic function over a HList. As written it
doesn't work at all. A (local) functional dependency to say that the
function determines its argument type is missing.

Towards this end I changed the Apply instance to:

   instance TypeCast a' a => Apply (a -> b) a' b
       where apply f x = f (typeCast x)

This change allows me to apply a polymorphic function to elements of
an HList by hand:

   (\(f :: forall a. a -> [a]) -> HCons (f 'a') (HCons (f "a") HNil))
(\x -> [x])

However, I need to explicitly write the polymorphic type of the
argument f. Thus I cannot use hMap.

So I have two questions:

 1) Am I missing something?

 2) Is there some way to pass an arbitrary (i.e. don't know explicit
type at compile time) polymorphic function as an argument to another
function?

thanks,
 Jeff
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to