[Haskell-cafe] Trying to understand HList / hMapOut

oleg at pobox.com oleg at pobox.com
Sat Oct 7 03:25:07 EDT 2006


> I am using a heterogenous list as in [1] all elements of which are of
> a given class C.
> Since foo maps all class members to Int, hMapOut should be a
> straight-forward way to produce homogenous Int lists from heterogenous
> CLists:
>
> test :: (CList l) => l -> [Int]
> test = hMapOut foo

Well, `foo' is a polymorphic function -- which is not, strictly
speaking, a first-class object in Haskell. Indeed, one cannot store
polymorphic functions in data structures, unless one wraps them in a
`newtype' or provide the explicit signature in some other way. In
other words, higher-rank types become necessary. 

Fortunately, Haskell98 already has some rudimentary higher-ranked
types (and multi-parameter type classes make them far more
usable). So, even if Haskell had not had higher-ranked types, we
could very easily get them from typeclasses, where they have been
lurking all the time. In HList, the class Apply can be used to pry
them out.

Here's the complete code that seems to solve the original
problem. There is no need to define the class CList.

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}
>
> module Foo where
> import HListPrelude
>
> data T = T Int
>
> class     C a  where foo :: a -> Int
> instance  C T  where foo (T i) = i
>
> data Fooable = Fooable
> instance C a => Apply Fooable a Int where apply _ x = foo x
>
> test l = hMapOut Fooable l
>
> testc = test (HCons (T 1) (HCons (T 2) HNil))

The inferred types are

*Foo> :t test
test :: (HMapOut Fooable r e) => r -> [e]
*Foo> :t testc
testc :: [Int]

so no explicit signatures are needed.



More information about the Haskell-Cafe mailing list