4

I am looking for a Haskell design to compose a chain of monadic actions (usually IO) in a manner, that later actions are dependent on previous ones but in some cases can be executed before they have finished.

The solution I came up with so far is:

type Future m a = m (m a)

Read: a monadic action, which starts some process and returns an action which will return the result of that process (possibly by waiting for this process to finish).

So in some chain a >>= b >>= c b gets an action returning a’s result. If b evaluates this action it waits for a to finish, otherwise it will be run in parallel. That also means that if some action does not require the result of the previous one as argument, it does not depend on it by definition, so the dependencies are explicit.

Some example code:

date :: Future IO String   -- long process to find out the date
date = do
    print "attempting to get date"  -- will usually start some thread or process to compute the date
    return (print "today")  -- will wait for this thread or process and return the computed date

main = do
    d <- date   -- starts recieving the date
    print "foo" -- some other process
    d >>= print -- waits until the date has been computed and prints it out

Output:

"attempting to get date"
"foo"
"today"

There is a problem through: if an action decides to wait for the previous one it will always be dependent on all the others before (in my case). But in the example above if c decides to wait for b but b did not decide to wait for a, c may start before a has finished, which should not happen.

As a solution I wrote another combining operator:

(>=>) :: Monad m => Future m a -> (m a -> Future m b) -> Future m b
a >=> f = do
    r1 <- a
    r2 <- f r1
    return (r1 >> r2)

So this will combine the “wait actions” and a >=> b >=> c will work just fine, if c waits for b this wait action will also wait for a. However there is another problem with this approach (apart from that you need to remember to use >=> instead of >>=): the wait actions may be evaluated many times. If b waits for a and c waits for b the wait for b will be connected to the wait for a nevertheless and thus the wait for a will be executed twice.

The actual problem is in >=>: f r1 may evaluate r1 in wich case it does not need to be sequenced with r2 in the return statement (as it already was executed and thus a has finished). But it also might not, I cannot know.

So what I basically want is exactly this but without the possibility to run the wait actions several times. Unfortunately I am not very experienced in functional design.

So I hope you can enlighten me in some way how to augment or change my design or point me to a different, more flexible approach.

Edit According to the answers so far I like to give some more clarification about what I actually want:

I do not want to defer (or even skip) the execution of actions, neither do I require threads or similar parallelism features. Actually I am calling external processes. An example would be

backup :: Future IO ExitCode
backup = do
    pid <- startProcess "backup"
    return (waitForProcessAndGetExitCode pid)

When I now chain actions like backup >=> otherAction, otherAction can run while the backup is running (which saves much time overall). But otherAction may require the backup to be completed, in which case it can use its parameter to wait for the backup and to check whether it was successful. Either way the backup has to be executed.

I am now looking for a nice general solution, ideally not tied to the IO monad.

Update I found a solution that worked for me. I described it in a seperate answer below.

4

5 に答える 5

2

I'm pretty sure you actually wanted this signature:

(>>=) :: Future m a -> (a -> Future m b) -> Future m b

Here's how you implement what you want:

import Control.Concurrent
import Control.Monad
import Control.Monad.Trans

newtype Future m a = Future { runFuture :: m (m a) }

instance (Monad m) => Monad (Future m) where
    return = Future . return . return
    m >>= f = Future $ do
        fut1 <- runFuture m
        return $ join $ join $ liftM (runFuture . f) fut1

instance MonadTrans Future where
    lift = Future . liftM return

In other words, Future is a monad transformer, and nothing about its implementation is specialized to the IO monad. However, the following example will show how you use it in conjunction with the IO monad to chain futures:

parallel :: IO a -> Future IO a
parallel m = Future $ do
    v <- newEmptyMVar
    forkIO $ m >>= putMVar v
    return $ takeMVar v

future1 = parallel $ do
    threadDelay 1000000
    putStrLn "Hello, World" 
    return 1
future2 n = parallel $ do
    threadDelay 1000000
    print n
    return 2
future3 = future1 >>= future2

main = do
    f <- runFuture future3
    putStrLn "I'm waiting..."
    r <- f
    print r

I haven't yet proven that it satisfies the monad laws or the monad transformer laws, but I will try to do that and I will update you on whether or not it checks out. Until then, there might be a misplaced join somewhere in there.

Edit: Nope! Not even close. It definitely does not satisfy the monad laws. I don't know if I was close or not, but just assume this answer is incorrect for now. However, I'm kind of intrigued now and wonder if it's possible.

于 2012-08-15T02:57:29.477 に答える
1

fおそらく1つの可能性は、その出力が要求されるまで実行することさえ拒否することです。

mma >=> fab = return $ do
    ma <- mma
    b  <- fab ma
    b

mma必要なものによっては、最初に実行することが重要な場合があります。

mma >=> fab = do
    ma <- mma
    return $ do
        b <- fab ma
        b
于 2012-08-14T15:57:38.127 に答える
1

MonadIOインスタンスがあるという制限を追加するとm、次のようなことができます(メモリから、テストされていません)。

share :: IO a -> IO (IO a)
share m = do
    ref <- newIORef Nothing
    let reader = do
          cached <- readIORef ref
          case cached of
            Just a -> return a
            Nothing -> m >>= \a -> writeIORef ref (Just a) >> return a
    return reader

share2 :: IO a -> IO aIORefの作成をでラップすることでこれをに変更でき、任意のインスタンスunsafePerformIOに一般化するのは簡単です。MonadIO

ただし、問題によっては、threadsまたはのようなものを使用した方がよい場合がありますIVar

