<div dir="ltr">For the open union used in extensible effects, apart from using the<div>Typeable mechanism, is there a more protected way to implement</div><div>the open sum type?</div><div><br></div><div>I managed to modified the Member class given in the paper, but</div>
<div>ended up having to use the vague OverlappingInstance. That&#39;s not</div><div>quite what I hope. I&#39;m not even sure whether the instance `Member t (t :&gt; r)`</div><div>is more specific than `Member t (t&#39; :&gt; r)`. </div>
<div><br></div><div>--</div><div>suhorng</div><div><br></div><div><div>{-# LANGUAGE KindSignatures, TypeOperators, GADTs, FlexibleInstances, </div><div>             FlexibleContexts, MultiParamTypeClasses, OverlappingInstances #-}</div>
<div>-- FlexibleContexts is for Show instance of Union</div><div><br></div><div>import Data.Functor</div><div>import Control.Applicative -- for several functor instances</div><div><br></div><div>-- open union</div><div>infixr 2 :&gt;</div>
<div>data (a :: * -&gt; *) :&gt; b</div><div><br></div><div>data Union r v where</div><div>  Elsewhere :: Functor t&#39; =&gt; Union r v -&gt; Union (t&#39; :&gt; r) v</div><div>  Here :: Functor t =&gt; t v -&gt; Union (t :&gt; r) v</div>
<div><br></div><div>class Member t r where</div><div>  inj :: Functor t =&gt; t v -&gt; Union r v</div><div>  prj :: Functor t =&gt; Union r v -&gt; Maybe (t v)</div><div><br></div><div>instance Member t (t :&gt; r) where</div>
<div>  inj tv = Here tv</div><div>  prj (Here tv)     = Just tv</div><div>  prj (Elsewhere _) = Nothing</div><div><br></div><div>-- Note: overlapped by letting t&#39; = t</div><div>instance (Functor t&#39;, Member t r) =&gt; Member t (t&#39; :&gt; r) where</div>
<div>  inj tv = Elsewhere (inj tv)</div><div>  prj (Here _)      = Nothing</div><div>  prj (Elsewhere u) = prj u</div><div><br></div><div>decomp :: Functor t =&gt; Union (t :&gt; r) v -&gt; Either (Union r v) (t v)</div><div>
decomp (Here tv)     = Right tv</div><div>decomp (Elsewhere u) = Left u</div><div><br></div><div>-- Auxiliary definitions for tests</div><div>data Void</div><div>newtype Func a = Func a</div><div><br></div><div>instance Show (Union Void a) where</div>
<div>  show _ = undefined</div><div><br></div><div>instance (Show (t v), Show (Union r v)) =&gt; Show (Union (t :&gt; r) v) where</div><div>  show (Here tv)     = &quot;Here &quot; ++ show tv</div><div>  show (Elsewhere u) = &quot;Elsewhere &quot; ++ show u</div>
<div><br></div><div>instance Functor Func where</div><div>  fmap f (Func x) = Func (f x)</div><div><br></div><div>instance Show a =&gt; Show (Func a) where</div><div>  show (Func a) = show a</div><div><br></div><div>type Stk = Maybe :&gt; Either Char :&gt; Func :&gt; Void</div>
<div>type Stk&#39; = Either Char :&gt; Func :&gt; Void -- used in `deTrue`, `deFalse`</div><div><br></div><div>unTrue :: Union Stk Bool</div><div>unTrue = inj (Func True)</div><div><br></div><div>unFalse :: Union Stk Bool</div>
<div>unFalse = inj (Just False)</div><div><br></div><div>-- `Func` is repeated</div><div>un5 :: Union (Maybe :&gt; Func :&gt; Either Char :&gt; Func :&gt; Void) Int</div><div>un5 = inj (Func 5)</div><div><br></div><div>maybe2 :: Maybe (Func Int)</div>
<div>maybe2 = prj un5</div><div><br></div><div>maybeTrue :: Maybe (Func Bool)</div><div>maybeTrue = prj unTrue</div><div><br></div><div>maybeFalse1 :: Maybe (Func Bool)</div><div>maybeFalse1 = prj unFalse</div><div><br></div>
<div>maybeFalse2 :: Maybe (Maybe Bool)</div><div>maybeFalse2 = prj unFalse</div><div><br></div><div>deTrue :: Either (Union Stk&#39; Bool) (Maybe Bool)</div><div>deTrue = decomp unTrue</div><div><br></div><div>deFalse :: Either (Union Stk&#39; Bool) (Maybe Bool)</div>
<div>deFalse = decomp unFalse</div></div><div><br></div><div class="gmail_extra"><br><br><div class="gmail_quote">2013/8/22 Alberto G. Corona <span dir="ltr">&lt;<a href="mailto:agocorona@gmail.com" target="_blank">agocorona@gmail.com</a>&gt;</span><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div>The paper is very interesting:</div><div><br></div><a href="http://www.cs.indiana.edu/~sabry/papers/exteff.pdf" target="_blank">http://www.cs.indiana.edu/~sabry/papers/exteff.pdf</a><br>
<div><br></div><div>It seems that the approach is mature enough and it is better in every way than monad transformers, while at the same time the syntax may become almost identical to MTL for many uses.</div>

<div><br></div><div>I only expect to see the library in Hackage with all the blessings, and with all the instances of the MTL classes in order to make the transition form monad transformers  to ExtEff as transparent as possible</div>


</div><div class="gmail_extra"><br><br><div class="gmail_quote">2013/8/22  <span dir="ltr">&lt;<a href="mailto:oleg@okmij.org" target="_blank">oleg@okmij.org</a>&gt;</span><div><div class="h5"><br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">


<br>
Perhaps effect libraries (there are several to choose from) could be a<br>
better answer to Fork effects than monad transformers. One lesson from<br>
the recent research in effects is that we should start thinking what<br>
effect we want to achieve rather than which monad transformer to<br>
use. Using ReaderT or StateT or something else is an implementation<br>
detail. Once we know what effect to achieve we can write a handler, or<br>
interpreter, to implement the desired operation on the World, obeying<br>
the desired equations. And we are done.<br>
<br>
For example, with ExtEff library with which I&#39;m more familiar, the<br>
Fork effect would take as an argument a computation that cannot throw<br>
any requests. That means that the parent has to provide interpreters<br>
for all child effects. It becomes trivially to implement:<br>
<div><br>
&gt; Another example would be a child that should not be able to throw errors as<br>
&gt; opposed to the parent thread.<br>
</div>It is possible to specify which errors will be allowed for the child<br>
thread (the ones that the parent will be willing to reflect and<br>
interpret). The rest of errors will be statically prohibited then.<br>
<div><br>
&gt; instance (Protocol p) =&gt; Forkable (WebSockets p) (ReaderT (Sink p) IO) where<br>
&gt;     fork (ReaderT f) = liftIO . forkIO . f =&lt;&lt; getSink<br>
<br>
</div>This is a good illustration of too much implementation detail. Why do we<br>
need to know of (Sink p) as a Reader layer? Would it be clearer to<br>
define an Effect of sending to the socket? Computation&#39;s type will<br>
make it patent the computation is sending to the socket.<br>
The parent thread, before forking, has to provide a handler for that<br>
effect (and the handler will probably need a socket).<br>
<br>
Defining a new class for each effect is possible but not needed at<br>
all. With monad transformers, a class per effect is meant to hide the<br>
ordering of transformer layers in a monad transformer stack. Effect<br>
libraries abstract over the implementation details out of the<br>
box. Crutches -- extra classes -- are unnecessary. We can start by<br>
writing handlers on a case-by-case basis. Generalization, if any,<br>
we&#39;ll be easier to see. From my experience, generalizing from concrete<br>
cases is easier than trying to write a (too) general code at the<br>
outset. Way too often, as I read and saw, code that is meant to be<br>
reusable ends up hardly usable.<br>
<br>
<br>
<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div></div></div><span class="HOEnZb"><font color="#888888"><br><br clear="all"><div><br></div>-- <br>Alberto.
</font></span></div>
<br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br></div></div>