Re: [Haskell-cafe] What Haskell Records Need

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-Semantic...
_______________________________________________ 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
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@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@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/ --------------------------------------------------------------------

On Thu, Aug 2, 2012 at 12:30 PM, Andrew Butterfield
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:
They do exactly that. They create 'lenses' which are getters/setters/modifiers combined, and allow you to compose these to get/set/modify deep inside nested data types. Look at the examples in the fclabels documentation [2] for more details. [2] http://hackage.haskell.org/packages/archive/fclabels/1.1.4/doc/html/Data-Lab...

Ah yes - the joy of Haskell It so easy to roll your own, rather than search to find someone else's (better/more elegant) solution... :-) On 2 Aug 2012, at 11:41, Erik Hesselink wrote:
On Thu, Aug 2, 2012 at 12:30 PM, Andrew Butterfield
wrote: 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:
They do exactly that. They create 'lenses' which are getters/setters/modifiers combined, and allow you to compose these to get/set/modify deep inside nested data types. Look at the examples in the fclabels documentation [2] for more details.
[2] http://hackage.haskell.org/packages/archive/fclabels/1.1.4/doc/html/Data-Lab...
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@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/ --------------------------------------------------------------------

Richard O'Keefe Said:
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.
I was taught that this kind of thing violates the Law of Demeter and that an object should not be mutating the parts of an acquaintance's parts, but should ask the acquaintance to do so. I'd say that a.b.c.d = val is at the very least a sign that some encapsulation did not happen.
Absolutely! But in Haskell how do you do the asking? I guess that's what I'm proposing is a built in way of doing just that! I'm shooting for as-easy-as the built in getters. Erik Hesselink said:
Isn't this exactly the problem solved by all the lens packages?
Yes it is. I think the existence of these packages along with all the proposals to change records is an indication that something is missing from the language as a whole. What I'm proposing is that the language give you something that is lightweight and easy to use to address this issue. You can still use lenses on top of all of this.
makeLens myField myField'
If I remember correctly, one of the problems with lenses is that they cannot support polymorphic updates (updates which change a type variable of the data). SEC functions, on the other hand support polymorphic updates. --Jonathan On Thu, Aug 2, 2012 at 4:48 AM, Andrew Butterfield < Andrew.Butterfield@scss.tcd.ie> wrote:
Ah yes - the joy of Haskell
It so easy to roll your own, rather than search to find someone else's (better/more elegant) solution... :-)
On 2 Aug 2012, at 11:41, Erik Hesselink wrote:
On Thu, Aug 2, 2012 at 12:30 PM, Andrew Butterfield
wrote: 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:
They do exactly that. They create 'lenses' which are getters/setters/modifiers combined, and allow you to compose these to get/set/modify deep inside nested data types. Look at the examples in the fclabels documentation [2] for more details.
[2] http://hackage.haskell.org/packages/archive/fclabels/1.1.4/doc/html/Data-Lab...
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@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/ --------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'm new to Haskell, but I do like your idea.
I prefer this as a built-in feature because it will create a standard
way of doing this, making the question "wich package should I use to
get mutatos? lens-foo, lens-bar, monad-lens, lens-lens-foo-bar, ...?"
simply go away.
So, yes, I up-vote your idea to write an official proposal.
Thiago.
2012/8/2 Jonathan Geddes
Richard O'Keefe Said:
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.
I was taught that this kind of thing violates the Law of Demeter and that an object should not be mutating the parts of an acquaintance's parts, but should ask the acquaintance to do so. I'd say that a.b.c.d = val is at the very least a sign that some encapsulation did not happen.
Absolutely! But in Haskell how do you do the asking? I guess that's what I'm proposing is a built in way of doing just that! I'm shooting for as-easy-as the built in getters.
Erik Hesselink said:
Isn't this exactly the problem solved by all the lens packages?
Yes it is. I think the existence of these packages along with all the proposals to change records is an indication that something is missing from the language as a whole. What I'm proposing is that the language give you something that is lightweight and easy to use to address this issue. You can still use lenses on top of all of this.
makeLens myField myField'
If I remember correctly, one of the problems with lenses is that they cannot support polymorphic updates (updates which change a type variable of the data). SEC functions, on the other hand support polymorphic updates.
--Jonathan
On Thu, Aug 2, 2012 at 4:48 AM, Andrew Butterfield
wrote: Ah yes - the joy of Haskell
It so easy to roll your own, rather than search to find someone else's (better/more elegant) solution... :-)
On 2 Aug 2012, at 11:41, Erik Hesselink wrote:
On Thu, Aug 2, 2012 at 12:30 PM, Andrew Butterfield
wrote: 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:
They do exactly that. They create 'lenses' which are getters/setters/modifiers combined, and allow you to compose these to get/set/modify deep inside nested data types. Look at the examples in the fclabels documentation [2] for more details.
[2] http://hackage.haskell.org/packages/archive/fclabels/1.1.4/doc/html/Data-Lab...
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@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/ --------------------------------------------------------------------
_______________________________________________ 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

