Using persistent from within a Conduit - haskell

First up, a simplified version of the task I want to accomplish: I have several large files (amounting to 30GB) that I want to prune for duplicate entries. To this end, I establish a database of hashes of the data, and open the files one-by-one, hashing each item, and recording it in the database and the output file iff its hash wasn't already in the database.
I know how to do this with iteratees, enumerators, and I wanted to try conduits. I also know how to do it with conduits, but now I want to use conduits & persistent. I'm having problems with the types, and possibly with the entire concept of ResourceT.
Here's some pseudo code to illustrate the problem:
withSqlConn "foo.db" $ runSqlConn $ runResourceT $
sourceFile "in" $= parseBytes $= dbAction $= serialize $$ sinkFile "out"
The problem lies in the dbAction function. I would like to access the database here, naturally. Since the action it does is basically just a filter, I first thought to write it like that:
dbAction = CL.mapMaybeM p
where p :: (MonadIO m, MonadBaseControl IO (SqlPersist m)) => DataType -> m (Maybe DataType)
p = lift $ putStrLn "foo" -- fine
insert $ undefined -- type error!
return undefined
The specific error I get is:
Could not deduce (m ~ b0 m0)
from the context (MonadIO m, MonadBaseControl IO (SqlPersist m))
bound by the type signature for
p :: (MonadIO m, MonadBaseControl IO (SqlPersist m)) =>
DataType -> m (Maybe DataType)
at tools/clean-wac.hs:(33,1)-(34,34)
`m' is a rigid type variable bound by
the type signature for
p :: (MonadIO m, MonadBaseControl IO (SqlPersist m)) =>
DataType -> m (Maybe (DataType))
at tools/clean-wac.hs:33:1
Expected type: m (Key b0 val0)
Actual type: b0 m0 (Key b0 val0)
Note that this might be due to wrong assumptions I made in designing the type signature. If I comment out the type signature and also remove the lift statement, the error message turns into:
No instance for (PersistStore ResourceT (SqlPersist IO))
arising from a use of `p'
Possible fix:
add an instance declaration for
(PersistStore ResourceT (SqlPersist IO))
In the first argument of `CL.mapMaybeM', namely `p'
So this means that we can't access the PersistStore at all via ResourceT?
I cannot write my own Conduit either, without using CL.mapMaybeM:
dbAction = filterP
filterP :: (MonadIO m, MonadBaseControl IO (SqlPersist m)) => Conduit DataType m DataType
filterP = loop
where loop = awaitE >>= either return go
go s = do lift $ insert $ undefined -- again, type error
loop
This resulted in yet another type error I don't fully understand.
Could not deduce (m ~ b0 m0)
from the context (MonadIO m, MonadBaseControl IO (SqlPersist m))
bound by the type signature for
filterP :: (MonadIO m,
MonadBaseControl IO (SqlPersist m)) =>
Conduit DataType m DataType
`m' is a rigid type variable bound by
the type signature for
filterP :: (MonadIO m,
MonadBaseControl IO (SqlPersist m)) =>
Conduit DataType m DataType
Expected type: Conduit DataType m DataType
Actual type: Pipe
DataType DataType DataType () (b0 m0) ()
In the expression: loop
In an equation for `filterP'
So, my question is: is it possible to use persistent like I intended to inside a conduit at all? And if, how? I am aware that since I can use liftIO inside the conduit, I could just go and use, say HDBC, but I wanted to use persistent explicitly in order to understand how it works, and because I like its db-backend agnosticism.

The code below compiles fine for me. Is it possible that the frameworks have moved on inthe meantime and things now just work?
However note the following changes I had to make as the world has changed a bit or I didn't have all your code. I used conduit-1.0.9.3 and persistent-1.3.0 with GHC 7.6.3.
Omitted parseBytes and serialise as I don't have your definitions and defined DataType = ByteString instead.
Introduced a Proxy parameter and an explicit type signature for the undefined value to avoid problems with type family injectivity. These likely don't arise in your real code because it will have a concrete or externally determined type for val.
Used await rather than awaitE and just used () as the type to substitute for the Left case, as awaitE has been retired.
Passed a dummy Connection creation function to withSqlConn - perhaps I should have used some Sqlite specific function?
Here's the code:
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction,
TypeFamilies, ScopedTypeVariables #-}
module So133331988 where
import Control.Monad.Trans
import Database.Persist.Sql
import Data.ByteString
import Data.Conduit
import Data.Conduit.Binary
import Data.Proxy
test proxy =
withSqlConn (return (undefined "foo.db")) $ runSqlConn $ runResourceT $
sourceFile "in" $= dbAction proxy $$ sinkFile "out"
dbAction = filterP
type DataType = ByteString
filterP
:: forall m val
. ( MonadIO m, MonadBaseControl IO (SqlPersist m)
, PersistStore m, PersistEntity val
, PersistEntityBackend val ~ PersistMonadBackend m)
=> Proxy val
-> Conduit DataType m DataType
filterP Proxy = loop
where loop = await >>= maybe (return ()) go
go s = do lift $ insert (undefined :: val)
loop

