concurrent orchestration in haskell

34
Concurrent Orchestration in Haskell John Launchbury Trevor Elliott

Upload: don-stewart

Post on 09-Apr-2015

436 views

Category:

Documents


2 download

TRANSCRIPT

Page 1: Concurrent Orchestration in Haskell

Concurrent Orchestration in Haskell

John LaunchburyTrevor Elliott

Page 2: Concurrent Orchestration in Haskell

Motivating Example

Xen hypervisor

Server Client2Client1Helper Tester

• Tester talks with each of the VMs concurrently• Many possible behaviors are “correct” / “incorrect”• Timeouts, VMs dying, etc.• Subtle concurrency bugs in test framework

Page 3: Concurrent Orchestration in Haskell

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

Page 4: Concurrent Orchestration in Haskell

Orc Intuitions

MonadIO MonadPlus

OrcIOliftI

O

List

liftList

putMVarreadTVar

<|>

MonadIO

Page 5: Concurrent Orchestration in Haskell

Basic Examples

fplang :: Orc Stringfplang = return “Haskell” <|> return “ML” <|> return “Scheme”

“Haskell” “ML” “Scheme”

fplang

Page 6: Concurrent Orchestration in Haskell

Basic Examples

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

metronome

delay 2.5()

Page 7: Concurrent Orchestration in Haskell

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!!”

Page 8: Concurrent Orchestration in Haskell

Searchqueens = fmap show (extend []) <|> return ("Computing 8-queens...")

extend :: [Int] -> Orc [Int]extend xs = if length xs == 8 then return xs else do j <- liftList [1..8] guard $ not (conflict xs j) extend (j:xs)

conflict :: [Int] -> Intconflict = ...

Concurrency point

MonadPlus operation

Page 9: Concurrent Orchestration in Haskell

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]":

Page 10: Concurrent Orchestration in Haskell

Orc APInewtype Orc a

return :: a -> Orc a(>>=) :: Orc a -> (a -> Orc b) -> Orc bstop :: Orc a(<|>) :: Orc a -> Orc a -> Orc a

eagerly :: Orc a -> Orc (Orc a)(<+>) :: Orc a -> Orc a -> Orc a

liftIO :: IO a -> Orc arunOrc :: Orc a -> IO ()

Classes: Functor, Monad, Applicative, Alternative, MonadPlus, MonadIO

Page 11: Concurrent Orchestration in Haskell

sync :: (a->b->c) -> Orc a -> Orc b -> Orc csync f p q = do po <- eagerly p qo <- eagerly q return f <*> po <*> qo

notBefore:: Orc a -> Float -> Orc ap `notBefore` w = sync const p (delay w)

• Entering the handle waits for the result

• Synchronization

cut:: Orc a -> Orc acut = join . eagerly

cut:: Orc a -> Orc acut p = do po <- eagerly p po

Using Eagerly

Monadic function application

Page 12: Concurrent Orchestration in Haskell

Web Queryquotes :: Query -> Query -> Orc Quotequotes srcA srcB = do quoteA <- eagerly $ getQuote srcA quoteB <- eagerly $ getQuote srcB cut ( (return least <*> quoteA <*> quoteB) <|> (quoteA >>= threshold) <|> (quoteB >>= threshold) <|> (delay 25 >> (quoteA <|> quoteB)) <|> (delay 30 >> return noQuote))

least x y = if price x < price y then x else ythreshold x = guard (price x < 300) >> return x

A

B

Need to book a ticket, under $300 if

possible…

quote

Page 13: Concurrent Orchestration in Haskell

Using <+>

count :: Orc a -> Orc (Either a Int)count p = do accum <- newTVar 0 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 amodifyTVar :: MonadIO io => TVar a -> (a -> a) -> io (a,a)

p

readTVar

accum

Counting the number of answers

Control.Concurrent.STM.MonadIO

Page 14: Concurrent Orchestration in Haskell

Orc Laws

Left-Return: (return x >>= k) = k xRight-Return: (p >>= return) = pBind-Associativity: ((p >>= k) >>= h) = (p >>= (k >=> h))

Stop-Identity: p <|> stop = pPar-Commutativity: p <|> q = q <|> pPar-Associativity: p <|> (q <|> r) = (p <|> q) <|> r

Left-Zero: (stop >>= k) = stopPar-Bind: ((p <|> q) >>= k) = ((p >>= k) <|> (q >>= k))

Page 15: Concurrent Orchestration in Haskell

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

Page 16: Concurrent Orchestration in Haskell

Repetition

