[Haskell] Data.Generics.gzip3 anyone?
David Fox
ddssff at gmail.com
Fri Jun 5 10:08:50 EDT 2009
I definitely think these functions should be added to syb. I certainly
could not have written them myself without hours, perhaps days, of study.
2009/6/2 José Pedro Magalhães <jpm at cs.uu.nl>
> Hello,
>
> Would there be interest in having this function added to the SYB library?
>
>
> Thanks,
> Pedro
>
> On Tue, Jun 2, 2009 at 00:40, Ralf Laemmel <rlaemmel at gmail.com> wrote:
>
>> > Thank you! What I have in mind is three way merging - you have two
>> > revisions based on the same original value, and you need to decide
>> whether
>> > they can be merged automatically or they need to be merged by a user.
>> You
>> > only have a real conflict when both revisions differ from the original
>> and
>> > from each other.
>>
>> Here is the completed exercise.
>> For comparison, the two args versions are shown up-front.
>> There is gzipWithM3 needed for gzip3, and gzip3 itself.
>> I also made it so that the top-level gzip functions have the
>> appropriate polymorphism.
>> Say same type for the args rather than independent polymorphism.
>>
>> {-# LANGUAGE RankNTypes #-}
>>
>> import Prelude hiding (GT)
>> import Data.Generics
>>
>> -- As originally defined: Twin map for transformation
>>
>> gzipWithT2 :: GenericQ (GenericT) -> GenericQ (GenericT)
>> gzipWithT2 f x y = case gmapAccumT perkid funs y of
>> ([], c) -> c
>> _ -> error "gzipWithT2"
>> where
>> perkid a d = (tail a, unGT (head a) d)
>> funs = gmapQ (\k -> GT (f k)) x
>>
>>
>> -- As originally defined: Twin map for transformation
>>
>> gzipWithM2 :: Monad m => GenericQ (GenericM m) -> GenericQ (GenericM m)
>> gzipWithM2 f x y = case gmapAccumM perkid funs y of
>> ([], c) -> c
>> _ -> error "gzipWithM"
>> where
>> perkid a d = (tail a, unGM (head a) d)
>> funs = gmapQ (\k -> GM (f k)) x
>>
>>
>> -- As originally defined: generic zip
>>
>> gzip2 ::
>> (forall x. Data x => x -> x -> Maybe x)
>> -> (forall x. Data x => x -> x -> Maybe x)
>>
>> gzip2 f = gzip2' f'
>> where
>> f' :: GenericQ (GenericM Maybe)
>> f' x y = cast x >>= \x' -> f x' y
>> gzip2' :: GenericQ (GenericM Maybe) -> GenericQ (GenericM Maybe)
>> gzip2' f x y =
>> f x y
>> `orElse`
>> if toConstr x == toConstr y
>> then gzipWithM2 (gzip2' f) x y
>> else Nothing
>>
>>
>> -- For three args now
>>
>> gzipWithT3 ::
>> GenericQ (GenericQ (GenericT))
>> -> GenericQ (GenericQ (GenericT))
>> gzipWithT3 f x y z =
>> case gmapAccumT perkid funs z of
>> ([], c) -> c
>> _ -> error "gzipWithT3"
>> where
>> perkid a d = (tail a, unGT (head a) d)
>> funs = case gmapAccumQ perkid' funs' y of
>> ([], q) -> q
>> _ -> error "gzipWithT3"
>> where
>> perkid' a d = (tail a, unGQ (head a) d)
>> funs' = gmapQ (\k -> (GQ (\k' -> GT (f k k')))) x
>>
>> gzipWithM3 :: Monad m
>> => GenericQ (GenericQ (GenericM m))
>> -> GenericQ (GenericQ (GenericM m))
>> gzipWithM3 f x y z =
>> case gmapAccumM perkid funs z of
>> ([], c) -> c
>> _ -> error "gzipWithM3"
>> where
>> perkid a d = (tail a, unGM (head a) d)
>> funs = case gmapAccumQ perkid' funs' y of
>> ([], q) -> q
>> _ -> error "gzipWithM3"
>> where
>> perkid' a d = (tail a, unGQ (head a) d)
>> funs' = gmapQ (\k -> (GQ (\k' -> GM (f k k')))) x
>>
>> gzip3 ::
>> (forall x. Data x => x -> x -> x -> Maybe x)
>> -> (forall x. Data x => x -> x -> x -> Maybe x)
>>
>> gzip3 f = gzip3' f'
>> where
>> f' :: GenericQ (GenericQ (GenericM Maybe))
>> f' x y z = cast x >>= \x' -> cast y >>= \y' -> f x' y' z
>> gzip3' ::
>> GenericQ (GenericQ (GenericM Maybe))
>> -> GenericQ (GenericQ (GenericM Maybe))
>> gzip3' f x y z =
>> f x y z
>> `orElse`
>> if and [toConstr x == toConstr y, toConstr y == toConstr z]
>> then gzipWithM3 (gzip3' f) x y z
>> else Nothing
>> _______________________________________________
>> Haskell mailing list
>> Haskell at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell
>>
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20090605/eeb24263/attachment-0001.html
More information about the Haskell
mailing list