As people in the comments suggest, you should just use monad transformers.
However you can avoid this in your case. Monads do not commute in general, so you can't write a function with this signature
bind' :: (Monad m, Monad n) => m (n a) -> (a -> m (n b)) -> m (n b)
But all is ok, if the inner monad is an instance of the Traversable
class:
import Data.Traversable as T
import Control.Monad
joinT :: (Monad m, Traversable t, Monad t) => m (t (m (t a))) -> m (t a)
joinT = (>>= liftM join . T.sequence)
liftMM :: (Monad m, Monad n) => (a -> b) -> m (n a) -> m (n b)
liftMM = liftM . liftM
bindT :: (Monad m, Traversable t, Monad t) => m (t a) -> (a -> m (t b)) -> m (t b)
bindT x f = joinT (liftMM f x)
and the Maybe
monad is; hence
type Token = String
getToken :: IO (Maybe Token)
getToken = undefined
getUsername :: Token -> IO (Maybe String)
getUsername = undefined
useToken :: IO (Maybe String)
useToken = getToken `bindT` getUsername
Also, with the {-# LANGUAGE RebindableSyntax #-}
you can write
(>>=) = bindT
useToken :: IO (Maybe String)
useToken = do
x <- getToken
getUsername x
Update
With the type-level compose
newtype (f :. g) a = Nested { runNested :: f (g a) }
you can define a monad instance for nested monads:
instance (Monad m, Traversable t, Monad t) => Monad (m :. t) where
return = Nested . return . return
x >>= f = Nested $ runNested x `bindT` (runNested . f)
Your example then is
type Token = String
getToken :: IO (Maybe Token)
getToken = undefined
getUsername :: Token -> IO (Maybe String)
getUsername = undefined
useToken :: IO (Maybe String)
useToken = runNested $ Nested getToken >>= Nested . getUsername
Or like you would do with the MaybeT
transformer:
type Nested = (:.)
type Token = String
getToken :: Nested IO Maybe Token
getToken = undefined
getUsername :: Token -> Nested IO Maybe String
getUsername = undefined
useToken :: Nested IO Maybe String
useToken = getToken >>= getUsername
runUseToken :: IO (Maybe String)
runUseToken = runNested useToken