
Hi there. recently I was trying to represent complex data by defining several datatypes and nesting them, such as data Foo = Foo { foo :: Bar } deriving (Eq,Show) data Bar = Bar { bar :: Int } deriving (Eq,Show) To change only a part of the data, syntactic sugar is quite convenient. But it seems to be quite painful with nested datatypes. b = Bar 10 f = Foo b foobar :: Int -> Foo -> Foo foobar i f = let nb = (foo f){bar = i} in f{foo = nb} So, my question is : is there a nifty way to modify data within a nested datatype, similar to the f{foo = bar} style ? If not, anyone is using some kind of workaround for this ?

(Note that the term "nested data type" also/already carries the meaning "non-regular data type", an example being data PerfectBinaryTree a = One a | Succ (PerfectBinaryTree (a,a)) ) Thomas Girod wrote:
recently I was trying to represent complex data by defining several datatypes and nesting them, such as
data Foo = Foo { foo :: Bar } deriving (Eq,Show) data Bar = Bar { bar :: Int } deriving (Eq,Show)
To change only a part of the data, syntactic sugar is quite convenient. But it seems to be quite painful with nested datatypes.
b = Bar 10 f = Foo b
foobar :: Int -> Foo -> Foo foobar i f = let nb = (foo f){bar = i} in f{foo = nb}
So, my question is : is there a nifty way to modify data within a nested datatype, similar to the f{foo = bar} style ? If not, anyone is using some kind of workaround for this ?
There is a nifty way, called "functional references". They're a pair of get and set functions data Ref s a = Ref { get :: s -> a, set :: a -> s -> s } The nice thing about them is that we can compose them like functions o :: Ref b c -> Ref a b -> Ref a c f `o` g = Ref (get f . get g) (\c a -> set (set c f $ get g a) g a) The example becomes data Foo = Foo Bar data Bar = Bar Int foo :: Ref Foo Bar foo = Ref (\(Foo x) -> x) (\x (Foo _) -> Foo y) bar :: Ref Bar Int bar = Ref (\(Bar x) -> x) (\x (Bar _) -> Bar x) foobar :: Ref Foo Int foobar = bar `o` foo See also http://luqui.org/blog/archives/2007/08/05/ haskell-state-accessors-second-attempt-composability/ and Sander Evers, Peter Achten, and Jan Kuper. "A Functional Programming Technique for Forms in Graphical User Interfaces". http://www.st.cs.ru.nl/papers/2005/eves2005-FFormsIFL04.pdf Writing getter and setter functions by hand can be tedious but somebody already automated this with Template Haskell or other other preprocessing tools. Regards, apfelmus
participants (2)
-
apfelmus
-
Thomas Girod