How to add Mask to a monadic stack - haskell

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.

Related

How to deal with a monadic return value `m (Maybe Foo)`?

I have a function which returns a value wrapped in a Monad,
produceMessage :: MonadIO m => KafkaProducer -> ProducerRecord -> m (Maybe KafkaError)
And I have some code to call this function like so
err <- produceMessage prod message
return $ Right ()
The above code has been written by someone else, I am just trying to understand what is happening here. This is the rest of the function
messageSender :: KafkaProducer -> String -> Config.KafkaP (Either KafkaError ())
messageSender prod msg = do
message <- mkMessage Nothing (Just $ pack msg)
err <- produceMessage prod message
--forM_ err print
return $ Right ()
I have three specific questions,
I am confused what does the type signature of produceMessage mean? The type constraint is MonadIO m, what does this mean?
The return type is m (Maybe KafkaError), so this returns a Maybe value wrapped in which monad?
How does Right () come into picture here? In general I am really not
able to understand the last two lines of messageSender.
The type constraint means that the function can be used to return a value for any type m that has a MonadIO instance. Typically, that means IO itself or a monad stack built on top of IO.
The value returned by produceMessage is in part determined by the caller. Need an IO (Maybe KafkaError) value? You can get that, because IO has a MonadIO instance. Need a MyCustomMonadStack (Maybe KafkaError)? You can get that, if you define a MonadIO instance for MyCustomMonadStack.
Presumably, Config.KafkaP also has a MonadIO instance, based on how messageSender uses produceMessage.
messageSender has a return value of Config.KafkaP (Either KafkaError ()). The expression return $ Right () first uses Right () to produce a value of type Either KafkaError (), then return is applied to that to produce a value of type Config.KafkaP (Either KafkaError ()). Note that the commented line -- forM_ err print is the only thing that might have used the value coming from produceMessage, so right now messageSender pretends that produceMessage worked, whether it did or not.
A more robust definition would actually use the return value of produceMessage in some way, perhaps like
err <- produceMessage prod message
return $ case err of
Nothing -> Right ()
Just theError -> Left theError

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

Haskell: Pattern matching with named fields

I got ReaderT from Control.Monad.Reader:
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
and Action from Database.MongoDB.Query:
type Action = ReaderT MongoContext
Query functions of MongoDB are something like this:
delete :: MonadIO m => Selection -> Action m ()
I'm trying to use pattern mathing with Action m () to check if it is Action IO () or Action _ ()
A simple case like this
case x of
Action IO () -> True
Action _ () -> False
doesn't work, because Action is not a data constructor. Probably I should use something like this:
case x of
ReaderT MongoContext IO () -> True
ReaderT MongoContext _ () -> False
But then I get an error:
The constructor ‘ReaderT’ should have 1 argument, but has been given 3
In the pattern: ReaderT MongoContext IO ()
In a case alternative:
ReaderT MongoContext IO ()
Should I pass MongoContext -> IO () instead? I'm out of ideas, please help me with that expression. Thanks <3
IO is a type, you absolutely cannot case match against it, it only exists at compile time.
In general, if you have a type variable constrained by a type class, you can only call things supported by that type class. You cannot know which particular type it is unless the typeclass implements methods for inspecting it, like Typeable. Neither Monad nor MonadIO implement this kind of run-time type discrimination, so what you want is, by design, not possible.
Also note that, you don't need to know "which m" delete is, since it's specialized to whatever m that YOU want it to be, so long as it is an instance of MonadIO. You can simply declare deleteIO sel = delete sel :: Action IO ()
What are you actually trying to get done here?
As Steven Armstrong said, what you're trying to do is very weird, you cannot pattern match on IO because is an abstract data type (constructors aren't visible) and if I were you I would rethink what I'm trying to achieve. Having said that, Haskell still gives you a way of inspecting types at runtime using Typeable eg (inside a ghci session):
import Data.Typeable
import Control.Monad.Trans.Reader
type MyType = ReaderT String IO
f :: MyType ()
f = ReaderT $ \env -> putStrLn env
checkF :: Typeable a => MyType a -> Bool
checkF x = case show (typeOf x) of
"ReaderT * [Char] IO ()" -> True
_ -> False
-- checkF f => True

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

What is the name of this Monad Stack function?

I've got a bunch of stateful functions inside a State monad. At one point in the program there needs to be some IO actions so I've wrapped IO inside a StateT getting a pair of types like this:
mostfunctions :: State Sometype a
toplevel :: StateT Sometype IO a
To keep things simple I don't want pass the IO context into the main set of functions and I would like to avoid wrapping them in the monad stack type. But in order to call them from the toplevel function I need something akin to a lift, but I'm not trying to lift a value from the inner monad. Rather I want to convert the state in the StateT monad into something equivalent in the State monad. To do this I've got the following:
wrapST :: (State Sometype a) -> StateT Sometype IO a
wrapST f = do s <- get
let (r,s2) = runState f s
put s2
return r
This then get used to interleave things like the following:
toplevel = do liftIO $ Some IO functions
wrapST $ Some state mutations
liftIO $ More IO functions
....
It seems like a fairly obvious block of code so I'm wondering does this function have a standard name, and it is already implemented somewhere in the standard libraries? I've tried to keep the description simple but obviously this extends to pulling one transformer out of a stack, converting the wrapped value to the cousin of the transformer type, skipping the monads below in the stack, and then pushing the results back in at the end.
It may be a good idea to refactor your code to use the type StateT SomeType m a instead of State SomeType a, because the first one is compatible to an arbitrary monad stack. If you'd change it like this, you don't need a function wrapST anymore, since you can call the stateful functions directly.
Okay. Suppose you have a function subOne :: Monad m => State Int Int:
subOne = do a <- get
put $ a - 1
return a
Now, change the types of all functions like this one from State SomeType a to StateT SomeType m a, leaving m as is. This way, your functions can work on any monadic stack. For those functions, that require IO, you can specify, that the monad at the bottom must be IO:
printState :: MonadIO m => StateT Int m ()
printState = do a <- get
liftIO $ print a
Now, it should be possible to use both functions together:
-- You could use me without IO as well!
subOne :: Monad m => StateT Int m ()
subOne = do a <- get
put $ a - 1
printState :: MonadIO m => StateT Int m ()
printState = do a <- get
liftIO $ print a
toZero :: StateT Int IO ()
toZero = do subOne -- A really pure function
printState -- function may perform IO
a <- get
when (a > 0) toZero
PS: I use GHC 7, some of the libs changed midway, so it might be a bit different on GHC 6.
A more direct answer to your question: the function hoist does exactly what you're describing in a slightly more generic way. Example usage:
import Control.Monad.State
import Data.Functor.Identity
import Control.Monad.Morph
foo :: State Int Integer
foo = put 1 >> return 1
bar :: StateT Int IO Integer
bar = hoist (return . runIdentity) foo
hoist is part of the MFunctor class, which is defined like this:
class MFunctor t where
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b
There are instances for most monad tranformers, but not ContT.

Resources