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.
infixl 8 ^.
s ^. l = getConst (l Const s)
With that combinator in hand:
(^.) :: s -> ((a -> Const a b) -> s -> Const a t) -> a
But we don't need the rank-2 aliases for anything other than clarity. In particular the code above can be written and typechecked entirely in Haskell 98.
We can also generate a 'getter' from a normal haskell function such that it can be composed with lenses and other getters:
to :: (s -> a) -> (a -> Const r b) -> s -> Const r t
to sa acr = Const . getConst . acr . sa
x^.to f = getConst (to f Const s) = getConst ((Const . getConst . Const . f) s) = f s
Then the examples where folks have asked to be able to just compose in an arbitrary Haskell function become:
(1,"hello")^._2.to length = 5
We can also write back through a lens:
They take on the more general pattern that actually allows type changing assignment.
modify :: ((a -> Identity b) -> s -> Identity t) -> (a -> b) -> s -> t
modify l ab = runIdentity . l (Identity . ab)
set l b = modify l (const b)
These can be written entirely using 'base' rather than with Identity from transformers by replacing Identity with (->) ()
With that in hand we can state the 'Setter' laws:
modify l id = id
modify l f . modify l g = modify l (f . g)
These are just the Functor laws!
and we can of course make a 'Setter' for any Functor that you could pass to modify:
mapped :: Functor f => (a -> Identity b) -> f a -> Identity (f b)
mapped aib = Identity . fmap (runIdentity . aib)
then you can verify that
modify mapped ab = runIdentity . Identity . fmap (Identity . runIdentity ab) = fmap ab
modify (mapped.mapped) = fmap.fmap
'mapped' isn't a full lens. You can't read from 'mapped' with (^.). Try it. Similarly 'to' gives you merely a 'Getter', not something suitable to modify. You can't 'modify the output of 'to', the types won't let you. (The lens type signatures are somewhat more complicated here because they want the errors to be in instance resolution rather than unification, for readability's sake)
But we can still use modify on any lens, because Identity is a perfectly cromulent Functor.
modify _2 (+2) (1,2) = (1,4)
modify _2 length (1,"hello") = (1,5) -- notice the change of type!
modify (_2._1) (+1) (1,(2,3)) = (1,(3,3))
modify (_2.mapped) (+1) (1,[2,3,4]) = (1,[3,4,5])
We can also define something very lens-like that has multiple targets. In fact we already know the canonical example of this, 'traverse' from Data.Traversable. So we'll call them traversals.
We can use modify on any 'traversal' such as traverse:
modify traverse (+1) [1,2,3] = [2,3,4]
This permits us to modify multiple targets with a lens in a coherent, possibly type changing manner.
We can make new traversals that don't exactly match the types in Data.Traversable as well:
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f tboth :: Traversal (a,a) (b,b) a bboth f (a,b) = (,) <$> f a <*> f b
modify both (+1) (1,2) = (3,4)
The laws for a traversal are a generalization of the Traversable laws.
Compositions of traversals form valid traversals.
Lens goes farther and provides generalizations of Foldables as 'Folds', read-only getters, etc. just by changing the constraints on 'f' in the (a -> f b) -> s -> f t form.
The key observation here is that we don't need to make up magic syntax rules for (.) just to get reverse application. We already have it!
The only thing we needed was a slightly different (.)-like operator to start the chain ((^.) above.).
This is nice because it allows us to talk about compositions of lenses as first class objects we can pass around.
Moreover they compose naturally with traversals, and the idioms we already know how to use with traverse apply. In fact if you squint you can recognize the code for modify and (^.) from the code for foldMapDefault and fmapDefault in Data.Traversable, except we just pass in the notion of 'traverse' as the extra lens-like argument.
Every Lens is a valid Traversal.
modify (both._1) (+1) ((1,2),(3,4)) = ((2,2),(4,4))
If you have a lens foo and a lens bar then baz = foo.bar is also a lens.
We can make lenses that can access fairly complex structures. e.g. we can make lenses that let us both read and write whether or not something is in a Set:
contains :: Ord k => k -> Lens' (Set k) Bool
| record projections. I would prefer to have dot notation for aActually I *hadn't* considered that. I'm sure it's been suggested before (there has been so much discussion), but I had not really thought about it in the context of our very modest proposal.
| general, very tightly-binding reverse application, and the type of the record
| selector for a field f changed to "forall r t. r { f :: t } => r -> t"
| instead of "SomeRecordType -> t". Such a general reverse application dot would
| allow things like "string.toUpper" and for me personally, it would
| make a Haskell OO library that I'm working on more elegant...
We're proposing, in effect, that ".f" is a postfix function with type "forall r t. r { f :: t } => r -> t". You propose to decompose that idea further, into (a) reverse function application and (b) a first class function f.
It is kind of weird that
f . g means \x. f (g x)
but f.g means g f
but perhaps it is not *more* weird than our proposal.
Your proposal also allows things like
data T = MkT { f :: Int }
foo :: [T] -> [Int]
foo = map f xs
because the field selector 'f' has the very general type you give, but the type signature would be enough to fix it. Or, if foo lacks a type signature, I suppose we'd infer
foo :: (r { f::a }) => [r] -> [a]
which is also fine.
It also allows you to use record field names in prefix position, just as now, which is a good thing.
In fact, your observation allows us to regard our proposal as consisting of two entirely orthogonal parts
* Generalise the type of record field selectors
* Introduce period as reverse function application
Both have merit.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-
| bounces@haskell.org] On Behalf Of Dominique Devriese
| Sent: 26 June 2013 13:16
| To: Adam Gundry
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Overloaded record fields
|
| I think it's a good idea to push forward on the records design because
| it seems futile to hope for an ideal consensus proposal.
|
| The only thing I dislike though is that dot notation is special-cased to
| record projections. I would prefer to have dot notation for a
| general, very tightly-binding reverse application, and the type of the record
| selector for a field f changed to "forall r t. r { f :: t } => r -> t"
| instead of
| "SomeRecordType -> t". Such a general reverse application dot would
| allow things like "string.toUpper" and for me personally, it would
| make a Haskell OO library that I'm working on more elegant...
|
| But I guess you've considered such a design and decided against it,
| perhaps because of the stronger backward compatibility implications of
| changing the selectors' types?
|
| Dominique
|
| 2013/6/24 Adam Gundry <adam.gundry@strath.ac.uk>:
| > Hi everyone,
| >
| > I am implementing an overloaded record fields extension for GHC as a
| > GSoC project. Thanks to all those who gave their feedback on the
| > original proposal! I've started to document the plan on the GHC wiki:
| >
| > http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
| >
| > If you have any comments on the proposed changes, or anything is unclear
| > about the design, I'd like to hear from you.
| >
| > Thanks,
| >
| > Adam Gundry
| >
| > _______________________________________________
| > Glasgow-haskell-users mailing list
| > Glasgow-haskell-users@haskell.org
| > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users