<div dir="ltr"><div>Mitchell,<br><br></div><div>You could pass in another argument that specifies which 's', which might not be as much of a pain if it was an implicit parameter like here: <<a href="http://lpaste.net/154303">http://lpaste.net/154303</a>>.<br><br><br></div><div>Another way to resolve the ambiguity would be to say that foo1 accesses first State in the list:<br></div><div><br>type family OuterState xs where<br>  OuterState (State s ': rest) = s<br>  OuterState (x ': xs) = OuterState xs<br><br></div><div>-- using ScopedTypeVariables<br></div><div>foo1 :: forall r s. (OuterState r ~ s, Member (State s) r, HasInt s) => Eff r Int<br>foo1 = getInt <$> (get :: Eff r s)<br><br><br></div><div></div><div>But I think you probably should just pin down the state type you're accessing because you can have multiple `State s`and they don't get in each other’s way at all if they have different types.<br></div><div><br></div><div>get2 :: Eff '[State Int, State Char] (Int,Char)<br></div><div>get2 = do i <- get; c <- get; return (i,c) -- works just fine<br><br></div><div>Regards,<br></div><div>Adam<br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Mar 8, 2016 at 7:02 PM, Mitchell Rosen <span dir="ltr"><<a href="mailto:mitchellwrosen@gmail.com" target="_blank">mitchellwrosen@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">Sorry, in "foo", the body should be "fmap getInt get". Still, same type error.<div><div class="h5"><br><br>On Tuesday, March 8, 2016 at 3:59:23 PM UTC-8, Mitchell Rosen wrote:<blockquote class="gmail_quote" style="margin:0;margin-left:0.8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">Hi all,<br><br>I'm trying to combine an extensible effects style state with classy lenses. That is, instead of pinning the type of my state down, I'd like to only require the pieces I need.<br><br>For example,<br><br><font face="courier new, monospace">{-# language FlexibleContexts #-}</font><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">import Control.Monad.Freer</font></div><div><font face="courier new, monospace">import Control.Monad.Freer.State</font><br><br><font face="courier new, monospace">class HasInt s where</font><br><font face="courier new, monospace">  getInt :: s -> Int</font><br><br><font face="courier new, monospace">foo :: (Member (State s) effs, HasInt s) => Eff effs Int</font><br><font face="courier new, monospace">foo = get</font><br><br><font face="arial, sans-serif">However, this fails to typecheck:</font></div><div><font face="courier new, monospace"><br></font><div><font face="courier new, monospace">    Overlapping instances for Member (State s0) effs</font></div><div><font face="courier new, monospace">    Matching givens (or their superclasses):</font></div><div><font face="courier new, monospace">      (Member (State s) effs)</font></div><div><font face="courier new, monospace">        bound by the type signature for</font></div><div><font face="courier new, monospace">                   foo :: (Member (State s) effs, HasInt s) => Eff effs Int</font></div><div><font face="courier new, monospace">        at example.hs:9:8-56</font></div><div><font face="courier new, monospace">    Matching instances:</font></div><div><font face="courier new, monospace">      instance Data.Open.Union.Member'</font></div><div><font face="courier new, monospace">                 t r (Data.Open.Union.FindElem t r) =></font></div><div><font face="courier new, monospace">               Member t r</font></div><div><font face="courier new, monospace">        -- Defined in ‘Data.Open.Union’</font></div><div><font face="courier new, monospace">    (The choice depends on the instantiation of ‘effs, s0’)</font></div><div><font face="courier new, monospace">    In the ambiguity check for the type signature for ‘foo’:</font></div><div><font face="courier new, monospace">      foo :: forall (effs :: [* -> *]) s.</font></div><div><font face="courier new, monospace">             (Member (State s) effs, HasInt s) =></font></div><div><font face="courier new, monospace">             Eff effs Int</font></div><div><font face="courier new, monospace">    To defer the ambiguity check to use sites, enable AllowAmbiguousTypes</font></div><div><font face="courier new, monospace">    In the type signature for ‘foo’:</font></div><div><font face="courier new, monospace">      foo :: (Member (State s) effs, HasInt s) => Eff effs Int</font></div><div style="font-family:arial,sans-serif"><br></div>Is this a weakness of extensible effects, or is there another way to express this function?<br><br>Thanks,</div><div>Mitchell</div></div></blockquote></div></div></div><br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br></div>