Você está na página 1de 34

Concurrent Orchestration

in Haskell

John Launchbury
Trevor Elliott
Motivating Example

Helper Server Client1 Client2 Tester

Xen hypervisor

• Tester talks with each of the VMs concurrently


• Many possible behaviors are “correct” / “incorrect”
• Timeouts, VMs dying, etc.
• Subtle concurrency bugs in test framework
Concurrent Scripting

• Management of multiple resources


– Multiple paths
– Timeouts and defaults
– Processing of data and results

• “Scripting” rather than “programming”


– Minimal concurrency paraphernalia
• E.g. thread identifiers, locks, etc. etc.
– Easy to get right
Orc Intuitions

lift
O Lis
l iftI t
IO Orc List

putMVar <|>
readTVar

MonadIO MonadPlus
Basic Examples

fplang :: Orc String


fplang = return “Haskell” <|> return “ML” <|> return “Scheme”

fplang

“Haskell” “ML” “Scheme”


Basic Examples

metronome :: Orc ()
metronome = return () <|> (delay 2.5 >> metronome)

metronome

delay 2.5
()
Basic Examples

metro :: Float -> Orc ()


metro j
= return () <|> (delay j >> metro j)

rsiReminder :: Orc ()
rsiReminder = do
metro 3600
email “john at galois.com” “Get up and stretch!!”
Search
queens = fmap show (extend [])
<|> return ("Computing 8-queens...")

extend :: [Int] -> Orc [Int]


extend xs = if length xs == 8 Concurrency
then return xs
point

else do
j <- liftList [1..8]
guard $ not (conflict xs j)
extend (j:xs)
MonadPlus
operation
conflict :: [Int] -> Int
conflict = ...
Search
*Main> printOrc (queens)
Ans = "Computing 8-queens..."
Ans = "[5,7,1,3,8,6,4,2]"
Ans = "[6,4,2,8,5,7,1,3]"
Ans = "[5,3,8,4,7,1,6,2]"
Ans = "[4,2,7,3,6,8,5,1]"
:
*Main> printOrc (queens)
Ans = "Computing 8-queens..."
Ans = "[4,2,7,3,6,8,5,1]"
Ans = "[6,4,7,1,8,2,5,3]"
Ans = "[3,6,4,2,8,5,7,1]"
Ans = "[2,7,3,6,8,5,1,4]"
:
Orc API
newtype Orc a

return :: a -> Orc a


(>>=) :: Orc a -> (a -> Orc b) -> Orc b
stop :: Orc a
(<|>) :: Orc a -> Orc a -> Orc a

eagerly :: Orc a -> Orc (Orc a) Classes:

(<+>) :: Orc a -> Orc a -> Orc a Functor, Monad,


Applicative, Alternative,

liftIO :: IO a -> Orc a MonadPlus, MonadIO

runOrc :: Orc a -> IO ()


Using Eagerly
sync :: (a->b->c) -> Orc a -> Orc b -> Orc c
sync f p q = do Monadic
function
• Entering the handle
po <- eagerly p
application waits for the result
qo <- eagerly q
• Synchronization
return f <*> po <*> qo

notBefore:: Orc a -> Float -> Orc a


p `notBefore` w = sync const p (delay w)

cut:: Orc a -> Orc a cut:: Orc a -> Orc a


cut p = do cut = join . eagerly
po <- eagerly p
po
Web Query
quotes :: Query -> Query -> Orc Quote
quotes srcA srcB = do A
quoteA <- eagerly $ getQuote srcA
B
quoteB <- eagerly $ getQuote srcB
cut ( (return least <*> quoteA <*> quoteB)
<|> (quoteA >>= threshold)
<|> (quoteB >>= threshold)
<|> (delay 25 >> (quoteA <|> quoteB)) Need to
book a ticket,
<|> (delay 30 >> return noQuote)) under $300 if
possible…

least x y = if price x < price y then x else y


threshold x = guard (price x < 300) >> return x quote
Using <+>
Counting the number of answers

count :: Orc a -> Orc (Either a Int) accum


p
count p = do
accum <- newTVar 0
readTVar
do x <- p
modifyTVar accum (+1)
return $ Left x
<+>
fmap Right (readTVar accum)

newTVar :: MonadIO io => a -> io (TVar a)


readTVar :: MonadIO io => TVar a -> io a
modifyTVar :: MonadIO io => TVar a -> (a -> a) -> io (a,a)
Control.Concurrent.STM.MonadIO
Orc Laws

