Apply a function to a value inside IO Maybe - haskell

I have a function of type a -> IO (Maybe b) and I want to apply it to IO (Maybe a) and get IO (Maybe b). I wrote a function to do that:
ioMaybeApply :: (a -> IO (Maybe b)) -> IO (Maybe a) -> IO (Maybe b)
ioMaybeApply f ioMaybeA = do
maybeA <- ioMaybeA
maybe (return Nothing) f maybeA
Is there a standard Haskell function to do that? I tried searching with Hoogle but I didn't find anything. If not, is my implementation good, or could it be simpler?

This can be achieved through the MaybeT monad transformer:
GHCi> import Control.Monad.Trans.Maybe
GHCi> :t \f m -> runMaybeT (MaybeT m >>= MaybeT . f)
\f m -> runMaybeT (MaybeT m >>= MaybeT . f)
:: Monad m => (a1 -> m (Maybe a)) -> m (Maybe a1) -> m (Maybe a)
import Control.Monad.Trans.Maybe
-- Making it look like your definition, for the sake of comparison.
ioMaybeApply :: (a -> IO (Maybe b)) -> IO (Maybe a) -> IO (Maybe b)
ioMaybeApply f ioMaybeA = runMaybeT $ do
a <- MaybeT ioMaybeA
MaybeT (f a)
If you are using this pattern in multiple places, it will likely pay off to change your a -> IO (Maybe b) functions to a -> MaybeT IO b -- then you can just use (>>=) and/or seamless do-blocks instead of your special-purpose function. On the other hand, if this is just an one-off you may reasonably think that using MaybeT would be overkill; in that case, your implementation is perfectly fine.
(It is worth mentioning that while there is a general-purpose wrapper for nested functors called Compose that has Functor and Applicative instances, it doesn't have a Monad instance, as nesting two monads doesn't necessarily result in something that can be given a legal Monad instance. That being so, we typically resort to monad transformers tailored for each combination that works.)

Related

How to deal with an IO (Maybe (IO (Maybe t))) type?

I am dealing with a library (ghcjs-dom) in which every function returns an IO (Maybe T).
I have a function a with returns an IO (Maybe x) and function b which takes x as an argument and returns an IO (Maybe y).
Is an operator that lets me do a ??? b and get an IO (Maybe y). My Hoogle search turned up nothing.
I am looking something like join that works for IO (Maybe (IO (Maybe t))) instead of IO (IO t) or Maybe (Maybe t).
From what I understand, you have:
a :: IO (Maybe X)
b :: X -> IO (Maybe Y)
There is a close relationship between IO (Maybe a) and MaybeT IO a, namely MaybeT converts one to the other:
MaybeT :: IO (Maybe a) -> MaybeT IO a
and the inverse operation is just runMaybeT:
runMaybeT :: MaybeT IO a -> IO (MaybeT a)
In the MaybeT monad the composition you want to perform is just
the bind operation:
MaybeT a >>= (\x -> MaybeT (b x)) :: MaybeT IO Y
This results in a value of type MaybeT IO Y. To convert it back to a IO (Maybe Y) just use runMaybeT.
Update
Here is an operator to "compose" a and b:
andThen :: IO (Maybe a) -> (a -> IO (Maybe b)) -> IO (Maybe b)
andThen a b = runMaybeT $ MaybeT a >>= (\x -> MaybeT (b x) )
However, if you find yourself using this operator a lot, perhaps you
should rework your functions so you work primarily in the MaybeT IO
monad, and then you can just use >>= with a single runMaybeT
on the outside.
If you don't want to use MaybeT what you need is sequenceA or traverse from Data.Traversable.
Prelude Data.Traversable Control.Monad> :t fmap join . join . fmap sequenceA
fmap join . join . fmap sequenceA
:: (Traversable m, Control.Applicative.Applicative f, Monad m,
Monad f) =>
f (m (f (m a))) -> f (m a)
In your case f is IO and m Maybe.

Lift a function with a monad parameter into a monad transformer

