Search code examples
haskelldependency-injectionseparation-of-concerns

Doing dependency injection using monad stacks


I'm trying different approaches to do what is sometimes known as dependency injection. For this I've elaborated a simple example of a weather app, where we want to fetch the weather data (from a web-service or from a hardware device), store the weather data (could be a database or simply a file), and report it (either print it to screen, or speak the weather). The idea is to write a program that uses some fetch, store, and report functions, whose implementations can vary.

I've managed to separate concerns and abstract away from the implementations of retrieval, storage, and reporting using functions and free-monads, however the solution I reached with monad stacks looks bad:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module WeatherReporterMTL where

import           Control.Monad.IO.Class
import           Control.Monad.Trans.Class

type WeatherData = String

class Monad m => WeatherService m where
    fetch :: m WeatherData

class Monad m => Storage m where
    store :: WeatherData -> m ()

class Monad m => Reporter m where
    report :: WeatherData -> m ()

-- | A dummy implementation of the @WeatherService@
newtype DummyService m a = DummyService { runDummyService :: m a }
    deriving (Functor, Applicative, Monad, MonadIO)

instance MonadIO m => WeatherService (DummyService m) where
    fetch = return "won't get any warmer in December."

-- | A dummy implementation of the @Storage@
newtype DummyStorage m a = DummyStorage { runDummyStorage :: m a }
    deriving (Functor, Applicative, Monad, MonadIO, WeatherService)

-- It seems wrong that the storage has to be an instance the weather service
-- (@WeatherService@) ...

instance MonadIO m => Storage (DummyStorage m) where
    store d = liftIO $ putStrLn $ "No room left for this report: " ++ d

-- | A dummy implementation of the @Reporter@
newtype DummyReporter m a = DummyReporter { runDummyReporter :: m a }
    deriving (Functor, Applicative, Monad, MonadIO, WeatherService, Storage)

-- Ok, now this seems even worse: we're putting information about
-- how we're gonna stack our monads :/

instance MonadIO m => Reporter (DummyReporter m) where
    report d = liftIO $ putStrLn $ "Here at the MTL side " ++ d

reportWeather :: (WeatherService m, Storage m, Reporter m) => m ()
reportWeather = do
    w <- fetch
    store w
    report w

dummyWeatherReport :: IO ()
dummyWeatherReport = runDummyService $ runDummyStorage $ runDummyReporter reportWeather

In the code above, both DummyStorage and DummyReporter have to have trivial instances for WeatherService, which seems plainly wrong. Moreover, these instances depend on the order monads are stacked in the end. Is there a way to avoid leaking information between the different stacks?


Solution

  • Instead of tying implementations to specific newtypes, perhaps you could have "free-floating" implementation functions that required access to IO and to some necessary bookkeeping state, like

    data WeatherState = WeatherState -- dummy
    fetch' :: (MonadState WeatherState m,MonadIO m) => m WeatherData
    fetch' = undefined 
    data StorageState = StorageState -- dummy
    store' :: (MonadState StorageState m,MonadIO m) => WeatherData -> m ()
    store' = undefined 
    data ReporterState = ReporterState -- dummy
    report' :: (MonadState ReporterState m,MonadIO m) => WeatherData -> m ()
    report' = undefined
    

    "Injecting" would mean creating some newtype over a StateT carrying the required states, and then declaring instances like

    newtype Injected a = 
        Injected { getInjected :: StateT (WeatherState,StorageState,ReportState) a } 
        deriving (Functor,Applicative,Monad)
    
    instance WeatherService Injected where
        fetch = Injected $ zoom _1 fetch'
    
    instance Storage Injected where
        store x = Injected $ zoom _2 $ store' x
    
    instance Reporter Injected where
        report x = Injected $ zoom _3 $ report' x
    

    (_1 is from microlens and zoom from microlens-mtl.)