Related

How to add Mask to a monadic stack

I am trying to use the bracket function from Exception.Safe Package which has a return type of
forall m a b c. MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c
This implies that my monad stack must have the Mask monad added to the stack ?
My calling function looks like this
sendMessage :: String -> Config.KafkaP (Either KafkaError ())
sendMessage msg=do
getProperties <- producerProps
let
mkProducer = newProducer getProperties
clProducer (Left _) = return ()
clProducer (Right prod) = closeProducer prod
runHandler (Left err) = return $ Left err
runHandler (Right prod) = messageSender prod msg
res <- bracket mkProducer clProducer runHandler
return res
And config.KakfaP has the type
ReaderT ProducerConfig IO a
And the error I get is ,
No instance for (exceptions-0.10.0:Control.Monad.Catch.MonadMask
Config.KafkaP)
arising from a use of ‘bracket’
Does this mean the monad stack needs to be something like this
Mask (ReaderT ProducerConfig IO a)
Ideally I would want the function to return what the run Handler returns which is Config.KafkaP (Either KafkaError ()) ,or anything more robust .
Adding a solution based on an answer
sendMessage :: String -> Config.KafkaP (Either KafkaError ())
sendMessage msg=do
getProperties <- producerProps
let
mkProducer = newProducer getProperties
--newProducer :: MonadIO m => ProducerProperties -> m (Either KafkaError KafkaProducer)
--mkProducer :: Config.KafkaP (Either KafkaError KafkaProducer)
clProducer (Left _) = return ()
clProducer (Right prod) = closeProducer prod
--closeProducer :: MonadIO m => KafkaProducer -> m ()
--clProducer :: Config.KafkaP (Either () ()) -- ??
runHandler (Left err) = return $ Left err
runHandler (Right prod) = messageSender prod msg
--messageSender :: KafkaProducer -> String -> Config.KafkaP (Either KafkaError ())
--runHandler :: Config.KafkaP (Either KafkaError ()) -- ??
Config.KafkaP $ bracket (Config.runK mkProducer) (Config.runK .clProducer) (Config.runK .runHandler)
If you were using the type ReaderT ProducerConfig IO a directly, there wouldn't be a problem, because the exceptions package provides an instance
MonadMask IO
That says you can use bracket with IO, and another instance
MonadMask m => MonadMask (ReaderT r m)
That says that if the base monad is an instance of MonadMask, then ReaderT over that monad is also an instance of MonadMask.
Notice that MonadMask is not a transformer that is part of the monad stack. Instead, it is a constraint that says "this monad stack supports masking / bracketing operations".
If you were using a type synonym like
type KafkaP a = ReaderT ProducerConfig IO a
there wouldn't be a problem either, because type synonyms don't create a new type, they just give an alias to an exiting one. One can still make use of all the existing typeclass instances for the type.
You mention in the comments that KafkaP is a newtype. A newtype is a cheap way of creating, well, a new type out of another. It's basically a constructor that holds a value of the original type.
And that's the problem. Because it is a new type, it doesn't share automatically all the typeclass instances of the old one. In fact, having different typeclass instances in newtypes is one of the main motivations for using newtypes!
What can be done? Well, supposing the newtype constructor is exported (sometimes they are hidden for purposes of encapsulation) you could unwrap the KafkaPs actions into ReaderT ProducerConfig IO a before sending them into bracket, and then re-wrap the result into KafkaP again. Some of the parameters are KafkaP-returning functions, so you'll probably need to throw in some function composition as well. Perhaps something like (assuming KafkaP is the name of the constructor, and runKafkaP the name of the corresponding accessor):
KafkaP $ bracket (runKafkaP mkProducer) (runKafkaP . clProducer) (runKafkaP . runHandler)
All this wrapping and unwrapping is tedious; sometimes using coerce from Data.Coerce can help. But this only works when the newtype constructor is exported.
You might also think of defining your own MonadMask instance for KafkaP using the technique above. This can be done, but instances which are defined neither in the module that defines the typeclass nor in the module that defines the type are called orphan instances and are somewhat frowned upon.

