On Thu, Jun 27, 2013 at 2:14 AM, AntC
<anthony_clayden@clear.net.nz> wrote:
> Edward Kmett <ekmett <at>
gmail.com> writes:
>
> Let me take a couple of minutes to summarize how the lens approach
tackles the composition problem today without requiring confusing changes
in the lexical structure of the language.
Thank you Edward, I do find the lens approach absolutely formidable. And I
have tried to read the (plentiful) documentation. But I haven't seen a
really, really simple example that shows the correspondence with H98
records and fields -- as simple as Adam's example in the wiki. (And this
message from you doesn't achieve that either. Sorry, but tl;dr, and there
isn't even a record decl in it.)
There was this one buried down near the bottom.
data Foo = Foo { _fooX, _fooY :: Int }
fooY f (Foo x y) = Foo x <$> f y
We could implement that lens more like:
fooY :: Lens' Foo Int
fooY f s = (\a -> r { _fooY = a }) <$> f (_fooY s)
if you really want to see more record sugar in there, but the code means the same thing.
So let me show you exactly what you just asked for. The correspondence with the getter and setter for the field:
The correspondence with the getter comes from choosing to use the appropriate functor. With some thought it becomes obvious that it should be Const. I won't explain why as that apparently triggers tl;dr. ;)
s ^. l = getConst (l Const s)
Recall that fmap f (Const a) = Const a, so
s ^. fooY = getConst ((\a -> r { _fooY = a }) <$> Const (_fooY s)) = getConst (Const (_fooY s)) = _fooY s
and we can recover the setter by choosing the Functor to be Identity.
modify l f s = runIdentity (l (Identity . f) s)
modify fooY f s = runIdentity (fooY (Identity . f) s) = runIdentity ((\a -> r { _fooY = a }) <$> (Identity . f) (_fooY s) )
if you remove the newtype noise thats the same as
modify fooY f s = s { _fooY = f (_fooY s) }
Similarly after expansion:
set fooY a s = s { _fooY = a }
I sought to give a feel for the derivation in the previous email rather than specific examples, but to work through that and the laws takes a fair bit of text. There isn't any getting around it.
With language support one could envision an option where record declarations cause the generation of lenses using whatever scheme one was going to use for the 'magic (.)' in the first place.
The only difference is you get something that can already be used as both the getter and setter and which can be composed with other known constructions as well, isomorphisms, getters, setters, traversals, prisms, and indexed variants all fit this same mold and have a consistent theoretical framework.
Does the lens approach meet SPJ's criteria of:
* It is the smallest increment I can come up with that
meaningfully addresses the #1 pain point (the inability to
re-use the same field name in different records).
The lens approach is orthogonal to the SORF/DORF design issue. It simply provides a way to make the field accessors compose together in a more coherent way, and helps alleviate the need to conconct confusing semantics around (.), by showing that the existing ones are enough.
* It is backward-compatible.
Lens already works today. So I'd dare say that the thing that works today is compatible with what already works today, yes. ;)
[I note BTW that as the "Plan" currently stands, the '.field' postfix
pseudo-operator doesn't rate too high on backward-compatible.]
I do think that freeing up the name space by not auto-generating a record-
type-bound field selector will help some of the naming work-rounds in the
lens TH.
I'm going to risk going back into tl;dr territory in response to the comment about lens TH:
Currently lens is pretty much non-commital about which strategy to use for field naming / namespace management.
We do have three template-haskell combinators that provide lenses for record types in lens, but they are more or less just 'what we can do in the existing ecosystem'.
I am _not_ advocating any of these, merely describing what we already can do today with no changes required to the language at all.
makeLenses - does the bare minimum to allow for type changing assignment
makeClassy - allows for easy 'nested record types'
makeFields - allows for highly ad hoc per field-name reuse
Consider
data Foo a = Foo { _fooBar :: Int, _fooBaz :: a }
and we can see what is generated by each.
makeLenses ''Foo
generates the minimum possible lens support
fooBar :: Lens' (Foo a) Int
fooBar f s = (\a -> s { _fooBar = a }) <$> f (_fooBar a)
fooBaz :: Lens (Foo a) (Foo b) a b
fooBaz f s = (\a -> s { _fooBaz = a }) <$> f (_fooBaz a)
makeClassy ''Foo generates
class HasFoo t a | t -> a where
foo :: Lens' t (Foo a)
fooBar :: Lens' t Int
fooBaz :: Lens' t a
-- with default definitions of fooBar and fooBaz in terms of the simpler definitions above precomposed with foo
It then provides
instance HasFoo (Foo a) a where
foo = id
This form is particularly nice when you want to be able to build up composite states that have 'Foo' as part of a larger state.
data MyState = MyState { _myStateFoo :: Foo Double, _myStateX :: (Int, Double) }
makeClassy ''MyState
instance HasFoo MyState Double where
foo = myStateFoo
This lets us write some pretty sexy code using HasFoo constraints and MonadState.
blah :: (MonadState s m, HasFoo s a) => m a
blah = do
fooBar += 1
use fooBaz
and that code can run in State Foo or State MyState or other transformer towers that offer a state that subsumes them transparently.
This doesn't give the holy grail of having perfect field name reuse, but it does give a weaker notion of reuse in that you can access fields in part of a larger whole.
I said above that I don't wholly endorse any one of these options, but I do view 'makeClassy' as having effectively removed all pressure for a better record system from the language for me personally. It doesn't permit some of the wilder ad hoc overloadings, but the constraints on it feel very "Haskelly".
Finally,
To provide full field name reuse, we currently use
makeFields ''Foo which is perhaps a bit closer to one of the existing record proposals.
It takes the membernames and uses rules to split it apart into data type name and field part, and then makes instances of Has<FieldName> for each one.
There are issues with all 3 of these approaches. I personally prefer the middle existing option, because I get complete control over naming even if I have to be more explicit.
I wasn't purporting to solve this portion of the record debate, however.
I was claiming that lenses offered a superior option to giving back 'r { f :: t } => r -> t
-Edward
> ...
You say:
>
> template-haskell functions for lens try to tackle the SORF/DORF-like
aspects. These are what Greg Weber was referring to in that earlier email.
>
errm I didn't see an email from Greg(?)
Sorry, I was dragged into this thread by Simon forwarding me an email -- apparently it was in another chain.
-Edward