On Thu, Aug 2, 2012 at 9:00 AM, Jonathan Geddes
Richard O'Keefe Said:
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.
I was taught that this kind of thing violates the Law of Demeter and that an object should not be mutating the parts of an acquaintance's parts, but should ask the acquaintance to do so. I'd say that a.b.c.d = val is at the very least a sign that some encapsulation did not happen.
Absolutely! But in Haskell how do you do the asking? I guess that's what I'm proposing is a built in way of doing just that! I'm shooting for as-easy-as the built in getters.
I consider that a strength of the lens approach. If I say 'set (a.b.c.d) 42 record', 'a', 'b' etc. don't have to be record fields, I can swap them out for other lenses later on. I can also easily precompose, e.g. 'setThis = a . b; setThat = b . c' and encourage people to use the composed ones (or require via export lists). This corresponds to "asking" in that it introduces a point of abstraction where I can change all access / modification in one place, or a module can retain control by only exporting the composed version.
Erik Hesselink said:
Isn't this exactly the problem solved by all the lens packages?
Yes it is. I think the existence of these packages along with all the proposals to change records is an indication that something is missing from the language as a whole. What I'm proposing is that the language give you something that is lightweight and easy to use to address this issue. You can still use lenses on top of all of this.
I put up a record suggestion a while back that was in two parts, one was a default lens implementation and the ability to write 'deriving (Lens)' on a record to create the lenses. The other was some magic syntax to make it easier to type in the lens names. Actually it was mostly magic syntax, since 'deriving (Lens)' pretty much speaks for itself, though you'd need to include a default lens implementation in the stdlib. I think that's a good idea anyway, but on the other hand people are still innovating in lens land. But back on the first hand again, threat of inclusion in the stdlib might force a much-needed consolidation and polishing in the lens world (pun honestly not intended). Automatically creating something (semantic editors) which isn't lenses but makes it easier to write lenses is an interesting compromise, though it is really convenient how lenses let you compose the getter and setter together. But I've found that even one line of boilerplate for each record field is already enough to discourage me from writing one for each record field since it only pays off if there's a nested update.
If I remember correctly, one of the problems with lenses is that they cannot support polymorphic updates (updates which change a type variable of the data). SEC functions, on the other hand support polymorphic updates.
This has been solved, yes? I haven't gotten time to investigate fully, but: http://hackage.haskell.org/package/lens-family I should look into it and update the lensy-record proposal if they're appropriate. Though it would be nice to see feedback on it, point out a fatal flaw, or at least someone could mention they read it, so I can know whether or not it's worth spending the time: http://hackage.haskell.org/trac/ghc/wiki/Records/SyntaxDirectedNameResolutio...

Evan Laforge wrote:
I consider that a strength of the lens approach. If I say 'set (a.b.c.d) 42 record', 'a', 'b' etc. don't have to be record fields, I can swap them out for other lenses later on.
I can also easily precompose, e.g. 'setThis = a . b; setThat = b . c' and encourage people to use the composed ones (or require via export lists). This corresponds to "asking" in that it introduces a point of abstraction where I can change all access / modification in one place, or a module can retain control by only exporting the composed version.
The same is true with SEC functions:
personsSalary' :: (Salary -> Salary) -> Person -> Person personsSalary' = job' . salary'
Here I've created a new updater that is composed of 2 that are generated for me (from the examples given in the original email). I can export whichever of these functions I like, generated or otherwise, and keep as much abstraction as I like! The nice part about the SEC functions is that they compose as regular functions. Lenses are super powerful in that they form a category. Unfortunately using categories other than functions feels a tad unwieldy because you have to hide something from prelude and then import Category. (A bit like exceptions, currently). If you like the look of "set" with lenses, you could define a helper function to use with SEC updaters.
set :: ((b -> a) -> c) -> a -> c set sec = sec . const
--and then use it like so: setPersonsSalary :: Salary -> Person -> Person setPersonsSalary salary = set personsSalary' salary
With it you can use an updater as a setter. I'd like to reiterate one of finer points of the original proposal.
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 [using update syntax] as well, currently).
And now back to lenses:
it is really convenient how lenses let you compose the getter and setter together.
I don't recall too many cases where having the getter and setter and modifier all in one place was terribly useful. Could anyone give me an example? But again, where that is useful, a lens can be created from a getter and a SEC updater. Thoughts? --Jonathan

