AntC <anthony_clayden@...> writes:

> 
>  <oleg@...> writes:
> > 
> 
> The headline news is that I have implemented hDeleteMany in Hugs.
> 

Yikes! I'd better post the code. This assumes all the usual HList 
infrastructure, especially class/method TypeCast as defined in-line per  
http://okmij.org/ftp/Haskell/typecast.html

Works on Hugs version Sep 2006 -- yes! it's been hiding in plain view all 
these years.

{- hDeleteMany does a type-indexed scan through an HList,
        removing all elements type `e`, even if they occur many times.
        Takes the standard HList idiom of 3 instances:
        - end of HList -- contains only HNil
        - HList's head contains the element of interest (HCons e l'')
        - HList's head not interesting, pass on (HCons e' l'')
        The 'interesting' instance overlaps the 'not interesting'.
-}

    class HDeleteMany e l l'            where           -- no fundep
        hDeleteMany     :: e -> l -> l'

    instance (TypeCast HNil l') => HDeleteMany e HNil l'        where
        hDeleteMany e HNil      = typeCast HNil
                                -- must typeCast the result

    instance (HDeleteMany e l'' l') => HDeleteMany e (HCons e l'') l'  where
        hDeleteMany e (HCons _ l'')     = hDeleteMany e l''

    instance (HDeleteMany e l'' l''', TypeCast (HCons e' l''') l')
         => HDeleteMany e (HCons e' l'') l'                where
            hDeleteMany e (HCons e' l'')        = typeCast (HCons e' 
(hDeleteMany e 
l''))
-- tests:
    somelist    = HCons True $ HCons 'H' $ HCons "HList" $ HCons (5 :: Int) 
HNil
    somemanylist        = HCons "hello" $ HCons False somelist

    unmanylist  = hDeleteMany "bye" (hDeleteMany (undefined :: Bool) 
somemanylist )
-- unmanylist ===> HCons 'H' (HCons 5 HNil)


AntC 





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

Reply via email to