Left-Return: (return x >>= k) = k x


Right-Return: (p >>= return) = p

Bind-Associativity: ((p >>= k) >>= h) = (p >>= (k >=> h))

Stop-Identity: p <|> stop = p

Par-Commutativity: p <|> q = q <|> p


Par-Associativity: p <|> (q <|> r) = (p <|> q) <|> r

Left-Zero: (stop >>= k) = stop


Par-Bind: ((p <|> q) >>= k) = ((p >>= k) <|> (q >>= k))
Non-Laws

Bind-Par?: p >>= (\x -> h x <|> k x) = (p >>= h) <|> (p >>= k)


Right-Zero?: p >> stop = stop

p `onlyUntil` done = cut (silent p <|> done)

silent p = p >> stop


Repetition
Re-invoke the Orc argument
after each success

repeating :: Orc a -> Orc a


p
repeating p = do
x <- p
return x <|> repeating p

x
p

The computation bifurcates if


p returns multiple values
x’
Permitting
An Orc term controls the
execution of another

p q
(<#>) :: Orc a -> Orc b -> Orc a
p <#> q = do
end <- newEmptyMVar
(p <+> silent (putMVar end ()))
<|> silent (q `onlyUntil` takeMVar end)

q is run for its effects


q is killed when p finishes
Worked Example
Controlling file downloads

downloads :: [(URL,Path)] -> IO ()


downloads fileList = do
Runs all the downloads
let downloads = map getFile fileList concurrently
runOrc $ msum downloads

getFile :: (URL,Path) -> Orc () IO code lifted into Orc


getFile (url,path) = liftIO $ do
res <- openURIString url
case res of
Left err -> putStrLn (url++": "++err)
Right content -> writeFile ("Files/"++path) content
Bounded
Parallelism
Unbounded parallelism

msum :: [Orc a] -> Orc a


msum ps = foldr (<|>) stop ps

Add a bound

msum’ :: Orc
Int Int -> [Orc
-> [Orc a]Orc
a] -> -> Orc
a a
msum’ bound ps = ...

Using Orc for the bound


allows it to be dynamic
Bounded
Parallelism
msum’ :: Orc Int -> [Orc a] -> Orc a
msum’ bound ps = do
t <- newTVar 0
msum (map (wrap t) ps) <#> setBound t bound

Launch p only if a
wrap :: TVar Int -> Orc a -> Orc a resource is available
wrap t p = do
checkModifyTVar t (>0) (\x->x-1)
p <+> silent (modifyTVar_ t (+1))

setBound :: TVar Int -> Orc Int -> Orc ()


setBound t bound = do
n <- bound Update resource bound
for each new bound
modifyTVar_ t (+n)
Example: file
downloads
downloads :: [(URL,Path)] -> IO ()
downloads fileList = do
let downloads = map getFile fileList
runOrc $ msum’ bounds downloads
Runs all the downloads
concurrently (bounded)
bounds = return 4
Example: file
downloads
downloads :: [(URL,Path)] -> IO ()
downloads fileList = do
let downloads = map getFile fileList
runOrc $ msum’ bounds downloads
Runs all the downloads
concurrently (bounded)
bounds = return 4 <|> promptUser

promptUser :: Orc Int


Dynamic bound
promptUser = do updating
xs <- repeating $
liftIO (putStrLn "Enter bounds changes (+/-) " >> getLine)
return (read xs)
Layered Implementation

• Layered implementation —
layered semantics
– Properties at one level depend
Orc Scripts
on properties at the level below
Orc Monad multiple results
• What properties should Orc terms
HIO Monad thread control
satisfy?
IO Monad external effects – Hence, what properties should
be built into HIO?
Transition Semantics

• Unresolved question: what laws


should the basic operations of the
IO monad satisfy?
Key Definitions
type Orc a = (a -> HIO ()) -> HIO ()

return x = \k -> k x
p >>= h = \k -> p (\x -> h x k)
Discard the
continuation
stop = \k -> return ()
p <|> q = \k -> fork (p k) >> q k Duplicate the
continuation

runOrc p = p (\x -> return ())


liftIO m = \k -> (liftIO m >>= k)

printOrc = runOrc $ do
a <- p
liftIO $ putStrLn ("Ans = " ++ show a)
HIO Monad
~~~~
~~~
~~~~
~~
~~~~ ~~
• Don’t want the programmer to have to do
~
~~
~ explicit thread management
~~~~ ~~
~~~
~~
~~~~
– Nested groups of threads
~~~~
~~~ • Want richer equational theory than IO
~~
~~~~~
~~
– e.g. by managing asynchronous exceptions
~~~
~ ~~
~~ ~~~~~
newtype HIO a =
~~~~ HIO {inGroup
~~~ :: Group -> IO a}
~~~~
type Group = (TVar Int, TVar Inhabitants)
~~~~
~
data Inhabitants ~~= Closed | Open [Entry]
data Entry = Thread ThreadId | Group Group

newPrimGroup :: IO Group
register :: Entry -> Group -> IO ()
killGroup :: Group -> IO ()
increment, decrement, isZero :: Group -> IO ()
Concluding

• Orc in Haskell
– Ready for use today for concurrent scripting
• cabal install orc
– Flexibility of embedded DSLs: discover new idioms
– Design principles emerge
• Two kinds of communications
• Many kinds of state elements

• Ongoing exploration in concurrency


– What are the right abstractions?
• Misra and Cook
– Thanks for their pioneering work on the Orc calculus
Backup
Eagerly Laws

Eagerly-Par: eagerly p >>= (\x -> k x <|> h) = (eagerly p >>= k) <|> h

Eagerly-Swap:
do y <- eagerly p = do x <- eagerly q
x <- eagerly q y <- eagerly p
return (x,y) return (x,y)

Eagerly-IO: eagerly (liftIO m) >> p = (liftIO m >> stop) <|> p


eagerly :: Orc a -> Orc (Orc a) Eagerly
eagerly p = \k -> do
r <- newEmptyMVar
forkM (p (\x -> putMVar r x))
read r
k (liftIO $ readMVarM r)

eagerly p ?
eagerly p
p p

=
k put r k
a

• Give p a continuation that will store its result

• Return the “value” that accesses that result for


the then current continuation
eagerly :: Orc a -> Orc (Orc a)
Eagerly
eagerly p = \k -> do
r <- newEmptyMVar
forkM (p `saveOnce` r))
k (liftIO $ readMVar r)

