5

I would like to use lens and extensible-effects to work a simple example.
Error messages say that type is ambiguous because of typeclass with parameter HasObj x and GHC cannot understand where pos come from, I guess.
makeClassy is really useful to define abstract data types with common data functions so it is needed in my real project.

My questions is: how can I make it work?
Or, is there a way to define lenses from data types and use them in Eff.State?

{-# LANGUAGE TemplateHaskell, TypeOperators, DeriveDataTypeable #-}
import Control.Eff
import Control.Eff.Lift
import Control.Eff.State.Strict
import Control.Lens hiding (use, (%=), (.=))
import Control.Monad
import Data.Typeable

-- define data types
data Obj = Obj { _pos :: Int } deriving (Show)
data Person = Person {
  _objPerson :: Obj,
  _greeting :: String
  } deriving (Show, Typeable)

-- make typeclasses and lenses
makeClassy ''Obj
makeLenses ''Person

instance HasObj Person where
  obj = objPerson

-- define lens operators in Eff
use k = fmap (^.k) get
l %= f = modify (l %~ f)
l .= f = modify (l .~ f)

-- update :: StateT Person IO ()
update :: Eff (State Person :> Lift IO :> ()) ()
update = do
  lift . putStrLn =<< use greeting
  pos %= (+10)
  p <- use pos
  when (p >= 100) $ do
    greeting .= "at 100, yeah!"

main = do
  let p = Person (Obj 0) "hi!"
  print $ p

  p' <- runLift $ execState p update
  print $ p'

Error Messages:

LensEE.hs:28:3:
    No instance for (HasObj s0) arising from a use of ‘pos’
    The type variable ‘s0’ is ambiguous
    Note: there are several potential instances:
      instance HasObj Obj -- Defined at LensEE.hs:15:1
      instance HasObj Person -- Defined at LensEE.hs:18:10
    In the first argument of ‘(%=)’, namely ‘pos’
    In a stmt of a 'do' block: pos %= (+ 10)
    In the expression:
      do { lift . putStrLn =<< use greeting;
           pos %= (+ 10);
           p <- use pos;
           when (p >= 100) $ do { greeting .= "at 100, yeah!" } }

LensEE.hs:28:7:
    Overlapping instances for Member
                                (State s0) (State Person :> (Lift IO :> ()))
      arising from a use of ‘%=’
    Matching instances:
      instance [overlap ok] Member t r => Member t (t' :> r)
        -- Defined in ‘Data.OpenUnion1’
      instance [overlap ok] Member t (t :> r)
        -- Defined in ‘Data.OpenUnion1’
    (The choice depends on the instantiation of ‘s0’
     To pick the first instance above, use IncoherentInstances
     when compiling the other instance declarations)
    In a stmt of a 'do' block: pos %= (+ 10)
    In the expression:
      do { lift . putStrLn =<< use greeting;
           pos %= (+ 10);
           p <- use pos;
           when (p >= 100) $ do { greeting .= "at 100, yeah!" } }
    In an equation for ‘update’:
        update
          = do { lift . putStrLn =<< use greeting;
                 pos %= (+ 10);
                 p <- use pos;
                 .... }

LensEE.hs:29:8:
    Overlapping instances for Member
                                (State a0) (State Person :> (Lift IO :> ()))
      arising from a use of ‘use’
    Matching instances:
      instance [overlap ok] Member t r => Member t (t' :> r)
        -- Defined in ‘Data.OpenUnion1’
      instance [overlap ok] Member t (t :> r)
        -- Defined in ‘Data.OpenUnion1’
    (The choice depends on the instantiation of ‘a0’
     To pick the first instance above, use IncoherentInstances
     when compiling the other instance declarations)
    In a stmt of a 'do' block: p <- use pos
    In the expression:
      do { lift . putStrLn =<< use greeting;
           pos %= (+ 10);
           p <- use pos;
           when (p >= 100) $ do { greeting .= "at 100, yeah!" } }
    In an equation for ‘update’:
        update
          = do { lift . putStrLn =<< use greeting;
                 pos %= (+ 10);
                 p <- use pos;
                 .... }

LensEE.hs:29:12:
    No instance for (HasObj a0) arising from a use of ‘pos’
    The type variable ‘a0’ is ambiguous
    Note: there are several potential instances:
      instance HasObj Obj -- Defined at LensEE.hs:15:1
      instance HasObj Person -- Defined at LensEE.hs:18:10
    In the first argument of ‘use’, namely ‘pos’
    In a stmt of a 'do' block: p <- use pos
    In the expression:
      do { lift . putStrLn =<< use greeting;
           pos %= (+ 10);
           p <- use pos;
           when (p >= 100) $ do { greeting .= "at 100, yeah!" } }
IruT
  • 323
  • 1
  • 8
  • 3
    The type of `pos %= (+10)` is `(HasObj s, Member (State s) r, Typeable s) => Eff r ()`. Notice that the type variable `s` is not mentioned in the type, only in the context. This means that `s` will always be ambiguous. The minimal example of this is `let x = modify (+1); x :: Eff (State Int :> ()) ()`. I believe that this is a deficiency in extensible-effects. One solution is to write `(pos :: Lens' Person Int) %= (+10)` but this is probably a bad solution since it requires a lot of typing. – user2407038 Aug 18 '14 at 02:14

0 Answers0