[Haskell-cafe] functional update

Ryan Ingram ryani.spam at gmail.com
Mon Apr 21 19:43:42 EDT 2008


I recommend this blog entry:
http://twan.home.fmf.nl/blog/haskell/overloading-functional-references.details

along with a few additional combinators for imperative update:

data FRef s a = FRef
   { frGet :: s -> a
   , frSet :: a -> s -> s
   }

(=:) :: MonadState s m => FRef s a -> a -> m ()
ref =: a = modify $ frSet ref a

fetch :: MonadState s m => FRef s a -> m a
fetch ref = get >>= frGet ref

Then (given the right fixity declarations which I don't remember off
the top of my head) you can write code like this:

attack :: Int -> Game ()
attack dmg = do
    h <- fetch (player.life)
    player.life =: h - dmg

which works, given MonadState GameState Game, player :: FRef GameState
Player, and life :: FRef Player Int.

Note that (.) here is not (.) from the prelude; it's from the Ref
class defined on that page.

  -- ryan

On 4/21/08, Evan Laforge <qdunkan at gmail.com> wrote:
> Here's some haskell to update a particular field in a data structure
> (the below run in a StateT / ErrorT context):
>
> > set_track_width :: (UiStateMonad m) =>
> >     Block.ViewId -> Int -> Block.Width -> m ()
> > set_track_width view_id tracknum width = do
> >     view <- get_view view_id
> >     track_views <- modify_at (Block.view_tracks view) tracknum $ \tview ->
> >         tview { Block.track_view_width = width }
> >     update_view view_id (view { Block.view_tracks = track_views })
>
> Plus some utilities:
>
> > modify_at xs i f = case post of
> >     [] -> throw $ "can't replace index " ++ show i
> >         ++ " of list with length " ++ show (length xs)
> >     (elt:rest) -> return (pre ++ f elt : rest)
> >     where (pre, post) = splitAt i xs
>
> > update_view view_id view = modify $ \st -> st
> >     { state_views = Map.adjust (const view) view_id (state_views st) }
>
> A similar imperative update would look something like this:
>
> > state.get_view(view_id).tracks[tracknum].width = width
>
> Has there been any work on improving update syntax in haskell?
> Possibly some improvement could be made with a typeclass or two and a
> few custom operators, to unify some of the disparate syntax.  Maybe
> more improvement could be made with some TH hackery.  A better record
> update syntax I'm sure could improve things even more.  Or maybe
> there's a way to structure existing code to improve the above?
>
> Does anyone know of work that's been done on analysing functional
> update syntax issues, and coming up with something concise and clear?
> Other functional languages that do this better?  It seems like an
> obvious candidate for improvement.  Probably not an easy one though.
> There are various overlapping issues: monadic binds not mixing easily
> with non-monadic functions, different data structures (maps, lists,
> ...) having different update functions, record update syntax being
> super wordy, and probably some other things I'm not thinking of.
>
>
> As an aside, on the record system side, I would love to see one of the
> proposed record systems implemented in GHC, whether it be trex or the
> "lighter weight" version proposed by one of the Simons.  Does anyone
> know what the main hangup is?  Unresolved issues in the proposal?  No
> consensus?  Backward incompatibility?  Not enough interested GHC devs?
>  All I can say is that as a heavy user of (.) I wouldn't mind
> replacing them all with (#) or (@) or whatever if I got a nicer record
> syntax.  It wouldn't be hard to write a search/replace for (.).
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list