Adding a field to a data record

Dear Group, It seems to me this should be easy, but I can't quite figure out how to do it without a lot of typing. Here is the question: Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data) Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile "a.data" (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new "a.data" file which has a new z::Int field. So far the only way I can think of is to make a new Data Foo1, which includes the z::Int, read in a.data as a list of Foo, write a function like: fooTofoo1 :: Foo -> Foo1 fooTofoo1 xx = Foo1 {a = a xx, ... y = y xx, z = 1} then write the file back out, and perhaps use emacs to query-replace all the Foo1's back to Foo's, add the z::Int field back into Foo, and read it back. Please tell me there is a better way. Thanks in advance. Best wishes, Henry Laxen PS: I have read syb1, and syb2 a couple of times now, but so far haven't been able to connect it with this kind of problem.

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

Malcolm Wallace
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

On Tue, Jul 28, 2009 at 7:47 AM, Henry Laxen
Malcolm Wallace
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

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.
OK, here is another hack-ish trick, since I notice your data is stored on disk as text, using "show". I assume you are using something like Read to retrieve it. Well, how about using a real parser instead? The parser during conversion can be slightly more lax, automatically adding in the extra field. For instance, using polyparse's Text.Parse, and DrIFT to derive the appropriate Parse instance for your datatype: module Foo where data Foo = Foo { a :: Int , b :: Bool , c :: Maybe Foo } {-! derive : Parse !-} DrIFT gives you this instance: {-* Generated by DrIFT : Look, but Don't Touch. *-} instance Parse Foo where parse = constructors [ ( "Foo" , return Foo `discard` isWord "{" `apply` field "a" `discard` isWord "," `apply` field "b" `discard` isWord "," `apply` field "c" `discard` isWord "}" ) ] Let's say the field 'b' is new, and your existing data does not have it. So just take the parser generated by DrIFT and make a small modification: {-* Generated by DrIFT but modified by hand for conversion purposes *-} instance Parse Foo where parse = constructors [ ( "Foo" , return Foo `discard` isWord "{" `apply` field "a" `apply` return True -- this field does not yet exist in data `discard` isWord "," `apply` field "c" `discard` isWord "}" ) ] Then do the obvious thing: parse the old data, immediately write it out again, and then throw away the modified parser in favour of the pure generated one. Regards, Malcolm

