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

Attachment: signature.asc
Description: Digital signature

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

Reply via email to