re[Haskell-cafe] cord update
-Steffen
steffen.siering at gmail.com
Tue Sep 14 13:10:35 EDT 2010
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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at 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.
More information about the Haskell-Cafe
mailing list