Re: is there a more concise way to generate helper functions for a datatype built on records?

Hi
Some of these can be automatically derived by the Data.Derive tool... The derivations Set, Is, From, Has, LazySet all look useful. ...
On Nov 24, 2007 4:01 PM, Thomas Hartman
wrote: I think I'm running into more or less the same issue discussed at
http://bloggablea.wordpress.com/2007/04/24/haskell-records-considered-grungy...
Just wondering if I missed anything, or if any of the ideas considering better records setter/getters have been implemented in
Neil Mitchell wrote: the
meantime.
Hi, the Ref deriviation (included in Data.Derive) seems to be a good way to solve some aspects of this problem; I have some questions on my own though. Here is a working example of updating the two player's state in the pong game:
{-# OPTIONS -cpp #-} {-# OPTIONS_DERIVE --output=file.h #-} module Main where import Control.Arrow #include "file.h"
Refs as in (http://www.haskell.org/pipermail/haskell-cafe/2007-June/026477.html ):
type Upd a = a -> a data Ref cx t = Ref { select :: cx -> t , update :: Upd t -> Upd cx } (@.) :: Ref a b -> Ref b c -> Ref a c a @. b = Ref { select = select b . select a, update = update a . update b }
The game model:
data Object2D = Object2D { x :: Double, y :: Double } deriving (Show {-! Ref !-}) data Player = Player { points :: Int, pos :: Object2D } deriving (Show {-! Ref !-}) data Game = Game { p1 :: Player, p2 :: Player, ball :: Object2D } deriving (Show {-! Ref !-}) sampleGame :: Game sampleGame = Game { p1 = Player 0 (Object2D 5 0), p2 = Player 0 (Object2D 5 10), ball = Object2D 5 5 }
Game update proceeds in several steps, we now consider the first one: Updating the 2 player's position - this happens, at least conceptually, *in paralell* (for example: both players might be aloud to have a look at the other players position in the last turn, but not at the updated position). Here's the update for one player:
updatePlayerPos :: Bool -> Upd Player updatePlayerPos moveRight = update (refPos @. refX) $ case moveRight of True -> ((min 10) . (+1)) False -> ((max 0) . (+(-1)))
If sequential update is ok for us, the game state update is simply:
updatePositions :: Bool -> Bool -> Upd Game updatePositions move1 move2 = update refP1 (updatePlayerPos move1) . update refP2 (updatePlayerPos move2)
To get it *actually* work in parallel we have to create a new reference for both players:
refPlayers :: Ref Game (Player,Player) refPlayers = Ref { select = select refP1 &&& select refP2, update = \pu g -> let (p1',p2') = pu (p1 g, p2 g) in g { p1 = p1', p2 = p2' } }
While the select part of the Ref is expressed using &&&, I don't know how the paralell update can be expressed in terms of combinators. Any hints ? Now, the game state update in the parallel version is easy. Note that it would also be possible now to take one player's position into account when updating the other player's position:
updatePositionsPar move1 move2 = (update refPlayers) $ updatePlayerPos move1 *** updatePlayerPos move2
So, the Ref deriviation is really nice for sequential updates; paralell updates on the other hand need some work. Furthermore, I don't really know how well Refs work if updates need information on other parts of the state without modifying it. (e.g. the AI player needs to know where the ball is, but does not modify the ball). I'd really appreciate if anyone has some additional clues. thanks, benedikt

Benedikt Huber wrote:
type Upd a = a -> a data Ref cx t = Ref { select :: cx -> t , update :: Upd t -> Upd cx }
Functional references are also called "lens", I'm going to use that term from now on. As a minor note, I somehow prefer a single primitive data Lens s a = Lens { focus :: s -> (a, a -> s) } put :: Lens s a -> a -> s -> s put x = flip $ snd . focus x get :: Lens s a -> s -> a get x = fst . focus x update :: Lens s a -> (a -> a) -> (s -> s) update x f s = let (a,g) = focus x s in g (f a)
So, the Ref deriviation is really nice for sequential updates; parallel updates on the other hand need some work. Furthermore, I don't really know how well Refs work if updates need information on other parts of the state without modifying it. (e.g. the AI player needs to know where the ball is, but does not modify the ball).
It's just a question of the right combinators, I hope? For sequential composition, lenses are morphisms of a category class Category c where id :: c a a (.) :: c b d -> c a b -> c a d instance Category Lens where id = Lens $ \a -> (a, id) y . x = Lens $ \a -> let (b,f) = focus x a; (c,g) = focus y b; in (c,g . f) For parallel composition, we have stuff corresponding to arrow functions like fst :: Lens (a,b) a fst = Lens $ \(a,b) -> (a, \a' -> (a',b)) swap :: Lens (a,b) (b,a) swap = Lens $ \(a,b) -> ((b,a),\(b',a') -> (a',b')) snd :: Lens (a,b) b snd = fst . swap first :: Lens a b -> Lens (a,c) (b,c) first x = Lens $ \(a,c) -> let (b,f) = focus x a in (b,\b' -> (f b',c)) second :: Lens a b -> Lens (c,a) (c,b) second x = swap . first x . swap Then, there's also (***) :: Lens a b -> Lens c d -> Lens (a,c) (b,d) x *** y = second y . first x but this is symmetric in x and y, the order matters. For a class hierarchy proposal, see http://thread.gmane.org/gmane.comp.lang.haskell.libraries/7663/focus=7777 but I think it needs further research, i.e. concerning whether the interface is minimal or corresponds to well-known categories.
To get it *actually* work in parallel we have to create a new reference for both players:
refPlayers :: Ref Game (Player,Player) refPlayers = Ref { select = select refP1 &&& select refP2, update = \pu g -> let (p1',p2') = pu (p1 g, p2 g) in g { p1 = p1', p2 = p2' } }
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) with for example players = player1 &&& player2 That's because the two arguments might not be parallel at all. For instance, consider dup :: Lens a (a,a) dup = id &&& id Which component of the pair should put dup :: a -> (a,a) -> (a,a) change? The first, the second, or even both? Regards, apfelmus

On Mon, 26 Nov 2007, apfelmus wrote:
Benedikt Huber wrote:
type Upd a = a -> a data Ref cx t = Ref { select :: cx -> t , update :: Upd t -> Upd cx }
Functional references are also called "lens", I'm going to use that term from now on.
As a minor note, I somehow prefer a single primitive
data Lens s a = Lens { focus :: s -> (a, a -> s) }
put :: Lens s a -> a -> s -> s put x = flip $ snd . focus x
get :: Lens s a -> s -> a get x = fst . focus x
update :: Lens s a -> (a -> a) -> (s -> s) update x f s = let (a,g) = focus x s in g (f a)
I proposed something similar on http://www.haskell.org/haskellwiki/Record_access

apfelmus wrote:
Benedikt Huber wrote:
type Upd a = a -> a data Ref cx t = Ref { select :: cx -> t , update :: Upd t -> Upd cx }
Functional references are also called "lens", I'm going to use that term from now on.
As a minor note, I somehow prefer a single primitive
data Lens s a = Lens { focus :: s -> (a, a -> s) }
nice name.
there cannot be a general parallel combinator
(&&&) :: Lens a b -> Lens a c -> Lens a (b,c)
with for example
players = player1 &&& player2
That's because the two arguments might not be parallel at all. For instance, consider
dup :: Lens a (a,a) dup = id &&& id
Which component of the pair should
put dup :: a -> (a,a) -> (a,a)
change? The first, the second, or even both?
put :: Lens s a -> a -> s -> s put x = flip $ snd . focus x
wouldn't put dup :: (a,a) -> a -> a ? Arrows IIRC resolve this dilemma by arbitrarily saying the first argument of (&&&) takes effect first... a solution I'm not entirely happy with. Here, first it would put the first element of the pair, then it would put the second, so the result would be the second element. If it were 2d vectors, x::Lens Vector Double, angle::Lens Vector Angle, it makes a difference whether x-coordinate or angle is changed first, and again, (&&&) could sequence. I wish there was some way to compose them that guaranteed order-independence, and didn't work otherwise, though. I suppose QuickCheck could be used to catch most parallel/disjoint-assumption-mistakes like that... Isaac

Isaac Dupree wrote:
apfelmus wrote:
dup :: Lens a (a,a) dup = id &&& id
Which component of the pair should
put dup :: a -> (a,a) -> (a,a)
change? The first, the second, or even both?
[...] put :: Lens s a -> a -> s -> s put x = flip $ snd . focus x
wouldn't put dup :: (a,a) -> a -> a
Oops, of course.
Arrows IIRC resolve this dilemma by arbitrarily saying the first argument of (&&&) takes effect first... a solution I'm not entirely happy with. Here, first it would put the first element of the pair, then it would put the second, so the result would be the second element. If it were 2d vectors, x::Lens Vector Double, angle::Lens Vector Angle, it makes a difference whether x-coordinate or angle is changed first, and again, (&&&) could sequence.
I wish there was some way to compose them that guaranteed order-independence, and didn't work otherwise, though. I suppose QuickCheck could be used to catch most parallel/disjoint-assumption-mistakes like that...
The situation is much worse, even dropping order-independence doesn't help: the lens laws get x (put x a s) = a put x (get x s) s = s are already violated for dup ! Assuming that get dup :: a -> (a,a) is total (i.e. first and second component not undefined ), parametric polymorphism dictates that it can only be get dup = \a -> (a,a) Now, we should have get dup x (put dup (a,a') s) = (put dup (a,a') s, put dup (a,a') s) = (a,a') but that's impossible when a is different from a'. Regards, apfelmus

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
participants (4)
-
apfelmus
-
Benedikt Huber
-
Henning Thielemann
-
Isaac Dupree