Trying to understand HList / hMapOut

Hello, I am using a heterogenous list as in [1] all elements of which are of a given class C. I am awed by the beauty of the code (HList, not mine :-). Here is what I am trying doing: import HListPrelude data T = T Int class C a where foo :: a -> Int instance C T where foo (T i) = i class HList l => CList l instance CList HNil instance (C c, CList cs) => CList (HCons c cs) 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 That would be too easy, though... ghci (6.4) sez: /home/fis/tmp/Main.hs:16:7: Could not deduce (HMapOut (a -> Int) l Int) from the context (CList l) arising from use of `hMapOut' at /home/fis/tmp/Main.hs:16:7-13 Probable fix: add (HMapOut (a -> Int) l Int) to the type signature(s) for `test' or add an instance declaration for (HMapOut (a -> Int) l Int) In the definition of `test': test = hMapOut foo hugs (version 20050308) sez: ERROR "/home/fis/esim/HList/FakePrelude.hs":113 - Overlapping instances for class "Show" *** This instance : Show (HSucc a) *** Overlaps with : Show (HSucc HZero) *** Common instance : Show (HSucc HZero) (oops? should i upgrade, or is there a switch that i missed?) I am trying to understand the ghci error message, which looks like I might have missed a point. It seems like I should make it more obvious to ghc that CLists actually consist of values of type C. Is that a good guess? But how do I actually do it? I have unsuccessfully to extend the context to (HMapOut (a -> Int) l Int, CList l) or even to (C a, HMapOut (a -> Int) l Int, CList l) and I can't see any reason why the instance declarations of HMap in HListPrelude shouldn't cover my code. I am feeling a little stuck again... thanks, Matthias [1] http://homepages.cwi.nl/~ralf/HList/

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.

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@pobox.com wrote:
To: fis@wiwi.hu-berlin.de Cc: haskell-cafe@haskell.org From: oleg@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@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

