How to use bind with nested monads?

后端 未结 2 1822
独厮守ぢ
独厮守ぢ 2020-12-31 08:14

I have two functions, one that tries to get a token from a webservice and may fail, and one that tries to use this token to get the username and may fail.

ge         


        
相关标签:
2条回答
  • 2020-12-31 08:47

    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
    
    0 讨论(0)
  • 2020-12-31 08:51

    I have defined a function useToken showing your use case:

    type Token = String
    
    getToken :: IO (Maybe Token)
    getToken = undefined
    
    getUsername :: Token -> IO (Maybe String)
    getUsername = undefined
    
    useToken :: IO (Maybe String)
    useToken = do
      token <- getToken
      case token of
        Just x -> getUsername x
        Nothing -> return Nothing
    

    If you don't want to use do notation, then you can use:

    useToken2 :: IO (Maybe String)
    useToken2 = getToken >>= \token -> maybe (return Nothing) getUsername token
    

    Or using monad transformers, your code will become simpler:

    import Control.Monad.Trans.Maybe
    type Token = String
    
    getToken :: MaybeT IO Token
    getToken = undefined
    
    getUsername :: Token -> MaybeT IO String
    getUsername = undefined
    
    useToken :: MaybeT IO String 
    useToken = do
      token <- getToken
      getUsername token
    

    Note that, you can also directly lift IO operations inside the monad transformer. As @Robedino points out, now the code will be more concise without do notation:

    useToken :: MaybeT IO String 
    useToken = getToken >>= getUsername
    
    0 讨论(0)
提交回复
热议问题