
Jacques Carette wrote:
Tim Newsham wrote:
I have to write:
do { x <- getSomeNum y <- anotherWayToGetANum return (x + y) }
even if the computation of x and y are completely independant of each other.
I too have really missed a "parallel composition" operator to do something like the above. Something like
do { { x <- getSomeNum || y <- anotherWayToGetANum} return (x+y) }
Actually, that syntax is rather hideous. What I would _really_ like to write is do { (x,y) <- getSomeNum || anotherWayToGetANum return (x+y) }
I would be happy to tell Haskell explicitly that my computations are independent (like the above), to expose parallelization opportunities. Right now, not only can I NOT do that, I am forced to do the exact opposite, and FORCE sequentiality.
Jacques
What is wanted is a specific relation of the ordering required by the Monad's structure. For pure computation Control.Parallel.Strategies may be helpful. If what was wanted was to keep sequencing but lose binding then the new Control.Applicative would be useful. It almost looks like we want your pair combinator: do { (x,y) <- parallelPair getSomeNum anotherWayToGetANum return (x+y) } This is principled only in a Monad that can supply the same "RealWorld" to both operations passed to parallelPair. After they execute, this same "RealWold" is the context for the "return (x+y)" statement. This ability to run three computations from the same "RealWorld" seems (nearly) identical to backtracking in a nondeterministic monad, which is usually exposed by a MonadPlus instance. The use of pairs looks alot like the arrow notation. And parallelPair a b = a &&& b looks right for arrows. And since monads are all arrows this works, but Kleisli implies ordering like liftM2. For a specific Monads you can write instances of a new class which approximate the semantics you want.
import Control.Arrow import Data.Char import Control.Monad import Control.Monad.State import System.IO.Unsafe
type M = State Int
main = print $ runState goPar 65 -- should be ((65,'A'),65)
opA :: (MonadState Int m) => m Int opA = do i <- get put (10+i) return i
opB :: (MonadState Int m) => m Char opB = do i <- get put (5+i) return (chr i)
goPar :: State Int (Int,Char) goPar = opA `parallelPair` opB
class (Monad m) => MonadPar m where parallelPair :: m a -> m b -> m (a,b)
instance MonadPar (State s) where parallelPair a b = do s <- get let a' = evalState a s b' = evalState b s return (a',b')
-- No obvious way to run the inner monad (without more machinery), -- so we have to resort to ordering instance (Monad m) => MonadPar (StateT s m) where parallelPair a b = do s <- get a' <- lift $ evalStateT a s b' <- lift $ evalStateT b s return (a',b')
-- Reader and Writer work like State
-- Use unsafeInterleaveIO to make a and b lazy and unordered... instance MonadPar IO where parallelPair a b = do a' <- unsafeInterleaveIO a b' <- unsafeInterleaveIO b return (a',b')
k :: State Int b -> Kleisli (State Int) a b k op = Kleisli (const op)
runK :: Kleisli (State Int) a a1 -> (a1, Int) runK kop = runState (runKleisli kop undefined) 65
go :: State Int a -> (a,Int) go op = runK (k op)
kab :: Kleisli (State Int) a (Int, Char) --kab = k opA &&& k opB kab = proc x -> do a <- k opA -< x b <- k opB -< x returnA -< (a,b)