[Haskell-beginners] Mixing monads?

Stephen Tetley stephen.tetley at gmail.com
Sun Mar 28 14:06:52 EDT 2010


Hello Ron

Further, here's a code sketch that shows roughly what you will need to do.

I've stubbed the CBC monad and CbcT transformer to be the Identity
monad (with different names) - the Identity Monad is the simplest
monad.

-- Code follows:


-- Stubbing CBC just as a warm up and so you can see the
-- difference between the monad and monad transformer
-- versions:

newtype CBC a = CBC { getCBC :: a }

-- The bind (>>=) and return of the Identity monad.
--
instance Monad CBC where
  return a = CBC a
  (CBC a) >>= mf = mf a


func :: Parser (CBC Word128)
func = do
   x <- word128
   let r = do
       y <- decryptCBC x
       if (y == 255)
           then return 0
           else undefined -- somehow read more from the parser?
   return r

--- With a transformer:


-- Make a transformer version of CBC:
--
-- For simplicity again I'm stubbing the monad as the Identity
-- monad transformer.
--
newtype CbcT m a = CbcT { getCbcT :: m a }


-- Note the instance of Monad for the transformer can use (>>=)
-- and return from the base monad.
--
-- The bind (>>=) and return here are equivalent to (>>=) and
-- return of the Identity monad.
-- 

instance Monad m => Monad (CbcT m) where
  return a = CbcT (return a)
  (CbcT ma) >>= mf = CbcT $ ma >>= (getCbcT . mf)


-- Make a type synonym for the combination of the CbcT
-- transformer and the base monad Parser.
--

type CbcParser a = CbcT Parser a

-- Make an instance of lift.
--
-- With a more powerfully monad than Identity - lift will
-- be more complicated.
--
-- Often, if the monad is based on a stack of transformers
-- lift is in the form
--
-- > lift = MyMonadT . lift . lift
-- 
--

instance MonadTrans CbcT where
  lift = CbcT

-- Again, a stub of the decryptCBC function.
--
-- Note the type signature here is more general than
-- necessary allowing it to be used with any base monad
-- not just Parser.
--
decryptCBC_T :: Monad m => Word128 -> CbcT m Word128
decryptCBC_T x = return (x-1)     -- just a dummy


-- The "func" function again.
--
-- Because we are using the combined monad CbcParser
-- (aka CbcT <transformer> + Parser <base>), we don't need
-- the "let r = ..." code that previously "ran" the CBC monad.
--
func_T :: CbcParser Word16
func_T = do
   x <- lift $ word128
   y <- decryptCBC_T x
   if (y == 255)
           then return 0
           else (lift $ word128) -- silly idea,
                                 -- just return next Word128


More information about the Beginners mailing list