I want to lift a function like mask_ :: IO a -> IO a to create a function with this signature: lmask_ :: StateT Bool IO a -> StateT IO a.
My problem is, how to handle the callback/first parameter? Wouldn't the following code be incorrect since it would execute the callback before mask_'s code?
lmask_ :: StateT Bool IO a -> StateT Bool IO a
lmask_ m = do
r <- m
lift (mask_ (return r))
Is there some general way to do this? A helper like lift1 :: MonadTrans t => (m a -> m a) -> (t m a -> t m a)?
If we generalize lmask_ to get rid of the StateT Bool IO, we get something like this:
lift1 :: (Monad m, Monad (t m), MonadTrans t) => (m a -> m a) -> (t m a -> t m a)
lift1 f term = do
x <- term
lift (f (return x))
In general this is not possible without knowing something about the monad transformer. However, there is a way how to do this for all the standard monad transformers. See type class MonadBaseControl. It's superclass MonadBase defines what is the bottom monad in a monad transformer stack (which is IO for all stacks that include IO), and MonadBaseControl defines a way how to embed the monad into the base monad. Its instances are somewhat convoluted, but once they're defined, it's possible to lift all such functions like mask_.
In your case, package lifted-base uses the above construction to re-define the standard IO functions lifted to MonadBaseControl. In particular, there is mask_
mask_ :: MonadBaseControl IO m => m a -> m a
which can be specialized to StateT Bool IO a -> StateT Bool IO a, as StateT s has an instance of MonadBaseControl.
See also Lift a function and its argument to a different monadic context.

a generic monadic `(<|>)`?

I'm looking for a more concise / idiomatic way of writing getAorB:
getAorB = do
a <- getA
case a of
Just _ -> return a
Nothing -> getB
Does this already exist as a library function somewhere?
Note that liftM2 (<|>) getA getB is the same as:
do a <- getA
b <- getB
return $ a <|> b
which is different from getAorB since bind is always called on getB even if getA returns a Just.
You can use the maybe function (b -> (a -> b) -> Maybe a -> b) with its default value:
getAorB :: Monad m => m a
getAorB = getA >>= maybe getB return
I don't think there's a single function that does this anywhere.
Trying to use an Alternative (such as MaybeT) doesn't work well here imo as it considers the second action to be fallible as well, which your getB isn't. If it if was, you should consider using MaybeT though:
getAorB :: Monad m => m (Maybe a)
getAorB = runMaybeT $ MaybeT getA <|> MaybeT getB
Sounds like an mplus for MaybeT.
Since (<|>) gets it's powers from applicative isn't this impossible?
It feels like the type you are looking for is something like
Monad m => a ->[m (Maybe a)] -> m a
instead? Or maybe
Monad m => a -> (a -> Bool) -> [m a] -> m a
Hoogle doesn't give me anything for either.
To hide all the transformers:
import Control.Monad.Trans.Maybe
getAOrB :: m (Maybe a) -> m (Maybe a) -> m (Maybe a)
getAOrB getA getB = runMaybeT (MaybeT getA <|> MaybeT getB)
But I would probably just use MaybeT everywhere instead:
getAOrB' :: MaybeT m a -> MaybeT m a -> MaybeT m a
getAOrB' = (<|>)
Note that this type is slightly different than the type of your first implementation; it has the same type as your second implementation but better behavior.

Lift a function and its argument to a different monadic context

