I'm attempting to allow embedding a state monad in my Free monad; here's my simple attempt:
{-# language FlexibleInstances, MultiParamTypeClasses #-}
module Main where
import Control.Monad.Free
import Control.Monad.State
import Data.Bifunctor
data Toy state next =
Output String next
| LiftState (state -> (next, state))
| Done
instance Functor (Toy s) where
fmap f (Output str next) = Output str $ f next
fmap f (LiftState stateF) = LiftState (first f . stateF)
fmap f Done = Done
instance MonadState s (Free (Toy s)) where
state = overState
overState :: (s -> (a, s)) -> Free (Toy s) a
overState = liftF . LiftState
output :: Show a => a -> Free (Toy s) ()
output x = liftF $ Output (show x) ()
done :: Free (Toy s) r
done = liftF Done
program :: Free (Toy Int) ()
program = do
start <- get
output start
modify ((+10) :: (Int -> Int))
end <- get
output end
done
interpret :: (Show r) => Free (Toy s) r -> s -> IO ()
interpret (Free (LiftState stateF)) s = let (next, newS) = stateF s
in interpret next newS
interpret (Free (Output str next)) s = print str >> interpret next s
interpret (Free Done) s = return ()
interpret (Pure x) s = print x
main :: IO ()
main = interpret program (5 :: Int)
I get the error:
• Overlapping instances for MonadState Int (Free (Toy Int))
arising from a use of ‘get’
Matching instances:
instance [safe] (Functor m, MonadState s m) =>
MonadState s (Free m)
-- Defined in ‘Control.Monad.Free’
instance MonadState s (Free (Toy s))
-- Defined at app/Main.hs:18:10
• In a stmt of a 'do' block: start <- get
In the expression:
do { start <- get;
output start;
modify ((+ 10) :: Int -> Int);
end <- get;
.... }
In an equation for ‘program’:
program
= do { start <- get;
output start;
modify ((+ 10) :: Int -> Int);
.... }
As far as I can gather; it's trying to apply this instance:
(Functor m, MonadState s m) => MonadState s (Free m)
from the
free package here; however in this case it would have to match Free (Toy s)
and there's no MonadState s (Toy s)
as required so I don't understand why it thinks that it applies.
If I remove my instance definition I get:
• No instance for (MonadState Int (Toy Int))
arising from a use of ‘modify’
Which supports my thought that the other instance doesn't actually apply; How can I get this to compile using my specified instance? And can you explain why this is occurring? Is it due to FlexibleInstances
being used?
Thanks!
The instance context (the (Functor m, MonadState s m)
bit) is simply ignored when choosing instances. This is to prevent the compiler from having to do a potentially costly backtracking search to choose an instance. So if two instances apply and one is ruled out only because of an instance context, as in your case, it's an overlap.
This is an unfortunate part of the design of mtl, and one I think each Haskell programmer has bumped up against at some point or other. There's not a lot of choices for fixes; generally you add a newtype and give your instance, as in
newtype FreeToy s a = FreeToy (Free (Toy s) a)
instance MonadState s (FreeToy s) where -- ...