<div dir="ltr">Roman, this is interesting. Is this arrow generalization in some library already? And does it have a name?<div><br></div><div>Best regards,</div><div>Petr Pudlak</div></div><div class="gmail_extra"><br><br><div class="gmail_quote">

2013/1/27 Roman Cheplyaka <span dir="ltr">&lt;<a href="mailto:roma@ro-che.info" target="_blank">roma@ro-che.info</a>&gt;</span><br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

* Petr P &lt;<a href="mailto:petr.mvd@gmail.com">petr.mvd@gmail.com</a>&gt; [2013-01-26 23:03:51+0100]<br>
<div class="im">&gt;   Dear Haskellers,<br>
&gt;<br>
&gt; I read some stuff about attribute grammars recently [1] and how UUAGC [2]<br>
&gt; can be used for code generation. I felt like this should be possible inside<br>
&gt; Haskell too so I did some experiments and I realized that indeed<br>
&gt; catamorphisms can be represented in such a way that they can be combined<br>
&gt; together and all run in a single pass over a data structure. In fact, they<br>
&gt; form an applicative functor.<br>
&gt;<br>
</div>&gt; ...<br>
<div class="im">&gt;<br>
&gt; My experiments together with the example are available at <a href="https://github" target="_blank">https://github</a><br>
&gt; .com/ppetr/recursion-attributes<br>
<br>
</div>Very nice! This can be generalized to arbitrary arrows:<br>
<br>
  {-# LANGUAGE ExistentialQuantification #-}<br>
<br>
  import Prelude hiding (id)<br>
  import Control.Arrow<br>
  import Control.Applicative<br>
  import Control.Category<br>
<br>
  data F from to b c = forall d . F (from b d) (to d c)<br>
<br>
  instance (Arrow from, Arrow to) =&gt; Functor (F from to b) where<br>
    fmap f x = pure f &lt;*&gt; x<br>
<br>
  instance (Arrow from, Arrow to) =&gt; Applicative (F from to b) where<br>
    pure x = F (arr $ const x) id<br>
    F from1 to1 &lt;*&gt; F from2 to2 =<br>
      F (from1 &amp;&amp;&amp; from2) (to1 *** to2 &gt;&gt;&gt; arr (uncurry id))<br>
<br>
Now your construction is a special case where &#39;from&#39; is the category of<br>
f-algebras and &#39;to&#39; is the usual (-&gt;) category.<br>
<br>
I wonder what&#39;s a categorical interpretation of F itself.<br>
<span class="HOEnZb"><font color="#888888"><br>
Roman<br>
</font></span></blockquote></div><br></div>