[Finish chapter 29 Bryan O'Sullivan **20080818012254] { move ./en/ch29-http-proxy.xml ./en/ch29-stm.xml addfile ./examples/ch29/Check.hs addfile ./examples/ch29/GameInventory.hs addfile ./examples/ch29/GetOpt.hs addfile ./examples/ch29/STMIO.hs addfile ./examples/ch29/STMPlus.hs addfile ./examples/ch29/gameInventory.ghci addfile ./examples/ch29/printf.ghci addfile ./examples/ch29/stm.ghci addfile ./web/rwh-200.jpg hunk ./en/00book.xml 39 - + hunk ./en/Makefile 46 + $(obj-websup)/rwh-200.jpg \ hunk ./en/Makefile 279 +vpath %.jpg ../web hunk ./en/Makefile 335 + cp $< $@ + +$(obj-websup)/%.jpg: %.jpg + @mkdir -p $(dir $@) hunk ./en/book-shortcuts.xml 54 +STM"> hunk ./en/book-shortcuts.xml 77 +atomically"> hunk ./en/book-shortcuts.xml 143 +orElse"> hunk ./en/book-shortcuts.xml 155 +retry"> hunk ./en/ch08-io.xml 1533 - options, you may find it useful. + options, you may find it useful. You can find an example of its + use in . hunk ./en/ch25-concurrent.xml 483 - + hunk ./en/ch25-concurrent.xml 570 - XXX. + . hunk ./en/ch29-stm.xml 3 - + hunk ./en/ch29-stm.xml 6 - Concurrent software is notoriously difficult to write. In a single-thread + In the traditional threaded model of concurrent programming, + when we share data among threads, we keep it consistent using + locks, and we notify threads of changes using condition variables. + Haskell's MVar mechanism improves somewhat upon these + tools, but it still suffers from all of the same problems. + + + + Race conditions due to forgotten locks + + + Deadlocks resulting from inconsistent lock ordering + + + Corruption caused by uncaught exceptions + + + Lost wakeups induced by omitted notifications + + + + These problems frequently affect even the smallest concurrent + programs, but the difficulties they pose become far worse in + larger code bases, or under heavy load. + + For instance, a program with a few big locks is somewhat + tractable to write and debug, but contention for those locks will + clobber us under heavy load. If we react with finer-grained + locking, it becomes far harder to keep our + software working at all. The additional book-keeping will hurt + performance even when loads are light. + + + The basics + + Software transactional memory (STM) gives us a few simple, + but powerful, tools with which we can address most of these + problems. We execute a block of actions using the &atomically; + combinator. Once we enter the block, other threads cannot see + any modifications we make until we exit: our execution is + isolated. Upon exit, only one of the + following things can occur. + + + + If no other thread concurrently modified the same data + as us, all of our modifications will simultaneously become + visible to other threads. + + + Otherwise, our modifications are discarded without being + performed, and our block of actions is automatically + restarted. + + + + This all-or-nothing nature of an &atomically; block is + referred to as atomic, hence the name of + the combinator. + + Atomicity and isolation work together to give every thread a + consistent view of our program's shared, + mutable state. If you have used databases that support + transactions, you should find that working with STM feels quite + familiar. + + + Some simple examples + + To explore the world of STM, let's start with a few simple + functions, and refine them as we learn more about the API. In a + multi-player role playing game, a player's character will have + some state such as health, possessions, and money. + + The STM API is provided by the stm package, and + its modules are in the Control.Concurrent.STM + hierarchy. + + &GameInventory.hs:import; + + The TVar parameterized type is a mutable + variable that we can read or write inside an + atomically block. For simplicity, we + represent a player's inventory as a list of items. Notice, too, + that we use &newtype; declarations so that we cannot + accidentally confuse wealth with health. + + To perform a basic transfer of money from one + Balance to another, all we have to do is adjust the + values in each TVar. + + &GameInventory.hs:basicTransfer; + + Let's write a small function to try this out. + + &GameInventory.hs:transferTest; + + If we run this in &ghci;, it behaves as we should + expect. + + &gameInventory.ghci:transferTest; + + The properties of atomicity and isolation guarantee that if + another thread sees a change in bob's balance, they + will also be able to see alice's balance + modified. + + Even in a concurrent program, we strive to keep as much of + our code as possible purely functional, since this makes it + easier both to reason about and to test. Here's a function that + removes an item from the list we use to represent a player's + inventory. + + &GameInventory.hs:removeInv; + + The result is mapped in Maybe so that we can + tell whether the item was actually present in the player's + inventory. + + Here is a function to give an item to another player. It is + slightly complicated by the need to determine whether the donor + actually has the item in question. + + &GameInventory.hs:maybeGiveItem; + + + + STM and safety + + If we are to provide atomic, isolated transactions, it is + critical that we cannot either deliberately or accidentally escape + from an &atomically; block. Haskell's type system enforces this + on our behalf, via the &STM; monad. + + &gameInventory.ghci:atomically; + + The action that the &atomically; block takes as its + parameter executes in the &STM; monad, and its result is made + available to us in the &IO; monad. The functions that we have + seen for manipulating TVar values operate in the + &STM; monad. + + &gameInventory.ghci:stm; + + This is also the case for the functions we defined + earlier. + + &GameInventory.hs:types; + + The &STM; monad does not let us perform I/O or manipulate + non-STM shared state such as MVar values. + + + + Retrying a transaction + + Our maybeGiveItem function is somewhat + awkward in its API. It only gives an item if the character + actually possesses it, which is reasonable. By returning a + Bool, it complicates the code of its callers. Here + is an item sale function that has to look at the result of + maybeGiveItem to decide what to do + next. + + &GameInventory.hs:maybeSellItem; + + The STM API provides a &retry; action which will immediately + terminate an &atomically; block that cannot proceed. As the + name suggests, execution of the block is restarted from scratch. + Here is a rewrite of maybeGiveItem to use + &retry;. + + &GameInventory.hs:giveItem; + + Our basicTransfer from earlier had a + different kind of flaw: it did not check the sender's balance to + see if it was sufficient to transfer. We + can use &retry; to correct this, while keeping the function's + type the same. + + &GameInventory.hs:transfer; + + Now that we are using &retry;, our item sale function + becomes dramatically simpler. + + &GameInventory.hs:sellItem; + + Its behavior is slightly different from our earlier + function. Instead of immediately returning &False; if the + seller doesn't have the item, it will block (if necessary) until + both the seller has the item and the buyer has enough money to + pay for it. + + The beauty of STM lies in the cleanliness of the code it + lets us write. We can take two functions that work correctly, + and use them to create a third that will also behave + itself, all with minimal effort. + + + What happens when we retry? + + In addition to the clean code that &retry; makes possible, + its underlying behavior seems nearly magical. If we call it, + it blocks our thread until one or more of the variables that + we touched before calling &retry; is changed by another + thread. + + For instance, if we invoke transfer + with insufficient funds, &retry; will automatically + wait until our balance changes before it starts + the &atomically; block again. The same happens with our new + giveItem function: if the sender doesn't + currently have the item in their inventory, the thread will + block until they do. + + + + + Choosing between alternatives + + We don't always want to restart an &atomically; action if it + calls &retry; or fails due to concurrent modification by another + thread. For instance, our new sellItem + function will retry indefinitely as long as we are missing + either the item or enough money, but we might prefer to just try + the sale once. + + The &orElse; combinator lets us perform a + backup action if the main one fails. + + &gameInventory.ghci:orElse; + + If sellItem fails, then &orElse; will + invoke the return False action, causing our sale + function to return immediately. + + + Higher order programming + + Imagine that we'd like to be a little more ambitious, and + buy the first item from a list that is both in the possession + of the seller and affordable to us, but do nothing if we + cannot afford something right now. We could of course write + code to do this in a direct manner. + + &GameInventory.hs:crummyList; + + This function suffers from the familiar problem of + muddling together what we want to do with how we ought to do + it. A little inspection suggests that there are two patterns + buried in this code which we can use in reusable forms. + + The first of these is to make a transaction fail + immediately, instead of retrying. + + &GameInventory.hs:maybeSTM; + + Secondly, we want to try an action over successive + elements of a list, stopping at the first that succeeds, or + performing a &retry; if every one fails. Conveniently for us, + &STM; is an instance of the MonadPlus + typeclass. + + &STMPlus.hs:instance; + + The Control.Monad module defines the + msum function as follows, which is + exactly what we need. + + &STMPlus.hs:msum; + + We now have a few key pieces of machinery that will help + us to write a much clearer version of our function. + + &GameInventory.hs:shoppingList; + + + + + + I/O and STM + + The &STM; monad forbids us from performing arbitrary I/O + actions because they can break the guarantees of atomicity and + isolation that the monad provides. Of course the need to + perform I/O still arises; we just have to treat it + differently. + + Most often, we will need to perform some I/O action as a + result of a decision we made inside an &atomically; block. In + these cases, the right thing to do is usually to return a piece + of data from &atomically;, which will tell the caller in the + &IO; monad what to do next. Indeed, since actions in monads are + first class values, we can if we wish return the &IO; action to + perform as the result of &atomically;, and use + join to execute it once we return to the + &IO; monad. + + &STMIO.hs:someTransaction; + + We occasionally need to perform an I/O operation from within + &STM;. For instance, reading immutable data from a file that + must exist does not violate the &STM; guarantees of isolation or + atomicity. In these cases, we can use + unsafeIOToSTM to execute an &IO; action. + This function is exported by the low-level GHC.Conc + module, so we must go out of our way to use it. + + &stm.ghci:unsafeIOToSTM; + + The &IO; action that we execute must not start another + &atomically; transaction. If a thread tries to nest + transactions, the runtime system will throw an exception. + + Since the type system can't help us to ensure that our &IO; + code is doing something sensible, we will be safest if we limit + our use of unsafeIOToSTM as much as + possible. Here is a typical error that can arise with &IO; + in an &atomically; block. + + &STMIO.hs:bad; + + If the mightRetry block causes our + transaction to restart, we will call + launchTorpedoes more than once. + + + Creating new top-level TVars + + If we are outside the &STM; monad, we can still create new + TVar values in the &IO; monad using the + newTVarIO function. This is occasionally + useful. + + + + + Communication between threads + + As well as the basic TVar type, the + stm package provides two types that are more useful + for communicating between threads. A TMVar is the + STM equivalent of an MVar: it can hold either + Just a value, or Nothing. The + TChan type is the STM counterpart of + Chan, and implements a typed FIFO channel. + + + + A concurrent web link checker + + As a practical example of using STM, we will develop a + program that checks an HTML file for broken links, that is, URLs + that either point to bad web pages or dead servers. This is a + good problem to address via concurrency: if we try to talk to a + dead server, it will take up to two minutes before our + connection attempt times out. If we use multiple threads, we + can still get useful work done while one or two are stuck + talking to slow or dead servers. + + We can't simply create one thread per URL, because that may + overburden either our CPU or our network connection if (as we + expect) most of the links are live and responsive. Instead, we + use a fixed number of worker threads, which fetch URLs to + download from a queue. + + &Check.hs:top; + + Our &main; function provides the top-level scaffolding for + our program. + + &Check.hs:main; + + Notice that we use the printf function + to print a report at the end. Unlike its counterpart in C, the + Haskell printf function can check its + argument types, and their number, at runtime. + + &printf.ghci:printf; + + Supporting &main; are several short functions. + + &Check.hs:modifyTVar_; + + The forkTimes function starts a number + of identical worker threads, and decreases the + alive count each time a thread exits. We use a + finally combinator to ensure that the count + is decremented, no matter whether the thread exits normally or + is killed by an uncaught exception. + + Next, the writeBadLinks function prints + each broken or dead link to stdout. + + &Check.hs:writeBadLinks; + + It uses the forever combinator, which + repeats an action endlessly. + + Our waitFor function uses + check, which calls + retry if its argument evaluates to + False. + + &Check.hs:waitFor; + + + Checking a link + + To check the status of a link, we perform a HEAD request + against it. + + &Check.hs:getStatus; + + + + Worker threads + + Each worker thread reads a task off the shared queue. It + either checks the given URL or exits. + + &Check.hs:worker; + + + + Finding links + + We structure our link finding around a state monad + transformer stacked on &IO;. Our state tracks links that we + have already seen (so we don't check a repeated link more than + once), the total number of links we have encountered, and the + queue to which we should add the links that we will be + checking. + + &Check.hs:Job; + + Strictly speaking, for a small standalone program, we + don't need the &newtype; wrapper, but we include it here for + practice. + + The &main; function maps checkURLs + over each input file, so checkURLs only + needs to read a single file. + + &Check.hs:checkURLs; + + Our extractLinks function doesn't + attempt to properly parse a HTML or text file. Instead, it + looks for strings that appear to be URLs, and treats them as + good enough. + + &Check.hs:extractLinks; + + + + + Command line parsing + + To parse our command line arguments, we use the + System.Console.GetOpt module. It provides useful + code for parsing arguments, but it is slightly involved to + use. + + &Check.hs:parseArgs; + + The getOpt function takes three + arguments. + + + + An argument ordering, which specifies whether options + can be mixed with other arguments (Permute, + which we use above) or must appear before them. + + + A list of option definitions. Each consists of a list + of short names for the option, a list of long names for + the option, a description of the option (e.g. whether it + accepts an argument), and an explanation for users. + + + A list of the arguments and options, as returned by + getArgs. + + + + The function returns a triple which consists of the parsed + options, the remaining arguments, and any error messages that + arose. + + We use the Flag algebraic data type to + represent the options our program can accept. + + &Check.hs:options; + + Our options list describes each option + that we accept. Each description must be able to create a + Flag value. Take a look at our uses of + NoArg and ReqArg above. These are + constructors for the GetOpt module's + ArgDescr type. + + &GetOpt.hs:ArgDescr; + + + + The NoArg constructor accepts a parameter + that will represent this option. In our case, if a user + invokes our program with or + , we will use the value + Help. + + + + The ReqArg constructor accepts a function + that maps a required argument to a value. Its second + argument is used when printing help. Here, we convert a + string into an integer, and pass it to our + Flag type's N + constructor. + + + + The OptArg constructor is similar to the + ReqArg constructor, but it permits the use of + options that can be used without arguments. + + + + + + + Practical aspects of STM + + We have so far been quiet about the specific benefits that + STM gives us. Most obvious is how well it + composes: to add code to a transaction, we + just use our usual monadic building blocks, &bind; and &bind_;. + The &STM; monad prevents us from accidentally performing + non-transactional I/O actions. We don't need to worry about + lock ordering, since our code contains no locks. We can forget + about lost wakeups, since we don't have condition variables. If + an exception is thrown, we can either catch it using + catchSTM, or be bounced out of our + transaction, leaving our state untouched. Finally, + theretry and orElse + functions give us some beautiful ways to structure our + code. + + + Getting comfortable with giving up control + + Whether with concurrency or memory management, there will + be times when we must retain control: some software must make + solid guarantees about latency or memory footprint, so we will + be forced to spend the extra time and effort managing and + debugging explicit code. For many interesting, practical uses + of software, garbage collection and STM will do more than well + enough. + + STM is not a complete panacea. It is useful to compare it + with the use of garbage collection for memory management. When + we abandon explicit memory management in favour of garbage + collection, we give up control in return for safer code. + Likewise, with STM, we abandon the low-level details, in + exchange for code that we can better hope to + understand. + + + + Using invariants + + STM cannot eliminate certain classes of bug. For + instance, if we withdraw money from an account in one + &atomically; block, return to the &IO; monad, then deposit it + to another account in a different &atomically; block, our code + will have an inconsistency. There will be a window of time in + which the money is present in neither account. + + &GameInventory.hs:bogusSale; + + In concurrent programs, these kinds of programs are + notoriously difficult to find and reproduce. For instance, + the inconsistency that we describe above will usually only + occur for a brief period of time. Problems like this often + refuse to show up during development, instead only occurring + in the field, under heavy load. + + The alwaysSucceeds function let us + define an invariant, a property of our + data that must always be true. + + &stm.ghci:alwaysSucceeds; + + When we create an invariant, it will immediately be + checked. To fail, the invariant must raise an + exception. More interestingly, the invariant will + subsequently be checked automatically at the end of + every transaction. If it fails at any + point, the transaction will be aborted, and the exception + raised by the invariant will be propagated. This means that + we will get immediate feedback as soon as one of our + invariants is violated. + + For instance, here are a few functions to populate our + game world from the beginning of this chapter with + players. + + &GameInventory.hs:newPlayer; + + This function returns an invariant that we can use to + ensure that the world's money balance is always + consistent: the balance at any point in time should be the + same as at the creation of the world. + + &GameInventory.hs:consistentBalance; + + Let's write a small function that exercises this. + + &GameInventory.hs:tryBogusSale; + + If we run it in &ghci;, it should detect the inconsistency + caused by our incorrect use of &atomically; in the + bogusTransfer function we wrote. + + &lameInventory.ghci:bogus; + + + hunk ./examples/ch29/Check.hs 1 +----------------------------------------------------------------------------- +-- | +-- Module : UrlCheck.hs +-- Copyright : (c) Don Stewart 2006 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : dons@cse.unsw.edu.au +-- Stability : stable +-- Portability : portable +-- +----------------------------------------------------------------------------- + +{-- snippet top --} +{-# LANGUAGE FlexibleContexts, GeneralizedNewtypeDeriving, + PatternGuards #-} + +import Control.Concurrent (forkIO) +import Control.Concurrent.STM +import Control.Exception (catch, finally) +import Control.Monad.State +import Data.Char (isControl) +import Data.List (nub) +import Network.URI +import Prelude hiding (catch) +import System.Console.GetOpt +import System.Environment (getArgs) +import System.Exit (ExitCode(..), exitWith) +import System.IO (hFlush, hPutStrLn, stderr, stdout) +import Text.Printf (printf) +import qualified Data.ByteString.Lazy.Char8 as B +import qualified Data.Set as S + +-- This requires the HTTP package, which is not bundled with GHC +import Network.HTTP + +type URL = B.ByteString + +data Task = Check URL | Done +{-- /snippet top --} + +{-- snippet main --} +main :: IO () +main = do + (files,k) <- parseArgs + let n = length files + + -- count of broken links + badCount <- newTVarIO (0 :: Int) + + -- for reporting broken links + badLinks <- newTChanIO + + -- for sending jobs to workers + jobs <- newTChanIO + + -- the number of workers currently running + workers <- newTVarIO k + + -- one thread reports bad links to stdout + forkIO $ writeBadLinks badLinks + + -- start worker threads + forkTimes k workers (worker badLinks jobs badCount) + + -- read links from files, and enqueue them as jobs + stats <- execJob (mapM_ checkURLs files) + (JobState S.empty 0 jobs) + + -- enqueue "please finish" messages + atomically $ replicateM_ k (writeTChan jobs Done) + + waitFor workers + + broken <- atomically $ readTVar badCount + + printf fmt broken + (linksFound stats) + (S.size (linksSeen stats)) + n + where + fmt = "Found %d broken links. " ++ + "Checked %d links (%d unique) in %d files.\n" +{-- /snippet main --} + +{-- snippet modifyTVar_ --} +modifyTVar_ :: TVar a -> (a -> a) -> STM () +modifyTVar_ tv f = readTVar tv >>= writeTVar tv . f + +forkTimes :: Int -> TVar Int -> IO () -> IO () +forkTimes k alive act = replicateM_ k . forkIO $ act + `finally` + (atomically $ modifyTVar_ alive (subtract 1)) +{-- /snippet modifyTVar_ --} + +{-- snippet writeBadLinks --} +writeBadLinks :: TChan String -> IO () +writeBadLinks c = + forever $ + atomically (readTChan c) >>= putStrLn >> hFlush stdout +{-- /snippet writeBadLinks --} + +{-- snippet waitFor --} +waitFor :: TVar Int -> IO () +waitFor alive = atomically $ do + count <- readTVar alive + check (count == 0) +{-- /snippet waitFor --} + +{-- snippet getStatus --} +getStatus :: URI -> IO (Either String Int) +getStatus = chase (5 :: Int) + where + chase 0 _ = bail "too many redirects" + chase n u = do + resp <- getHead u + case resp of + Left err -> bail (show err) + Right r -> + case rspCode r of + (3,_,_) -> + case findHeader HdrLocation r of + Nothing -> bail (show r) + Just u' -> + case parseURI u' of + Nothing -> bail "bad URL" + Just url -> chase (n-1) url + (a,b,c) -> return . Right $ a * 100 + b * 10 + c + + getHead uri = simpleHTTP request + where + request = Request { rqURI = uri, + rqMethod = HEAD, + rqHeaders = [], + rqBody = "" } + bail = return . Left +{-- /snippet getStatus --} + +{-- snippet worker --} +worker :: TChan String -> TChan Task -> TVar Int -> IO () +worker badLinks jobQueue badCount = loop + where + loop = do + job <- atomically $ readTChan jobQueue + case job of + Done -> return () + Check x -> run (B.unpack x) >> loop + + run url = case parseURI url of + Just uri -> do + code <- getStatus uri `catch` (return . Left . show) + case code of + Right 200 -> return () + Right n -> report (show n) + Left err -> report err + _ -> report "invalid URL" + + where report s = atomically $ do + modifyTVar_ badCount (+1) + writeTChan badLinks (url ++ " " ++ s) +{-- /snippet worker --} + +{-- snippet Job --} +data JobState = JobState { linksSeen :: S.Set URL, + linksFound :: Int, + linkQueue :: TChan Task } + +newtype Job a = Job { runJob :: StateT JobState IO a } + deriving (Monad, MonadState JobState, MonadIO) + +execJob :: Job a -> JobState -> IO JobState +execJob = execStateT . runJob +{-- /snippet Job --} + +{-- snippet checkURLs --} +checkURLs :: FilePath -> Job () +checkURLs f = do + src <- liftIO $ B.readFile f + let urls = extractLinks src + filterM seenURI urls >>= sendJobs + updateStats (length urls) + +updateStats :: Int -> Job () +updateStats a = modify $ \s -> + s { linksFound = linksFound s + a } + +-- | Add a link to the set we have seen. +insertURI :: URL -> Job () +insertURI c = modify $ \s -> + s { linksSeen = S.insert c (linksSeen s) } + +-- | If we have seen a link, return False. Otherwise, record that we +-- have seen it, and return True. +seenURI :: URL -> Job Bool +seenURI url = do + seen <- (not . S.member url) `liftM` gets linksSeen + insertURI url + return seen + +sendJobs :: [URL] -> Job () +sendJobs js = do + c <- gets linkQueue + liftIO . atomically $ mapM_ (writeTChan c . Check) js +{-- /snippet checkURLs --} + +{-- snippet extractLinks --} +extractLinks :: B.ByteString -> [URL] +extractLinks = concatMap uris . B.lines + where uris s = filter looksOkay (B.splitWith isDelim s) + isDelim c = isControl c || c `elem` " <>\"{}|\\^[]`" + looksOkay s = http `B.isPrefixOf` s + http = B.pack "http:" +{-- /snippet extractLinks --} + +{-- snippet parseArgs --} +data Flag = Help | N Int + deriving Eq + +parseArgs :: IO ([String], Int) +parseArgs = do + argv <- getArgs + case parse argv of + ([], files, []) -> return (nub files, 16) + (opts, files, []) + | Help `elem` opts -> help + | [N n] <- filter (/=Help) opts -> return (nub files, n) + (_,_,errs) -> die errs + where + parse argv = getOpt Permute options argv + header = "Usage: urlcheck [-h] [-n n] [file ...]" + info = usageInfo header options + dump = hPutStrLn stderr + die errs = dump (concat errs ++ info) >> exitWith (ExitFailure 1) + help = dump info >> exitWith ExitSuccess +{-- /snippet parseArgs --} + +{-- snippet options --} +options :: [OptDescr Flag] +options = [ Option ['h'] ["help"] (NoArg Help) + "Show this help message", + Option ['n'] [] (ReqArg (\s -> N (read s)) "N") + "Number of concurrent connections (default 16)" ] +{-- /snippet options --} hunk ./examples/ch29/GameInventory.hs 1 +{-- snippet import --} +-- file: GameInventory.hs +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +import Control.Concurrent.STM +import Control.Monad + +data Item = Scroll + | Wand + | Banjo + deriving (Eq, Ord, Show) + +newtype Gold = Gold Int + deriving (Eq, Ord, Show, Num) + +newtype HitPoint = HitPoint Int + deriving (Eq, Ord, Show, Num) + +type Inventory = TVar [Item] +type Health = TVar HitPoint +type Balance = TVar Gold + +data Player = Player { + balance :: Balance, + health :: Health, + inventory :: Inventory + } +{-- /snippet import --} + +{-- snippet removeInv --} +removeInv :: Eq a => a -> [a] -> Maybe [a] +removeInv x xs = + case takeWhile (/= x) xs of + (_:ys) -> Just ys + [] -> Nothing +{-- /snippet removeInv --} + +{-- snippet basicTransfer --} +basicTransfer qty fromBal toBal = do + fromQty <- readTVar fromBal + toQty <- readTVar toBal + writeTVar fromBal (fromQty - qty) + writeTVar toBal (toQty + qty) +{-- /snippet basicTransfer --} + +{-- snippet transfer --} +transfer :: Gold -> Balance -> Balance -> STM () + +transfer qty fromBal toBal = do + fromQty <- readTVar fromBal + when (qty > fromQty) $ + retry + writeTVar fromBal (fromQty - qty) + readTVar toBal >>= writeTVar toBal . (qty +) +{-- /snippet transfer --} + +transferTest :: STM (Gold, Gold) +{-- snippet transferTest --} +transferTest = do + alice <- newTVar 12 + bob <- newTVar 4 + basicTransfer 3 alice bob + liftM2 (,) (readTVar alice) (readTVar bob) +{-- /snippet transferTest --} + +{-- snippet types --} +basicTransfer :: Gold -> Balance -> Balance -> STM () +maybeGiveItem :: Item -> Inventory -> Inventory -> STM Bool +{-- /snippet types --} + +{-- snippet maybeGiveItem --} +maybeGiveItem item fromInv toInv = do + fromList <- readTVar fromInv + case removeInv item fromList of + Nothing -> return False + Just newList -> do + writeTVar fromInv newList + readTVar toInv >>= writeTVar toInv . (item :) + return True +{-- /snippet maybeGiveItem --} + +{-- snippet giveItem --} +giveItem :: Item -> Inventory -> Inventory -> STM () + +giveItem item fromInv toInv = do + fromList <- readTVar fromInv + case removeInv item fromList of + Nothing -> retry + Just newList -> do + writeTVar fromInv newList + readTVar toInv >>= writeTVar toInv . (item :) +{-- /snippet giveItem --} + +{-- snippet maybeSellItem --} +maybeSellItem :: Item -> Gold -> Player -> Player -> STM Bool +maybeSellItem item price buyer seller = do + given <- maybeGiveItem item (inventory seller) (inventory buyer) + if given + then do + basicTransfer price (balance buyer) (balance seller) + return True + else return False +{-- /snippet maybeSellItem --} + +{-- snippet sellItem --} +sellItem :: Item -> Gold -> Player -> Player -> STM () +sellItem item price buyer seller = do + giveItem item (inventory seller) (inventory buyer) + transfer price (balance buyer) (balance seller) +{-- /snippet sellItem --} + +{-- snippet trySellItem --} +trySellItem :: Item -> Gold -> Player -> Player -> STM Bool +trySellItem item price buyer seller = + sellItem item price buyer seller >> return True + `orElse` + return False +{-- /snippet trySellItem --} + +{-- snippet crummyList --} +crummyList :: [(Item, Gold)] -> Player -> Player + -> STM (Maybe (Item, Gold)) +crummyList list buyer seller = go list + where go [] = return Nothing + go (this@(item,price) : rest) = do + sellItem item price buyer seller + return (Just this) + `orElse` + go rest +{-- /snippet crummyList --} + +{-- snippet shoppingList --} +shoppingList :: [(Item, Gold)] -> Player -> Player + -> STM (Maybe (Item, Gold)) +shoppingList list buyer seller = maybeSTM . msum $ map sellOne list + where sellOne this@(item,price) = do + sellItem item price buyer seller + return this +{-- /snippet shoppingList --} + +{-- snippet maybeSTM --} +maybeSTM :: STM a -> STM (Maybe a) +maybeSTM m = (Just `liftM` m) `orElse` return Nothing +{-- /snippet maybeSTM --} + +{-- snippet bogusSale --} +bogusTransfer qty fromBal toBal = do + fromQty <- atomically $ readTVar fromBal + -- window of inconsistency + toQty <- atomically $ readTVar toBal + atomically $ writeTVar fromBal (fromQty - qty) + -- window of inconsistency + atomically $ writeTVar toBal (toQty + qty) + +bogusSale :: Item -> Gold -> Player -> Player -> IO () +bogusSale item price buyer seller = do + atomically $ giveItem item (inventory seller) (inventory buyer) + bogusTransfer price (balance buyer) (balance seller) +{-- /snippet bogusSale --} + +{-- snippet newPlayer --} +newPlayer :: Gold -> HitPoint -> [Item] -> STM Player +newPlayer balance health inventory = + Player `liftM` newTVar balance + `ap` newTVar health + `ap` newTVar inventory + +populateWorld :: STM [Player] +populateWorld = sequence [ newPlayer 20 20 [Wand, Banjo], + newPlayer 10 12 [Scroll] ] +{-- /snippet newPlayer --} + +{-- snippet consistentBalance --} +consistentBalance :: [Player] -> STM (STM ()) +consistentBalance players = do + initialTotal <- totalBalance + return $ do + curTotal <- totalBalance + when (curTotal /= initialTotal) $ + error "inconsistent global balance" + where totalBalance = foldM addBalance 0 players + addBalance a b = (a+) `liftM` readTVar (balance b) +{-- /snippet consistentBalance --} + +{-- snippet tryBogusSale --} +tryBogusSale = do + players@(alice:bob:_) <- atomically populateWorld + atomically $ alwaysSucceeds =<< consistentBalance players + bogusSale Wand 5 alice bob +{-- /snippet tryBogusSale --} hunk ./examples/ch29/GetOpt.hs 1 +{-- snippet ArgDescr --} +data ArgDescr a = NoArg a + | ReqArg (String -> a) String + | OptArg (Maybe String -> a) String +{-- /snippet ArgDescr --} hunk ./examples/ch29/STMIO.hs 1 +import Control.Concurrent.STM +import Control.Monad +import GHC.Conc + +someAction = undefined + +{-- snippet someTransaction --} +stmTransaction :: STM (IO a) +stmTransaction = return someAction + +doSomething :: IO a +doSomething = do + ioAction <- atomically stmTransaction + join ioAction +{-- /snippet someTransaction --} + +launchTorpedoes = undefined +doStuff = undefined +mightRetry = undefined +{-- snippet bad --} +launchTorpedoes :: IO () + +notActuallyAtomic = do + doStuff + unsafeIOToSTM launchTorpedoes + mightRetry +{-- /snippet bad --} hunk ./examples/ch29/STMPlus.hs 1 +{-- snippet instance --} +instance MonadPlus STM where + mzero = retry + mplus = orElse +{-- /snippet instance --} + +{-- snippet msum --} +msum :: MonadPlus m => [m a] -> m a +msum = foldr mplus mzero +{-- /snippet msum --} hunk ./examples/ch29/gameInventory.ghci 1 +--# transferTest +:load GameInventory +atomically transferTest + +--# atomically +:type atomically + +--# stm +:type newTVar +:type readTVar +:type writeTVar + +--# orElse +:type orElse hunk ./examples/ch29/printf.ghci 1 +--# printf +:m +Text.Printf +printf "%s" (True) +printf "%d and %d\n" (3::Int) +printf "%s and %d\n" "foo" (3::Int) hunk ./examples/ch29/stm.ghci 1 +:m +Control.Concurrent.STM + +--# unsafeIOToSTM +:m +GHC.Conc +:type unsafeIOToSTM + +--# alwaysSucceeds +:type alwaysSucceeds hunk ./web/index.html.in 12 -

This is the online home of the book “Real World Haskell”. We - are currently writing the book, and regularly post early drafts of beta chapters for public - review. Please let us know what you think of our work!

+ + Real World Haskell book cover + + +

This is the online home of the book “Real World Haskell”. We + are currently finishing the book, and regularly post drafts of beta chapters for public + review. Please let us know what you think of our work!

hunk ./web/index.html.in 22 -

The book will be published by O'Reilly Media. A - publication date has not yet been set.

+

The book will be published by O'Reilly Media. A + final publication date has not yet been set, but we expect it to + be available around the end of October.

hunk ./web/index.html.in 27 -

Please visit - our blog for news about our progress.

+

Please visit + our blog for news about our progress.

+
+ +

Buy online

+ + + +

What's that creature on the cover?

+ +

The illustration on our cover is of a Hercules + beetle. These beetles are among the largest in the world. + They are also, in proportion to their size, the strongest + animals on Earth, able to lift up to 850 times their own weight.

+ binary ./web/rwh-200.jpg oldhex * newhex *ffd8ffe000104a46494600010101004800480000ffdb0043000604050605040606050607070608 *0a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29 *191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a282828282828282828 *282828282828282828282828282828282828282828282828282828282828282828282828282828 *2828ffc0001108010700c803012200021101031101ffc4001c0001000202030100000000000000 *000000000607020501040803ffc400511000010303020207020907090507050000010203040005 *110621123107133241516171228114161723559193a1d1081542547494b135363752628292b2f0 *243344c1d243457273a2c2e12634536364ffc4001a010100030101010000000000000000000000 *010203040506ffc4002d1101000201020502060202030000000000000102030411121314515205 *211531323341712261428191a1b1ffda000c03010002110311003f00f523684f00d872ad56a4d3 *d0350c24c4b936b5321616021652723cc7ad6e1bec0f4159522764c4cc4ef0807c94e98fd5e4fe *f0aa7c94e98fd5e4fef0aa9fd2afccb776bd465f29403e4a74c7eaf27f78553e4a74c7ead27f78 *57e353fa53996ee75197c901f929d31fabc9fde1543d14e981ff000d27f7857e353ea11914e65b *b9d465f2955d33416908f21d64c696a2ca50a78890ac3614703393cf6e437fbaba8ee91d0cd3ed *b603eb4ac2f896990bc23871907cf71b73ab3a4dae2497bad7986d6e1001511cf19c7d5935f045 *82da8712e261b095857105040041f1cfba9ccb773a8cbe4afa4e88d1d1a6fc19e8d312a2843814 *5f560a55c5b8df3b701cfa8ae4689d0ea61f79bebd6865214be17d679a8a463c72a4902ac77ed7 *1243ab71f61b71c584a54a52724819c0ff00d4afacd60dd9a0b4d3ad37159436ef6d2940015b92 *3ef24d3996ee75197c95cbba2b45b0e755319931de040e0548513be3faa4e398ff00445613b46e *8a8888ab31e63889292b4292fab64829049c918dd491efab1d362b725d2e086c758772a29c93d9 *effeea7fc228ed8edeea5b4bb118586901b402804252304271e1b0faa9ccb773a8cbe4ad3e29e8 *6128b7d5c9eac01877af5709273b0df24ec3fc42bb4ce8ad0ef3adb4d07d4b70e1203ce6fbe3f8 *8ab00d8adc780986c128c709e1dd38c6307fba9faabeccdaa232f25d6a3b68713c402929c1f68e *4fd669ccb773a8cbe4ae20e87d17325aa2b6cca0f85a90125f5fb582a19cf2c7b2afaab6df253a *63f5693fbc2aa6116d10623c97634565a7120a429290080719fe03eaaefd3996ee75197ca5011d *14e98fd5a4fef0aa7c94e97fd5a4fef0afc6a7d4a732ddcea32f94a027a29d307fe1e4fef0aae3 *e4a74c7eaf27f78554fe94e65bb9d465f29403e4a74bfeaf27f78554934de9cb7e9d86b8b6c6d6 *9656b2e10b5959e2200e67d2b774a89bccfcd4be5bde36b4be4b42784ec2959b9d934aaa837d81 *e959562df607a56540a52940a52940a52940a52940a52940a52940a52940a52940a52940a52940 *a529418b9d934a39d934a037d81e959562d7607a56321e430d2dc755c28424a947c00a0fa52b5d *6dbd5bee59f80ca69f210973093fa0aecabd0e0e0d778b83bb9d0674ad58bf5bcda45c95202219 *570f5ab4948cf170f7f9ed5f31a92d254e244e6896d450ac64f0a82b8483e7c5b7ad06e295f30e *0c6735d26af111d8d2e421c3d4c55ad0ea8a08c1476bbb7c79506c695f08129b9b0d992c125979 *097104820949191b1e5b1afbd0294a50294a50294a50294a50294a50294a50294a5062e764d28e *764d28386ffdd8f4ad16b76e7c8d39362da9b5ae549475095254016c2b652f7239024fae2b7cd7 *607a5407a65b84cb6e9869eb7c97633a64a5056dab048c1daad5af14ecd31639cb78a47e5d01a7 *6f4d4ee0ea56b60a9d60be95232a6863e0e0a72004a12a58c63b5be0d7c9db36a74b519688af3a *fc5548524b92812be04a911c73ece0a5473ba940938aaafe36ea1fa6677da1a7c6ed43f4ccdfb5 *35d3d1dbbbd4f8365f285f972b0babe8f1db2c46c07d30832d24abf4d291c393ea064d6891a62f *486ef4e153685c89a992da585614a0a0df59827911f3813e678b99aa80eaed423fef99bf6a69f1 *bb50fd3337ed0d3a4b77447a4649ff00285d0e582e52ee414eb6e356a0a79d4c54482938ea92da *5b241db88f1acf86ddf935a6469fd44ed9170244257ce36d0203e9e105d5f148573dd795286f90 *0018c926ab0f8dda87e999df6a683576a1fa6677da9a4e92ddc9f47c91f3b43d471d3d5b494848 *484800247203c2b3c9af2cfc6ed43f4d4efb534f8dda87e999df6a69d1dbba7e0d97ca1ea7cd33 *5e58f8dda87e999df6a69f1bb50fd333bed4d3a3b773e0d97ca1ea6cd335e5b6f55ea375c4368b *c4e2b51e103adc64fbeb7d753ad2d5626eeb3eef25b61c752db694c8e352b209cedb636f1aace9 *663da659dfd2ed4988b5a3797a1f35c66bcb5f1bb50fd3337ed0d71f1bb50fd333bed4d5ba3b77 *69f06cbe50f5364d326bcb3f1b750fd333bed4d0eaed43f4ccefb534e8eddcf8365f287a9b34cd *79d74d3dad3513a136ebac928070a5ae48484f9e39fdd5ac5ea1d4c2e4e4145e662de4baa687cf *70824123bfd3beabd34efb6ece3d32d369af1c6f0f4ee699af3bdfddd6560b7439772bc4947c29 *45286d2ff11c019c9c6dfc6b43f1bb5167f9666fda1a46966def129c7e957c91c55b44c3d4f9ae *02b7af2cfc6ed43f4ccefb535737431729b73d3721eb84a764ba992a485b8ac903853b5572609c *71bccb2d4fa75f4f4e3b4ac073b2695c2fb069583cf72df607a5571d3aff003459fda91fc15563 *b7d81e955c74ebfcd064ff00fd48fe0aad30fd70e9d1fdfa7ed425314a57b0fb45b5d0cdc24dca *45d23dc1c125b65942db0ea01e13923638aacae9749b73778e73ea778544a410004e7c00ab0fa0 *800dcef409c0f83a37fef1a852ad56ce350f8c31399ff8777fe9ae6acc464b3c9c534c7a9c9bc7 *6742d9749b6c7b8e0c85345447100010ac7883567f4cb70936c55a1ab7ac4643ecad6ef5490388 *fb3df8f3355fa2d36b2b483a8620f687fc3bdff4d4dfa78c09362c1e201858c8efdd3516989c90 *8cd6a5f538f68eeab3381935c90a00288201e448a93e6d167d331de8eeb532fd2fda271c49888f *43b71776f5bee89a5bf76bf4ab7dcdd54b86f455a94d3e78c6411b8cf2e6795696c9b44db6755f *5535a4e48afb42bacd13951c24127c00cd7dcb295dc7e0fc5c082f7579fea8e2c66a69d20db2e1 *a6a7b4c5b1b7e35a12d20b6f3191c6ac7b456b1bf167c7bb955a6fb4c477697d4445ab4fcca067 *3b83cfc2ac6bbff42566c93ffde1fe2e544ae97d72e9658916624392e3baa224103896d91b051e *648352dbb7f42567fdb55fc5cacf26f335dfbb935369b4e39b46dfc95c9500719a710ff46a5162 *90ee9b089b3c2781cf9c6a0a9092a7b6c052b23d947de71b0efaf83722e5abef71a071328321df *650d329421b18dcec338033df5a71fe7f0eaea2779988fe31f947b3b81df5cab20e14083e0462a *6da8ed971b4dc1db6e9fb6cd6d88f842e521925c90ac6eae3c6c3c00dab65a16d376bb4e72dfa8 *e1497ad6e34acb92810a6943b250a3b83e9559cbedc4cadad88a733db6fdfbb5fd0c0ffebc63bb *e61df7ed514bf006fb7204647c25dff39a9b745d08db7a507212d5c463a5f6f8bc71df509be7f2 *edcbf6977fce6ab4da724cff004a6298b6a6d31f9884e35f7f479a34924fcdf7ff00e0155d558b *afff00a3bd19ff0095ff00b055755383e969a0fb53fb9ffd2af7e81bf9ab2ff6b57f9535447855 *efd037f3565fed6aff002a6a9abfa187abfd8ff6b295d834a2bb0695e6be5dcb7d81e955c74ebf *cd067f6a4ff05558e8ec0f4aadfa75fe67b3fb523f82ab4c5f5c3a745f7e9fb50b4a509af61f66 *b3fa09fe50bdfecc8ff32aab05768fad4ef436aab2e94329c0c5ca53d250942b21b484819e5ed7 *9d442e9f9bfade2b6197c0a2494c84a4148eec14939ac2913cc999879f822d1a8bda6b3b4ece90 *e63d455a5d3a83d7d87f675ff14d5756dfcdfd6937354b080414a63a5249f1c92463baa61ae355 *d9755086a5c7b945722a14841486d4140e39efe54bc4f32b3b1a88b4ea2968aced08e45b1a9bb3 *a6ef745ae3dbd6be0642465c7d5be7841d80dbb47ea3531e87a6217ab1d662c56d86044593fa6e *2b74e38967d790c0f2ae937aaac373d1f06cfa821cd4bb040ea9d8853be0633b9f0e75d0d29ab6 *3e9bbe25e830949b7a8143c95a82de707712ad80c780c0e7ceab6e2bc4c4c31c919b3e3bd6d59d *ff00e91b5477665d171e320b8f3af292940ef393b54ab4ff0048d79b4c74c49496ae1112387ab9 *03da03c38bf106b56bbd5be1ea68f73b440712cb320be52fb9952f3fa3b6c903bb9fad75ee4ab2 *cc9cec98ee4d88dbab2b2c1612e7013b9095718dbd455e638a36b437b5632c4572d3db64b35942 *b2de748b7a9ec91841792f066430000327c86d9dc1c8ee35db7267c07a19b43c961979c12c86cb *a9e2085712fdac72246fcf6a854cbc36fdba2da1843b1ed2cb85d5e30a75c59fd23c87a0e5eb5b *e99a8ec32346c5d3c18ba21b8ee75a97f0d9255939c8cf2f68d6534b6d113efeee5b60c9c35a4c *4cc44eff00e9b8b9b0cf489a645ca0b6846a18080990ca76eb923c3ef23de2a3bd14486a2ebb81 *f08c242c2da055b6145271f7edefae9e87be47d3b7b170717314100a7aa6529c3a93dcac9dbb8e *d5f4d5975b35d2e2e5ced2c4e81314a0b28211c0559ed020e41eff005ab70da37a7e1a72af4e2c *1113c33f2fe98f482c4bb76b2ba34f38f242de2ea0951f692adc11f78f7547faf7bffcceff008c *d4e9cd6569d416e6a36b0b7bce496461b9b1080bf7838fab71e42a2379d47a3accbcdbc4a95213 *ba44b2952527c7811cfde40a9ade291c3685f1e68c548a65a7bc7fc251d0c92ad791ce49cb2eee *4e73b5452f9fcbb72fda5dff0039ae8e9be9323d82e4abac4b64cb85c38569f9d5a5a687177ed9 *276f4a895d3545d27ce9121b6e3c6eb9c53bc0905ce1c92719ff00e2b28cd58c932e6aeb71c6a2 *d7f9fb6cbcf5f7f477a37ff2bff60aaebbea3132fbab2ef0e1c4953a52e2451c2c361b42420631 *dc33f5d7512c6a052701e93c5e25400a9c5966b1b6cbe975538e9c3c13f394cb3bd5efd037f352 *5fed6aff002a6bcb8d3ba85857b4853c9077c949dbfc3574f423d20b76a86e5b2ff0244343d20a *9b96527ab2a200e13e7b7713e955d464e3aedb32f51d4c65c3b70cc7bbd0abec1f4a57cdb790f3 *01c6d414850ca549390478834ae1780cd1d81e951fd6fa611aa6d2882ec85c74a5d0e71a5215c8 *1db07d6a42d7607a5655313313bc2d4b4d2d16afce1527c8bc5fa6247d8a7f1a7c8bc5fa6247d8 *a7f1ab6e95af3f277757c4351e6a93e45e2fd3123ec53f8d3e45e2fd3123ec53f8d5b74a73f277 *3afd4792a4f9188bf4c48fb14fe34f9178bf4c48fb14fe356dd29cfc9dcebf51e4a93e45e2fd31 *23ec53f8d3e45e29e77891f629fc6adba539f93b9d7ea3c9527c8bc5fa6247d8a7f1a0e8622fd2 *effd8a7f1ab6e94e7e4ee75fa8f2549f23117e9891f629fc69f22f17e9891f629fc6adbad16add *5169d2b6a5dc2f731b8b1d3b278b7538afeaa523751f214e7e4ee75fa8f2400f433106ff009e1f *fb14fe35567484f691d24e2e245bccabc5cd390a622b69e06cff006d79c0f4193e55aee923a62b *dead5b906d05cb55a370a4257875d4f8b8b1d918fd11ef26aab8d196f480c410953e4295c44849 *3c209c273dff0079a73f2774f5fa8f276e75d6e5717036ebaa682cfb31981952bcb0373efa99e8 *de8bef17addd8cb889240e153656e11e3e02ae9e83fa2eb640d3902f53d08933e6b697c2b9f025 *432139f4233e7574311da65b0869b4a123b922b3b5e6def2e7be6be49ded3ba85b77e4f51169e3 *9d7790544764a02b1f7e2b68cf42f668d244545e96990b49586cb69e2291b138cf2e4335743ce2 *59694b59e14247113e00551fd23eb4b1cad55a0e6e9cba352ae26e2db4a11d44f14677d9505f80 *391807cea6b7b57e49a6a3253e996e3e46229ffbe1ff00b14fe34f9178bf4bbff629fc6ada4f2a *e6afcfc9ddaf5fa8f25487a188b8fe587fec53f8d4b34c6898766b049b448526e11a4385c587db *183900631eea97d2ab6cb6b46d32a64d565cb1c37b6f0d2699b29b0db1705325c911d2e2d4cf59 *da6d07708cf7e37dcef4adcb9d934acdce37d81e959562df607a56540a52940a52940a5284e281 *4ae0a80efaae35bf4bfa6b4bbcf45f841b85c5b252a8d1483c07c14ae40f973f2a0b1c9c574ee7 *75836b8aa937298c44612325c7dc0848f79af2a6ade9eb545c56b66d018b5b249012d2438e633d *ea3cbdc2ab0b9cdba5ee4fc22f5364ca74e4e5e70ad43ebe544ecf49eb6fca0ed103ac8ba4d855 *da66e3af582db08f3c9dd5eec0f3af3d6a2bf5e3575c9db95f272df58070b2708653fd56d3c80f *3ad7dbe0ae74a4c288d9cabd951e655ffc789afa5ddc4a640831c81198185287259ef3e63c289d *9d8d37629baa2ef16d56764f58f12493d90391593cebd5fa0fa21d3da7ad496a7408f729ae27e7 *9e92d85e4f80073815abfc9c7483368d228bbc86d0a9b72f9c0b1bf0b7fa29fe35702d6869056e *292842464951c002889975ad5023dae0310a134198ac2781b6c1384a7b80aede6b57a8662a3582 *7c98f259616dc771c43ce60a1042490a3e55443bf943293674a22da9122e4a47fbc53852d838e6 *520673e40fbe885add2deb18ba3b46cd98f2d265ba82cc4673bb8ea8606de0399f215e6efc9cf4 *a3fa8f5db17294857c02cc7af5288d94f1ec247a1f6bdde75afb759f55f4bdab7ad7e429e50d9e *92e20a59888fea81c879246e7bfc6bd6ba234b5bf48d823daad6d90cb632b5abb4eacf3528f89a *090a795294a05294a0c5cec9a51cec9a501bec0f4acab16fb03d2b2a05294a05295f290f218694 *e3ab4a1b48ca94a3800507d14a006e6ab3e907a4f8b624ae35ad225cce4549c14a3d37dcfdd511 *e91ba5354d2fdb74fad0d34494079d5f075c476b1dfc236f5cd53189925f7e23521c9d242ca8a5 *09eb1290a1cb1cf63f56d9344a4af7497ace75de32a0dd1e69c7560253eca9b00e71c4390cf2e5 *507d7d21d9da9e7cb7d843325d21c75b6d271c6529e22077648271e26bbf1ec773b7dc22dcdc2d *a1b8cea5eea16a6c120119c7b58cf763dc2b7dd2ed923b72235e6daf34a8d2d257b2b7402af64e *fdc7383e18f2a0ae9096d842481ed019c9dabe4b7d6fa821036ce338dbfd73ac5e7329403b9500 *4a94363cebb50a1bae93d4214eb89c12940c9db738f1c5129c5ba2fc5ce8fa5de948099b395f03 *8b9e694e32b5796c523fbc6a06c801b513c5c7b80951c7aef5b9d457572441b7c1cb888ed9e2ea *c9e5cbbbc76ae8436173653311a4252a788471ad24f563bd5b6e700776e683d7da0f5ce9963415 *91d9374816f488881d53cea5a2387d93849e6320ee2a05d31f4cb6793a667d9f4d95cd7a5a0b06 *57094b48079f093ba8e39636f3aa7b51df97167418d160a9966db1be0ecb53e3f11df7eb0a1630 *14773e59a957465d105d35ba5179bf487225b1df692be1f9c7c7f64724a7cfea14420722ff007d *d430a2d91a5cd90c0096d10da71c5256472f9b071f755a9d1d74093a7ad999ac0aa1c418221364 *75ab1e0a23b23eff004abf74968ab0e958c96ecb6f6995e30a788e2757eab3bfbb954900c506be *c765b7d8edcd41b4c46a244687b2d34303d4f89f3ad8d294414a52814a5283173b269473b26940 *6bb03d2b2ac5bec0f4aca814a56bef7768766b73d3ae0f2198cd0ca96a3f501e24f70a0fadcae1 *1add0dd9535e432c343896b59c002bcdbd307488eded0e438af7516b4af012857b6f60f7e37c6f *5abe9375c4ad6f3cc28c24a6de9754d371d090aeb0803dae78273f563c2b51a5ec0971a7ee6e25 *13e7175438092940701c2bb8f7e77f4c512d5586db26ff003a4b339c5b5f0709cb2da4a57c2a19 *48e7b02307c6a5da7586a44531224293052cb850eb4b6f8784800e493dae7cf7add686b03d16f9 *a8a43ee32e191210a4701048470ed91ef2397757da730cc58b3accf15dd654990541a90a00202c *820776c13b8037a08bea6891edfd4052029f964a51823ac572f1e5b786fb5746ccfbcc407acd77 *6146cf312aea9c713c462b9bfb63fb241f6bd09f1ccf4c08916f6a66ed2dc7e4164cc6c38c80db *21394a885e3638ee27f8d6a74e58a6ea19ce3b0a5351d063852a44f673ece5581c3c871733df8c *5052f3e1390e63d1de496dc616a6d59c1f692ac100ff00cfc2a55d1b6b63a3e5cb9498acc875c6 *8b60389d864f3ff9571a8f4e4962eef30fbdd71eaf0a5b67882babe1ca7c7212a1839ce0e09dab *5d234db696199427c76e23ebe04baf9294856e4050c13b01bf3c6d44b5377b93977b9bb31f012b *51c908400919dea4fd1edb6e6c5f23dea1447dc6232960badb4a70e4a14329480492320fbb6add *e99e8d3e15718f1dce09ea9190c98e425a48c64a96ae640df6dbdf5ea7d3d6366c9618f6f8b849 *69be12be1192af1a21e46d4766973ef11d0bf8494b68492b9318b2002a270a077c1c2b04e09e1e *55ec2d3cbeb2c905612ca5259410964e50063609f2c54334159753d9aef3625ed36c996c74a9df *87233d7bce6460ac1273b6de5818ab1129c0a21cd294a05294a05294a05294a0c5cec9a51cec9a *501bec0f4acab16fb03d0565418b8a094924e001926bca3d326b87756dedd816e742ed709c098e *94fb41f73971118df7e58eef5af4074b73deb6f471a864c5243e988b4a08e60a870ffcebc91666 *5a82cb2e9482fac14b3c292a2903652fc892303cb7ef142122b55b50d498e971c266849438a428 *f56d276f9b18db6c649ef39eec6641a3d3749ae5c7e04ea998a992801a9d1c871b4e32b6c0ce38 *48c608c91935f2d05604ae4befa82db53ae71f002339efe2efdf9ffadec775c443656fa9b010ca *3ac580144fb2924f0800e7dde344a3f11a8cc6acbcc36adb1985486187172d4bc9782f880053b1 *ce41c60f7e6a40dc387018656a6da1821414b4827880c71027bf1b679e2a19aedb4876d37db74f *88c5c16d0432c4a6b8be14321c08503cb6c9c633c58c115ae8c5776b85a352337252da92d29335 *a7dd092d3009057c3b0484a8709c6dc8ee72487db55fc3af17b7ff0037dc4fc19b4a985b493c25 *085252559febf1148f7122b48bbd4db2332e234f8696e80a70a508415af032484a479779dbcaa4 *d71bb4080a43968b743798500acad016301270e213cb7ce36c646f5a09eebb72bba386221db83a *80b6d9564a1b047fbd706361e039939eea0d5d963ce9f3d4999b2e321c90e39c58ca9d6d3c083f *d521283fe8d4ced7a33e37f45705805b37165c5ada5b6410324e12bc6dcb7cf88f5a88eb5c5874 *a370a33ab725dd5d3d73abcf138060ad7f5fb3b6d8cf3abafa03b3aa169c69e51009652929e1c6 *4a895e7ea50141e79d3173d51a1b55ae3c14c94498c545f8582a6d494eea046f8db7e21e5cc57a *eb40eaeb7eb1b03572b7123f41e655da65c1cd27fe47bc106a39d2bf4656fd676f71e69288d794 *20f53213ecf1f8257e23cfbb3eeaa3b455e750f4537f26ef62b818ce214d491be1fc1252a49238 *7d9e40e7704efcb01eb9c0f0a551c7f288b304fb365b971e32429c6863ff005568ae7f944ca796 *1ab359194bab3c28eb5c5bca51f24a427fcd443d0f2653315be390e25b47104f12ce0649000f79 *2057d7ac15e3eb8defa43d6da9a2dbe5c9763ca7161d660abfd99921078fb2ad967618e2e2ab82 *d9d1bdfee76d2fccd71a923aa584ba5a51085b471ba55b9efee4f08a1b2e20a06b9aac62682d53 *1657c219e902eae1090381f692b4ab7e441d80f400f9d7c2527a51b1c653cdc8b3df5947128b3d *5290f91b918390957a6c7d682d5a5561d1c74aad6a8baaacf72b4cbb55d503050e8f614a009291 *9c107009c11dc6acf140a529418b9d934a39d934a035d81e95ca8e0570820207a545b5feb2b5e9 *0b33b2ae32fab74a0865a4a78d6b59d8009f5f1da829dfca435548917d81a561bcb446083225a5 *00e56ae12a424e3b8633eb8aab263ad43d44e2547ab61b52032b03608e118c7f771bf99a98684d *1d7bbceaaba5c351f58f5c17055252e287b5d77cd929239670a29c7772eead46a3b0a106320b88 *6cb2ac3320ec85a39042cf770e0007901b1208c9252685a8d322d6b896b92a852548494485212a *0bcefb0ce79647215bebb6a9930ee36c8305b62538f00b7cba4a4b6dec38c1e5cf3b73e5556db6 *24cb72f0888fa8a88564a15c191b6463623df5bbeb66a990fbee311b71edc9570048df18e591b5 *04f265d2d525d6d2e460fbc5414871e48504ab1cc13b0560938e78cd7c2ed7f86d405650c30d29 *250e174278559d88391ed0350db7dbe5c92c47b23125c0c652890ac351124807882482578e2381 *8f1deb5f3ee112cf74ea034bbfdf90e86d0eb83e65b59c7b0d201dce4f33cb96683bb67b35d350 *3896e2f5aa654e214875d8a9414048184b0d007001fd25f96ddf56ddbb4c5af46da1eb9ea1288f *092389c64acbaec870e31c4be6a513b70efddddb54dfa3fb1bb68d370d372ead7765b6152dd4a4 *0cacee5231c80ce3dd551f4f49bb5fb5fda74cda78dd53d04ada6d2be14b6b5b985baaf46d2a1e *3851c73a0aaef1366748daed4ea5aeafae29659693ba63c64e709dbbf209279673dd5eb9d176e4 *5b6cadb48421209c8091818c009ee1dc0568b42f465a7f4a5b92cb111122529290f497bda2b237 *d872033dc3df9a9da12109012300510e48cd60b650b185a42878119ace941d236a80493f028d9f *1ea93f856a66e8eb24bbcdbae8ab7b0dce80e171975a4841dd25242b1da1be707bea474a0f8bb1 *58794853ccb6b520f120a920949f11e15f5000e55cd2815c29208ae69411b8da4e0b3a9645ed49 *5392dc20a73fa071824799181e83d6a483952940a529418b9d934a39d934a0adf5f6bb97066a34 *fe93888b8ea275be3e05e436ca3915a95b72f0efacb47f4630edcebd70d44fbb7abdbe72a95214 *541a079a5b07b2339df9e2b0e84acfc3a5a3dfee054f5e6edc72a4bee270a3c6ac84fa00138036 *ab2c0c507598851e395299650852892484e09c924e4fa93518d45a2a25cdf76447e161e712a0b4 *a9016dac91cc8ee3e62a614a0a663f458f8755c70edcd27ffd4ead2951f1c240ac2e9a56c3a16d *49baddd3190a4a92db498d182de5acec10d951db233e95714d9088919d7dd2436da4a9440ce00a *f345c65cde9afa4036c61e916eb1c5694eb2e0482a42463e708ceca5123033b0f3cd128d6acd7f *36ee8543b0f04361c514acc5cad6472092eed927c1b0077655564f41bd14bb6d763ea1d4ac9f86 *363fd8e339ff00620fe9a8771df61ddccefca7fa03a32b0e8d8e83159f854fe6a98fa415fa2472 *48f4f79353a4a7846d4003036af3f748f3ff00337e505629ee7cda4b319014558e24a9c71b5636 *fed8db6e59af411e55e7bfca5a12d8be69fb90513d7e23e703e6cb6e2560fbf88e7d0510f41a4e *d5cd60c9cb69279e056740a52940a52940a52940a52940a52940a529418b9d934a39d934a0d4e9 *9b626d56b6a336a714d247b01ce691e1e1f56078015b8ac5aec0f4aca814ac4ac0193b5696f3aa *6cb67c0b9dce247511c412b707128790e67dd4113e9e7513762d033501e4b52268f83379192411 *ed903c939dfbab5bf93a6925d8747fe729a9c4ebaf0bd829c16d909c369fab7fef556dac2e9f29 *5d21db23b21e55b952531a1378c71b40853efa87724a4601f3f235e9f61b4b4d210da425090000 *06001e141f4a138a54475feb0674dc00db01322f32be6e1431925e7390ce392724649c0a0d8ea8 *d516bd3509526eb2d967d9250da9c016e792413b9aa2f599d4dd2c5abf3bdaed89b759ede87036 *990f7ceba7d92b570f0ff54606fcf3bd4e74af478bb95d19d4bac9c12eecf349518e1212d30adf *00247f541e649dcf955a0cc469a63a943684b58c7004e07d544b8b6952a0462e76cb49cfae0576 *6b84a78795734414a52814a52814a52814a52814a52814a5283173b269473b26941acbf5f2dfa7 *ad0edc6ef2511a1b29cadc57f003993e42aba97ad7586a4b52e5e89d3a22c538ea655d57c25fdf *6286864e3cc9151ee982d7729bd23587f3c2cc8d2c0b6ea2303c295292a1c69df62e1072013ba4 *1037e77ac7082d2785384e06063181e94155c6e8e6f578965fd5fa9e7c96d68cbb0e1b8a623970 *f7000e4a00f424efb577e1743ba5a3434b0ec432565414e4878e5c501c9208c613b0cf8f7e6aca *007857341123a462a7585a6eb19861845be2b8c242138273c294a7ff000800fdd52d03029814cd *07ca53a861871d75412da1254a51e400dc9aadfa3b6d1ace4c9d637040710ec85376b6d601ea18 *4129c8f052cf113ee1dd53ad4b6966fb629f6c90486a5b2a6944731918cfbaa39d1769a97a4ec6 *9b6494464a1bc60b0aca54ac60a86402338ce0e719c64d04d52302b9a52814a52814a52814a528 *14a13815d217389f0a5c6f8437d7a73c48e2dc6003fc08fac5077695f2f84378cf1271eb583d35 *865aeb1d71294642724f79d80f5dc6d41d8a574537684a5252243654ae401f3c7f1dab89377851 *9f4b2fbe943aa1c4127bc6ff00f49fa8d077e95f1125b233c407beb343895f6483ddb1a0e5cec9 *a51cec9a50601b438da42d21436382335a4d5d75916b8d09bb7a1a54c9b29111a53c4f5682a049 *52b1b9c049c0db27032335be6fb02ba779b5c4bc415c4b83097d85e094ab6c107208237041dc11 *b8a0864dd437fb64ab84092604a93121fe700fb485369535ed829520a8f0ab89230724107bb15a *385d205ea4da19707501e5cf6a2179301e51c2a3f5aaff0067e2e3c83b03c88dc6d56040d2d6b8 *316630c47511313c1216ebab71c753823056a2558009c6fb66bad3b4559672db5bd156971b4b68 *42d9796d2806c108dd241c80a50cf3c1a0d469cd57719dab5769921953286d67ac0ca9a5a886a3 *2f252a24a77795b1dc600ee35f07f57ddd8d3116f8986c4a68ca7a23d1d0781655d7a9a6949513 *8c6424287f6891cb0772ee84b238e21cea24a5e4ff00db2263a95abd8420f1282b2766d1cfc2b3 *8fa22cd1d2ea50c3e5b75ceb54d2e53aa405f59d66424ab00f18cec283bf654de83a7f3baa129b *ea91831c281eb31edec49db3cab73815c20600ae6814a52814a528317161082a51c00324d6a22e *a2b7c8e1cbdd515b6875097470952159e150f2383fe88ad94d8c89715d8ee825b75250a0090704 *60ee3956ad7a6edcb214b8dc4b0908e22a39e11c24279f2052938f2a0fbbb7c80982e4c4c84b8c *365214a41ce38b18cf87686fcb15c357fb6a93954a6d0ae2e02959e15056718c7ae47bab16ac30 *9a8ab8cdb4a430b395242ce15ecf0639f2e118c57c0696b584ba9119403841561c56e42b8877f8 *d0765cbfdad2df12a7301277c958e5c2559fa813ee35197edf6a70c9b8fc2572fe7ce5bc00971c *2a4ac24edb81c281e401f3addfc54b51520aa29570a52900b8a23013c236cf86d5dc5596214a47 *56470baa7c10a390a5678beb048c5044dcb35b19761a654f75b5c80b75b420242000a2af0ee2b4 *8fee8aecc35589a8aa611392d18b2cba82e293b142543977a7850a1fdd3e15bb5e9e8af492ec84 *f1f0a3aa6523d90d23041031e3939ae11a5ed686c21310009e4788e473efcf9abfc47c4d069ae3 *6ab7a9b10cc993c4ca56b716809e249778b894a51dbdae224a7c81c6d5d77ad7630e071dbbe029 *61402969dc95938e5dfc4a1e86a4d3ac106738e2a547e3eb31c69e2202c849482403b9009ff42b *06f4ddb5b79c7531471b8b4b8b2544f1292ae20ae7cf207d5411a16ab13884e6ee708425ac9524 *7b412539e5cf2a07d426a4ba6a3c78ed3e204a4bf194e156d8f6544e48c8e7b1481e4057074d5b *cb8e38b69d714b4ad04ade52b2178c8dcf97bab65020b305b5371d1c0852d4b233de4e4d0761ce *c9a51cec9a5060d389e01bf7565d627c694a07589f1a1753e34a5003a8f1fba9d6a3c694a075a8 *f1fba9d6a3c7eea5281d6a3c69d627c694a07589f1a7589f1a5281d6a3c7eea75a8f1fba94a075 *89f1a75a8f1fba94a075a9f1a0751e3f7529402ea07334eb51e3f752940eb51e34eb13e34a503a *d478fdd4eb51e3f7529418add4709dfeea52941fffd9 }