On Fri, Aug 3, 2012 at 10:11 AM, Jonathan Geddes
The nice part about the SEC functions is that they compose as regular functions. Lenses are super powerful in that they form a category. Unfortunately using categories other than functions feels a tad unwieldy because you have to hide something from prelude and then import Category. (A bit like exceptions, currently).
FWIW this is also true for van Laarhoven lenses[1] type FTLens a b = forall f. Functor f => (b -> f b) -> (a -> f a) newtype Const a b = Const { unConst :: a } deriving Functor get :: FTLens a b -> a -> b get ft = unConst . ft Const {- ft :: forall f. (b -> f b) -> (a -> f a) Const :: forall x. b -> Const b x ft Const :: a -> Const b a -} newtype Id a = Id { unId :: a } deriving Functor set :: FTLens a b -> b -> a -> a set ft b = unId . ft (\_ -> Id b) modify :: FTLens a b -> (b -> b) -> a -> a modify ft k = unId . ft (Id . k) -- example fstLens :: FTLens (a,b) a fstLens aToFa (a,b) = (,b) <$> aToFa a -- and you get compose :: FTLens b c -> FTLens a b -> FTLens a c compose = (.) identity :: FTLens a a identity = id
If you like the look of "set" with lenses, you could define a helper function to use with SEC updaters.
set :: ((b -> a) -> c) -> a -> c set sec = sec . const
--and then use it like so: setPersonsSalary :: Salary -> Person -> Person setPersonsSalary salary = set personsSalary' salary
With it you can use an updater as a setter. I'd like to reiterate one of finer points of the original proposal.
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 [using update syntax] as well, currently).
And now back to lenses:
it is really convenient how lenses let you compose the getter and setter together.
I don't recall too many cases where having the getter and setter and modifier all in one place was terribly useful. Could anyone give me an example? But again, where that is useful, a lens can be created from a getter and a SEC updater.
Thoughts?
--Jonathan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oops, forgot my references
[1] Original post:
http://www.twanvl.nl/blog/haskell/cps-functional-references
[2] polymorphic update support: http://r6.ca/blog/20120623T104901Z.html
[3] another post about these:
http://comonad.com/reader/2012/mirrored-lenses/
On Fri, Aug 3, 2012 at 1:53 PM, Ryan Ingram
On Fri, Aug 3, 2012 at 10:11 AM, Jonathan Geddes < geddes.jonathan@gmail.com> wrote:
The nice part about the SEC functions is that they compose as regular functions. Lenses are super powerful in that they form a category. Unfortunately using categories other than functions feels a tad unwieldy because you have to hide something from prelude and then import Category. (A bit like exceptions, currently).
FWIW this is also true for van Laarhoven lenses[1]
type FTLens a b = forall f. Functor f => (b -> f b) -> (a -> f a)
newtype Const a b = Const { unConst :: a } deriving Functor
get :: FTLens a b -> a -> b get ft = unConst . ft Const
{- ft :: forall f. (b -> f b) -> (a -> f a) Const :: forall x. b -> Const b x ft Const :: a -> Const b a -}
newtype Id a = Id { unId :: a } deriving Functor
set :: FTLens a b -> b -> a -> a set ft b = unId . ft (\_ -> Id b)
modify :: FTLens a b -> (b -> b) -> a -> a modify ft k = unId . ft (Id . k)
-- example fstLens :: FTLens (a,b) a fstLens aToFa (a,b) = (,b) <$> aToFa a
-- and you get compose :: FTLens b c -> FTLens a b -> FTLens a c compose = (.)
identity :: FTLens a a identity = id
If you like the look of "set" with lenses, you could define a helper function to use with SEC updaters.
set :: ((b -> a) -> c) -> a -> c set sec = sec . const
--and then use it like so: setPersonsSalary :: Salary -> Person -> Person setPersonsSalary salary = set personsSalary' salary
With it you can use an updater as a setter. I'd like to reiterate one of finer points of the original proposal.
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 [using update syntax] as well, currently).
And now back to lenses:
it is really convenient how lenses let you compose the getter and setter together.
I don't recall too many cases where having the getter and setter and modifier all in one place was terribly useful. Could anyone give me an example? But again, where that is useful, a lens can be created from a getter and a SEC updater.
Thoughts?
--Jonathan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Andrew Butterfield
-
Erik Hesselink
-
Evan Laforge
-
Jonathan Geddes
-
Ryan Ingram
-
Thiago Negri