Print to console and update Monad state in same function

I want to define a function that expects an Int, prints an error in the console depending on the number (x) and then updates the State with Nothing.
How can I join those commands in one function?
Here's what I got:
type Env = [(Variable,Int)]
newtype StateError a = StateError { runStateError :: Env -> Maybe (a, Env) }
class Monad m => MonadError m where
throw :: Monad m => a -> m a
instance MonadError StateError where
throw x = StateError (\s -> Nothing)
But I can't figure out how to perform the IO side-effect and then the State update in the same function definition
No
A function in the state monad, such as a -> State s b, is a pure function (no IO) that happens to have an extra function argument s hidden though some handy plumbing.
You can't print to the console from the state monad.
However, Yes!
However! You can use a monad transformer to get both State and some underlying monad such as IO.
I'll provide an example using transformers instead of a custom monad and mtl as it appears you were using. With mtl you can use classes like MonadError to leverage a throw that works well with other libraries that use the mtl classes. On the other hand, if you are the end consumer of this transformer it is less important.
First we'll import the modules that give us MonadIO, StateT, MaybeT, and use newtype deriving so we don't have to type out the monad instance boilerplate:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import qualified Control.Monad.Trans.State as S
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Control.Monad.Trans
Just to be complete we'll spell out the types useful to your abstraction:
type Variable = String
type Env = [(Variable,Int)]
Now we can get to the interesting part - a Monad definition and functions for plumbing. The monad stack is StateT MaybeT IO:
newtype StateError a = StateError { unStateError :: S.StateT Env (MaybeT IO) a }
deriving (Monad, Applicative, Functor)
And we can run it by first unwrapping the newtype, then running the state, and finally the MaybeT:
run :: StateError a -> IO (Maybe (a, Env))
run = runMaybeT . flip S.runStateT [] . unStateError
Usually you'll write an army of functions that provide your monad abstraction. For this question it's just "update the state" and "print to stdout":
modify :: (Env -> Env) -> StateError ()
modify = StateError . S.modify
emit :: Show a => a -> StateError ()
emit = StateError . liftIO . print . show
Armed with our Monad of Power, we can do fancy things like update state and emit IO messages and track failure or success:
updateAndPrint :: Variable -> Int -> StateError ()
updateAndPrint v i =
do emit (v,i)
modify ((v,i):)
Oh, and failure is pretty simple - just fail in our MaybeT monad:
throw :: a -> StateError b
throw _ = fail "" -- same as 'MaybeT (pure Nothing)'
We can use this monad as expected:
> run $ updateAndPrint "var" 1
"(\"var\",1)"
Just (() -- ^ return value of `updateAndPrint`
,[("var",1)]) -- ^ resulting state

Monad type mismatch

I am attempting to use the IO monad in a Spock application. The following code does not compile:
get "api/entities" $ do
entities <- loadEntities
let e1 : xs = entities
text $ note e1
loadEntities has the type IO [Entity]
The error is Couldn't match type ‘ActionT IO ()’ with ‘t0 -> IO b0’
Is Spock using a monad other than IO? If so, how do I get the result of loadEntities?
Writing answer so people can see a better explanation.
If you look at get it has the type.
get :: MonadIO m => SpockRoute -> ActionT m () -> SpockT m ()
ActionT is a monad transformer and it requires in inner monad to have an instance of MonadIO. If we look at the typeclass MonadIO it has a function
liftIO :: IO a -> m a
This means every that you call execute functions of the type IO a in that stack by using liftIO. ActionT has an instance of MonadIO also and which is the one you are using here to call your IO function. So to call loadEntities you had to
entities <- liftIO loadEntities
If you end of calling a certain function like that a lot you can create a separate module import it qualified and export a more friendly one.
module Lifted (loadEntities) where
import qualified SomeModule as IO
loadEntities :: MonadIO m => m Entities
loadEntities = liftIO IO.loadEntities
This will make it so you don't always have you use liftIO

