Question

Suppose that in a Haskell program I have some data whose type is something like:

  • IO [ IO (Int, String, Int) ], or
  • IO [ (Int, String, IO Int) ], or
  • [ (Int, String, IO Int) ]

but I have pure functions that should operate on [ (Int, String, Int) ]. It seems that I'd have to clumsily remove the inside values from the IO monad, until I got something like IO [ (Int, string, Int) ] and then (from inside the IO monad) apply the pure functions. There is no easy pre-defined way to do this, I suppose? Something that would lift a whole data structure into a monad, turning all inside types into pure types? (That would be very convenient!)

Was it helpful?

Solution

You could use the liftM* function from the Control.Monad module, or the liftA* functions for applicatives.

liftM allows you to lift a pure function to work inside a Monad, e.g.:

ghci> let s = return "Hello" :: IO String
ghci> liftM reverse s
"olleH"

This way you don't have to manually write things like "s >>= \x -> return (reverse x)" everywhere.

Although, this won't help you with your [(String, Int, IO Int)] example, if the pure function you have deals with a [(String, Int, Int)]. Since the third element in the tuple really isn't an Int.

In that case I'd suggest to first write a function [(String, Int, IO Int)] -> IO [(String, Int, Int)] and that apply the lifted pure function.


This is the most general function I could come up with to do this:

conv :: Monad m => (f (m a) -> m (f a)) -> [f (m a)] -> m [f a]
conv f = sequence . map f

You can call it like so:

liftTrd :: Monad m => (a, b, m c) -> m (a, b, c)
liftTrd (x, y, mz) = mz >>= \z -> return (x, y, z)

conv liftTrd [("hi", 4, return 2)] :: IO [(String, Int, Int)]

This function will only work if you have a single monad that's somewhere deep in a type. If you have multiple, I think you should really be thinking about the type your working in with and see if you can't make it simpler.

OTHER TIPS

First some usage example for the solution below called reduce (unless you suggest a better name):

> reduce [(["ab", "c"], "12")] :: [(String, String)]
[("ab","12"),("c","12")]

> reduce [(["ab", "c"], "12")] :: [(Char, Char)]
[('a','1'),('a','2'),('b','1'),('b','2'),('c','1'),('c','2')]

> reduce [("ab", "12"), ("cd", "3")] :: [(Char, Char)]
[('a','1'),('a','2'),('b','1'),('b','2'),('c','3'),('d','3')]

Your example is also solved with it:

complexReduce :: Monad m => m (m (a, b, m [m (c, m d)])) -> m (a, b, [(c, d)])
complexReduce = reduce

And the implementation of reduce:

{-# LANGUAGE FlexibleContexts, FlexibleInstances, IncoherentInstances, MultiParamTypeClasses, UndecidableInstances #-}

import Control.Monad

-- reduce reduces types to simpler types,
-- when the reduction is in one of the following forms:
-- * make a Monad disappear, like join
-- * move a Monad out, like sequence
-- the whole magic of Reduce is all in its instances
class Reduce s d where
  reduce :: s -> d

-- Box is used only for DRY in Reduce instance definitions.
-- Without it we, a Reduce instance would need
-- to be tripled for each variable:
-- Once for a pure value, once for a monadic value,
-- and once for a reducable value
newtype Box a = Box { runBox :: a }
instance Monad m => Reduce (Box a) (m a) where
  reduce = return . runBox
instance Reduce a b => Reduce (Box a) b where
  reduce = reduce . runBox
redBox :: Reduce (Box a) b => a -> b
redBox = reduce . Box

-- we can join
instance (Monad m
  , Reduce (Box a) (m b)
  ) => Reduce (m a) (m b) where
  reduce = join . liftM redBox

-- we can sequence
-- * instance isnt "Reduce [a] (m [b])" so type is always reduced,
--   and thus we avoid overlapping instances.
-- * we cant make it general for any Traversable because then
--   the type system wont find the right patterns.
instance (Monad m
  , Reduce (Box a) (m b)
  ) => Reduce (m [a]) (m [b]) where
  reduce = join . liftM (sequence . fmap redBox)

instance (Monad m
  , Reduce (Box a) (m c)
  , Reduce (Box b) (m d)
  ) => Reduce (a, b) (m (c, d)) where
  reduce (a, b) = liftM2 (,) (redBox a) (redBox b)

instance (Monad m
  , Reduce (Box a) (m d)
  , Reduce (Box b) (m e)
  , Reduce (Box c) (m f)
  ) => Reduce (a, b, c) (m (d, e, f)) where
  reduce (a, b, c) =
    liftM3 (,,) (redBox a) (redBox b) (redBox c)
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top