
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 (.).

I recommend this blog entry:
http://twan.home.fmf.nl/blog/haskell/overloading-functional-references.detai...
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, 21 Apr 2008, Ryan Ingram wrote:
I recommend this blog entry: http://twan.home.fmf.nl/blog/haskell/overloading-functional-references.detai...
along with a few additional combinators for imperative update:
data FRef s a = FRef { frGet :: s -> a , frSet :: a -> s -> s }
http://darcs.haskell.org/record-access/src/Data/Accessor.hs http://darcs.haskell.org/record-access/src/Data/Accessor/Example.hs I should upload this to Hackage, I know ...

On Tue, Apr 22, 2008 at 6:26 AM, Henning Thielemann
On Mon, 21 Apr 2008, Ryan Ingram wrote:
I recommend this blog entry:
http://twan.home.fmf.nl/blog/haskell/overloading-functional-references.detai...
along with a few additional combinators for imperative update:
data FRef s a = FRef { frGet :: s -> a , frSet :: a -> s -> s }
http://darcs.haskell.org/record-access/src/Data/Accessor.hs http://darcs.haskell.org/record-access/src/Data/Accessor/Example.hs
I should upload this to Hackage, I know ...
Not to toot my own horn, but there's already something like this on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-0.0... Which has template haskell routines for generating accessors for record types also. Luke

Thanks everyone, this is all good stuff. I did look at Clean and it looks like it has somewhat nicer record syntax... but it doesn't look like anything haskell couldn't do better if it one day got a real record system. As for the rest of Clean, I'm afraid that spending too much time with it will just make me wish for more features in haskell :) I'm going to experiment with the TH and FRef stuff. Maybe someday when we have a nice record system, these techniques can be standardized and integrated into the standard library.

Recent discussions inspired me to cook up the attached, which through controlled abuse of various extensions gives functional references for all records deriving Data and Typeable for free, with no template haskell necessary. Composition is fully supported, as is "overloading" of standard record accessors. For the sake of preserving at least mild sanity, the (.) operator is not overloaded, and composition is instead provided via an overloaded `o`. For anyone that doesn't mind the absurdity of how this is implemented, it should be suitable for "drop in" use. For those that do mind the absurdity, it nonetheless serves as a proof-of-concept for how far Haskell's reflective capacities can be pushed. Cheers, and happy hacking, Sterl. Example usage: data Test = Test {t1 :: Int, t2 :: Int, t3 :: String, t4 :: InnerTest} deriving (Data, Typeable, Show) data InnerTest = InnerTest {t'1 :: Int, t'2 :: Int, t'3 :: String} deriving (Data, Typeable, Show) testData = Test {t1 = 1, t2 = 2, t3 = "foo", t4 = InnerTest {t'1 = 2, t'2 = 3, t'3 = "bar"}} *GenericFRef> set t1 23 testData Test {t1 = 23, t2 = 2, t3 = "foo", t4 = InnerTest {t'1 = 2, t'2 = 3, t'3 = "bar"}} *GenericFRef> set (t'1 `o` t4) 23 testData Test {t1 = 1, t2 = 2, t3 = "foo", t4 = InnerTest {t'1 = 23, t'2 = 3, t'3 = "bar"}} *GenericFRef> update (t2) (\x->x*x) testData Test {t1 = 1, t2 = 4, t3 = "foo", t4 = InnerTest {t'1 = 2, t'2 = 3, t'3 = "bar"}} *GenericFRef> update (t'2 `o` t4) (\x->x*x) testData Test {t1 = 1, t2 = 2, t3 = "foo", t4 = InnerTest {t'1 = 2, t'2 = 9, t'3 = "bar"}} p.s. I have a nagging sensation that somebody may have done this before, although I can't trace the source.

On Tue, Apr 22, 2008 at 4:12 AM, Evan Laforge
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?
Here are two little TH functions I find useful: -- \f x -> x { field = f (field x) } alter :: Name -> Q Exp alter field = do f <- newName "f" x <- newName "x" lamE [varP f, varP x] $ recUpdE (varE x) [return (field, AppE (VarE f) (AppE (VarE field) (VarE x)))] -- \a x -> x { field = a } set :: Name -> Q Exp set field = do a <- newName "a" x <- newName "x" lamE [varP a, varP x] $ recUpdE (varE x) [return (field, VarE a)] They're not as flexible as FRefs (though they could be helpful in manually defining FRefs), but they still solve some of my frustrations with record update syntax. Usage: $(set 'fieldname) value record -- sets the value of the "fieldname" field to "value" $(alter 'fieldname) f record -- produces a new record where "fieldname" has been transformed by f Stuart
participants (6)
-
Evan Laforge
-
Henning Thielemann
-
Luke Palmer
-
Ryan Ingram
-
Sterling Clover
-
Stuart Cook