
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway: I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
with equivalent semantics. Here => reads "is transformed by". Operator = could still be used for assignment as in current record updates. The best part about such an extension, in my opinion, is that it would open the door for anonymous lambda record updates. Something like:
someUpdate :: MyRecord -> MyRecord someUpdate = \{field1 => f, field2 => g, field3 => h}
again, with the same semantics. This becomes possible because you no longer need to refer to the record within the {} part of the update. This would be useful, for example, in the State monad. We could write:
someStateTransform :: State MyRecord () someStateTransform = do modify $ \{field1 => (++"!")} ...
where currently we see code like
someStateTransform :: State MyRecord () someStateTransform = do modify $ \record->record{field1 = (++"!") $ field1 record} ...
which repeats the record name 3 times and the field name twice. The repetition just feels out of place next to all the other terse, readable Haskell code in the program. So what do my fellow haskellers think? Is this idea worth writing up a proposal for? Alternatively, can you offer me some advice on writing code in Haskell 2010 that avoids the ugly, repetitive style of record update? --Jonathan

Jonathan Geddes schrieb:
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway:
I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
data-accessor and similar packages may become your friends. data-accessor allows you to write: someUpdate = (field1 ^: f) . (field2 ^: g) . (field3 ^: h)

On Sat, Sep 11, 2010 at 11:53 AM, Henning Thielemann
Jonathan Geddes schrieb:
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway:
I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
data-accessor and similar packages may become your friends.
data-accessor allows you to write:
someUpdate = (field1 ^: f) . (field2 ^: g) . (field3 ^: h)
data-accessor is a pretty cool package, but if I understand correctly, your "fields" are not the same as the straight functions you get from defining a record, and cant' be used as regular functions. So you have to create these Data.Accessor.Accessors. Is defining accessors really any better than just writing update functions like the following?
updateField1 :: (Field1Type -> Field1Type) -> MyRecord -> MyRecord updateField1 f x = x{field1 = f $ field1 x} someUpdate = (updateField1 f) . j(updateField2 g) . (updateField3 h)
I understand that there is a package data-accessor-template for generating accessors, but couldn't you use TH for generating updater functions as well? It seems like something as fundamental as record update should have a clean, build-in syntax. Or am I thinking too imperatively? --Jonathan

On Sat, 11 Sep 2010, Jonathan Geddes wrote:
On Sat, Sep 11, 2010 at 11:53 AM, Henning Thielemann
data-accessor and similar packages may become your friends.
data-accessor allows you to write:
someUpdate = (field1 ^: f) . (field2 ^: g) . (field3 ^: h)
data-accessor is a pretty cool package, but if I understand correctly, your "fields" are not the same as the straight functions you get from defining a record,
right
and cant' be used as regular functions.
right
So you have to create these Data.Accessor.Accessors.
right
Is defining accessors really any better than just writing update functions like the following?
It's just, that you can use the same name for all kinds of access (set, get, modify) and have nice combinators.
updateField1 :: (Field1Type -> Field1Type) -> MyRecord -> MyRecord updateField1 f x = x{field1 = f $ field1 x} someUpdate = (updateField1 f) . j(updateField2 g) . (updateField3 h)
I understand that there is a package data-accessor-template for generating accessors, but couldn't you use TH for generating updater functions as well?
Sure. But what about names? You would need distinct names for 'get' (like 'field1') and 'modify' (like 'updateField1'), but then you can also write update field1 (or (modify field1) as in data-accessor)
It seems like something as fundamental as record update should have a clean, build-in syntax. Or am I thinking too imperatively?
I think accessors are even more functional than the built-in record syntax. You can nicely combine them with Category's '.' operator in order to access fields in sub-records. It would be cool, if the field identifiers of Haskell records would be Accessors and not just Getters. This would be a recursive problem, since Accessor is itself a record. However, field names could represent functions of type record -> (field, field -> record) .

On 11 September 2010 18:21, Jonathan Geddes
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
Applicatively, using no additional libraries, is how I do it: updateAllThree :: MyRecord -> MyRecord updateAllThree = (\s a b c -> s { field1 = f a, field2 = g b, field3 = h c}) <*> field1 <*> field2 <*> field3 Note - (<$>) is not used, and the left hand function has one extra argument. This style exploits the fact that (<*>) is the Startling (S) combinator. Unfortunately, I haven't worked out how to do nested records in this style.

