[Haskell-cafe] What Haskell Records Need

Andrew Butterfield Andrew.Butterfield at scss.tcd.ie
Thu Aug 2 12:30:57 CEST 2012


On 2 Aug 2012, at 09:25, Erik Hesselink wrote:

> Isn't this exactly the problem solved by all the lens packages?
> Current popular ones are fclabels [0] and data-lens [1].
> 
> [0] http://hackage.haskell.org/package/fclabels
> [1] http://hackage.haskell.org/package/data-lens

Not sure what all of these do, but I have a simple solution I use
in my work:
> 
>> Take the following types from a contrived
>> example.
>> 
>>> type Salary = Integer
>>> 
>>> data Job = Job
>>> { title  :: String
>>> , salary :: Salary
>>> }

Rather than setTitle :: String -> Job -> Job  we lift the first argument
and define

setfTitle  :: (String -> String) -> Job -> Job
setfTitle f jobrec = jobrec{ title = f $ title jobrec }

then setTitle = setfTitle . const

This is all just boilerplate, so we continue

setfSalary :: (Salary -> Salary) -> Job -> Job
setfSalary f jobrec = jobrec{ salary = f $ salary jobrec }

>>> 
>>> data Person = Person
>>> { name :: String
>>> , job  :: Job
>>> }
>> 


setfName :: (String -> String) -> Person -> Person
setfName f prec = prec{ name = f $ name prec }

setfJob :: (Job -> Job) -> Person -> Person
setfJob f prec = prec{ job = f $ job prec }

Now we can use function composition to do two levels

setfTitleInPerson :: (String -> String) -> Person -> Person
setfTitleInPerson = setfJob . setfTitle

setTitleInPerson :: String -> Person -> Person
setTitleInPerson = setfTitleInPerson . const

Simple function composition works to put these together...


I was frustrated by this problem a while back, and decided to approach it formally
(I write literate Haskell/LateX documents), and went to work, doing the math
with the intention of writing a suitable combinator, until I discovered I didn't
need one .... lifting from  X -> R -> R   to (X -> X) -> R -> R gave me all I needed...



>> Since I've used record syntax, I get
>> getter/accessor functions (title, salary,
>> name, job) for free. Now suppose I want to
>> create an aggregate getter function: return
>> the salary of a given person. Piece of cake,
>> it's just function composition
>> 
>>> getSalary :: Person -> Salary
>>> getSalary = salary . job
>> 
>> Done! Now suppose I want to write a
>> setter/mutator function for the same nested
>> field
>> 
>>> setSalaryMessy :: Salary -> Person -> Person
>>> setSalaryMessy newSalary person =
>>> person {
>>>  job = (job person) {
>>>    salary = newSalary
>>>  }
>>> }
>> 
>> Ouch! And that's not even very deeply nested.
>> Imagine 4 or 5 levels deep. It really makes
>> Haskell feel clunky next to `a.b.c.d = val`
>> that you see in other languages. Of course
>> immutability means that the semantics of
>> Haskell are quite different (we're creating
>> new values here, not updating old ones) but
>> it's still common to model change using these
>> kinds of updates.
>> 
>> What if along with the free getters that
>> the compiler generates when we use record
>> syntax, we also got semantic editor
>> combinator (SEC) functions[0] that could be
>> used as follows?
>> 
>>> setSalary newSalary = job' $ salary' (const newSalary)
>>> 
>>> giveRaise amount = job' $ salary' (+amount)
>>> 
>>> givePercentRaise percent = job' $ salary' (*(1+percent))
>> 
>> For each field x, the compiler generates a
>> function x' (the tic is mnemonic for change).
>> These little functions aren't hard to write,
>> but they're classic boilerplate.
>> 
>>> job' :: (Job -> Job) -> Person -> Person
>>> job' f person = person {job = f $ job person}
>> 
>>> salary' :: (Salary -> Salary) -> Job -> Job
>>> salary' f job = job { salary = f $ salary job}
>> 
>> These type of utility functions are a dream
>> when working with any reference type or
>> State Monad.
>> 
>>> modify $ givePercentRaise 0.25
>> 
>> The compiler could also generate polymorphic
>> SEC functions for polymorphic fields.
>> Further, the compiler could disallow using
>> old-style update syntax for fields whose SEC
>> update function is not in scope, giving us
>> fine-grained control over access and update.
>> On the other hand we currently have to create
>> new functions to achieve this (exporting the
>> getter means exporting the ability to update
>> as well, currently).
>> 
>> Of course this doesn't address the
>> namespacing issues with records, but it is
>> likely nicely orthogonal to other proposals
>> which do.
>> 
>> Also note that there's a package on hackage [1]
>> that will generate SEC functions using TH.
>> It's nice, but I prefer the style of field
>> names used above for updaters (field' vs
>> editField).
>> 
>> Let me know what you think. I'll write up an
>> official proposal if there's a bit of
>> general interest around this.
>> 
>> Thanks for reading,
>> 
>> --Jonathan
>> 
>> [0] - http://conal.net/blog/posts/semantic-editor-combinators
>> [1] -
>> http://hackage.haskell.org/packages/archive/sec/0.0.1/doc/html/Data-SemanticEditors.html
>> 
>> 
>> 
>> 
>> _______________________________________________
>> 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

--------------------------------------------------------------------
Andrew Butterfield     Tel: +353-1-896-2517     Fax: +353-1-677-2204
Lero at TCD, Head of Foundations & Methods Research Group
Director of Teaching and Learning - Undergraduate,
School of Computer Science and Statistics,
Room G.39, O'Reilly Institute, Trinity College, University of Dublin
                         http://www.scss.tcd.ie/Andrew.Butterfield/
--------------------------------------------------------------------
--------------------------------------------------------------------
Andrew Butterfield     Tel: +353-1-896-2517     Fax: +353-1-677-2204
Lero at TCD, Head of Foundations & Methods Research Group
Director of Teaching and Learning - Undergraduate,
School of Computer Science and Statistics,
Room G.39, O'Reilly Institute, Trinity College, University of Dublin
                          http://www.scss.tcd.ie/Andrew.Butterfield/
--------------------------------------------------------------------




More information about the Haskell-Cafe mailing list