[Haskell-cafe] Re: Adding a field to a data record

Jason Dagit dagit at codersbase.com
Tue Jul 28 10:56:06 EDT 2009


On Tue, Jul 28, 2009 at 7:47 AM, Henry Laxen <nadine.and.henry at pobox.com>wrote:

> Malcolm Wallace <Malcolm.Wallace <at> cs.york.ac.uk> writes:
>
> >
> > > and perhaps use emacs to
> > > query-replace all the Foo1's back to Foo's
> >
> > At least this bit can be avoided easily enough, by using
> > module qualification during the conversion process.
> >
> >      module Original (Foo(..)) where
> >      data Foo = Foo { ... y :: Int } deriving ...
> >
> >      module New (Foo(..)) where
> >      data Foo = Foo { ... y, z :: Int } deriving ...
> >
> >      module Convert where
> >      import Original as Old
> >      import New as New
> >      newFoo :: Old.Foo -> New.Foo
> >      newFoo old{..} = New.Foo { a=a, b=b, ... z=1 }
> >
> > Finally rename module New.
> >
> > Regards,
> >      Malcolm
> >
>
> Thanks Malcolm, yes, that keeps me out of emacs, but the part I would
> really
> like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the
> field
> names are many, long, and varied.  Yes, I could cut and paste, but I'm
> hoping
> for a "better way."  Thanks.


I guess you could define:
type UpgradeFoo = (Foo, Int)

And then write the conversion code as a zip.  upgradeFoo foos = zip foos
[1..]

instance Show UpgradeFoo where ...

And then use the module trick to switch the code around?

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090728/33fce6e4/attachment.html


More information about the Haskell-Cafe mailing list