On Sat, 11 Sep 2010, Stephen Tetley wrote:
On 11 September 2010 18:21, Jonathan Geddes
wrote: someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
Applicatively, using no additional libraries, is how I do it:
updateAllThree :: MyRecord -> MyRecord updateAllThree = (\s a b c -> s { field1 = f a, field2 = g b, field3 = h c}) <*> field1 <*> field2 <*> field3
Cute!
Note - (<$>) is not used, and the left hand function has one extra argument. This style exploits the fact that (<*>) is the Startling (S) combinator.
It uses the Applicative instance for functions.

Am Samstag, den 11.09.2010, 11:21 -0600 schrieb Jonathan Geddes:
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway:
I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
with equivalent semantics. Here => reads "is transformed by". Operator = could still be used for assignment as in current record updates.
The best part about such an extension, in my opinion, is that it would open the door for anonymous lambda record updates. Something like:
someUpdate :: MyRecord -> MyRecord someUpdate = \{field1 => f, field2 => g, field3 => h}
again, with the same semantics. This becomes possible because you no longer need to refer to the record within the {} part of the update.
This would be useful, for example, in the State monad. We could write:
someStateTransform :: State MyRecord () someStateTransform = do modify $ \{field1 => (++"!")} ...
where currently we see code like
someStateTransform :: State MyRecord () someStateTransform = do modify $ \record->record{field1 = (++"!") $ field1 record} ...
which repeats the record name 3 times and the field name twice. The repetition just feels out of place next to all the other terse, readable Haskell code in the program.
So what do my fellow haskellers think? Is this idea worth writing up a proposal for?
Alternatively, can you offer me some advice on writing code in Haskell 2010 that avoids the ugly, repetitive style of record update?
--Jonathan
You might want to have a look at the records package: http://hackage.haskell.org/package/records Here is a code example:
import Data.Kind import Data.TypeFun import Data.Record import Data.Record.Combinators
data Surname = Surname deriving (Show) data Age = Age deriving (Show) data Room = Room deriving (Show)
instance Name Surname where name = Surname instance Name Age where name = Age instance Name Room where name = Room
oldData = X :& Surname := "Jeltsch" :& Age := 31 :& Room := "EH/202" `withStyle` Id KindStar
newData = modify (X :& Age := (+2) :& Room := const "HG/2.39") oldData
Evaluating newData gives you:
X :& Surname := "Jeltsch" :& Age := 33 :& Room := "HG/2.39"
If you have any question regarding the records package, please ask, since I’m its author. :-) Best wishes, Wolfgang

