I'm having difficulty using the zoom
function given by Control.Lens
. With my custom monad transformer HearthMonad
, I cannot figure out how to satisfy GHC's "ambiguous type" complaint.
The code in question is in drawCard
.
How can I solve this? Do I have to create my own custom zoom operator to handle the Monad m
in Hearth m
?
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module EngineZoom where
--------------------------------------------------------------------------------
import Control.Applicative
import Control.Lens
import Control.Monad.State
import Data.List
import Data.Maybe
--------------------------------------------------------------------------------
type PlayerHandle = String
data Card = Card String
deriving (Show, Eq, Ord)
data Player = Player {
_playerHandle :: PlayerHandle,
_hand :: [Card]
} deriving (Show, Eq, Ord)
makeLenses ''Player
data GameState = GameState {
_gamePlayers :: [Player]
} deriving (Show, Eq, Ord)
makeLenses ''GameState
newtype Hearth m a = Hearth {
unHearth :: StateT GameState m a
} deriving (Functor, Applicative, Monad, MonadState GameState, MonadIO, MonadTrans)
type HearthMonad = MonadIO
runHearth :: (HearthMonad m) => m ()
runHearth = evalStateT (unHearth runGame) mkGameState
mkGameState :: GameState
mkGameState = GameState { _gamePlayers = map mkPlayer ["Bob", "Joe"] }
mkPlayer :: PlayerHandle -> Player
mkPlayer handle = Player { _playerHandle = handle, _hand = [] }
runGame :: (HearthMonad m) => Hearth m ()
runGame = do
card <- drawCard "Bob"
liftIO $ print card
getPlayer :: PlayerHandle -> Lens' GameState Player
getPlayer handle f st = fmap put' get'
where
players = st^.gamePlayers
put' player = let
g p = case p^.playerHandle == handle of
True -> player
False -> p
in set gamePlayers (map g players) st
get' = f $ fromJust $ find (\p -> p^.playerHandle == handle) players
drawCard :: (HearthMonad m) => PlayerHandle -> Hearth m Card
drawCard handle = do
let card = Card "Yeti"
--getPlayer handle.hand <>= [card]
zoom (getPlayer handle) $ hand <>= [card]
return card
EngineZoom.hs:86:5:
Could not deduce (Control.Lens.Internal.Zoom.Zoomed (Hearth m)
~ Control.Lens.Internal.Zoom.Zoomed m0)
from the context (HearthMonad m)
bound by the type signature for
drawCard :: HearthMonad m => PlayerHandle -> Hearth m Card
at EngineZoom.hs:82:13-60
NB: `Control.Lens.Internal.Zoom.Zoomed' is a type function, and may not be injective
The type variable `m0' is ambiguous
Relevant bindings include
drawCard :: PlayerHandle -> Hearth m Card
(bound at EngineZoom.hs:83:1)
In the expression: zoom (getPlayer handle)
In a stmt of a 'do' block:
zoom (getPlayer handle) $ hand <>= [card]
In the expression:
do { let card = Card "Yeti";
zoom (getPlayer handle) $ hand <>= [card];
return card }
The problem is your newtype can only hold one state, namely GameState
. Zoom essentially changes the state to the target of your lens, but since Hearth
cannot have Player
as a state, zoom (getPlayer handle)
can't be used with Hearth
.
The simple solution is to replace the newtype with type Hearth = StateT GameState
and zooming works. If you want a newtype you'll need to have the state parameterised, here's an example:
import Control.Lens.Internal.Zoom
newtype HearthS s m a = Hearth {
unHearth :: StateT s m a
} deriving (Functor, Applicative, Monad, MonadState s, MonadIO, MonadTrans)
type Hearth = HearthS GameState
type instance Zoomed (HearthS s m) = Focusing m
instance Monad z => Zoom (HearthS s z) (HearthS t z) s t where
zoom l (Hearth m) = Hearth (zoom l m)