[Haskell-cafe] Re: Trying to understand HList / hSequence now [why it works]

oleg at pobox.com oleg at pobox.com
Tue Oct 10 22:45:28 EDT 2006


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.



More information about the Haskell-Cafe mailing list