repeating :: Orc a -> Orc arepeating p = do x <- p return x <|> repeating p

p

x p

x’

Re-invoke the Orc argument after each success

The computation bifurcates ifp returns multiple values

Page 17: Concurrent Orchestration in Haskell

Permitting

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

An Orc term controls the execution of another

p q

q is run for its effectsq is killed when p finishes

Page 18: Concurrent Orchestration in Haskell

Worked Example

downloads :: [(URL,Path)] -> IO ()downloads fileList = do let downloads = map getFile fileList runOrc $ msum downloads

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

Runs all the downloads concurrently

IO code lifted into Orc

Controlling file downloads

Page 19: Concurrent Orchestration in Haskell

Bounded Parallelism

msum :: [Orc a] -> Orc amsum ps = foldr (<|>) stop ps

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

Unbounded parallelism

Add a bound

Using Orc for the boundallows it to be dynamic

Page 20: Concurrent Orchestration in Haskell

Bounded Parallelism

msum’ :: Orc Int -> [Orc a] -> Orc amsum’ bound ps = do t <- newTVar 0 msum (map (wrap t) ps) <#> setBound t bound

wrap :: TVar Int -> Orc a -> Orc awrap 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 modifyTVar_ t (+n)

Update resource bound for each new bound

Launch p only if a resource is available

Page 21: Concurrent Orchestration in Haskell

Example: file downloads

downloads :: [(URL,Path)] -> IO ()downloads fileList = do let downloads = map getFile fileList runOrc $ msum’ bounds downloads

bounds = return 4

Runs all the downloads concurrently (bounded)

Page 22: Concurrent Orchestration in Haskell

Example: file downloads

downloads :: [(URL,Path)] -> IO ()downloads fileList = do let downloads = map getFile fileList runOrc $ msum’ bounds downloads

bounds = return 4 <|> promptUser

promptUser :: Orc IntpromptUser = do xs <- repeating $ liftIO (putStrLn "Enter bounds changes (+/-) " >> getLine) return (read xs)

Runs all the downloads concurrently (bounded)

Dynamic bound updating

Page 23: Concurrent Orchestration in Haskell

Layered Implementation

• Layered implementation —layered semantics– Properties at one level depend

on properties at the level below

• What properties should Orc terms satisfy?– Hence, what properties should

be built into HIO?

• Unresolved question: what laws should the basic operations of the IO monad satisfy?

Transition Semantics

IO Monad

HIO Monad

Orc Monad

Orc Scripts

external effects

thread control

multiple results

Page 24: Concurrent Orchestration in Haskell

type Orc a = (a -> HIO ()) -> HIO ()

return x = \k -> k xp >>= h = \k -> p (\x -> h x k)

stop = \k -> return ()p <|> q = \k -> fork (p k) >> q k

runOrc p = p (\x -> return ())liftIO m = \k -> (liftIO m >>= k)

Key Definitions

printOrc = runOrc $ do a <- p liftIO $ putStrLn ("Ans = " ++ show a)

Discard the continuation

Duplicate the continuation

Page 25: Concurrent Orchestration in Haskell

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 Groupregister :: Entry -> Group -> IO ()killGroup :: Group -> IO ()increment, decrement, isZero :: Group -> IO ()

Page 26: Concurrent Orchestration in Haskell

• 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

Concluding

Page 27: Concurrent Orchestration in Haskell

Backup

Page 28: Concurrent Orchestration in Haskell

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

Page 29: Concurrent Orchestration in Haskell

• 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 p = \k -> do r <- newEmptyMVar forkM (p (\x -> putMVar r x)) k (liftIO $ readMVarM r)

put r

p

k

?

read r

k

eagerly p

=

eagerly pp

a

Eagerly

Page 30: Concurrent Orchestration in Haskell

Eagerly

• 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 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)

Page 31: Concurrent Orchestration in Haskell

Eagerly

• 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 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)

Page 32: Concurrent Orchestration in Haskell

Eagerly

• 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

eagerly :: Orc a -> Orc (Orc a)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)

Page 33: Concurrent Orchestration in Haskell

• The implementation of val (the alternative that uses lazy thunks) is almost identical

val :: Orc a -> Orc aval p = \k -> do r <- newEmptyMVar g <- newGroup local e $ forkM (p `saveOnce` (r,g)) k (unsafePerformIO $ 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)

val pp

a

Val

Page 34: Concurrent Orchestration in Haskell

quotesVal :: Query -> Query -> Orc QuotequotesVal 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 apublish x = deepseq x $ return x

• Good: use the lazy values directly• Bad: have to be careful about evaluation

Web Query