[Haskell] Data.Generics.gzip3 anyone?

David Fox ddssff at gmail.com
Mon Jun 1 16:47:47 EDT 2009


On Mon, Jun 1, 2009 at 12:20 PM, Ralf Laemmel <rlaemmel at gmail.com> wrote:

> On Mon, Jun 1, 2009 at 8:20 PM, David Fox <david at seereason.com> wrote:
> > Is there a Scrap Your Boilerplate guru out there who could whip up a
> three
> > argument version of gzip for me?
>
> This can be done of course (untested but type-checked code follows).
> Left wondering what the scenario might be :-)
>
> Ralf
>
> 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
>
> -- 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
>

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.

-david
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20090601/bfd563b1/attachment.html


More information about the Haskell mailing list