[Haskell-cafe] Re: Trying to understand HList / hMapOut

Matthias Fischmann fis at wiwi.hu-berlin.de
Sat Oct 7 06:18:24 EDT 2006



thanks, to both of you!

"data Fooable" is the solution, and also very neat.  it took me a
moment to learn the useful fact that a little explicit type
information can be worse than none, in particular with incomplete
contexts.  but in the end it worked both without type signatures and
with the right ones.

cheers,
matthias



On Sat, Oct 07, 2006 at 12:25:07AM -0700, oleg at pobox.com wrote:
> To: fis at wiwi.hu-berlin.de
> Cc: haskell-cafe at haskell.org
> From: oleg at pobox.com
> Date: Sat,  7 Oct 2006 00:25:07 -0700 (PDT)
> Subject: Trying to understand HList / hMapOut
> 
> 
> > 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.

-- 
Institute of Information Systems, Humboldt-Universitaet zu Berlin

web:      http://www.wiwi.hu-berlin.de/~fis/
e-mail:   fis at wiwi.hu-berlin.de
tel:      +49 30 2093-5742
fax:      +49 30 2093-5741
office:   Spandauer Strasse 1, R.324, 10178 Berlin, Germany
pgp:      AD67 CF64 7BB4 3B9A 6F25  0996 4D73 F1FD 8D32 9BAA
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20061007/b1b8a205/attachment.bin


More information about the Haskell-Cafe mailing list