问题
I have monad transformers corresponding to independent features of my app.
In Weather module:
class Monad m => WeatherT m where
byCity :: String -> m WeatherData
newtype MockWeather m a = MockWeather {
...
} deriving (Functor, Applicative, Monad, MonadTrans)
instance Monad m => WeatherT (MockWeather m) where
...
In Counter module:
class Monad m => CounterT m where
increment :: m Int
current :: m Int
newtype MockCounter m a = MockCounter {
...
} deriving (Functor, Applicative, Monad, MonadTrans)
instance Monad m => CounterT (MockCounter m) where
...
They both may have multiple instances with different implementations, for example they both have a mock instance that I use here in my main: MockCounter
and MockWeather
.
In the Main module I define MyApp
monad as:
newtype MyAppM m a = MyAppM { unMyAppM :: MockCounter (MockWeather m) a }
deriving (Functor, Applicative, Monad, CounterT, WeatherT)
This definition requires me to make (MockCounter (MockWeather m)
an instance of WeatherT
:
instance Monad m => WeatherT (MockCounter (MockWeather m))
I define this instance in the main module, because I don't want Weather and Counter modules to depend on each others.
But defining this instance in the main module makes it an Orphan instance.
Questions:
- Am I on the right track here with
CounterT
,WeatherT
andMyAppM
? I want to build my app by composing decoupled and mockable functionalities. - How can I avoid orphan instances?
Full code:
Main module
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where
import Counter
import Weather
newtype MyAppM m a = MyAppM { unMyAppM :: MockCounter (MockWeather m) a }
deriving (Functor, Applicative, Monad, CounterT, WeatherT)
instance Monad m => WeatherT (MockCounter (MockWeather m))
runMyAppM :: Int -> MyAppM m a -> m (a, Int)
runMyAppM i = runMockWeather . (`runMockCounter` i) . unMyAppM
myApp :: (Monad m, CounterT m , WeatherT m) => m String
myApp = do
_ <- increment
(WeatherData weather) <- byCity "Amsterdam"
return weather
-- Testing it:
main :: IO ()
main = runMyAppM 12 myApp >>= print
Weather module:
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Weather where
import Control.Monad.Trans.Class
import Control.Monad.Trans.Identity
newtype WeatherData = WeatherData String deriving (Show)
class Monad m => WeatherT m where
byCity :: String -> m WeatherData
default byCity :: (MonadTrans t, WeatherT m', m ~ t m') => String -> m WeatherData
byCity = lift . byCity
newtype MockWeather m a = MockWeather {
unMockWeather :: IdentityT m a
} deriving (Functor, Applicative, Monad, MonadTrans)
runMockWeather :: MockWeather f a -> f a
runMockWeather = runIdentityT . unMockWeather
instance Monad m => WeatherT (MockWeather m) where
byCity city = MockWeather $ return $ WeatherData $ "It is sunny in " ++ city
Counter module:
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Counter where
import Control.Monad.Identity
import Control.Monad.State
import Control.Monad.Trans.Class
class Monad m => CounterT m where
increment :: m Int
current :: m Int
default increment :: (MonadTrans t, CounterT m', m ~ t m') => m Int
increment = lift increment
default current :: (MonadTrans t, CounterT m', m ~ t m') => m Int
current = lift current
newtype MockCounter m a = MockCounter {
unMockCounter :: StateT Int m a
} deriving (Functor, Applicative, Monad, MonadTrans, MonadState Int)
defaultMockCounter :: MockCounter Identity ()
defaultMockCounter = MockCounter $ put 0
runMockCounter :: MockCounter m a -> Int -> m (a, Int)
runMockCounter = runStateT . unMockCounter
instance Monad m => CounterT (MockCounter m) where
increment = MockCounter $ do
c <- get
let n = c + 1
put n
return n
current = MockCounter get
回答1:
You need an instance WeatherT m => WeatherT (MockCounter m)
which just lifts a WeatherT m
instance through MockCounter m
thanks to the fact that MockCounter
is a monad transformer. (The point of the default methods you wrote is to define such instances.)
To avoid orphan instances, one way is to separate Weather
and Counter
each into Class
and Trans
modules. Class
don't need to depend on each other, while each Trans
module may depend on all the Class
modules (the other way around is also possible, and is in fact how mtl
does it, but IMO Trans
depending on Class
is better: Class
defines the interface, and Trans
the implementation).
This is indeed a (known) problem because if you have n
transformers and m
classes, you potentially need n*m
lifting instances. One solution is to define a polymorphic overlappable instance for all transformers (MonadTrans t, WeatherT m) => WeatherT (t m)
. Overlapping instances are often frowned upon but I'm not sure what actual problems there are in this case.
By the way, following the naming convention from mtl
and transformers
we would have MonadWeather
and MonadCounter
classes, and WeatherT
and CounterT
types (monad Transformers).
来源:https://stackoverflow.com/questions/49149787/avoiding-orphan-instances-with-monad-transformers