Hi, here is how you do sequencing for HList, and a question why the type signatures are valid. Here is the code: {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} module Foo where import Char import HListPrelude class (Monad m, HList l) => HSequence m l l' | l -> m l' where hSequence :: l -> m l' instance (Monad m, HSequence m HNil HNil) => HSequence m HNil HNil where hSequence _ = return HNil instance (Monad m, HSequence m l l') => HSequence m (HCons (m a) l) (HCons a l') where hSequence (HCons ma ml) = do a <- ma l <- hSequence ml return (HCons a l) hlist = HCons (Just 1) (HCons (Just 'c') HNil) testHSequence = hSequence hlist *Foo> testHSequence Just (HCons 1 (HCons 'c' HNil)) :: Maybe (HCons Integer (HCons Char HNil)) what staggers me is the instance declaration of "HSequence m HNil HNil": how can i use the goal of the declaration as one of the conditions without causing some sort of black hole in the type inference algorithm? also i wanted to show off with the code :-). should i submit it somewhere? cheers, matthias

Matthias Fischmann wrote:
instance (Monad m, HSequence m HNil HNil) => HSequence m HNil HNil where hSequence _ = return HNil
how can i use the goal of the declaration as one of the conditions without causing some sort of black hole in the type inference algorithm?
Very easily: the instance head is implicitly the part of its own context (so that a method can be recursive). A simple way to see that is the following deliberately erroneous class:
class C a where mc :: a -> Bool instance Eq a => C a where mc x = x > x
The error message says Could not deduce (Ord a) from the context (C a, Eq a) arising from use of `>' at /tmp/f2.hs:30:36 It is revealing to observe the context that the typechecker thinks is available: it is (C a, Eq a). "Eq a" is there because we explicitly wrote it in the instance declaration. C a is there just by default. We could just as well written
instance (Ord a, C a) => C a where mc x = x > x
Incidentally, the hSequence can be written as follows
import TypeCastGeneric2 data ConsM
instance (TypeCast (m1 l) (m l), Monad m) => Apply ConsM (m a, m1 l) (m (HCons a l)) where apply _ (me,ml) = liftM2 HCons me (typeCast ml)
hSequence l = hFoldr (undefined::ConsM) (return HNil) l
hlist = HCons (Just 1) (HCons (Just 'c') HNil) hlist2 = HCons ([1]) (HCons (['c']) HNil) testHSequence = hSequence hlist testHSequence2 = hSequence hlist2
*Foo> :t testHSequence testHSequence :: Maybe (HCons Integer (HCons Char HNil)) *Foo> testHSequence Just (HCons 1 (HCons 'c' HNil)) *Foo> testHSequence2 [HCons 1 (HCons 'c' HNil)] The typechecker will complain if we try to mix different monads within the same HList, and then sequence it.

Hello oleg, Wednesday, October 11, 2006, 6:45:28 AM, you wrote:
instance (Monad m, HSequence m HNil HNil) => HSequence m HNil HNil where hSequence _ = return HNil
how can i use the goal of the declaration as one of the conditions without causing some sort of black hole in the type inference algorithm?
Very easily: the instance head is implicitly the part of its own context (so that a method can be recursive).
as an example: data T = C instance Eq T where C==C = True (/=) = not (==) instance declarations may be even mutually recursive: instance Eq T where a==b = compare a b == EQ instance Ord T where compare a b = EQ a

On Tue, Oct 10, 2006 at 07:45:28PM -0700, oleg@pobox.com wrote:
To: fis@wiwi.hu-berlin.de Cc: haskell-cafe@haskell.org From: oleg@pobox.com Date: Tue, 10 Oct 2006 19:45:28 -0700 (PDT) Subject: Re: Trying to understand HList / hSequence now [why it works]
Matthias Fischmann wrote:
instance (Monad m, HSequence m HNil HNil) => HSequence m HNil HNil where hSequence _ = return HNil
how can i use the goal of the declaration as one of the conditions without causing some sort of black hole in the type inference algorithm?
Very easily: the instance head is implicitly the part of its own context (so that a method can be recursive). A simple way to see that is the following deliberately erroneous class:
That explains why it is legal, but not why it can be necessary. In my code, I had to add the instance goal to the context in order for type inference to quite complaining about incomplete context. But never mind. I should really do some reading. Your hSequence implementation I like, yes. I will try that instead of mine, perhaps that'll soothen the type checker. thanks! matthias
class C a where mc :: a -> Bool instance Eq a => C a where mc x = x > x
The error message says
Could not deduce (Ord a) from the context (C a, Eq a) arising from use of `>' at /tmp/f2.hs:30:36
It is revealing to observe the context that the typechecker thinks is available: it is (C a, Eq a). "Eq a" is there because we explicitly wrote it in the instance declaration. C a is there just by default. We could just as well written
instance (Ord a, C a) => C a where mc x = x > x
Incidentally, the hSequence can be written as follows
import TypeCastGeneric2 data ConsM
instance (TypeCast (m1 l) (m l), Monad m) => Apply ConsM (m a, m1 l) (m (HCons a l)) where apply _ (me,ml) = liftM2 HCons me (typeCast ml)
hSequence l = hFoldr (undefined::ConsM) (return HNil) l
hlist = HCons (Just 1) (HCons (Just 'c') HNil) hlist2 = HCons ([1]) (HCons (['c']) HNil) testHSequence = hSequence hlist testHSequence2 = hSequence hlist2
*Foo> :t testHSequence testHSequence :: Maybe (HCons Integer (HCons Char HNil)) *Foo> testHSequence Just (HCons 1 (HCons 'c' HNil)) *Foo> testHSequence2 [HCons 1 (HCons 'c' HNil)]
The typechecker will complain if we try to mix different monads within the same HList, and then sequence it.

Hello oleg, Saturday, October 7, 2006, 11:25:07 AM, you wrote:
Well, `foo' is a polymorphic function -- which is not, strictly speaking, a first-class object in Haskell.
btw, GHC 6.6 supports impredicative polymorphism described in User Guide 7.4.9. is this makes polymorphic functions first-class citizens? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (3)
-
Bulat Ziganshin
-
Matthias Fischmann
-
oleg@pobox.com