
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