[Haskell-cafe] Re: is there a more concise way to generate helper functions for a datatype built on records?

Benedikt Huber benjovi at gmx.net
Wed Nov 28 06:24:12 EST 2007


apfelmus schrieb:
> Benedikt Huber wrote:
>> So, the Ref deriviation is really nice for sequential updates;
>> parallel updates on the other hand need some work.
>> ..
>> While the select part of the Ref is expressed using &&&, I don't know
>> how the
>> parallel update can be expressed in terms of combinators. Any hints ?
>
> You can't do that, and for good reason! While
>
>   players :: Lens Game (Player,Player)
>
> is entirely fine since  Game ~ (Player,Player,Object2D), there cannot be
> a general parallel combinator
>
>   (&&&) :: Lens a b -> Lens a c -> Lens a (b,c)
>
Thanks for the nice overview.
I see there can't be a general purpose combinator (&&&) for lenses.
One could still define a helper function though:

combineDisjoint :: Lens a b -> Lens a c -> Lens a (b,c)
combineDisjoint l1 l2 = Lens $ select &&& update
   where
     select = (fst . focus l1) &&& (fst . focus l2)
     update cx (a,b) = flip (snd . focus l2) b $ (snd . focus l1) cx a

which performs the first update using the initial context, and the
second one using the updated context. Just to have a simple way of
defining lensPlayers in term of lensPlayer1 `combineDisjoint`
lensPlayer2. While it is not a (general purpose) combinator, it is still
helpfull for combining lenses focusing on fields of a record.

--

I just want to rephrase my question about paralell updates; it has more
to do with records updates than with References / Lenses, though:

Suppose we have a record

data R = R { a:: A, b :: B, c :: C } deriving (Show {-! Ref !-})

and update functions

fa :: a -> a, fb :: b -> b, fc :: c -> c

Now the standard way to perform the update on R would be

updateR = \r@(R {a=a,b=b,c=c}) -> r { a = fa a,b = fb b,c = fc c }

which is 'a little bit' cumbersome.


With update deriviations (like Update using DrIFT), references (Ref 
using Data.Derive) or lenses it is easy to perform the update 
sequentially (using DrIFT style for simplicity):

updateR' = a_u fa . b_u fb . c_u fc

But this corresponds to

updateR' = (\f r -> r { a = f (a r) }) fa .
            (\f r -> r { b = f (b r) }) fb .
            (\f r -> r { c = f (c r) }) fc

which (in some way) is not 'the same' as updateR.

First, I (uneducatedly) guess that the record updates cannot be 
'executed' in paralell, i.e. the record has to be deconstructed and 
build up again three times.
And second, neither the types of the updates (e.g. a_u fa :: R -> R) nor 
the structure of updateR' (composing R->R functions) do reflect the fact
that actually disjoint fields of the record are updated.


Now I know there are great record proposals (which extend the haskell
language or use some type hackery), but I wondered if there is also a
solution which can be used right now and which works fine with the
standard record types.

I'll give a naive ad-hoc example to illustrate the idea.
One could automatically derive the following data type and the
associated functions for R:

data R_upd = R_upd { updA :: A -> A, updB :: B -> B, updC :: C -> C }
rUpd = R_upd id id id
updR :: R_upd -> R -> R
updR rupd r@(R { a=a,b=b,c=c }) = r
   { a = (updA rupd a),
     b = (updB rupd b),
     c = (updC rupd c) }

which would allow to write things like

updGame $
   gameUpdate { updPlayer1 = increaseScore, updPlayer2 = decreaseScore })

Though simple, I hope it is possible to understand the idea (I know 
there is a lot of namespace pollution).
And of course, someone has thought of something much more sophistacted
already :)
What are the drawbacks of such an approach ?

thanks,
benedikt




More information about the Haskell-Cafe mailing list