<div dir="ltr">Hi Oleg,<div><br></div><div>How easy should it be to "create a Traversable newtype over your type" ?</div><div><br></div><div>data Q6 a b c = Q61 a (Identity b) | Q62 [b] | Q63 c</div><div><br></div><div>newtype Q6b a c b = Q61b (Q6 a b c)</div><div><br></div><div>I cannot automatically derive anything for Q6b (Functor, Foldable, Traversable). </div><div>So we are back to hand writing lenses for Q6, or I miss something ?</div><div><br></div><div>For the rest, it was a very nice followup, I'm still rereading. </div><div><br></div><div>Thanks</div><div><br></div><div>Best</div><div><br></div><div>.p</div><div><br></div><div><br></div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">2018-05-02 23:06 GMT+02:00 Oleg Grenrus <span dir="ltr"><<a href="mailto:oleg.grenrus@iki.fi" target="_blank">oleg.grenrus@iki.fi</a>></span>:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Here's a little gist I wrote.<br>
<br>
See <a href="https://gist.github.com/phadej/04aae6cb98840ef9eeb592b76e6f3a67" rel="noreferrer" target="_blank">https://gist.github.com/<wbr>phadej/<wbr>04aae6cb98840ef9eeb592b76e6f3a<wbr>67</a><br>
for syntax highlighted versions.<br>
<br>
Hopefully it gives you some insights!<br>
<br>
\begin{code}<br>
{-# LANGUAGE RankNTypes, DeriveFunctor, DeriveFoldable,<br>
DeriveTraversable, TupleSections #-}<br>
import Data.Functor.Identity<br>
import Data.Profunctor<br>
import Data.Profunctor.Traversing<br>
import Data.Traversable<br>
import Data.Tuple (swap)<br>
<span class=""><br>
data Q5 a b = Q51 a (Identity b) | Q52 [b]<br>
<br>
lq5Twan :: Applicative f => (b -> f b') -> Q5 a b -> f (Q5 a b')<br>
lq5Twan f (Q51 a bs) = Q51 a <$> traverse f bs<br>
lq5Twan f (Q52 bs) = Q52 <$> traverse f bs<br>
<br>
</span><span class="">data BT tt tt' b t t' a = BT1 (tt -> b) (t a) | BT2 (tt' -> b) (t' a)<br>
deriving (Functor,Foldable,Traversable)<br>
runBT (BT1 f x) = f x<br>
runBT (BT2 f x) = f x<br>
<br>
</span><span class="">lq5Profunctor :: forall p a b b' . Traversing p => p b b' -> p (Q5 a b)<br>
(Q5 a b')<br>
</span><span class="">lq5Profunctor = dimap pre post . second' . traverse' where<br>
  pre (Q51 a x) = ((), BT1 (Q51 a) x)<br>
  pre (Q52 bs) = ((), BT2 Q52 bs)<br>
  post ((),x) = runBT x<br>
</span>\end{code}<br>
<br>
\begin{code}<br>
instance Functor (Q5 a) where fmap = fmapDefault<br>
instance Foldable (Q5 a) where foldMap = foldMapDefault<br>
instance Traversable (Q5 a) where<br>
    traverse f (Q51 a bs) = Q51 a <$> traverse f bs<br>
    traverse f (Q52 bs) = Q52 <$> traverse f bs<br>
<span class=""><br>
lq5Twan' :: Applicative f => (b -> f b') -> Q5 a b -> f (Q5 a b')<br>
</span>lq5Twan' = traverse<br>
<span class=""><br>
lq5Profunctor' :: forall p a b b' . Traversing p => p b b' -> p (Q5 a b)<br>
(Q5 a b')<br>
</span>lq5Profunctor' = traverse'<br>
\end{code}<br>
<br>
And in general: three steps:<br>
<br>
1. create a Traversable newtype over your type<br>
2. dimap pre post . traverse'<br>
3. Profit!<br>
<br>
Compare that to writing Lens<br>
<br>
1. bijection your 's' to (a, r) (Note: 'r' can be 's'!)<br>
2. dimap to from . first'<br>
3. Profit!<br>
<br>
Trivial examples:<br>
<br>
\begin{code}<br>
type Lens s t a b = forall p. Strong p => p a b -> p s t<br>
<br>
_1 :: Lens (a, c) (b, c) a b<br>
_1 = dimap id id . first'<br>
<br>
_2 :: Lens (c, a) (c, b) a b<br>
_2 = dimap swap swap . first'<br>
\end{code}<br>
<br>
Note again, that in usual `lens` definition we pick r to be s:<br>
we "carry over" the whole "s", though "s - a = r" would be enough.<br>
But in practice constructing "residual" is expensive.<br>
Think about record with 10 fields: residual in a single field lens<br>
would be 9-tuple - not really worth it.<br>
<br>
Interlude, one can define Traversal over first argument too.<br>
Using Bitraversable class that would be direct.<br>
<br>
In this case it's Affine (Traversal), so we can do "better" than using<br>
`traverse'`.<br>
<br>
\begin{code}<br>
lq5ProFirst :: forall p a a' b. (Choice p, Strong p) => p a a' -> p (Q5<br>
a b) (Q5 a' b)<br>
lq5ProFirst = dimap f g . right' . first' where<br>
    -- Think why we have chosen [b] + a * b<br>
    -- compare to definition of Q5!<br>
    --<br>
    -- The r + r' * s shape justifies the name Affine, btw.<br>
    f :: Q5 a b -> Either [b] (a, Identity b)<br>
    f (Q51 a x) = Right (a, x)<br>
    f (Q52 bs)  = Left bs<br>
<br>
    g (Left bs) = Q52 bs<br>
    g (Right (a, x)) = Q51 a x<br>
\end{code}<br>
<br>
Note: how the same<br>
<br>
1. bijection to some structure (`r' + r * a` in this case<br>
2. dimap to from . ...<br>
3. Profit<br>
<br>
pattern is applied again.<br>
<br>
Another way to think about it is that we<br>
<br>
1. Use `Iso` (for all Profunctor!) to massage value into the form, so<br>
2. we can use "Optic specific" transform<br>
3. Profit!<br>
<br>
And optic specific:<br>
- Lens -> Products<br>
- Prism -> Coproducts (Sums)<br>
- Traversal -> Traversable<br>
- Setter -> Functor (Mapping type class has map' :: Functor f => p a b<br>
-> p (f a) (f b))<br>
- etc.<br>
<br>
So the fact that defining arbitrary Traversals directly is more handy with<br>
`wander`, than `traverse'` (as you can omit `dimap`!) is more related to the<br>
fact that we have<br>
<br>
\begin{spec}<br>
class Traversable t where<br>
    traverse :: Applicative f => (a -> f b) -> t a -> f (t b)<br>
\end{spec}<br>
<br>
... and we (well, me) don't yet know another elegant way to capture "the<br>
essense of Traversable". (I don't think FunList is particularly "elegant")<br>
<br>
<br>
Sidenote: we can define Lens using Traversing/Mapping -like class too,<br>
hopefully it gives you another viewpoint too.<br>
<br>
\begin{code}<br>
class Functor t => Singular t where<br>
    single :: Functor f => (a -> f b) -> t a -> f (t b)<br>
<br>
fmapSingle :: Singular t => (a -> b) -> t a -> t b<br>
fmapSingle ab ta = runIdentity (single (Identity . ab) ta)<br>
<br>
instance Singular Identity where<br>
    single f (Identity a) = Identity <$> f a<br>
<br>
instance Singular ((,) a) where<br>
    single f (a, b) = (a,) <$> f b<br>
<br>
class Profunctor p => Strong' p where<br>
    single' :: Singular f => p a b -> p (f a) (f b)<br>
<br>
instance Strong' (->) where<br>
    single' ab = fmap ab<br>
<br>
instance Functor f => Strong' (Star f) where<br>
    single' (Star afb) = Star (single afb)<br>
<br>
-- lens using Strong' & Single: 1. 2. 3.<br>
lens' :: Strong' p => (s -> a) -> (s -> b -> t) -> p a b -> p s t<br>
lens' sa sbt = dimap (\s -> (s, sa s)) (\(s,b) -> sbt s b) . single'<br>
\end{code}<br>
<br>
Cheers, Oleg<br>
<span class=""><br>
<br>
On 02.05.2018 20:09, Paolino wrote:<br>
> I'm not using any lens libraries, I'm writing both encodings from<br>
> scratch based on standard libs, as a learning path.<br>
> I see anyway that Traversing class is declaring exactly the Twan -><br>
> Profunctor promotion (given the Applicative on f)  which looks a lot <br>
> like a white flag on the "write traversal as profunctor" research.<br>
> Actually I was induced from purescript to think that the profunctorial<br>
> encoding was completely alternative to the twan, but I had no evidence<br>
> of the fact, so I should better dig into purescript library.<br>
><br>
> .p<br>
><br>
> 2018-05-02 18:43 GMT+02:00 Tom Ellis<br>
> <<a href="mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk">tom-lists-haskell-cafe-2013@<wbr>jaguarpaw.co.uk</a><br>
</span>> <mailto:<a href="mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk">tom-lists-haskell-<wbr>cafe-2013@jaguarpaw.co.uk</a>>>:<br>
<span class="">><br>
>     I'm not sure what you mean.  If you want to write a profunctor<br>
>     traversal<br>
>     then `wander lq5Twan` seems fine.  If you want to understand why<br>
>     it's hard<br>
>     to directly write profunctor traversals then I'm afraid I'm as<br>
>     puzzled as<br>
>     you.<br>
><br>
>     On Wed, May 02, 2018 at 06:29:09PM +0200, Paolino wrote:<br>
>     > Well, I can accept it as an evidence of why  not to use the<br>
>     profunctor<br>
>     > encoding for multi target lens (if that's the name).<br>
>     > But I guess we are already in philosophy (so I'm more puzzled<br>
>     than before)<br>
>     > and I hope you can elaborate more.<br>
>     ><br>
>     > .p<br>
>     ><br>
>     ><br>
>     > 2018-05-02 18:10 GMT+02:00 Tom Ellis <<br>
>     > <a href="mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk">tom-lists-haskell-cafe-2013@<wbr>jaguarpaw.co.uk</a><br>
</span>>     <mailto:<a href="mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk">tom-lists-haskell-<wbr>cafe-2013@jaguarpaw.co.uk</a>>>:<br>
<div class="HOEnZb"><div class="h5">>     ><br>
>     > > On Wed, May 02, 2018 at 03:07:05PM +0200, Paolino wrote:<br>
>     > > > I'm trying to write a lens for a datatype which seems easy<br>
>     in the Twan<br>
>     > > van<br>
>     > > > Laarhoven encoding but I cannot find it as easy in the<br>
>     profunctorial one<br>
>     > > ><br>
>     > > > data Q5 a b = Q51 a (Identity b) | Q52 [b]<br>
>     > > ><br>
>     > > > lq5Twan :: Applicative f => (b -> f b') -> Q5 a b -> f (Q5 a b')<br>
>     > > > lq5Twan f (Q51 a bs) = Q51 a <$> traverse f bs<br>
>     > > > lq5Twan f (Q52 bs) = Q52 <$> traverse f bs<br>
>     > > [...]<br>
>     > > > lq5Profunctor :: forall p a b b' . Traversing p => p b b' -><br>
>     p (Q5 a<br>
>     > > > b) (Q5 a b')<br>
>     > > [...]<br>
>     > > > Which simpler ways to write the lq5Profunctor we have ?<br>
>     > ><br>
>     > > Is `wander lq5Twan` good enough, or is your question more<br>
>     philosophical?<br>
><br>
>     ______________________________<wbr>_________________<br>
>     Haskell-Cafe mailing list<br>
>     To (un)subscribe, modify options or view archives go to:<br>
>     <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
>     <<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a>><br>
>     Only members subscribed via the mailman list are allowed to post.<br>
><br>
><br>
><br>
><br>
> ______________________________<wbr>_________________<br>
> Haskell-Cafe mailing list<br>
> To (un)subscribe, modify options or view archives go to:<br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
> Only members subscribed via the mailman list are allowed to post.<br>
<br>
<br>
</div></div><br>______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
Only members subscribed via the mailman list are allowed to post.<br></blockquote></div><br></div>