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

Lennart Augustsson lennart at augustsson.net
Wed Jul 29 06:23:17 EDT 2009


With the RecordWildCard extension you should be able to write

newFoo Old.Foo{..} = New.Foo { .., z=1 }



On Tue, Jul 28, 2009 at 3:47 PM, 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.
> Best wishes,
> Henry Laxen
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list