[Haskell-cafe] Conditional lens

Edward Kmett ekmett
Fri Oct 11 04:14:53 UTC 2013


`ifL` isn't a legal lens for several reasons.

Lens s t a b generally requires that the types a subsumes b and b subsumes
a, and that s subsumes t and t subsumes s.

Lens s (Maybe t) (Maybe a) b is a huge red flag.

There is an 'illegal prism' provided by lens that is a more principled
version of this, however.

>>> (0,2) & _1.filtered even .~ 2

(2,2)
filtered only claims to be a Fold, because that is all it can legally claim
to pass the laws for, however it is implemented in such a way that you can
use it as a Traversal or even a Prism. To sleep soundly you should ensure
that the elements you write back pass the filter function as True,
otherwise you'll violate a law and the lens police will come for you in the
night.

You can of course implement the method you want without any of these
shenanigans and still sleep well at night, though.

changeTyCon tc tc' = tyCon $ \a -> if a == tc then Just tc' else Nothing

changeTyCon tc tc' = tyCon $ \a -> tc' <$ guard (a == tc)

-Edward



On Thu, Oct 10, 2013 at 5:00 PM, Artyom Kazak <yom at artyom.me> wrote:

> Hello!
>
> I am working with TypeReps, and while writing some functions I have
> noticed that I could use lenses to simplify them; however, I have stumbled
> upon some difficulties.
>
> First I?ll try to clarify which functions I want to write:
>
>     * a function for converting TypeRep of, say, `Maybe x` to `[x]`
>       (for all x). It requires checking if the TyCon is `Maybe` and
>       replacing it with []-TyCon. If it wasn?t `Maybe`, I return Nothing.
>
>     * a similar function for replacing `Char`s and `Lazy.Text`s to just
>       `Text`. Again, if the TypeRep-to-be-replaced doesn?t satisfy my
>       conditions, I return Nothing.
>
> These two functions (and some others, I suppose) can be written concisely
> with the help of one combinator. I don?t know how to write it as
> a composable Lens, so I?ll give it here as an ad-hoc Lens-modifying
> function instead:
>
>     ifL :: (a -> Bool) -> Lens s t a b -> Lens s (Maybe t) (Maybe a) b
>     ifL p l = lens getter setter
>       where
>         get s = getConst $ l Const s
>         getter s   = let a = get s
>                      in  if p a then Just a else Nothing
>         setter s b = let a = get s
>                      in  if p a then Just (set l b s) else Nothing
>
> It works like this:
>
>     > (0, 2) & ifL even fs .~ "hello"
>     Just ("hello",2)
>
>     > (1, 2) & ifL even fs .~ "hello"
>     Nothing
>
> With `ifL`, my initial ugly
>
>     changeTyCon :: TyCon -> TyCon -> TypeRep -> Maybe TypeRep
>     changeTyCon tc tc' t | t^.tyCon == tc = Just $ t & tyCon .~ tc'
>                          | otherwise      = Nothing
>
> boils down to
>
>     changeTyCon tc tc' = ifL (== tc) tyCon .~ tc'
>
> Why did I call the initial version ?ugly?? Well, because
>
>     a) it manually handles `Maybe`s, and
>     b) it has to perform both getting and setting (two passes).
>
> So, my questions are:
>
>     1. What would be the idiomatic way to write `ifL`?
>
>     2. How can I do something like `t ^. ifL (== tc) tyCon`?
>        Currently it doesn?t work because view?s type has been
>        simplified in lens-3.9.
>
>     3. Perhaps it would be better to represent `ifL` as a Traversal
>        which simply ignores values that don?t match the condition?
>        Then I could (?) use `failover` to do what I want. I searched
>        for something filter-like in lens library, but haven?t found
>        anything.
>
>     4. If I haven?t missed anything and it indeed can?t be done with bare
>        lens, would `ifL` or something similar be welcome as an addition
>        to the library?
>
> Thanks!
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131011/9288da9f/attachment.html>



More information about the Haskell-Cafe mailing list