4

I'm trying to get used to some basic lens features. I started with the following type and function, before trying to introduce lenses:

import qualified Data.Set as S

data Sets = Sets {pending, placed, open :: S.Set Int}
interesting :: Sets -> [Int]
interesting = toList . pending <> placed

i.e., I want the union of the pending and placed nodes, expressed as a list (I later use the result in a list comprehension, so a set is inconvenient).

My basic question is: How do I replicate this using tools from lens? What follows below is skippable if you have a good answer to that question; it's a record of my own beginner explorations of that space.

I renamed the fields to give myself lenses:

{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
import qualified Data.Set as S

data Sets = Sets {_pending, _placed, _open :: S.Set Int}
makeLenses ''Sets

and now wish to reimplement interesting. Of course, it is not hard to do without lenses (toList . _pending <> _placed), but I am trying to get the hang of lenses, and this seems a useful exercise.

My first thought is that pending and placed are still both functions, and I still want to pointwise-mappend things that are sorta related to their results but not really, so pending <> placed ought to be at least interesting to look at:

*Main Data.Foldable> :t pending <> placed
pending <> placed
  :: (Semigroup (f Sets), Functor f) =>
     (S.Set Int -> f (S.Set Int)) -> Sets -> f Sets

Now, what is this type, and what operations can I perform on it? It looks sorta like a constrained Getter, maybe, even though I can't get GHCI to tell me what the constraints are by writing :t pending <> placed :: Getter _s _a. We can try passing it to view anyway, which wants a Getter, and that works:

*Main Data.Foldable> :t view (pending <> placed)
view (pending <> placed) :: MonadReader Sets m => m (S.Set Int)

which, okay, that's a generalization of Sets -> S.Set Int, and I can compose that with toList to get back what I had to begin with:

*Main Data.Foldable> :t toList . view (pending <> placed)
toList . view (pending <> placed) :: Sets -> [Int]

But this doesn't seem very satisfying: it's just what I had before but with an extra view call, and I don't feel like I used any of the power of lenses here. I also don't really understand what pending <> placed "means" in this context.

The other thing I considered is that what I want to do is a lot like foldMap, and what I have is kinda like a Getter, so I should be able to do some foldMapOf.

*Main Data.Foldable> :t foldMapOf (pending <> placed)
foldMapOf (pending <> placed)
  :: Semigroup r => (S.Set Int -> r) -> Sets -> r

This needs one more argument, and the obvious candidate is toList:

*Main Data.Foldable> :t foldMapOf (pending <> placed) toList
foldMapOf (pending <> placed) toList :: Sets -> [Int]

This has the right type, but alas different semantics: it uses <> after the conversion to [Int] rather than on the underlying Set Ints, so if _pending and _placed share elements, we get duplicate copies in the result.

Another thing I could do would be to use toListOf (pending <> placed), yielding a list of sets, and then use ordinary non-lens functions to mush those together:

*Main Data.Foldable> :t toList . mconcat . toListOf (pending <> placed)
toList . mconcat . toListOf (pending <> placed) :: Sets -> [Int]

This works, but is rather ugly and seems to miss the point.

So, do lenses give me any better tools here? Have I chosen a problem so simple that I can't see the advantage of lenses over simple record-field getters?

amalloy
  • 89,153
  • 8
  • 140
  • 205
  • 2
    I'm no lens expert, but I really don't think lenses have anything to offer you here. Each lens lets you manipulate a particular piece of `Sets`, but anything you want to do to combine those manipulations will depend on just what they are. In particular, since Van Laarhoven lenses (at least) don't come with any sort of orthogonality, there's no canonical way to combine edits through two lenses into the same structure. – dfeuer Oct 29 '21 at 01:58
  • Thanks, @dfeuer. I at least found a good lens tool for a different operation on this type: deleting an Int from one of the sets and adding it to another. That is, `moveNode idx from to = over from (S.delete idx) . over to (S.insert idx)`. – amalloy Oct 29 '21 at 02:09
  • Sure, but that's just using one lens and then using another. There's no combining going on. – dfeuer Oct 29 '21 at 03:19

1 Answers1

3

Have I chosen a problem so simple that I can't see the advantage of lenses over simple record-field getters?

That's largely it, I'd say. Intuitively, pending <> placed is a read-only target: there is no sensible way to modify the union of the two sets as a part of the Sets structure, as it doesn't corresponds to anything actually in it. That's why you end up with a getter, which is, as you have found out, essentially a function.

*Main Data.Foldable> :t pending <> placed
pending <> placed
  :: (Semigroup (f Sets), Functor f) =>
     (S.Set Int -> f (S.Set Int)) -> Sets -> f Sets

Now, what is this type, and what operations can I perform on it? It looks sorta like a constrained Getter, maybe, even though I can't get GHCI to tell me what the constraints are by writing :t pending <> placed :: Getter _s _a.

While the type allows for some other not very relevant things, what you really want from it is f ~ Const (S.Set Int), which makes the mappend on the lenses actually mappend the retrieved sets. Specialising to Const does give you a getter, or, being fussy, a Getting. :t on that is slightly more helpful:

ghci> :t pending <> placed :: Getting _ _ _

<interactive>:1:34: error:
    • Found type wildcard ‘_’ standing for ‘S.Set Int’
      To use the inferred type, enable PartialTypeSignatures
    • In the third argument of ‘Getting’, namely ‘_’
      In the type ‘Getting _ _ _’
      In an expression type signature: Getting _ _ _

<interactive>:1:32: error:
    • Found type wildcard ‘_’ standing for ‘Sets’
      To use the inferred type, enable PartialTypeSignatures
    • In the second argument of ‘Getting’, namely ‘_’
      In the type ‘Getting _ _ _’
      In an expression type signature: Getting _ _ _

<interactive>:1:30: error:
    • Found type wildcard ‘_’ standing for ‘_’
      Where: ‘_’ is a rigid type variable bound by
               the inferred type of
                 it :: Semigroup _ => Getting _ Sets (S.Set Int)
               at <interactive>:1:1
      To use the inferred type, enable PartialTypeSignatures
    • In the first argument of ‘Getting’, namely ‘_’
      In the type ‘Getting _ _ _’
      In an expression type signature: Getting _ _ _
duplode
  • 33,731
  • 7
  • 79
  • 150