
Hello there, I'm starting to use a bit more extensively the lens package. It is clearly very powerful, but it feels like a maze of related components (Setting/Setter/Lens'/LensLike/Lens/Traversal/Traversal') which can be swapped for one another except when they can't. The first (concrete) problem I ran into is how to update the members of a set with the result of an IO action. I have managed to do this with a pure function (prefixName) but I'm not sure of how to do this with promptName. Full program below: {-# LANGUAGE TemplateHaskell #-} import Control.Lens import Data.Set import Data.Set.Lens data Dog = Dog { _name :: String, _legs :: Int } deriving (...) makeLenses ''Dog data Dogs = Dogs { _dogs :: Set Dog } deriving Show makeLenses ''Dogs fourLegs :: Traversal' Dog Dog fourLegs = filtered (λd -> d^.legs == 4) promptName :: String -> IO String promptName dogName = do putStr $ "New name for " ++ dogName getLine prefixName :: Dog -> Dog prefixName dog = set name ("PREFIXED: " ++ dog^.name) dog main :: IO () main = do let fido = Dog "fido" 4 let milou = Dog "milou" 4 let cripple = Dog "cripple" 3 let doggies = Dogs $ fromList [fido, milou, cripple] -- prefix dog names via a pure function let doggies' = over (dogs.setmapped) prefixName doggies print doggies' -- change dog names by prompting the user ? return () Help would be appreciated (in particular, 'cripple' would love to be renamed). Since I was struggling with the library, I had the idea to look at the internals, but got stuck at the definition of Lens: type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t a) I'm not sure why the explicit forall is needed here (isn't this equivalent to just Functor f => ...)? b) My understanding is that a lens packs both getter and setters, but I don't know which is supposed to be which here... c) Is there any kind of in-depth guide to Control.Lens somewhere? I have found some examples and tutorials but nothing that seemed to do more than scratch the surface. Thanks, Emm

Hi Emmanuel, On Sun, Jul 14, 2013 at 10:47:16PM +0200, Emmanuel Surleau wrote:
Hello there,
The first (concrete) problem I ran into is how to update the members of a set with the result of an IO action. I have managed to do this with a pure function (prefixName) but I'm not sure of how to do this with promptName.
Unfortunately you cannot do this using a Set. The reason is that modifying the contents of a Set might result in a smaller Set and that cannot possibly satisfy the lens laws. However, if we change the Set of dogs to be a list, we can do this using the (%%~) operator:
... same as before ...
data Dogs = Dogs { _dogs :: [Dog] } deriving Show makeLenses ''Dogs
main :: IO () main = do ... as before ...
-- change dog names by prompting the user doggies' <- doggies & (dogs.traverse.name) %%~ prefixName print doggies'
return ()
But astoundingly, if you look at the implementation of (%%~), it is... (%%~) = id! So this code also works: doggies' <- (dogs.traverse.name) prefixName doggies That's right, the magic solution is to just treat the (dogs.traverse.name) lens as a *function* and apply it to prefixName! To understand why this works we have to look a bit at the implementation. I am not surprised that you were baffled by it because it looks quite magical if you don't understand where it comes from.
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
Instead of trying to understand why this is the definition, let's just see what happens if we take the right-hand side and set f = IO: (a -> IO b) -> s -> IO t In the above example, a = b = String, and s = t = Dogs, that is, (dogs.traverse.name) has type Lens Dogs Dogs String String which expands to (String -> IO String) -> Dogs -> IO Dogs (actually this is a lie, it is really just a Traversal and not a Lens, but it's the same idea). So if we apply it to 'prefixName :: String -> IO String' we get a function of type Dogs -> IO Dogs! Nifty! Now, to answer your specific questions:
a) I'm not sure why the explicit forall is needed here (isn't this equivalent to just Functor f => ...)?
Yes, it is equivalent; the explicit forall is not strictly necessary. The forall is there to emphasize that the 'f' does not show up on the left-hand side: something of type Lens s t a b is a function which works for *any* specific Functor f that a user might choose. (E.g., we specifically chose IO in the example above). So e.g. a lens cannot do IO operations, because then it would only work for IO and not for other Functors. So a lens may only interact with the f via the fmap function. (Similarly a Traversal must work with all Applicatives, and so on.)
b) My understanding is that a lens packs both getter and setters, but I don't know which is supposed to be which here...
You can think of lenses as generalizations of getters+setters, but that is NOT how they are implemented! Nothing in the type (a -> f b) -> s -> f t corresponds directly to getters or setters. For understanding more about what this type means and why it corresponds to the idea of lenses, I highly recommend the video of Edward's presentation to the NY Haskell user's group: http://youtu.be/cefnmjtAolY?hd=1 .
c) Is there any kind of in-depth guide to Control.Lens somewhere? I have found some examples and tutorials but nothing that seemed to do more than scratch the surface.
You can find pretty much everything there is on lens here: http://lens.github.io/ -Brent

