extensible effects + classy lenses

Hi all, 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. For example, {-# language FlexibleContexts #-} import Control.Monad.Freer import Control.Monad.Freer.State class HasInt s where getInt :: s -> Int foo :: (Member (State s) effs, HasInt s) => Eff effs Int foo = get However, this fails to typecheck: Overlapping instances for Member (State s0) effs Matching givens (or their superclasses): (Member (State s) effs) bound by the type signature for foo :: (Member (State s) effs, HasInt s) => Eff effs Int at example.hs:9:8-56 Matching instances: instance Data.Open.Union.Member' t r (Data.Open.Union.FindElem t r) => Member t r -- Defined in ‘Data.Open.Union’ (The choice depends on the instantiation of ‘effs, s0’) In the ambiguity check for the type signature for ‘foo’: foo :: forall (effs :: [* -> *]) s. (Member (State s) effs, HasInt s) => Eff effs Int To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘foo’: foo :: (Member (State s) effs, HasInt s) => Eff effs Int Is this a weakness of extensible effects, or is there another way to express this function? Thanks, Mitchell

Sorry, in "foo", the body should be "fmap getInt get". Still, same type error. On Tuesday, March 8, 2016 at 3:59:23 PM UTC-8, Mitchell Rosen wrote:
Hi all,
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.
For example,
{-# language FlexibleContexts #-}
import Control.Monad.Freer import Control.Monad.Freer.State
class HasInt s where getInt :: s -> Int
foo :: (Member (State s) effs, HasInt s) => Eff effs Int foo = get
However, this fails to typecheck:
Overlapping instances for Member (State s0) effs Matching givens (or their superclasses): (Member (State s) effs) bound by the type signature for foo :: (Member (State s) effs, HasInt s) => Eff effs Int at example.hs:9:8-56 Matching instances: instance Data.Open.Union.Member' t r (Data.Open.Union.FindElem t r) => Member t r -- Defined in ‘Data.Open.Union’ (The choice depends on the instantiation of ‘effs, s0’) In the ambiguity check for the type signature for ‘foo’: foo :: forall (effs :: [* -> *]) s. (Member (State s) effs, HasInt s) => Eff effs Int To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘foo’: foo :: (Member (State s) effs, HasInt s) => Eff effs Int
Is this a weakness of extensible effects, or is there another way to express this function?
Thanks, Mitchell

Mitchell,
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: <
http://lpaste.net/154303>.
Another way to resolve the ambiguity would be to say that foo1 accesses
first State in the list:
type family OuterState xs where
OuterState (State s ': rest) = s
OuterState (x ': xs) = OuterState xs
-- using ScopedTypeVariables
foo1 :: forall r s. (OuterState r ~ s, Member (State s) r, HasInt s) => Eff
r Int
foo1 = getInt <$> (get :: Eff r s)
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.
get2 :: Eff '[State Int, State Char] (Int,Char)
get2 = do i <- get; c <- get; return (i,c) -- works just fine
Regards,
Adam
On Tue, Mar 8, 2016 at 7:02 PM, Mitchell Rosen
Sorry, in "foo", the body should be "fmap getInt get". Still, same type error.
On Tuesday, March 8, 2016 at 3:59:23 PM UTC-8, Mitchell Rosen wrote:
Hi all,
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.
For example,
{-# language FlexibleContexts #-}
import Control.Monad.Freer import Control.Monad.Freer.State
class HasInt s where getInt :: s -> Int
foo :: (Member (State s) effs, HasInt s) => Eff effs Int foo = get
However, this fails to typecheck:
Overlapping instances for Member (State s0) effs Matching givens (or their superclasses): (Member (State s) effs) bound by the type signature for foo :: (Member (State s) effs, HasInt s) => Eff effs Int at example.hs:9:8-56 Matching instances: instance Data.Open.Union.Member' t r (Data.Open.Union.FindElem t r) => Member t r -- Defined in ‘Data.Open.Union’ (The choice depends on the instantiation of ‘effs, s0’) In the ambiguity check for the type signature for ‘foo’: foo :: forall (effs :: [* -> *]) s. (Member (State s) effs, HasInt s) => Eff effs Int To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘foo’: foo :: (Member (State s) effs, HasInt s) => Eff effs Int
Is this a weakness of extensible effects, or is there another way to express this function?
Thanks, Mitchell
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

In show . read ambiguity, is it a weakness of show or read? :) This isn't a weakness of extensible effects per se; rather, this a consequence of extensible effects and classy lenses being too polymorphic, so that they can't be combined without a further disambiguation. In monad-classes, there is a 'Zoom' effect which, given a lens from 'big' into 'small', transforms State requests over 'small' into State effects over 'big'. If you work with only a handful of lenses but use them often, it may be worth considering. I also remember someone developing an EE library based on the ideas from monad-classes and mtlx, where you disambiguate every single effect with singleton types. But in general, for best experience, make one of those two things less polymorphic: mtl + classy lenses (Kmett's preferred way) or EE + monomorphic lenses (my preferred way). Roman On 03/09/2016 01:59 AM, Mitchell Rosen wrote:
Hi all,
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.
For example,
{-# language FlexibleContexts #-}
import Control.Monad.Freer import Control.Monad.Freer.State
class HasInt s where getInt :: s -> Int
foo :: (Member (State s) effs, HasInt s) => Eff effs Int foo = get
However, this fails to typecheck:
Overlapping instances for Member (State s0) effs Matching givens (or their superclasses): (Member (State s) effs) bound by the type signature for foo :: (Member (State s) effs, HasInt s) => Eff effs Int at example.hs:9:8-56 Matching instances: instance Data.Open.Union.Member' t r (Data.Open.Union.FindElem t r) => Member t r -- Defined in ‘Data.Open.Union’ (The choice depends on the instantiation of ‘effs, s0’) In the ambiguity check for the type signature for ‘foo’: foo :: forall (effs :: [* -> *]) s. (Member (State s) effs, HasInt s) => Eff effs Int To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘foo’: foo :: (Member (State s) effs, HasInt s) => Eff effs Int
Is this a weakness of extensible effects, or is there another way to express this function?
Thanks, Mitchell
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (3)
-
adam vogt
-
Mitchell Rosen
-
Roman Cheplyaka