Hello,
you may also find the package "pretty-show"
(http://hackage.haskell.org/package/pretty-show) useful. It contains
code to convert automatically derived instances of "Show" into an
explicit data structure, which you can then manipulate (e.g., by
adding the extra field), and then render back to text.
-Iavor
On Tue, Jul 28, 2009 at 6:07 PM, Malcolm
Wallace
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.
OK, here is another hack-ish trick, since I notice your data is stored on disk as text, using "show". I assume you are using something like Read to retrieve it. Well, how about using a real parser instead? The parser during conversion can be slightly more lax, automatically adding in the extra field.
For instance, using polyparse's Text.Parse, and DrIFT to derive the appropriate Parse instance for your datatype:
module Foo where data Foo = Foo { a :: Int , b :: Bool , c :: Maybe Foo } {-! derive : Parse !-}
DrIFT gives you this instance:
{-* Generated by DrIFT : Look, but Don't Touch. *-} instance Parse Foo where parse = constructors [ ( "Foo" , return Foo `discard` isWord "{" `apply` field "a" `discard` isWord "," `apply` field "b" `discard` isWord "," `apply` field "c" `discard` isWord "}" ) ]
Let's say the field 'b' is new, and your existing data does not have it. So just take the parser generated by DrIFT and make a small modification:
{-* Generated by DrIFT but modified by hand for conversion purposes *-} instance Parse Foo where parse = constructors [ ( "Foo" , return Foo `discard` isWord "{" `apply` field "a" `apply` return True -- this field does not yet exist in data `discard` isWord "," `apply` field "c" `discard` isWord "}" ) ]
Then do the obvious thing: parse the old data, immediately write it out again, and then throw away the modified parser in favour of the pure generated one.
Regards, Malcolm _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
Malcolm Wallace
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data)
Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile "a.data" (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new "a.data" file which has a new z::Int field.
This seems to depend on what you want to accomplish. Is your goal just to rewrite this whole file? If it is, the idea of just adding a field to Foo would be enough. You could then add that 'z' field in your file using 'sed' (or, as you said, emacs) and then read it back. In general, however, if you want to deal with this kind of translation of text to data, what you really want is to take some time to learn something like Parsec. http://www.haskell.org/ghc/docs/latest/html/libraries/parsec/Text-ParserComb...
So far the only way I can think of is to make a new Data Foo1, which includes the z::Int, read in a.data as a list of Foo, write a function like:
fooTofoo1 :: Foo -> Foo1 fooTofoo1 xx = Foo1 {a = a xx, ... y = y xx, z = 1}
Note that this would not work exactly like that. 'a' is a "field" of Foo, and that means it's a function like a :: Foo -> Int So, you can't use it as a field of Foo1, as that would imply a :: Foo1 -> Int Best, Maurício

Henry Laxen
It seems to me this should be easy, but I can't quite figure out how to do it without a lot of typing. Here is the question:
Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data)
Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile "a.data" (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new "a.data" file which has a new z::Int field.
One approach to this would be to temporarily redefine Foo data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data) | NuFu {a :: Int, b :: Int, ... many other fields ... y :: Int, z :: Int} deriving (Eq, Read, Show, Typeable, Data) read the file, map Foo to NuFoo + whatever the initial value of z is and write it out again. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Hello Henry, The paper "A Lightweight Approach To Datatype-Generic Rewriting" [1] describes a way to generically add a constructor to any regular datatype using type-indexed datatypes [2]. A similar technique could be used to add a new field to each constructor. Then you get something like: data Foo
type Extended f = ...
|Extended Foo| represents your |Foo| datatype with an added |z| field of
type |Int|. Since the underlying generic programming library used (regular
[3]) has Template Haskell generation, you don't even have to write the
generic representations for your many datatypes.
(As far as I know, SYB does not mix with type-indexed datatypes.)
Cheers,
Pedro
[1] Thomas van Noort, Alexey Rodriguez, Stefan Holdermans, Johan Jeuring,
Bastiaan Heeren. A Lightweight Approach to Datatype-Generic Rewriting.
Submitted to the Workshop on Generic Programming 2008.
http://www.cs.uu.nl/wiki/bin/view/Alexey/ALightweightApproachToDatatype-Gene...
[2] http://www.iai.uni-bonn.de/~ralf/publications/SCP2004.pdf
[3] http://www.cs.uu.nl/wiki/GenericProgramming/Regular
On Tue, Jul 28, 2009 at 16:29, Henry Laxen
Dear Group,
It seems to me this should be easy, but I can't quite figure out how to do it without a lot of typing. Here is the question:
Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data)
Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile "a.data" (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new "a.data" file which has a new z::Int field.
So far the only way I can think of is to make a new Data Foo1, which includes the z::Int, read in a.data as a list of Foo, write a function like:
fooTofoo1 :: Foo -> Foo1 fooTofoo1 xx = Foo1 {a = a xx, ... y = y xx, z = 1}
then write the file back out, and perhaps use emacs to query-replace all the Foo1's back to Foo's, add the z::Int field back into Foo, and read it back.
Please tell me there is a better way. Thanks in advance. Best wishes, Henry Laxen
PS: I have read syb1, and syb2 a couple of times now, but so far haven't been able to connect it with this kind of problem.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (8)
-
Henry Laxen
-
Iavor Diatchki
-
Jason Dagit
-
Jon Fairbairn
-
José Pedro Magalhães
-
Lennart Augustsson
-
Malcolm Wallace
-
Maurício CA