Hi Brent,
Thanks for the link to the video. I watched the first half yesterday, and
it's definitely content rich. But the overall design of the library is
starting to make sense now. The reason it doesn't work for Sets (and I
assume any similar structure like hashmaps) is because, depending on the
implementation of Eq on the item the Set is parametrized on and the field
being modified, you could accidentally remove another item - and this would
be a BAD THING, since applying a setter on a traversal is basically
"fmap++" and fmap doesn't let you remove things. Is this correct?
Also, thanks for the traversal example with the list, that's certainly
going to be useful.
Cheers,
Emm
On Mon, Jul 15, 2013 at 3:16 PM, Brent Yorgey
Hi Emmanuel,
Hello there,
The first (concrete) problem I ran into is how to update the members of a set with the result of an IO action. I have managed to do this with a
On Sun, Jul 14, 2013 at 10:47:16PM +0200, Emmanuel Surleau wrote: pure
function (prefixName) but I'm not sure of how to do this with promptName.
Unfortunately you cannot do this using a Set. The reason is that modifying the contents of a Set might result in a smaller Set and that cannot possibly satisfy the lens laws. However, if we change the Set of dogs to be a list, we can do this using the (%%~) operator:
... same as before ...
data Dogs = Dogs { _dogs :: [Dog] } deriving Show makeLenses ''Dogs
main :: IO () main = do ... as before ...
-- change dog names by prompting the user doggies' <- doggies & (dogs.traverse.name) %%~ prefixName print doggies'
return ()
But astoundingly, if you look at the implementation of (%%~), it is... (%%~) = id! So this code also works:
doggies' <- (dogs.traverse.name) prefixName doggies
That's right, the magic solution is to just treat the (dogs.traverse.name) lens as a *function* and apply it to prefixName!
To understand why this works we have to look a bit at the implementation. I am not surprised that you were baffled by it because it looks quite magical if you don't understand where it comes from.
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
Instead of trying to understand why this is the definition, let's just see what happens if we take the right-hand side and set f = IO:
(a -> IO b) -> s -> IO t
In the above example, a = b = String, and s = t = Dogs, that is, (dogs.traverse.name) has type
Lens Dogs Dogs String String
which expands to
(String -> IO String) -> Dogs -> IO Dogs
(actually this is a lie, it is really just a Traversal and not a Lens, but it's the same idea). So if we apply it to 'prefixName :: String -> IO String' we get a function of type Dogs -> IO Dogs! Nifty!
Now, to answer your specific questions:
a) I'm not sure why the explicit forall is needed here (isn't this equivalent to just Functor f => ...)?
Yes, it is equivalent; the explicit forall is not strictly necessary. The forall is there to emphasize that the 'f' does not show up on the left-hand side: something of type Lens s t a b is a function which works for *any* specific Functor f that a user might choose. (E.g., we specifically chose IO in the example above). So e.g. a lens cannot do IO operations, because then it would only work for IO and not for other Functors. So a lens may only interact with the f via the fmap function. (Similarly a Traversal must work with all Applicatives, and so on.)
b) My understanding is that a lens packs both getter and setters, but I don't know which is supposed to be which here...
You can think of lenses as generalizations of getters+setters, but that is NOT how they are implemented! Nothing in the type (a -> f b) -> s -> f t corresponds directly to getters or setters.
For understanding more about what this type means and why it corresponds to the idea of lenses, I highly recommend the video of Edward's presentation to the NY Haskell user's group: http://youtu.be/cefnmjtAolY?hd=1 .
c) Is there any kind of in-depth guide to Control.Lens somewhere? I have found some examples and tutorials but nothing that seemed to do more than scratch the surface.
You can find pretty much everything there is on lens here:
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, Jul 16, 2013 at 07:09:43AM +0200, Emmanuel Surleau wrote:
Hi Brent,
Thanks for the link to the video. I watched the first half yesterday, and it's definitely content rich. But the overall design of the library is starting to make sense now. The reason it doesn't work for Sets (and I assume any similar structure like hashmaps) is because, depending on the implementation of Eq on the item the Set is parametrized on and the field being modified, you could accidentally remove another item - and this would be a BAD THING, since applying a setter on a traversal is basically "fmap++" and fmap doesn't let you remove things. Is this correct?
Yes, that's a good way to think of it.
Also, thanks for the traversal example with the list, that's certainly going to be useful.
Glad I could be of help! -Brent
Cheers,
Emm
On Mon, Jul 15, 2013 at 3:16 PM, Brent Yorgey
wrote: Hi Emmanuel,
Hello there,
The first (concrete) problem I ran into is how to update the members of a set with the result of an IO action. I have managed to do this with a
On Sun, Jul 14, 2013 at 10:47:16PM +0200, Emmanuel Surleau wrote: pure
function (prefixName) but I'm not sure of how to do this with promptName.
Unfortunately you cannot do this using a Set. The reason is that modifying the contents of a Set might result in a smaller Set and that cannot possibly satisfy the lens laws. However, if we change the Set of dogs to be a list, we can do this using the (%%~) operator:
... same as before ...
data Dogs = Dogs { _dogs :: [Dog] } deriving Show makeLenses ''Dogs
main :: IO () main = do ... as before ...
-- change dog names by prompting the user doggies' <- doggies & (dogs.traverse.name) %%~ prefixName print doggies'
return ()
But astoundingly, if you look at the implementation of (%%~), it is... (%%~) = id! So this code also works:
doggies' <- (dogs.traverse.name) prefixName doggies
That's right, the magic solution is to just treat the (dogs.traverse.name) lens as a *function* and apply it to prefixName!
To understand why this works we have to look a bit at the implementation. I am not surprised that you were baffled by it because it looks quite magical if you don't understand where it comes from.
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
Instead of trying to understand why this is the definition, let's just see what happens if we take the right-hand side and set f = IO:
(a -> IO b) -> s -> IO t
In the above example, a = b = String, and s = t = Dogs, that is, (dogs.traverse.name) has type
Lens Dogs Dogs String String
which expands to
(String -> IO String) -> Dogs -> IO Dogs
(actually this is a lie, it is really just a Traversal and not a Lens, but it's the same idea). So if we apply it to 'prefixName :: String -> IO String' we get a function of type Dogs -> IO Dogs! Nifty!
Now, to answer your specific questions:
a) I'm not sure why the explicit forall is needed here (isn't this equivalent to just Functor f => ...)?
Yes, it is equivalent; the explicit forall is not strictly necessary. The forall is there to emphasize that the 'f' does not show up on the left-hand side: something of type Lens s t a b is a function which works for *any* specific Functor f that a user might choose. (E.g., we specifically chose IO in the example above). So e.g. a lens cannot do IO operations, because then it would only work for IO and not for other Functors. So a lens may only interact with the f via the fmap function. (Similarly a Traversal must work with all Applicatives, and so on.)
b) My understanding is that a lens packs both getter and setters, but I don't know which is supposed to be which here...
You can think of lenses as generalizations of getters+setters, but that is NOT how they are implemented! Nothing in the type (a -> f b) -> s -> f t corresponds directly to getters or setters.
For understanding more about what this type means and why it corresponds to the idea of lenses, I highly recommend the video of Edward's presentation to the NY Haskell user's group: http://youtu.be/cefnmjtAolY?hd=1 .
c) Is there any kind of in-depth guide to Control.Lens somewhere? I have found some examples and tutorials but nothing that seemed to do more than scratch the surface.
You can find pretty much everything there is on lens here:
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (2)
-
Brent Yorgey
-
Emmanuel Surleau