For completeness, using fclabels (yet another record package) you can write it like this:
{-# LANGUAGE TemplateHaskell #-} module Records where
import Data.Record.Label
data MyRecord = MyRecord { _field1 :: String, _field2 :: Int, _field3 :: Bool }
$(mkLabels [''MyRecord])
modifyThree f g h = modL field1 f . modL field2 g . modL field3 h
-chris On 11 sep 2010, at 19:21, Jonathan Geddes wrote:
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway:
I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
with equivalent semantics. Here => reads "is transformed by". Operator = could still be used for assignment as in current record updates.
The best part about such an extension, in my opinion, is that it would open the door for anonymous lambda record updates. Something like:
someUpdate :: MyRecord -> MyRecord someUpdate = \{field1 => f, field2 => g, field3 => h}
again, with the same semantics. This becomes possible because you no longer need to refer to the record within the {} part of the update.
This would be useful, for example, in the State monad. We could write:
someStateTransform :: State MyRecord () someStateTransform = do modify $ \{field1 => (++"!")} ...
where currently we see code like
someStateTransform :: State MyRecord () someStateTransform = do modify $ \record->record{field1 = (++"!") $ field1 record} ...
which repeats the record name 3 times and the field name twice. The repetition just feels out of place next to all the other terse, readable Haskell code in the program.
So what do my fellow haskellers think? Is this idea worth writing up a proposal for?
Alternatively, can you offer me some advice on writing code in Haskell 2010 that avoids the ugly, repetitive style of record update?
--Jonathan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

While we are at it using Semantic Editor Combinators (sec on hackage):
{-# LANGUAGE TemplateHaskell #-}
module T where
import Data.SemanticEditors
data MyRecord = MyRecord { field1 :: String, field2 :: Int, field3 :: Bool } deriving(Show)
mkEditors [''MyRecord]
editRecord str = (editField1.set) newName -- set field1 to new value . editField3 not -- apply function (not) to field3 . (editIf field3.editField2.editIf (<10)) (1+) -- increase field2's value if field2's value < 10 -- and field3 is True
sec also supports functions, lists, Maybe and other monads Chris Eidhof wrote:
For completeness, using fclabels (yet another record package) you can write it like this:
{-# LANGUAGE TemplateHaskell #-} module Records where
import Data.Record.Label
data MyRecord = MyRecord { _field1 :: String, _field2 :: Int, _field3 :: Bool }
$(mkLabels [''MyRecord])
modifyThree f g h = modL field1 f . modL field2 g . modL field3 h
-chris
On 11 sep 2010, at 19:21, Jonathan Geddes wrote:
I know that record updates is a topic that has become a bit of a dead horse, but here I go anyway:
I find that most of the record updates I read and write take the form
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
I find myself wishing I could write something more like
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 => f , field2 => g , field3 => h }
with equivalent semantics. Here => reads "is transformed by". Operator = could still be used for assignment as in current record updates.
The best part about such an extension, in my opinion, is that it would open the door for anonymous lambda record updates. Something like:
someUpdate :: MyRecord -> MyRecord someUpdate = \{field1 => f, field2 => g, field3 => h}
again, with the same semantics. This becomes possible because you no longer need to refer to the record within the {} part of the update.
This would be useful, for example, in the State monad. We could write:
someStateTransform :: State MyRecord () someStateTransform = do modify $ \{field1 => (++"!")} ...
where currently we see code like
someStateTransform :: State MyRecord () someStateTransform = do modify $ \record->record{field1 = (++"!") $ field1 record} ...
which repeats the record name 3 times and the field name twice. The repetition just feels out of place next to all the other terse, readable Haskell code in the program.
So what do my fellow haskellers think? Is this idea worth writing up a proposal for?
Alternatively, can you offer me some advice on writing code in Haskell 2010 that avoids the ugly, repetitive style of record update?
--Jonathan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://old.nabble.com/record-update-tp29686064p29710821.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Wow, I had no idea there were so many record packages! This indicates a couple things to me: a) Haskell is very flexible. b) I'm not the only one who things the built-in record system isn't perfect. Digging a bit deeper, it looks like some of the record-related ghc extensions might also be useful, such as record punning and field disambiguation. Since these are already extensions, they're more likely to make it into Haskell 20XX. Are these considered to be the solution to current record syntax problems? With these extensions, couldn't I write the following?
someUpdate :: MyRecord -> MyRecord someUpdate myRecord@(MyRecord{..}) = let { field1 = f field1 , field2 = g field2 , field3 = h filed3 } in myRecord{..}

On 15 September 2010 04:31, Jonathan Geddes
Wow, I had no idea there were so many record packages! This indicates a couple things to me: a) Haskell is very flexible. b) I'm not the only one who things the built-in record system isn't perfect. Digging a bit deeper, it looks like some of the record-related ghc extensions might also be useful, such as record punning and field disambiguation. Since these are already extensions, they're more likely to make it into Haskell 20XX. Are these considered to be the solution to current record syntax problems? With these extensions, couldn't I write the following?
someUpdate :: MyRecord -> MyRecord someUpdate myRecord@(MyRecord{..}) = let { field1 = f field1 , field2 = g field2 , field3 = h filed3 } in myRecord{..}
or just: someUpdate :: MyRecord -> MyRecord someUpdate myRecord@MyRecord{..} = myRecord{ field1 = f field1 , field2 = g field2 , field3 = h field3 } Conrad.

On Tue, Sep 14, 2010 at 1:31 PM, Jonathan Geddes
With these extensions, couldn't I write the following?
someUpdate :: MyRecord -> MyRecord someUpdate myRecord@(MyRecord{..}) = let { field1 = f field1 , field2 = g field2 , field3 = h filed3 } in myRecord{..}
No, those are recursive let bindings! If f = (1:), then field1 = [1,1,1,1...] As Conrad suggests, use: someUpdate myRecord@(MyRecord{..}) = myRecord { field1 = f field1 , field2 = f field2 , field3 = f field3 } The reason this works is that "field1" in "field1 = " is not a real scoped variable, but rather an identifier for a field in the record. It's all somewhat subtle... Luke
participants (9)
-
-Steffen
-
Chris Eidhof
-
Conrad Parker
-
Henning Thielemann
-
Henning Thielemann
-
Jonathan Geddes
-
Luke Palmer
-
Stephen Tetley
-
Wolfgang Jeltsch