saveOnce :: Orc a -> MVar a -> HIO ()


p `saveOnce` r = do
p (\x -> putMVar r x)

• Give p a continuation that will store its result (but


once only even if duplicated)
• Return the “value” that accesses that result for
the then current continuation
eagerly :: Orc a -> Orc (Orc a)
Eagerly
eagerly p = \k -> do
r <- newEmptyMVar
forkM (p `saveOnce` r))
k (liftIO $ readMVar r)

saveOnce :: Orc a -> MVar a -> HIO ()


p `saveOnce` r = do
ticket <- newMVar ()
p (\x -> takeMVar ticket >> putMVar r x)

• Give p a continuation that will store its result (but


once only even if duplicated)
• Return the “value” that accesses that result for
the then current continuation
eagerly :: Orc a -> Orc (Orc a)
Eagerly
eagerly p = \k -> do
r <- newEmptyMVar
g <- newGroup
local e $ forkM (p `saveOnce` (r,g))
k (liftIO $ readMVar r)

saveOnce :: Orc a -> (MVar a,Group) -> HIO ()


p `saveOnce` (r,g) = do
ticket <- newMVar ()
p (\x -> takeMVar ticket >> putMVar r x >> close g)

• Give p a continuation that will store its result (but


once only even if duplicated)
• Return the “value” that accesses that result for
the then current continuation
• Thread management can be carried over too
val :: Orc a -> Orc a Val
val p = \k -> do
r <- newEmptyMVar
val p
g <- newGroup
p
local e $ forkM (p `saveOnce` (r,g))
k (unsafePerformIO $ readMVar r)

a
saveOnce :: Orc a -> (MVar a,Group) -> HIO ()
p `saveOnce` (r,g) = do
ticket <- newMVar ()
p (\x -> takeMVar ticket >> putMVar r x >> close g)

• The implementation of val (the alternative that


uses lazy thunks) is almost identical
quotesVal :: Query -> Query -> Orc Quote Web Query
quotesVal srcA srcB = do
quoteA <- val $ getQuote srcA
quoteB <- val $ getQuote srcB
cut ( publish (least quoteA quoteB)
<|> (threshold quoteA)
<|> (threshold quoteB)
<|> (delay 25 >> (publish quoteA <|> publish quoteB))
<|> (delay 30 >> return noQuote))

publish :: NFData a => a -> Orc a


publish x = deepseq x $ return x

• Good: use the lazy values directly


• Bad: have to be careful about evaluation

Você também pode gostar