Using returned EitherT in haskell program

I'm trying to use the "citation-resolve" package in a Haskell project I'm working on, but I'm having trouble getting my head around using EitherT's in real code. I get that they're monad transformers, and I think I understand what that means, however I can't seem to actually work out how to use them. The toy example that represents what I'm trying to do is as follows:
module Main where
import Text.EditDistance
import Text.CSL.Input.Identifier
import Text.CSL.Reference
import Control.Monad.Trans.Class
import Control.Monad.Trans.Either
main = do
putStrLn "Resolving definition"
let resRef = runEitherT $ resolveEither "doi:10.1145/2500365.2500595"
case resRef of
Left e -> do
putStrLn ("Got error: "++ e)
Right ref -> do
putStrLn ("Added reference to database: "++ (show ref))
Here, resolveEither has the type:
resolveEither :: (HasDatabase s,
Control.Monad.IO.Class.MonadIO m,
mtl-2.1.3.1:Control.Monad.State.Class.MonadState s m)
=> String -> EitherT String m Reference
and runEitherT $ resolveEither "ref" has the type:
runEitherT $ resolveEither "ref"
:: (HasDatabase s,
Control.Monad.IO.Class.MonadIO m,
mtl-2.1.3.1:Control.Monad.State.Class.MonadState s m)
=> m (Either String Reference)
However, this gives the following error:
Main.hs:10:34:
No instance for (Control.Monad.IO.Class.MonadIO (Either [Char]))
arising from a use of ‘resolveEither’
In the first argument of ‘runEitherT’, namely
‘(resolveEither "doi:10.1145/2500365.2500595")’
In the expression:
runEitherT (resolveEither "doi:10.1145/2500365.2500595")
In an equation for ‘resRef’:
resRef = runEitherT (resolveEither "doi:10.1145/2500365.2500595")
Which I have no idea how to resolve, or work around.
Any help would be appreciated, especially pointers to tutorials dealing with monad transformers from a usage perspective, not an implementation one.
Edit:
To reflect the comments on answers by dfeuer and Christian, I still get errors if I change main to the following:
main = do
putStrLn "Resolving definition"
resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595")
case resRef of
Left e -> do
putStrLn ("Got error: "++ e)
Right ref -> do
putStrLn ("Added reference to database: "++ (show ref))
The error I get now is:
No instance for (MonadState s0 IO)
arising from a use of ‘resolveEither’
In the first argument of ‘runEitherT’, namely
‘(resolveEither "doi:10.1145/2500365.2500595")’
In a stmt of a 'do' block:
resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595")
In the expression:
do { putStrLn "Resolving definition";
resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595");
case resRef of {
Left e -> do { ... }
Right ref -> do { ... } } }
I'm editing my question as well as commenting, as nice code formatting is substantially easier here than in a comment.
I believe the problem is that you're trying to pattern match on resRef when what you probably want to do is execute it and pattern match on the result.
So you should try this:
main = do
putStrLn "Resolving definition"
resRef <- runEitherT $ resolveEither "doi:10.1145/2500365.2500595"
case resRef of
Left e -> do
You've encountered one of the shortcomings of the mtl class-based approach: intimidating type errors. I think it'll be helpful to imagine what the situation would look like with normal transformers-based monad transformers. I hope this will also help you get your feet with monad transformers in general. (It looks like you already understand most of this, by the way; I'm just spelling it out.)
Giving the types is a great way to start. Here's what you had:
resolveEither :: (HasDatabase s,
MonadIO m,
MonadState s m)
=> String -> EitherT String m Reference
There's a type hidden in the constraints, s, which came back to bite you a little later. The constraints, roughly speaking, express the following: s has a database (whatever that means in context); the monad or monad stack m has IO at its base, and somewhere in the monad stack m is a StateT s layer. The simplest monad stack m satisfying those properties would be HasDatabase s => StateT s IO. So we could write this:
resolveEither' :: HasDatabase s
=> String -> EitherT String (StateT s IO) Reference
resolveEither' = resolveEither
All we've done is specify the type of m so it's no longer a variable. We don't need to do that as long as we satisfy the class constraints.
Now it's clearer that there are two layers of monad transformers. Since our main function is in the IO monad, we want to end up with a value of type IO, which we can "run", for instance using <- in do notation. I think of it as "stripping away" layers of the monad transformer, from out to in. (This is what "using" monad transformers boils down to.)
For EitherT, there's a function runEitherT :: EitherT e m a -> m (Either e a). See how the m moves from "inside" the EitherT to "outside"? For me, that's the critical intuitive observation. Similarly for StateT, there's runStateT :: StateT s m a -> s -> m (a, s).
(Incidentally, both are defined as record accessors, which is idiomatic but causes them to show up a bit oddly in Haddock and with the "wrong" type signature; it took me a while to learn to look in the "Constructor" section on Haddocks and mentally add the EitherT e m a -> etc. to the front of the signature.)
So this adds up to a general solution, which you've basically worked out: we need an appropriate value of type s (which I'll call s), then we can use flip runStateT s . runEitherT $ resolveEither "ref" which has type IO ((Either String Reference), s). (Assuming I've kept the types straight in my head, which I probably didn't. I had forgotten flip the first time.) We can then pattern-match or use fst to get to the Either, which seems to be what you really want.
If you'd like me to explicate the errors GHC was giving you, I'd be glad. Informally, it was saying that you weren't "running" or stripping off all the monad transformers. More precisely, it was observing that IO wasn't something like StateT s IO. By using runStateT and runEitherT, you force or constrain the type such that the class constraints end up satisfied. This is kind of confusing when you get things slightly wrong.
Oh, regarding an idiomatic way to write the solution: I'm not sure that a separate retEither function would be idiomatic here, because it looks like it's meddling with global state, i.e. opening some sort of database file. It depends what the library's idiom is like.
Also, by using evalStateT, you're implicitly throwing away the state after evaluation, which may or may not be a bad idea. Does the library expect you to reuse the database connection?
Finally, you have some extra parentheses and some missing type signatures; hlint will help you with those.
Okay, so I think I've worked out a solution to my original problem, which was getting a value of the type IO (Either String Reference) from the function resolveEither (which it does for the resolveDef function it provides).
So, resolveEither returns a type of
(HasDatabase s, MonadIO m, MonadState s m) => String -> EitherT String m Reference
which we can transform to one of type
(HasDatabase s, MonadIO m, MonadState s m) => String -> m (Either String Reference)
using runEitherT . resolveEither. This was where I'd got up to when I asked the question. From there, i tried looking at the source to see how the library extracted a Reference type from the function resolveEither. The library uses the following function:
resolve :: (MonadIO m, MonadState s m, HasDatabase s) => String -> m Reference
resolve = liftM (either (const emptyReference) id) . runEitherT . resolveEither
however, we want to preserve the either, i.e. removing liftM (either (const emptyReference) id)
This however gets us back to where we started, so I looked at the source again, and worked out how this function is used. In the library, the function is used within the following, which transforms the output type of resolve from a value of type (MonadIO m, MonadState s m, HasDatabase s) => m Reference to one of type IO Reference:
resolveDef :: String -> IO Reference
resolveDef url = do
fn <- getDataFileName "default.db"
let go = withDatabaseFile fn $ resolve url
State.evalStateT go (def :: Database)
We can replace resolve in the previous with runEitherT.resolveEither to get a function that returns a IO (Either String Reference):
retEither s = do
fn <- getDataFileName "default.db"
let go = withDatabaseFile fn $ ( (runEitherT.resolveEither) s)
State.evalStateT go (Database Map.empty)
(I've replaced (def :: Database) with (Database Map.empty) as def is only defined internally in citation-resolve)
The overall solution then becomes:
module Main where
import Text.EditDistance
import Text.CSL.Input.Identifier.Internal
import Text.CSL.Input.Identifier
import Text.CSL.Reference
import Control.Monad.Trans.Either
import Control.Monad.State as State
import qualified Data.Map.Strict as Map
main = do
putStrLn "Resolving definition"
resRef <- retEither "doi:10.1145/2500365.2500595"
case resRef of
Left e -> putStrLn ("Got error: "++ e)
Right ref -> putStrLn ("Added reference to database: "++ (show ref))
retEither s = do
fn <- getDataFileName "default.db"
let go = withDatabaseFile fn $ ((runEitherT.resolveEither) s)
State.evalStateT go (Database Map.empty)
Which solves the original problem!
Any pointers on style, or ways of simplifying the whole process would however be very much appreciated.

Modular Program Design - Combining Monad Transformers in Monad Agnostic functions

I am trying to come up with a modular program design and I, once again, kindly request your help.
As a follow-up to these following posts Monad Transformers vs passing Parameters and Large Scale Design in Haskell, I am trying to build two independent modules that use Monad Transformers but expose Monad-agnostic functions, then combine a Monad-agnostic function from each of these modules into a new Monad-agnostic function.
I have been unable to run the combining function e.g. how do I call mainProgram using runReaderT in the example below ?.
The subsidiary question is: is there a better way to achieve the same modular design goal ?
The example has two mock modules (but compiles), one that performs logging and one that reads an user input and manipulates it. The combining function reads the user input, logs it and prints it.
{-# LANGUAGE FlexibleContexts #-}
module Stackoverflow2 where
import Control.Monad.Reader
----
---- From Log Module - Writes the passed message in the log
----
data LogConfig = LC { logFile :: FilePath }
doLog :: (MonadIO m, MonadReader LogConfig m) => String -> m ()
doLog _ = undefined
----
---- From UserProcessing Module - Reads the user Input and changes it to the configured case
----
data MessageCase = LowerCase | UpperCase deriving (Show, Read)
getUserInput :: (MonadReader MessageCase m, MonadIO m) => m String
getUserInput = undefined
----
---- Main program that combines the two
----
mainProgram :: (MonadReader MessageCase m, MonadReader LogConfig m, MonadIO m) => m ()
mainProgram = do input <- getUserInput
doLog input
liftIO $ putStrLn $ "Entry logged: " ++ input
There is a way to write a fully modular version of the program. The way you need to approach the problem is to bundle up your reader configuration into one data structure, and then define type classes that describe the partial interface that specific functions need towards that data structure. For example:
class LogConfiguration c where
logFile :: c -> FilePath
doLog :: (MonadIO m, LogConfiguration c, MonadReader c m) => String -> m ()
doLog = do
file <- asks logFile
-- ...
class MessageCaseConfiguration c where
isLowerCase :: c -> Bool
getUserInput :: (MonadIO m, MessageCaseConfiguration c, MonadReader c m) => m String
getUserInput = do
lc <- asks isLowerCase
-- ...
data LogConfig = LC { logConfigFile :: FilePath }
data MessageCase = LowerCase | UpperCase
data Configuration = Configuration { logging :: LogConfig, casing :: MessageCase }
instance LogConfiguration Configuration where
logFile = logConfigFile . logging
instance MessageCaseConfiguration Configuration where
isLowerCase c = case casing c of
LowerCase -> True
UpperCase -> False
mainProgram :: (MonadIO m, MessageCaseConfiguration c, LogConfiguration c, MonadReader c m) => m ()
mainProgram = do
input <- getUserInput
doLog input
liftIO . putStrLn $ "Entry logged: " ++ input
Now you can call mainProgram with a Configuration in a ReaderT monad and it'll work as you would expect.
Your mainProgram signature is problematic, because the MonadReader typeclass contains the functional dependency MonadReader r m | m -> r. This essentially means that a single concrete type cannot have a MonadReader instance for multiple different types. So when you say that the type m has both instances MonadReader MessageCase and MonadReader LogConfig it goes against the dependency declaration.
The easiest solution is to change mainProgram to have a non-generic type:
mainProgram :: ReaderT MessageCase (ReaderT LogConfig IO) ()
mainProgram = do input <- getUserInput
lift $ doLog input
liftIO $ putStrLn $ "Entry logged: " ++ input
This also requires the explicit lift for doLog.
Now you can run the mainProgram by running each ReaderT separately, like this:
main :: IO ()
main = do
let messageCase = undefined :: MessageCase
logConfig = undefined :: LogConfig
runReaderT (runReaderT mainProgram messageCase) logConfig
If you want to have a generic function that uses two different MonadReader instances, you need to make it explicit in the signature that one reader is a monad transformer on top of the other reader.
mainProgram :: (MonadTrans mt, MonadReader MessageCase (mt m), MonadReader LogConfig m, MonadIO (mt m), MonadIO m) => mt m ()
mainProgram = do input <- getUserInput
lift $ doLog input
liftIO $ putStrLn $ "Entry logged: " ++ input
However, this has the unfortunate effect that the function is no longer fully generic, because the order in which the two readers appear in the monad stack is locked. Maybe there is a cleaner way to achieve this, but I wasn't able to figure one out from the top of my head without sacrificing (even more) genericity.

Resources