I am not sure how to formulate this question scientifically exact, so I am just going to show you an example.
I am using state in a StateT transformer. Underlying is IO. Inside the StateT IO operation I need to use alloca. However, I can't lift alloca to StateT IO because it expects an argument of type (Ptr a -> IO a) while I require it to work with an argument of (Ptr a -> StateT IO MyState a).
(However, this is a generic question about monad transformers rather than specific to IO, StateT or alloca.)
I came up with the following, working solution:
-- for reference
-- alloca :: (Storable a) => (Ptr a -> IO b) -> IO b
allocaS :: (Storable a) => (Ptr a -> StateT s IO b) -> StateT s IO b
allocaS f = do
state <- get
(res, st) <- liftIO $ alloca $ \ptr -> (runStateT (f ptr) state)
put st
return res
However, it seems wrong to me that I should have to de- and reconstruct the StateT action in order to use it with alloca. Also, I have seen this pattern in some variations more than once and it's not always as simple and safe as here with StateT.
Is there a better way to do this?
This can be accomplished using MonadBaseControl in monad-control, which has been devised exactly for this purpose:
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad
import Control.Monad.Trans.Control
import qualified Foreign.Ptr as F
import qualified Foreign.Marshal.Alloc as F
import qualified Foreign.Storable as F
alloca :: (MonadBaseControl IO m, F.Storable a) => (F.Ptr a -> m b) -> m b
alloca f = control $ \runInIO -> F.alloca (runInIO . f)
This enhanced version of alloca can be used with any monad stack based on IO that implements MonadBaseControl, including StateT s IO.
Instances of MonadBaseControl allow their monadic values to be encoded in the base monad (here IO), passed to a function in the base monad (like F.alloca) and then reconstruct them back.
See also What is MonadBaseControl for?
Package lifted-base contains many of the standard IO functions lifted to MonadBaseControl IO, but alloca isn't (yet) among them.
Good afternoon,
AFAIK, there is no general way to turn a function of type (a -> m b) -> m b into (a -> t m b) -> t m b because that would imply the existence of a function of type MonadTrans t => (a -> t m b) -> (a -> m b).
Such a function cannot possibly exist, since most transformers cannot be stripped so easily from a type signature (how do you turn a MaybeT m a into an m a for all a ?). Hence, the most general way to turn (a -> m b) -> m b to (a -> t m b) -> t m b is undefined.
In the case of StateT s m, there is a loophole that allows you to define it anyway. Since StateT s m a === s -> m (s,a), we can rewrite the type equation to :
(a -> StateT s m b) -> StateT s m b
=== (a -> s -> m (s,b)) -> s -> m (s,b)
=== s -> (s -> (a -> m (s,b)) -> m (s,b) -- we reorder curried arguments
=== s -> (s -> (A -> m B)) -> m B -- where A = a, B = (s,b)
Solving this new type signature is now trivial :
liftedState f s run = f (run s)
allocaS :: Storable a => (Ptr a -> StateT IO b) -> StateT IO b
allocaS = isomorphic (liftedState alloca)
That is about the best we can do in terms of code reuse, short of defining a new subclass of MonadTrans for all monads that exhibit the same behaviour.
I hope I made myself clear enough (I didn't want to go into too much detail for fear of being confusing)
Have an excellent day :-)

Why is there a nested IO monad, IO (IO ()), as the return value of my function?

Why does this function have the type:
deleteAllMp4sExcluding :: [Char] -> IO (IO ())
instead of deleteAllMp4sExcluding :: [Char] -> IO ()
Also, how could I rewrite this so that it would have a simpler definition?
Here is the function definition:
import System.FilePath.Glob
import qualified Data.String.Utils as S
deleteAllMp4sExcluding videoFileName =
let dirGlob = globDir [compile "*"] "."
f = filter (\s -> S.endswith ".mp4" s && (/=) videoFileName s) . head . fst
lst = f <$> dirGlob
in mapM_ removeFile <$> lst
<$> when applied to IOs has type (a -> b) -> IO a -> IO b. So since mapM_ removeFile has type [FilePath] -> IO (), b in this case is IO (), so the result type becomes IO (IO ()).
To avoid nesting like this, you should not use <$> when the function you're trying to apply produces an IO value. Rather you should use >>= or, if you don't want to change the order of the operands, =<<.
Riffing on sepp2k's answer, this is an excellent example to show the difference between Functor and Monad.
The standard Haskell definition of Monad goes something like this (simplified):
class Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
However, this is not the only way the class could have been defined. An alternative runs like this:
class Functor m => Monad m where
return :: a -> m a
join :: m (m a) -> m a
Given that, you can define >>= in terms of fmap and join:
(>>=) :: Monad m => m a -> (a -> m b) -> m b
ma >>= f = join (f <$> ma)
We'll look at this in a simplified sketch of the problem you're running into. What you're doing can be schematized like this:
ma :: IO a
f :: a -> IO b
f <$> ma :: IO (IO b)
Now you're stuck because you need an IO b, and the Functor class has no operation that will get you there from IO (IO b). The only way to get where you want is to dip into Monad, and the join operation is precisely what solves it:
join (f <$> ma) :: IO b
But by the join/<$> definition of >>=, this is the same as:
ma >>= f :: IO a
Note that the Control.Monad library comes with a version of join (written in terms of return and (>>=)); you could put that in your function to get the result you want. But the better thing to do is to recognize that what you're trying to do is fundamentally monadic, and thus that <$> is not the right tool for the job. You're feeding the result of one action to another; that intrinsically requires you to use Monad.

Resources