I met this question today while learning haskell monad transformers.
Assume I have a type instance Monad m => Monad (CustomT m).
If there's a function f :: CustomT IO Int, and there's g :: IO (Maybe Int).
How do I access the Int of g in f?
I tried something like
f = do
mVal <- g
This didn't work because f is under CustomT IO monad while g is under MaybeT IO monad.
And then I tried
f = do
mVal <- return g
This seems to work but mVal is IO (Maybe Int) type, I eventually get nested IO like CustomT IO (IO something)
Is there a way to get that Int or Maybe Int out in f?
What knowledge is involved?
Thanks in advance.
In the general case, Jeremy's answer is what you want. But let's see if we can work with your specific case here. We have f :: CustomT IO Int and g :: IO (Maybe Int), given that there exist some instances to the effect of instance Monad m => Monad (CustomT m) and instance MonadTrans CustomT.
And what you want is to get at the Int inside of a g within the context of CustomT IO. Since we're inside of CustomT, we can basically strip that layer off trivially. Like Jeremy says, use lift to get rid of that.
lift :: (MonadTrans t, Monad m) => m a -> t m a
So now we have CustomT IO (Maybe Int). Like I said, we're inside a do-block, so using Haskell's bind (<-) syntax gets rid of the monad layer temporarily. Thus, we're dealing with Maybe Int. To get from Maybe Int to Int, the usual approach is to use maybe
maybe :: b -> (a -> b) -> Maybe a -> b
This provides a default value just in case the Maybe Int is actually Nothing. So, for instance, maybe 0 id is a function that takes a Maybe Int and yields the inner Int, or 0 if the value is Nothing. So, in the end, we have:
f = do
mVal <- maybe 0 id $ lift g
-- Other code
In the Control.Monad.Trans you have this definition for monad transformers:
class MonadTrans (t :: (* -> *) -> * -> *) where
lift :: Monad m => m a -> t m a
Which means that if CustomT has been defined properly you can do this:
f = do
mVal <- lift g
Related
I have function:
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
When I use do notation in the body of the function, it uses m as the monad. As you might expect, I actually want it to be using m Maybe. But, it doesn't understand that m Maybe is a monad. How do I express that to Haskell?
EDIT: This may be slightly malformed at the moment. The concrete type should be
StateT IntCodeState Maybe (), but I'm trying not to declare the concrete type, so the question is: how do I declare that?
EDIT 2: Another attempt: I've got some functions that look like this:
getValueIndex :: (MonadState IntCodeState m) => Int -> m (Maybe Int)
Here, I'm working on the level of the state monad. However, I now want to be able to act "as if" m Maybe was the monad. I was hoping this was simple but I can't figure out a way of expressing it. The code I want to write looks like this
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
step = do
full <- opCode
let len = length (snd full) + 1
process full <* (next += len)
But opCode returns a m (Maybe a) and I want full to be an a
But opCode returns a m (Maybe a) and I want full to be an a
Looks like you want to use the MaybeT monad transformer, which is m (Maybe a) under the hood, with its Monad instance doing what you need:
The MaybeT monad transformer extends a monad with the ability to exit the computation without returning a value.
A sequence of actions produces a value only if all the actions in the sequence do. If one exits, the rest of the sequence is skipped and the composite action exits.
Here are the types:
MaybeT :: m (Maybe a) -> MaybeT m a
runMaybeT :: MaybeT m a -> m (Maybe a)
This will also be helpful, specialised from MonadTrans:
lift :: m a -> MaybeT m a
So in your case:
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
step = runMaybeT $ do
full <- MaybeT opCode -- :: MaybeT opCode :: MaybeT m a, full :: a
let len = length (snd full) + 1
lift $ process full <* (next += len)
I've assumed process returns an m () and used lift to change it into MaybeT m ().
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.
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.
Say I have some foo :: Maybe Int and I want to bind it for example with bar :: Int -> MaybeT (Writer String) Int, what would be the idiomatic way to do that?
I could define my own liftMaybe function, and then use that, like:
let liftMaybe = maybe (fail "Nothing") return in liftMaybe foo >>= bar
But is there a more idiomatic (or at least concise) way to do that?
MaybeT . return :: (Monad m) => Maybe a -> MaybeT m a
I think it's a shame it doesn't have a standard name, however doing a hoogle search, we see that the relude packages uses hoistMaybe:
hoistMaybe :: Applicative m => Maybe a -> MaybeT m a
A more general form is
liftMaybe :: (MonadPlus m) => Maybe a -> m a
liftMaybe = maybe mzero return
which is preferable to the use of fail. I'd just put it in a convenient module somewhere.
I am new to Haskell. I wrote my own monad which is the State monad with error handling:
newtype MyMonad a = MyMonad (State -> Either MyError (State, a))
I use it in an interpreter of a small language. Now I want to add some IO operations to my language (reading/writing), but I don't know how to enclose IO monad inside mine. I know I could combine ErrorT, StateT, IO and achieve this result but is there other way to do it without them?
You can look at how StateT is implemented:
newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
To combine state with IO you just put IO in place of m and get the desired type: s -> IO (a,s).
If you have errors too, this becomes something like s -> IO (Either e (a, s)) or s -> IO (Either e a, s) depending on whether you want the failed computations to affect state.
Note that you can't make s -> Either e (IO (a, s)) a monad without a time machine.
Update
It turns out you can't make it a monad even with time machine.
To show why it is impossible, let us simplify our monad by using () instead of s first: data M e a = M { runM :: Either e (IO a) }
Now, imagine the following program:
unsafePerformIO :: IO a -> a
unsafePerformIO io = fromLeft $ runM $ do
a <- M $ Right $ io
M $ Left a
Obviously, this function is impossible and thus the monad instance for M is impossible too.
What time machine could give you is the ability to treat IO exactly like one treats State. However, I didn't realise that Either e (s -> (a, s)) is not a monad.