于 2012-08-14T18:10:03.850 に答える
0

私が抱えている問題の完全な解決策ではありませんが、私は自分で解決策を見つけました。

アクションが前のアクションに依存しているかどうかを、事前に何とかして知る必要があることに気づきました。私はさまざまなアプローチを試しましたが、これから説明することを均等に思いつきました。私のソリューションでは、次のようなコードを記述できます

a :: Process IO x ()
a = independant $ do
    print "start a"
    return $ print "end a"

b :: Process IO x Int
b = independant $ do
    print "start b"
    return $ print "end b" >> return 0

c :: Process IO Int ()
c = dependant $ \x -> do
    print $ "start c with " ++ show x
    return $  print ("end c, started with " ++ show x)

chain = a >~ b >~ c
main = exec chain

-- outputs:
"start a" "start b" "end a" "end b" "start c with 0" "end c, started with 0"

(以下のその他の例)

私は次のタイプを使用しました

type Future m a = m (m a)
type Action m a b = a -> Future m b
type Process m a b = forall c. Action m c a -> Action m c b  -- will need -XRank2Types

次のプリミティブを使用します。

-- sequences f after g, f is dependant of g and gets its result
-- dependant :: Monad m => Action m a b -> Action m c a -> Action c b
dependant :: Monad m => Action m a b -> Process m a b
dependant f g a = join (g a) >>= f

-- sequences f after g, f is independant of g
independant :: Monad m => Future m a -> Process m b a
independant f g a = do
    w1 <- g a
    w2 <- f
    return (w1 >> w2)

-- concenation of processes
(>~) = flip (.)

このアプローチにより、他のプリミティブも処理しやすくなります。たとえば、次のようになります。

-- lifts a pure function into an action
pureA :: Monad m => (a -> b) -> Action m a b
pureA f a = return . return $ f a

-- makes an action wich always returns the same result
constA :: Monad m => b -> Action m a b
constA = pureA . const

-- no operation action
nop :: Monad m => Action m a ()
nop = constA ()

-- puts a sequence point
wait :: Monad m => Process m a a
wait = dependant $ pureA id

-- modify its result with a pure function
modify :: (Monad m, Functor m) => (a -> b) -> Process m a b
modify f act a = do
    x <- act a
    return (fmap f x)

-- makes a process, wich always returns the same result
constP :: (Monad m, Functor m) => b -> Process m a b
constP = modify . const

そして最後に、プロセスを実行する関数:

-- executes a process
exec :: Monad m => Process m () b -> m b
exec p = join $ p nop undefined

したがって、もう少し複雑な例をいくつか示します。

simleI :: String -> a -> Process IO b a
simpleI name r = independant $ do
    print ("start " ++ name)
    return $ print ("end " ++ name) >> return r

simpleD :: (Show a, Show b) => String -> (a -> b) -> Process IO a b
simpleD name f = dependant $ \a -> do
    print ("start " ++ name ++ " with " ++ show a)
    let r = f a
    return $ print ("end " ++ name ++ " with " ++ show r ++ " (started with " ++ show a ++ ")") >> return r

a = simpleI "a" ()
b = simpleI "b" 42
c = simpleD "c" (+1)
d = simpleI "d" ()

chain1 = a >~ b >~ c >~ d       -- == d . c . b . a
chain2 = a >~ wait >~ b >~ c >~ d
chain3 = a >~ b >~ modify (+1) >~ c >~ d

main = do
    exec chain1
    print "---"
    exec chain2
    print "---"
    exec chain3

出力:

"start a"
"start b"
"end a"
"end b"
"start c with 42"
"start d"
"end c with 43 (started with 42)"
"end d"
"---"
"start a"
"end a"
"start b"
"end b"
"start c with 42"
"start d"
"end c with 43 (started with 42)"
"end d"
"---"
"start a"
"start b"
"end a"
"end b"
"start c with 43"
"start d"
"end c with 44 (started with 43)"
"end d"

これはほぼ正確に私が欲しいものです。

アクションとプロセスを分類する方法に少し興味があります。それらはモナドではありません。それらはArrowsかもしれませんが、私はArrowsに慣れていないのでわかりません。プロセスは、fmap=modifyおよびpure=constのアプリケーションである可能性があります。constAまたはそのようなもの。

私のアプローチ、特にそれを拡張または単純化する方法について頭に浮かんだことは何でもコメントしてください。

于 2012-08-17T16:34:19.013 に答える
0

For cases, when you want to spark some threads and at some moment to collect results, check http://hackage.haskell.org/packages/archive/base/4.5.1.0/doc/html/Control-Concurrent-SampleVar.html and http://hackage.haskell.org/packages/archive/base/4.5.1.0/doc/html/Control-Concurrent.html#g:2 , as they seems relevant

For cases, when you need execute actions on demand, you may find this code useful Not checked in GHC but should work after typos fixed

module Promise (SuspendedAction, createSuspendedAction, getValueFromSuspendedAction)
import Data.IORef

data Promise a = Suspended (IO a) | Done a

data SuspendedAction = SA (IORef (Promise a))

createSuspendedAction :: m a -> m (SuspendedAction a)
createSuspendedAction act = newIORef (Suspended act)

readSuspendedAction :: SuspendedAction a -> m a
readSuspendedAction (SA ref) = readIORef ref >>= \suspended -> case suspended of
  Done a -> return a
  Suspended sact -> sact >>= \rv -> writeIORef ref (Done rv) >> return rv

BTW, check hackage carefully, there was package which allow to execute IO actions lazily while respecting their order.

于 2012-08-14T18:14:26.057 に答える