[Haskell-cafe] extensible effects + classy lenses
Mitchell Rosen
mitchellwrosen at gmail.com
Tue Mar 8 23:59:22 UTC 2016
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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160308/4342cefb/attachment.html>
More information about the Haskell-Cafe
mailing list