[improved examples directory; start at index.html sydow@chalmers.se**20081024131749] { move ./examples/Primes2.t ./examples/Primes.t addfile ./examples/Counter.t hunk ./examples/Counter.t 1 - +module Counter where + +struct Counter where + incr :: Action + decr :: Action + value :: Request Int + +counter = class + + n := 0 + + incr = action n := n+1 + + decr = action n := n-1 + + value = request result n + + result Counter{..} addfile ./examples/Counter_descr.html hunk ./examples/Counter_descr.html 1 + + + +Counter + + + +

Counter

+ +

+The Counter example is a minimal example of a class from which one +can instantiate objects with state. Several variations are possible; +here is the one we choose: +


+
+module Counter where
+
+struct Counter where
+  incr  :: Action
+  decr  :: Action
+  value :: Request Int
+
+counter = class
+
+   n := 0
+
+   incr  = action n := n+1
+
+   decr  = action n := n-1
+   
+   value = request result n
+
+   result Counter{..}
+
+

+Comments: +

+
+

Variation

+Java programmers and others may miss constructor methods in the class +definition. In fact, counter itself has the role played +by constructor methods as seen from the usage indication above. To, +hopefully, make this clearer we note that one might want to create +counter objects with some other initial value than 0. We can easily +achieve this by a slight modification of counter: +
+counterInit init = class
+  
+   n := init
+
+   ...
+
+The rest of the class is as before. To create an object with initial +value 5, we would write +
+ctr = new counterInit 5
+
+

+Thus, we have the typing counterInit :: Int -> Class Counter. +

+We might still keep the definition of counter, but this would +mean code duplication that should be avoided. Instead, we could write +

+counter = counterInit 0
+
+and get a class counter with the same usage as our original +definition. + addfile ./examples/Echo.t hunk ./examples/Echo.t 1 +module Echo where + +import POSIX + +root env = class + + echo str = action + env.stdout.write str + + result + action + env.stdin.installR echo + addfile ./examples/Echo2.t hunk ./examples/Echo2.t 1 +module Echo2 where + +import POSIX + +root env = class + + count := 1 + + prompt = do + env.stdout.write (show count++"> ") + count := count+1 + + echo str = action + env.stdout.write str + prompt + + result + action + env.stdin.installR echo + env.stdout.write "Welcome to Echo2!\n" + prompt + addfile ./examples/Echo2_descr.html hunk ./examples/Echo2_descr.html 1 + + + +Echo2 + + + +

Echo2

+ +

+Let us make the Echo program just a little bit more +interesting: We add an initial welcome phrase and a +prompt with a line number. Here is the program: +


+
+module Echo2 where
+
+import POSIX
+
+root env = class
+
+   count := 1
+
+   prompt = do
+      env.stdout.write (show count++"> ")
+      count := count+1
+
+   echo str = action
+      env.stdout.write str
+      prompt
+
+   result 
+      action 
+         env.stdin.installR echo
+         env.stdout.write "Welcome to Echo2!\n"
+         prompt
+
+
+

+The root definition now has two more components: +

+

+In addition, the callback and the initial action both call +prompt, and a greeting phrase is added. +

+Some additional details: +

+ addfile ./examples/Echo3.t hunk ./examples/Echo3.t 1 +module Echo3 where + +import POSIX + +root env = class + + current := "Hello!\n" + + save str = action + current := str + + tick = action + env.stdout.write current + after (sec 1) tick + + result + action + env.stdin.installR save + tick addfile ./examples/Echo3_descr.html hunk ./examples/Echo3_descr.html 1 + + +Echo3 + + + +

Echo3

+ +

+Now, let's try a variation; program Echo3 writes +Hello!\n to stdout once a second. The user can change this +message by typing a line on stdin; after the line is finished +with a return, the line typed will be the new message. Here is the program: +


+
+module Echo3 where
+
+import POSIX
+
+root env = class
+
+   current := "Hello!\n"
+
+   save str = action
+      current := str
+
+   tick = action
+      env.stdout.write current
+      after (sec 1) tick
+
+   result 
+      action 
+         env.stdin.installR save
+         tick
+
+
+ +

+When running Echo3 one notices a peculiarity of the standard +implementation of the POSIX environment: the screen doubles + as both the output +device stdout and as user feedback part of the input device +stdin. Thus, output is intertwined with input characters in a +rather unsatisfactory way. + addfile ./examples/EchoServer.t hunk ./examples/EchoServer.t 1 - +module EchoServer where + +import POSIX + +port = Port 12345 + +root env = class + + log str = action + env.stdout.write ('[':str ++ "]\n") + + result action + env.inet.tcp.listen port (server log) + +server log sock = class + + n := 1 + + p = show sock.remoteHost + + echo str = action + sock.outFile.write (show n ++"> "++str) + n := n+1 + + close = request + log (p ++ " closing") + result () + + neterror str = log ("Neterror: "++str) + + established = action + log ("Connected from " ++ p) + sock.inFile.installR echo + + result Connection{..} addfile ./examples/EchoServer2.t hunk ./examples/EchoServer2.t 1 - +module EchoServer2 where + +import NEWPOSIX +import Counter + +port = Port 12345 + +root env = class + + clients = new counter + + log str = action + env.stdout.write ('[':str ++ "]\n") + + result action + maxClients = parse (env.argv ! 1) + env.inet.tcp.listen port (server maxClients clients log) + +server :: Int -> Counter -> (String -> Action) -> Socket -> Class Connection +server maxClients clients log sock = class + + n := 1 + + p = show sock.remoteHost + + echo str = action + sock.outFile.write (show n ++"> "++str) + n := n+1 + + close = request + clients.decr + log (p ++ " closing") + result () + + neterror str = log ("Neterror: "++str) + + established = action + cl <- clients.value + if cl < maxClients then + clients.incr + log ("Connected from " ++ p) + sock.inFile.installR echo + else + sock.outFile.write "Server busy" + log ("Refused " ++ p) + sock.close + + result Connection{..} addfile ./examples/EchoServer2_descr.html hunk ./examples/EchoServer2_descr.html 1 + + + +EchoServer2 + + + +

EchoServer2

+

+This is a minor extension of EchoServer: when started, it +expects an integer command line argument maxClients, denoting +the maximal number of concurrently served clients. If more clients +connect, they are just informed that the server is busy and +disconnected. +


+
+module EchoServer2 where
+
+import POSIX
+import Counter
+
+port = Port 12345
+
+root env = class
+ 
+    clients = new counter
+
+    log str = action
+       env.stdout.write ('[':str ++ "]\n")
+
+    result action
+       maxClients = parse (env.argv ! 1)
+       env.inet.tcp.listen port (server maxClients clients log)
+
+server maxClients clients log sock = class
+
+   n := 1
+
+   p = show sock.remoteHost
+
+   echo str = action
+      sock.outFile.write (show n ++"> "++str)
+      n := n+1
+
+   close = request
+      clients.decr
+      log (p ++ " closing")
+      result ()
+
+   neterror str = log ("Neterror: "++str)
+
+   established = action
+      cl <- clients.value
+      if cl < maxClients then
+         clients.incr
+         log ("Connected from " ++ p)
+         sock.inFile.installR echo
+      else
+         sock.outFile.write "Server busy"
+         log ("Refused " ++ p)
+         sock.close
+
+   result Connection{..}
+
+
+The differences to EchoServer are the following: +

+ We need to keep track of the number of served clients. + For this we use a Counter + object, created by the root object. +

When a new client connects, the counter value is retrieved and + only if this value is small enough is an echo action installed; + otherwise the client is informed that the server is busy and the + socket closed. When a client closes the connection, the counter is decreased. +

+ A Counter object is appropriate here, since several server objects, + each interacting with one client, interacts with it. On the + contrary, the line number local to each server object is maintained + in a simple integer state variable. + + addfile ./examples/EchoServer_descr.html hunk ./examples/EchoServer_descr.html 1 + + + +EchoServer + + + +

EchoServer

+

+Now, let's look at a further feature of the POSIX +environment. It also supports writing network programs, +that communicate over the Internet using sockets. +A socket can be thought of as a two-way communication channel, +consisting of both an RFile and a WFile. +

+Two network programs, which +execute on different machines, may connect over +the network and communicate using a socket. +Typically, one of the programs will be a server +and the other a client. Here is a trivial server, the +EchoServer. + This server waits indefinitely for clients to connect on port + 12345. When a client connects, the server starts a session, where + client input rows are echoed back to the client, prefixed by a line + number. Several clients may be served concurrently and + line numbering is independent for each client. + +


+
+module EchoServer where
+
+import POSIX
+
+port = Port 12345
+
+root env = class
+
+    log str = action
+       env.stdout.write ('[':str ++ "]\n")
+
+    result action
+       env.inet.tcp.listen port (server log)
+
+
+server log sock = class
+
+   n := 1
+
+   p = show sock.remoteHost
+
+   echo str = action
+      sock.outFile.write (show n ++"> "++str)
+      n := n+1
+
+   close = log (p ++ " closing")
+
+   neterror str = log ("Neterror: "++str)
+
+   established = action
+      log ("Connected from " ++ p)
+      sock.inFile.installR echo
+
+   result Connection{..}
+
+
+

+Comments to the code: +

+

+In order to let you run the server, we provide a simple client, +TCPClient. We do not list the code here; you may review +it in TCPClient.t. The client accepts a host name and a port +number as command line arguments and connects to a server on that +address. When connection is established, the client accepts user input +lines, sends them to the server and displays replies obtained on the +screen. + addfile ./examples/Echo_descr.html hunk ./examples/Echo_descr.html 1 + + + +Echo + + + +

Echo

+ +

+Our first example runs in a very simple setting: a computing environment +where the interaction between the external world and the program is through a keyboard and a text screen. +The user provides input using the keyboard and the program prints +output on the screen. +

+We consider a reactive program, where the user +input is just echoed on the screen, line by line, +by the program. This trivial interaction, the "Hello, world" of +reactive programs, goes on indefinitely. +

+Here is the program: +


+
+module Echo where
+
+import POSIX
+
+root env = class
+
+   echo str = action
+      env.stdout.write str
+
+   result 
+      action 
+         env.stdin.installR echo
+
+
+

+Let us explain the program: +

+

When executed, the runtime system invokes the +result action of the root definition (see +Echo2 for a more careful description.) +After that, the program is idle, waiting for user input. +When such (line-buffered) input occurs, the runtime system +invokes the callback with the input line as argument. +

+This trivial program is typical for the Timber programming idiom; +we describe how the program should react to external events and +install, or register, this description with the external device. +

+We note, finally, that the use of stdout and +stdin is consistent with their types as +specified in Env: +

+ addfile ./examples/MasterMind_descr.html hunk ./examples/MasterMind_descr.html 1 + + + + + +

MasterMind

+MasterMind is a board game with two players; in this +case the user choses the secret and the program does the guessing. +Here is a sample interaction: +
+examples> ./MasterMind
+Welcome to Mastermind!
+Choose your secret. Press return when ready.
+
+My guess: Red Blue Blue Red
+Answer (two integers): 1 1
+My guess: Blue Black Yellow Red
+Answer (two integers): 2 0
+My guess: Green Black Red Red
+Answer (two integers): 0 0
+My guess: Blue Blue Yellow White
+Answer (two integers): 3 0
+My guess: Blue Blue Yellow Blue
+Answer (two integers): 3 0
+My guess: Blue Blue Yellow Yellow
+Answer (two integers): 4 0
+Yippee!
+Do you want to play again? (y/n) n
+examples> 
+
+The program is too long to display here. We only note a few things: + + + hunk ./examples/Primes.t 13 - test k = loop 0 + isPrime k = loop 0 hunk ./examples/Primes.t 23 - p <- test k + p <- isPrime k addfile ./examples/Primes_descr.html hunk ./examples/Primes_descr.html 1 + + + +Primes + + + +

Primes

+

+As a reactive program, this is quite degenerate: when started, it +expects +a positive integer n>2 as command line argument. It +computes all primes smaller than or equal to n, prints +the number of such primes to stdout and terminates. +

+The algorithm used illustrates imperative programming using updatable +arrays in Timber. Here is the program: +


+
+module Primes where
+
+import POSIX 
+
+root env = class
+   limit :: Int
+   limit = parse (env.argv!1)
+   primesBound = limit `div` log3 limit
+
+   primes := uniarray primesBound 0
+   count  := 0
+
+   isPrime k = loop 0
+      where loop n = do 
+              p = primes!n
+              if p*p > k then
+                 result True
+              elsif k `mod` p  == 0 then
+                 result False
+              else loop (n+1)
+
+   checkFrom k = do
+     p <- isPrime k
+     if p then 
+        primes!count := k
+        count := count + 1
+     if k < limit then checkFrom (k+1)
+
+   result action
+     primes!0 := 2
+     count := 1
+     checkFrom 3
+     env.stdout.write (show count++"\n")
+     env.exit 0
+
+
+log3 :: Int -> Int
+log3 n  
+  | n < 3       = 0
+  | otherwise   = 1 + log3 (n `div` 3)
+
+
+
+Prime numbers are stored in array primes, which is +initialised with all zeros (primitive function uniarray +creates an array, whose size is given by the first argument, where +all elements are initialised to the value of the second argument +The program uses the moderately clever bound that the number +of primes up to n is at most n `div` log3 n. +

+The root action notes that 2 is a prime and initiates count +to 1; it then checks numbers for primeness, starting with 3 in +procedure checkFrom. The iterative check is expressed using +recursion, checking for successive numbers up to limit. +

+The procedure isPrime works by trial division, using already +discovered primes: to check whether k is a prime, one tries +to find a proper prime factor p such that p*p <= k. If +none is found, k is prime. + + + hunk ./examples/Reflex.t 29 - print (format t++" secs") + print (format t) hunk ./examples/Reflex.t 37 -format t = show (secOf t) ++ '.' : fracs +format t = show (secOf t) ++ '.' : fracs ++ " secs" addfile ./examples/Reflex_descr.html hunk ./examples/Reflex_descr.html 1 + + + +Reflex + + + +

Reflex

+ +

+Reflex is a simple reaction time tester. +Only the Return key is used in interaction with +the program. When pressing Return for the first time, +the user is instructed to Wait...; after a few seconds, +the program says Go! and the user must +strike Return again as fast as possible. The elapsed +time is displayed and the test can be repeated. +

+Here is the program: +


+
+module Reflex where
+
+import POSIX
+
+data State = Idle | Holding Msg | Counting
+
+root env = class
+  
+   print str = env.stdout.write (str ++ "\n")
+
+   tmr = new timer
+
+   state := Idle
+  
+   enter _ = action
+      case state of
+        Idle ->         msg <- after (sec 2) action
+                           tmr.reset
+                           print "Go!"
+                           state := Counting 
+                        print "Wait..."
+                        state := Waiting msg
+                 
+        Holding msg ->  abort msg
+                        print "Cheat!!!"
+                        state := Idle
+
+        Counting ->     t <- tmr.sample
+                        print (format t)
+                        state := Idle
+
+   result 
+     action
+       env.stdin.installR enter
+       print "Press return to start"
+
+format t = show (secOf t) ++ '.' : fracs ++ " secs"
+  where t100  = microsecOf t `div` 10000
+        fracs = if t100<10 then '0':show t100 else show t100 
+
+
+

+Comments to the code: +

+ addfile ./examples/TCPClient.t hunk ./examples/TCPClient.t 1 +module TCPClient where + + import POSIX + + root env = class + + result action + if size env.argv /= 3 then + env.stdout.write "Usage: TCPClient host port\n" + env.exit 0 + host = Host (env.argv!1) + port = Port (parse (env.argv!2)) + env.stdout.write "Connecting..." + env.inet.tcp.connect host port (handler env) + +private + + handler env sock = class + + rounds := 0 + + neterror err = action + env.stdout.write (err ++ "\n") + env.exit 0 + + close = request + env.stdout.write "Server closing; Bye!\n" + env.exit 0 + + receive str = action + case str of + [] -> sock.inFile.close + env.stdout.write ("Server closing after "++show rounds++" rounds\n") + env.exit 0 + rounds := rounds+1 + _ -> env.stdout.write (str ++ "\n") + + echo str = action + sock.outFile.write (init str) + + established = action + env.stdout.write "Hello!\n" + env.stdin.installR echo + sock.inFile.installR receive + + result Connection{..} + + + init [x] = [] + init (x :xs) = x : init xs addfile ./examples/index.html hunk ./examples/index.html 1 + + + +A summary of Timber + + + + + + + + + + +<body> +Please use a browser with support for frames. +</body> + + + + addfile ./examples/intro.html hunk ./examples/intro.html 1 + + + + + +

Introduction

+

+This directory contains a number of simple Timber examples. +In addition to the pages that describe the programs and comment on +the code, the source files are here and can be compiled and run. +

+Module Echo is stored in file Echo.t and is compiled +and linked by the shell command +

+timberc --make Echo
+
+which produces an executable file called Echo which can be +run by the command +
+./Echo
+
+This is generalized in the expected way to other programs; in +particular, the --make option makes sure that all +(recursively) imported modules are compiled in the proper order +before linking is done. +

+Some programs require a command line argument as described in the +respective page. +

A brief summary of the programs is the following: +

+ + addfile ./examples/logo.gif binary ./examples/logo.gif oldhex * newhex *4749463839615a019c00f700003636363838383e3e414343434c4c4c4d4f5b52535b5353535758 *5b5b5b5b616161686c866b6b6b6e59366f7286735c39735e4073624a7460457474747566557760 *3f78726a797b877a664b7a76707b623d7b63427b6c667b6d597c7c7c7d694b7d6a507f79747f80 *87806640806c508075798080808084a182838a8374698389b484725584735c848693856a42857e *8e85889c867d81868aa2877d7c878889888293898ca3898dab8a6e448a87a38a8a8a8a8fb18b8c *928b8d9b8b90ab8b91b38c7c668d71468d80768d92bb8e90a38f72488f95c48f96c8908e8a9091 *b89198cc92826c92867a928b93928ea79292929294a3929ad49375499385759393999397b3949d *db959fe196784b9698a3969abb96a0e597897697a1ea989cc398a3ec997a4c9990939aa3e29aa5 *f39b8d7a9b9ca29b9cac9ba1d09ba3dc9ba6f99d9d9d9e9eb29e9ebd9ea2c29ea8ee9eaafe9f7f *509f804f9fa0a39fa2bc9fa8e2a07f4fa07f50a09aa5a19484a1a9e8a1abf2a1adfea29b93a2a2 *a3a38251a3a4b3a3a7d5a3abe1a4a8c5a4aadba5b1fea69b8ca6a4aba6b0f5a7a8afa7a8b3a886 *53a9acd5aab1e1aab5feababababadc9abb1daabb2ecabb4f2ac8955acacb4acacbcada498aeb0 *d6aeb8feaf8c58b08c57b0b5dbb28e58b2acacb2b2b2b2bcfeb3b4bab3b4c7b3b5d6b3b8e4b4aa *9eb4bbf2b6915ab6c0ffb7bbdbb9945cb9bcccbab2a6bab3acbabde3bbbbbbbbbcd5bbc3febcc2 *eebcc2f3be985ebeb8b1bec2ddbfbdc0c0c7fec1bcc1c2c2d6c2c6e6c2c8f3c39c61c3c5dbc3ca *fec4bdb5c6c6c6c6c6c9c89f63c8c6d4c8cefec9cbe4caccdacacef1cbcbcbcca366ccc5bccccb *d5ccd2fecec9c4ced1eed0a667d0ced6d0d6fed1d3e6d1d5f1d2cdc9d3d3d3d3d3dad4a969d4d9 *fed5d9f3d7d8e0d8ac6cd8d5d4d9d6dcd9ddfedbdbdbdbdceddcdce2ddb06edddff2dde1fedee0 *f3e0dcd7e1e5fee2b571e2e2e2e2e4f3e4e1dde5e5e9e5e9fee6b872e7e8e8e8e6e4eaecfeebeb *ebececf3edbd76eef0fef0c077f0eff0f3f4fef5c379f5f5f6f6f8fef8c67bfcca7efecb80fefe *fe21f90404000000002c000000005a019c000008ff009ff41948b0a0c183039f9858684207c287 *1009aa6168424dc48b0775501488b1a3c78f7dca3cd14871a18e271641aa5cd9474e4b39306196 *9949b3a6cd9b3873eacc99a5a7cf9e50820a1d4ab4685022489326b5c1b4a9d3a6302822fb47b5 *2ad53e56b36add4a351d49134fe4711dcb351dc57464d35a95a7d0245ab570e3c2d557cd535b86 *3a1c21132bb76fd57dfff609c647b8b0e1c3880dd75bccb85ebcc79023476e47b9f2b9cb983393 *dbccd99b67cfd8428b161d2d1ab3d3a85113f3c5ba356b58b063c33ef5a9b6ed4f983035dabd9b *10a13dc0dfbcb9c1f00957ac7eb7ea9bc8b05a72ad6619be7d5eb51a4535faa86b27fbcd15738a *7d804dffdf1e57f03ec28313ab57dfd8b163c9f0e355b69cb93ee7fbe43e831e4dda34ea2aaab9 *26a06cb2dd565b6ebcf5f61b707b08670545df6c851c7954b9429127e445b7d078cf7942912b14 *86988e2ddf31548678215267de79ebb598587bf1c5371f7df59d835f679ff1d75f69a80160c026 *cc10b39a80af11389b81b8e9c69b6f0b36285c0b0c4d689594145ac71076da696802877d2d4791 *73293e970e307d9454912b1186b9dd8ae9b9d8627b8cc528d98c94d568e38df9e9e78d8ed894e6 *1f33010c108003bb0c49a42f461e69a0924b36199c11146597159514b285579ac969c9655cdf7c *15969a72c9834c99253d812660a086785e9b6ebe09a79c90d1ff69276678eac767683c9e160001 *040c204015860e9828924926c824830d8e4111305a511aa223cb8a79d673c050e448aa6989eac8 *570b3de1493592624b219bacb68ad8abb04e26ebac37ea79ab9fa6ed9ac001821a00c9a188264a *dba28c36722c836fd8505cb3e222035ea6d37649ea4253899b155d9e70db9023e03a9ca2608105 *669eb9ebc1f95ebaf2cd38eb65edbaaba39fba12a0800209f43aa82c44260a0b92081aeb1bc06f *4441115f55399ba257c5f10c97a67db173970e9baa09f15d26e925b4c56a92cb22c72f7a0c329d *edb05bb2ad7cf2b8ab021330306faf02fc20ac91fbde56b382c8261bad553a609aaa3e0b9b00e6 *d009c365e5427d84ff9b6a7725f21dcc3b50174ed58a54770c63ba5867ad357e5c771dafca1378 *3001cbf40660af6bfaa66d5bbffede1c5cc0576675259ad85ac81086784b1797870c81f8b77766 *8697b4e1d80236d8d48917862ec8218b5c63ad26f307efd7132c1436cb2e3b0073be049ee2f981 *fdfeebe41191c25d3b8a61ee5d91df65e53d9697cda93966dd0ba9813aeeec6b4c6eefe73616cf *c772caeab87d5bef2739f227e960b9d80720db0f6e21b3e9e5a67aa273d217be34a57f006e7b4f *a38ea54c22b7ad108d3b9e8ae073e4412633a9af82ed0ba1c6e05735f95d6d5d76cadf9e24170d *fea9410d0ab11ce604558041e88b58a04ba070d28082d535b02a4b2b495efff6421e6831845963 *b92057aac5906b6d475b12f356c5444845f7bd8f84f88011fdea273cfc112f47272b8d0b1dd107 *356864792d1394034a81369a21b049c2214eb77ea81588492c2f534c8ec1a204beaa28f161756b *5872e8b2ad527dab8f554ce4c6b0e8bbc531ae8b295461185b48391da8c1139e70040cfd17b6b1 *f96a07d1a359824207c737408a21741c0b140d99c7b800ad5b1afca31f8f763bae04912243d460 *2215b9b17225ee778f84a46624b9bf4a5e1218aef044196378b979d1d086b0981ef56c56ca07b9 *ee2a7dd156031ec0cd6e7af39be00ca738c749ce729ab3010148a73ad7c9ce76baf39df08ca73c *e749cf7adaf39ef8cca73e5de8ff0960200318992ce31919c03c412d808dd15cd428ad271c6531 *44903e4bcb03e0e0878a5af4a218cda84637cad18e7ab4a3707800af464ad2929af4a4284da94a *57cad296baf4a5308da94c673a52b059b29fdfa8063292a9c991fccf930250c1ccdc68339cbda1 *870b61dd3f224a9607f821159388aa54a74ad5aa5af5aa58cdaa56af9a0a3f3c6065600dab58c7 *4ad6b29af5ac684dab5ad7cad6b6baf5ad700deb046e0a8c6fa4e31bff4ce6324d20436706a000 *6810253591f586a8f0ad67cf71ea24c0f0d1c63af6b190ad281826e1d50958f6b298cdac6637cb *d9ce7af6b3a00dad68474bdad29af6b498a5eb37e4a18f74e814a06434a309d0e8b205ff48426d *6fc4991c2b82d8e428f6a9a908ae70874bdce21af7b8c84dae7289eb07ca3e4007d08dae74a74b *ddea5af7bad8cdae76b7cbddee7af7bbe00def748ff90d49c923a73bcde4267f1a405fa9e073b9 *1ddd10f0d25bbffc3615c978867ef7cbdffefaf7bf000eb08007acdf6474d5b92f4cb08217cce0 *063bf8c1108eb084274ce10a5bf8c218ce3083fb80d370b516afc854260cf9dacccc01f6808305 *d8291752dfbedcf719e888b18c674ce31adbf8c638ceb18e63fc8c037b1593400eb290874ce422 *1bf9c8484eb29297cce4263bf9c9502e725dc1d7dad70654b6b435a82416aac33728217b4b4d6c *739f0a637a98f9cc684eb39ad7cce636bbf9ffcde8e8f1981f008c3adbf9ce78ceb39ef7cce73e *fbf9cf800eb4a0074de8421b5acfc828ef56ceab539eaeb793ed0d2a9771a63386488aa9637931 *3ae8910f7e78fad3a00eb5a8474dea529b7ad4f9a0479c7dfc806fb8fad5b08eb5ac674deb5adb *fad6b8ceb5ae77cdeb5efbfad7b546e43f3e9c57113373867fb582824a59e985f0c54cd086b6a6 *e9c18f7e58fbdad8ceb6b6b7cded6e7b7bdbfc50b59c9dab8f729bfbdce84eb7bad7cdee76bbfb *ddf08eb7bce74def7adb9bddd972ed3faf3cd08206e0001e887649de22f0829b60dad5feb6c2b5 *ed0f7f2cfce1d70ef7aae77cef8a5bfce218cfb8c637eeee7c5b39b6fd4ee3bf036ef02d61d3b7 *63ff4e45993b7dea968bdada2e8ff9a7533d71e702fbe638cfb9ce77cef39edf5ad8c40ef15efb *6a62655bcf49cd36015f30cd9569bff9e96aee34cc530df5aa9bb9e65e3db4d6b7cef5ae7bfdeb *60e773a211c9e8f4f6949300249b0a528c7430337d2b9adeb1dc694c6d98ab7aee78c7fa03a2cc *f7befbfdef800fbce08d3ce587e91bb6029d2d41456edbf83ae9cb963eb97d539e5f025b7ebfd7 *d874c2257e8dcb7bdec073d6b0e8474ffad29bfef4a86f30870b4f95a0eb75c444a7211ad6b66c *9cadd8042d96cb7d97cbfbe1cea2cc9b17f72c7a4f7c568bf7f8c84fbef297cffce65797bce645 *afa37d0a69b57f8ecba59caf49721f17c53236b21f55b9ffe6ed3e71f07b74b29545adfad7cffe *f6bbfffdf0cfac6a597b787e2bdedfb685afe3e3583ac9bbf8a95b158053c558e25777fd207172 *36590228805df55571f58010188112388114588172a55a77556c435762b247548d524a86650213 *f2765a3151e6d751514566e37780e276609475821b1552343583345883367883389883246553e4 *d568ea457d69e75e43a5504585334865024a458254a14de6d484dea40129077ce4376e7ea0014e *7885e8b44f5ab8855cd8855ef88560984ec6d44ffb0672f7c778086540fbf7060ec530dc5747d5 *5048b874487ef14a60910e083785ac960eb4e417fa800c72881774b84b846815bdc448f5904526 *144cc2344c90ff1339a32146632874b0c7817f054dd2447ba48433d6b4216f386c75c134134344 *cfb1477c931d79c8827a376c81244180184583588821842a88c3488a18278b013c8de888380289 *b822893c884967c75e64034ab29189d84758b7974afbd01da2e810a4a81d46b41048f40fa98880 *ac56154cb4104e9425a3e241eb238becb348b648188ec48834c28bf7513cc643493c6886591600 *07d546fcc276fc374788f54025613b2132410d2137d7d8827366159d123422d24125a13eb5248e *aab248bc4342e7082bbb48325fb44293e44295886c3554401eb889a373543e54151273260be917 *df701de01390ab68155ed2001af09230199331d9005ce19232299314ff001edc03178570933249 *935b61933e399431b9012b4006bf206c5c81316440944ef99432f900d0101f24009544b9011f00 *047d500cbef88bee38574008546623333884406df3065dc04055713a201422aa93547017852b88 *8d03a9159ea00193b05c93a0015c8197c8350923c007a22882d1b815cd300279795c7bd9978959 *7ca9600aa6b05845a0014bc00d7db10f5c00068e597c9ce00253091f24a0089b195c91e9075230 *02206008b7d227930336cab378cdf33c9d23581f8833d8137922a968d842376a598272698074e9 *5c7d990a520006c6799cc82905a9c0975ba101c4899cc789057ea0081bc05aa128444e9315f2b0 *018ae00758009dc6a99cccffa915ce599ce0799ed0f99d7e009960e00240000f7001185c2059e8 *599ff6799c52600a9e49958b759ff6e9079a900a8a10041b500993f495b1a739f7d21ab3598fb5 *393a02933e93e23076f804b7a39254f800c309069c705c9ca099e39915cec9a1c5f5a11fba022c *19877744872bc0a1244a5c1fba9c1bdaa1c507999ca00860800593600a60b001bf9016e6319fcd *359ac9c5a3faf9999241028b15a08e690a9c405960500702ea0229e00c91e83594138465e31a04 *744344f8a04e92066ff38914628a22a894d6f89bc1b792e4990a9a990cd710a7726a6020baa1f8 *25a771ca0b9c8005c489078bf68a25d101ca89059cc00b787a0d742aa3cde9a677ff7aa88e7aa8 *cf900cbc900a9ce09d4fea02854016415a519300a78ffaa9a01aa7cf300b6070a4fcc9a19e1aaa *909a0cc2c00b91c9583cba01bdd01f29b33222e73c31e3a56a334aa143693b33a1a9328d26508d *99a6a67a58976daa9999e70eccea0ee8700d8c1aa25631a2a9b0acccfaacbc80a3faa90c64210f *c1d0073a60012ec0a38a60a8e8d0accf1aad766aadcddaaeee7aade8200e883a0b1fba9e38e0a7 *5ad14b42daa9e2f0aefefaafed8a0edb40aaa60a1f20b0589c900ce70ab0fe1aafdbf00caeea9d *a65007b2ca9afe212f99b339f8428fb865963813a16041306ae28f710317189a8d8baaacee900f *2c9b0fee00ad759ab2d5bab22c2b90d3ffb901f09916f0a001dda9829cc6b22fabae327b0d34db *b2467bb4464b0fce8aa8a6e007a58a03a49015bab3a9cda5b0f680b4589bb52d4b0f035baafb69 *b008abb05aabb557b70dc9300b08eb071ba00bb90228bce22bc0b2b1ba4a3d8ee7364724b229e2 *3d5862b2c6aa8a19baae2b6b6d2e0bb38a9aac339b0f824b0fe2900c3cfaa124a01624e0a2a690 *0ce2c069821bb4316bb8448bb8107780a9e60e66db5560a0091b609987a33b85b1af569b709d8b *6da9d6b5059ba4618b0e9c0b71fc50b3d8faa13c0a02ccf027813228bb1024721b3dc8688fa604 *66a9441e6f8984ff475905b8a67f3bb481db0f832bb49a1bb80ef7bac9b0a7c4490664410683ff *9ab0db60b9d98bb9cb191eec20a28cbab9fde0709d7bbb8a0b7a94f501f88031e4a2bae8600fed *dbbaaecbb504fbb59271b0a84abbfbfbbe34770dbc90099a290561f0273e020941122c9c33b7d3 *04a6c2f10650725878bb1dbc593ecdebb3d08bb2d7cbb9d59bb9eaabb2b57bbb2fcb0b8ba59f3f *ba15bf30ae9365a82bcbba25bc9c78919dd4cabed43bb62dcbbaf0bbb83c9a0a41b00a863835f8 *abbf9eebc3640bbb2eb00c73d20e029cb004bcc43eccbad46b0fd88aa39ca001baf01fa921c1ac *d1a5a1d4916c333a9d68026da98449e429e93b79ce2b857e2bc2277cb8974bb81ab0293b3cbd30 *a7c5d0caa91bb00e5ab10e1bf082d59abf587cc31aff601742b4c724acb4007b665257bedbc0c2 *93b501f59b1e2c92c476c7b00c2bb0ff0bc5ea32c5629bb80c2bc9889bbd2d58079a000642901a *a721c60c4a960eda2884351c032321e461a67d2366713c9702299cd24bc2e6ab0126204855e1c8 *3097b8423cba7540027ea30f1fc0caa54ab9967b80772cb4f300a826a0ccd4fbb2a1ba0d957bb5 *7dbc6a9a8903cd6045a9cba9566b77f2aaaa9f3aaa5e2bcac123c5b3fbc8dba0aae2b069b59b6a *8bbba75d1cbc612ccbd0738c999843a594960f751cdb21acc40ac7207cacc23cc2d90ca2dc58c7 *3cdccf5cbbbd0b3c05563105ca89aae3dbcf155db855e1adde5cbdc8c50bc9b00d889cb895dc9d *75b004e4ff48189ccc82e230a9a369a44f1c2b9541ca55fcba3a6d5cb360a895dbcf415b07a620 *057730d0c3cbb1f065bcbba50363c1c66b71346da97b7d1b9c5e05b8c48cc7064915298dd4083c *0958600a3860c4ffb00a38600a3a4ac3fdfcd5d68bd1d35bc2e8e90785cac3fca0c51ccd0998bc *2a8671d3e196d34eeb9fe7999f3d5dcff63cc0f83c0b850d9e759097d6fcc8393d0976e0072ce0 *d44442c6c75896c6bb4077cbd0c9a1b768cab7bf0c9cc1dcd5c35cd21a50226092d2d7bcd7cfea *d87130091b600ee650c871e007b39079f69070a926d7263cadeb5bd7983bd4c315b6475dd223c0 *0e8921d88acb0b784da49d49cff301d48dad99c655afe2f7db82ff8b0e8c7bd61a400c0172281c *499bb63c3a3f405f559d1ccbab54db71b2c84ad7c22da3b0b3102002dbde4dbdf1eba6f3fb01cd *f5a6cb7d80f670cd8aecd525ed0232e902788dc2304db038400dcfcdcef9ebced26dd656e9930f *00c57482dd0ffeb437999f6050ae239db884eb02ad10cb04dda0b8f5d963aacb72413e0b7137e4 *21df134ddfac4d157a9bd2ccaad1ffac9958c0a7a83ae0df6cdc788ce0df8cc777e10116a001ad *4cc59c1b6e958cd752f00b135eb5158ed3172e05ac608e11192358e3e1fcedc4b9a01fce200441 *e0a6a60063f8cc0b75c00941f008b1fcd49dfda5cb564a206b1c64a18415aa4bbe1cd1733cdfc4 *ede0496ebdfec8e344ffeeb295bc58c135c3dbc0c7fe6ce4733de8765ce8753a0fd7190114aec4 *52bee55d8e18d04dd893c0e5c0543f8a4d1962febaff5be6b6f20138daa955dce954fe074242e7 *b171d075fb06694ce330ae16c1602da062e3aa4dd1966ed2ff60443c7e0d032edbd7e0d8c6c9db *be0ddc8a9bd1c58ce4076e15e950c8609009a5cc8253ce09557ee5b0cee9d1dd5ca4fee5602e2b *a9eebf5ecbea1629049b6e77533eea6b20bce64dc1c562c14fd27f7b0e170e9d2ac2aea1ab5dec *d2fa0fd592ecd19eb8e5578051eec7d47ee403afc82430f113bf019aa999cf50d75cebe6a61004 *cd20eeedace5e6be01145ff2267ff27c70ea97b1ee64ae3fd3a0ed502eefd2ff0dee7f802f057d *eb3493efb5373ab7e7e764ba84588d2d016fedd5ae15df90ec702ded423cb9cb3eb8709de3118f *b9684b5590f9d6255eec2e8004a0600d89b8ce584eee84ad094fba805105065380352b7fcf1fae *9f94900b6eff0aa10002215de9aafeb48f60eb8a52cb1ea9401f02174c45dae232f4510ff1c45e *bd2d7dcd63ce0bbc70f5636e600f3fe9c95cdcc27d9edf3909e6dacfe0edd6a6a001247726da80 *0fa12edddf69d8c84959673f1f99c1f2041b042ed0faad8f03406ef9577fc3288ef70965e7bd0a *300d12827aae1611f5de1623f8855ff4c30fad4c1fdb0effd2fc2dc4744ffc385ee89c10fdd21f *fda6900ae66ae01bff822c403b81ff1aef5a3efde01ffed3dfb3a75f27a9aff6634eaa9c0099ec *0f9938aa08bd5dc5d40bde00bd01b67fd0c9383a90b71059bdc14004106a4c0c3451eddf418409 *152e64c8f0819f497e523d43478f5fbf7efce8a17b960aa29f070d35a40293ea9abb7c18f3b9bb *46329506912e4fa6ecb7b2a5c46b152fd6dc5891a64674374da254c9d2254c86234bce2c7a2dd9 *53a8509f5d13e71323bf7c41499a0a420b1fbe78d640511918c10fc464e8ec5da5272eea5bb851 *7945f433a5dddd7379f582980486535a9af9e86d9be507cc61c460eaf8e1c48b22bdc08379293a *9bc2d765ccbe606de60cebd427d0a141636a54ba3421d47b54bf79d385a0094f0d19f659ff184e *07c127f264efe6bdf061c4893ad972f41831645299446b1a2d8974a1d2a181994fe23573a760c8 *576dce5daadce6d198dd23a3235fde3c3a779053fae3b98dbba60df3becec7376f198bb393d2ae *cdd8f3fcffffdca2cbae76f432902fbf005349b2591a74b0415e784926a7ec54d20a0caefec8ec *b2ce3afc4cb44f3021cd34d408516db5345ac0adb784684b0898d71cc187451a77fb4da2c77602 *aaa38f8e7b2e39e95a6a2ebce89a22c92f5eb6a9b0269adae38593c38a5c4ec89788648ac97cb2 *d4724b2d315ad02d533094a210facae422bffdb4e3724d36374a664003e344f02f7422dbe64e3c *f3bc13bdecd813ccbdbee0db10b30e37fb5034ff114d6ba44413577b6388d774abd1c57ff071e4 *35606ad4b4a11b83b368381e8db3d23be6aa444e3c2331c43019712ae4e7bab69209334c29bf1b *f2d422d9f372575e77c5aa2d1e218aaf4cface444bad7e74ed75595fed41e7cdb3ec8a73afbee8 *8c8c1e6cb3d5165b7bf2d98927b7b692a289410b3514c410472431b513dfb0e235643675519e27 *08d2219c4df355a8d31c412d0ea45183040fd72b6d2d0c47abbc148cb8b3664175ca817f445559 *66fdb15861c1c4e1d1af0dba21763e63f543966266997516dabaa6cd8b9c3915cc884d2ebf5d30 *a88327d940960dcd3d1444754f63770fd6be88315fdaaa794d8d79f455fa207e85eb8f61510926 *954affe71482aee052a154a4ba3a75ccea9ac9fc023255532596122b98b594f9d77021aa63858f *bf0a39cd97d34efb64385566b95a0549ee95e45f839a0b0b53705823b35bccf50cdd7415fd19e8 *375224480d7dfb00e5b5d8965ebae94f9f0e1560a905bed56caca99422152ca853d2cec15339fd *615bcbb67a6c9eb6b55dbd8bfc8c95132c52c10198b8e746b6bfdb8bd7f6d9bc572667f9bd13ac *33d99279459b1e77346e5d8a10caf590f110155df467d6deb0c15e4937bd8d208334dffc234f75 *dce8731f6787bdd4aa13ba7a6a974650d51456d58b7556308c8076b1ab1f42ee271d3d25b02af4 *e896c2583299b3c0ed63c2e38f46c491400ceac929c953defff25af63c2ca5ed2af6688b5352a1 *88de810104382394e27696ae9e7def4490831441bea134dc944f7dfae29cfba0063ad2e16f74f2 *ab15fd1e42194fbdcf2394d9c001c956c08338714abc78d08322948c6d248c1f27a3d508c241ac *7a50902de2a06215cd7846ba744015d33807f398f7c1f100482db0da86304c6118d46120169849 *9c0bd195a87581ef0d4780d7d20622a31d6aae87feea51c09ee8488835c70223d0da2c72423345 *f86504d490220121f91dc324e6307e508429b8660f58810d2258b0047deaf14a31f6878c991465 *2d6d7996080c44078658e31bf906c23fc56575dad14a8ff6d8429dfdd17b8c6a97bb5ee30acd99 *2053895424fbfaffe5b97fc5cf7e03a4df27e9078c0ee00075aa0354ef7060897f74b29ba1239b *29dcf94e4e18863a57b2e09bc0e00716cca71ef880259a8667415e90f29d032568413dd281f311 *84077f78c5077ec93a4e4434a2fc6b5564c0549220908b433a7b61f79629c82d604e7d94a36635 *8173cd1d65d39b545b2978c2110155fd2519500a1310a2c84d962e641feaa4120e5cf0d39f0641 *22096ad5759e650ac26de02baf646a2c010a11300055aa53a5aa0b98400e67a8c20c28780d041e *ba20c224060b38e91a58dfa3815168c68f3cf3def71a05b92e707520945a1a5d4b9aaf4562b391 *ec8ca4ecb639bf9ca6a3026e4b452aea10910ddce3a6808d1842f6b153ff9c1e851b93ad46357e *b1013068c20f96ac1001d5c1d47ac4231e53f06705db12d04948810fcb606d6b5dcbda610c2317 *b3cd8534dc488e6284a20c26f0aaf3ece4b0544c621224519dab9cd591c382a1038a8305e30019 *c866c6952076551a75ef5aa3bca674af41149d5f0d18d9d17143039ab8a761e0c38def32f656fb *38c86321abde97102b1c1b40aa299ee11d7a08c9142e0807685f49da6399968c10914227ee72e0 *02a94c2fb7659e37bc810d0c7cb53d0edbaf04a430abb4742e633335a7190ac5bde7faecad4193 *ab0948ba43eb5e9745d955e2768958bac6feb588393d0829c4890573a233bd333e0a7bddfb587c *f0f4281ffb004d5d26986b50ffd805d678a568450b60910918b5053eb0823bc8600767d91b7004 *ab9243b101ca6cf64a5354441c6c568ace7434c4eb6ae6174a7c6214ab9887d6749a76a3c6dd47 *f2d5930959c2e95c17011ddc70b13c6ece8fdd1b64f0c6b74cf3a02fe1ee1b19fdbaa01b4e7632 *94e9f6d4d41a38c10a667083b5ec602e4f18432e0881095c80d44c60d1556e2209945260a88e36 *2e90237e839b27a78f92a658ce36a273e7ec0cc4170bd1bb8386f110ffa18f0f9ce5011e18c834 *855ce8af00f92bcf56f47cc2c1022940c9249d2dd508d841e92797768c53ee8495178ce54f3f18 *1ba1fe9392336002986a9b22a834eb2408e7022f2c4e998e2b5133b7f0e6ebea7ad7ff9ceab50f *e1d75263efb8d8defd860634d089d71802d1f0d580b4e9436d17385ce3fa1b272f8a6aa167d477 *03e00e7780c7bd4a8da75ce52b77f80372a1656cc49cdd8351f21acc60020df4656b63b6c9c1fc *b0815238b7adfd76d4155e23f0ea0e5c532cfea136152e6c28a633d15064052bfe611bdc505b03 *717b362f0afbf5c26a020b8ab02408b7883c30288204241fadb86519504e805dee73973b275cf0 *7275c77cdd126ef7a84571192a8893a8ab3eaa9862f0c79e11bd5def9aae9c91aef48430fde07a *5e279efb1a7584cc432003d13ad7c16bcb7b7262168f611d540bc1764bfff3b4a1047debc170e1 *bbeb5df6330feb7eff7e191080e1a473acff3786460088d0c4d0ad33648d1244ea78c8d348f22a *a53c8d83dd5dcc23041f97c3f9d43dcf58ba17564214fac9715de28265a0deed00cd7ef9bf3eab *d8cb5ee67ca7b9df31838a0d40a9b83ff9dabf3080095943773540ab61b307fef8e4fb87e57331 *195bb8a8d33a8530b41f339acefb189eba06088c4009dc0671488ff570129dc300b66b3b939325 *09fc4010fcc06750b25750bff5f3ad2e733fcc6882d7a1a8cefa1f8cb2002f08848fa2b537b881 *d7489f5d03c0e41bc03b7bbe3cb3bc3dfb87c76a2f43fb0a76684062e924ea7107277cc227cc16 *6f511818e48a4e00b7bbe0c028630b28ec422fec4274a83d172841f58b06da53b2dbe3100c2025 *ffb29a420ccc2c0d283513b0012fc803c5638d318081d710b4ff4b08f60a40df283846fac10284 *3a847b893ffcb1683b42252c934eb21bb5d99585b989b3c08076a034044bbd0a8244bb69bffd22 *436c8806513443f613c334d48c4518813099bf11228ee49280d7300114f00125f882d5b88212cb *8de4eb03052c42220444cef196c0993c21ac3c20bcbc7d88367cb0b825b43e071c1bbf899e97d9 *08b0e98bfdc205d142b003d344e891c692e9bb4f0cc55164066638c351bb848dda8c19b8b055d1 *89c0011bb1f31d1b38831f28b18140811be83f13e04114ebc51f73ac3f9433ced996a63bc4039c *ba648c9b66a4b8eb93126ff412ac2021ebb137d72103ff27d3c6bbd0449979485e01c7311c4772 *2cc752543274ec905200b38699097ba81eb0b9a31482003d400d3750821bb04782802640ec0362 *51c465f4c7440cc85fdc94a60110627c3e2de9a65e3ca0a3a41a857c46f158ca2173cae8e0442e *c196304c86134a211238078cac324da44a48f4c48f8c8690244738d212b12cc90e618353c38254 *5392a0c04a9d330529d88021781c67ca41403c089d544869f349f732425fc42ef6498667384cc4 *3c4cac244085438f27bc10444c4a99704c2784ccad6b4a479c4c28b4cc86cc892ffc4c77200f71 *700a5eb8a39200830f1887ae34104bab40d07c4d3014c35728cb90fca0cd14c345d09914f08b92 *78866d7886ff27c1233f7081128849e27b8328381a1d0ac0bec4cc9e5c44fa004cc12442436baf *4e31bf6cfa49f7828e09f940ac2cb4bf4c46ee04c1efac36e79cb854e84e092ccfcb7425f454cf *100cc16748062a32854c2a2529608172d04695b1b4f8fc4f001dc1519b4dda14c904014101ddaf *dcdc9e48d8009d9390ac9c044e9082085002417a831f38bebde4cbf3fc98f05cc4f0044cf7fa8d *f23a0b133d517902097f548ab8a33b6dab38a76cd1b97bd10e9db656cb3e1a75a5576251ec9c3b *77e28488182b8f18013ce0ca2a533028eb5125053bf423d0b2240604d184ec43bf053d97d07002 *c18ba828a9830d78813d782bc8f90215419f0d6d911a3dd33261c6ffe87cac87082ee17a533885 *538f788084cc4c2970bdd3694f3bc553f374ce91b8d3d6cb53ff62aa3f75bdd6c382d0bb231c00 *8161a8b24debcfb3305449053dd8735272240628ed0b3c5550ce609cdceb0b2c00521ca0003400 *d3f03102e52c53334553563dcf078003148d5514858307e0bae1c2ce49d0d38bbb55f3cbd533cd *b91ecdd53e98874105d625655253e88bba64015b403073d38b292889639dd654b03b51084962c0 *0c1050841eb5bbdc8cb54f1884f81b2e30d8801c781ca0c9434c51558568ce567dd78f69800798 *577aad577ba5d706889b06603996cbd778e5d795f3d70edd57804db90630011ee8afd0122d822d *5880dd001298024f0007ffbc78d60e620287cdd88c7d806bcdd6cc00018dd58007003ea16b841a *9082e1e4003bb441e3cb217655083980579925960020000598001d50034f00866fd0077df80660 *f00435d081095000020880994d5a991dd4575287dd228860d840a9c5c4aeacd867edb406238774 *cb3b131447b22c50daf4d84141a664423c7589800d4802305d8d2f9081677ad9858859a59dd99a *bdd99cddd99efdd9a01ddaa23ddab9fddbf3645a4a0b2dea1b084a985a92ab5a67b558ac5d9ead *75b0ae8db95124cbaf05db6c15dbb1652e7ddb3745418398b44142c28d7480db852803c085d7ba *c5599de5599f055aa1255aa345dad3555aa6ad5dff023763780d2a0087a9cdc2ffaae54ae0bd5a *ac7d5cae35c1c9ad5cb065064c1ddbcc602e701591c49321e2eb023d248869225d8530ddd965d5 *d4bd5bd6d5dbd7ed5bd9ddde1add277eda27f4b5dd8545dc7800877a19081a3006b653dc4765dc *c6dd5a6c28de3204c9e4555e5fc05ced71a15883de8f9a21c8799454c5ded205ada5325ff2fd98 *ee5dddbc755dbe8ddd072e5ff51d5cf64d5c44788d50b844fa3d52e16d5cadc5dfc8f55a51ecdf *4b5d5ee6552be672aefc13315345ce12d381785160862883416d601ebee008c6dbd6dd5bd8f5db *0bd6d10656df268b8724dee00d5485d7280375f8dde01de1e17ddc13d6bbc95561ff6de13e7a61 *106b2b9f39ce2e705b82f0045cc3e1ff1c4662ff72cfbffde1efa5e0211e5fc055e3da65623bbe *c876908684e2016910618b6d2312765c133ee12cd66200ce5ccd0531e11bbe664a037d5483d145 *e3862803275b583a665a23d627078e1b379e6021165f3465e0f3bde441bde33b56dc7278da8150 *853f3eb7fb1de42b2ee4fec5d443ce19cd7d5e3056bc0356821abe61499ee4a9052dd12265a6c2 *074a0080004866655e6665b659d50562f0ade0a365666a0e0000a0845126664b662a53b6e310ae *b2c2358144a0e22ab6e25896e5e4a5e5164ec7b532db1ab4412b18d381708533fe6560eee64aa6 *e304180002e8677ffe677fb65b090ee2f0355a803e680218800450e3615e5f25c66753fee6ff04 *dbb45e28312ac8863809644ffbb4fcbd62144e612d5e67b2f59053186002e637bc7c832d20e343 *5a4e7b2e5d8826b9255662a632869a4d0005c8699ddee99c7ee637fe649e0e6a054880a3955f9a *5edf998ee9889668ab9d9669208b7bec054026616f28618ef6e85044612ddee275d65ccf30e95c *d6e5a0c1c1c989e497de0d4a566a2616810138809b9d00b88e6bb9f6694f0edfb9be6b05388001 *1001b5ee6bdffde6565e993f780d507865e2c56aafdd6a755ee72e4ea6e75d3346769431c850dc *d0c1b346ebbede6075180085660066d301d00e6dd11ee868166dd3be0d0f60807d1e0075c8ec53 *0661a6aedf3f661e27268832c886db32678f3edeffad2647911ee9ede11e8f7ae7e31c037db4e1 *cba691b4be44d7dec044b8e9093081275003eaaeeeeaee036876dd3eb06eeeae970920ea004884 *e6dec0d85edcc0ce68062b8684d28162205efd8d5c744ee75a0ee076e699e146e91936eed7d081 *eb4deede2803fa1def784080b6166847f004044ff004ff69056f7047a860bd4e0001cfc6f236d2 *f39e168dce0655360155b8eadd8e6ff9fe6d76e62845163e666aa6c9deeffef6efff2e6f0ac767 *9b268004f0ec27c06e60b8711cbf7164986064c8f11cf7843e7882d4066fa346dc2cc4c2f2e6cf *0bc7708d765cabae84d7f803c4fee8de66e1dff6eae6126ed288a17e9be12fa06c5d5a7116ffef *e04df2ffae4c5ce616ad0b28f0e856034770851dff06399ff309a6f339470657787013285abdbe *00aa3d723397e20269ea256f72377adc5ab0e8633867fe55e1c5e6622c2f692d37715d5e8d2d20 *6b5df2e531af913288133f0e74c51d07ce9e710ff0de6a480779f059553f0855f7597948876a10 *e221e76cd504758cd40bd95e72573674abd6ed63806a594485fd05f1e415f111f790cd45bcb04e *69776169e9d6f44de7f456b6da234df23f806ee9c6ee1daf67d9f859640072ef06ef3f48f2bcf0 *635de7345e3f742b7eef501c6c82a884e345de599e6f44765e492ff1653f4ee4acde8150033e8c *f64de9f47357998afddd76300036cfd9374706b3968d74c0f3ff07875dbd368082cf755c1f7874 *9f6a43776f989bf250780d283886dec65663c7f264e79945ae74c8190323b0c73e6878800f7837 *521e8cb7d85eb8691ab7f16a70e98490875807f7213f5aa9aef9f34ef74ee378c89df2e3d5051e *b0975a98772b17e94817eed168044a4757d6e8821d88454fe0f998e77412a679a237903577eb36 *5ff89e6d086fcf7381e0f301b880b1cfe82b33fa12ee75589ef28fa65c72dc852c788d47085be5 *a5775bf66aaa87deab67f628e077e916f3afcf9732a07bb1d7f56c1875cf3675984708589775d5 *e66c8c3ef7e5997bbaaf7ba44f7abc975c620f4941780d33f085c02f7993bf77e7826c46595ba0 *f9822170f97f6ffcffa52903070bfdd037906b97f1e8ae714fd8f685f07670df73717765d0f77d *aa1efd9863f758367d901e795428311e3826a93779aa8f61fc3660c8b10267d70157f07add777c *f7767e434778b3577838bffc87677b891f0003507f5e1ffd2c8bfed2c7e2786f74c506085fc464 *513161d004245f0a172e84e5f021c487a73e4dfc64f1a2454c1a3135eae8911048427b46927cf3 *a6cb1014074da8a9f6ef25cc983267d2ac69f326ce9c3a6596f1e6f327d0a03ec9012567f428d2 *a44a8dd60a402001030f4ffa7802564d5e4c79d58079eaf3c40383040402d45a6af62c51a16ad7 *626bebf62ddcb86da3cd8d66d72eb3bc7af7f2d54b4c2043856b56ceb9d5ff30226258a716636c *fc4963238e1e3b86044972a4c9374a60acd4e109ebced0a247931e9de5adcfb66b57ab353a94e8 *d20b030e2898c0d2912b64dff4bdd4f70d992b476a4c4c507060c005b3458fb26e1e542e74e874 *b1ddc5dbf77a5f627fff060efc68251459891133767c71a3e4c995455ece6ce5c64a137d5c96ae *6fff3ee9d3d1517b53edfcbf4fd30c3000541ee8a04655d5a4f3523a5b79a2860e602530e03400 *02e8df7e19ca555d75d879e89776dc7537a242a3f070100a8c8c375145e6a137d947955db64766 *5ba4b4d213c0f0861f8f3dfa18937e1a0a890d50fe35b7865309d8369527bac923cf6f5d3d419c *5801ac612186436ae9d6741ce2ff65dd87d711c34c88249a19912c50ac2408442d9a97517a30ae *3763665f18d142679e2cf8239f7ddaa7df745b0aba9f01b3d576206ec8a4930e70c2e950dc7106 *0c3aa9745e76c80c986166c79d88660676cb780fb5b152156f9ef7188ceac9d81e8d631cc1d94a *8e7ce327adb58a0685a577513a282a4946c5a4550e7a25e158a8ec3a69ae996a8a9d76647afa6c *a88941a292413c44e2e246a93632677b268d6104ac07cd672bb9e5de04455f5f26cbe1b16ec946 *9b6d6a24dae870900ee040bbd455a76fae7a29bbeca69d3e4b62b4e36124490f2b01026764da6e *6bd98c98bd6167b806f581cc8ee66abcf13fe802ccd7baebd635575bc7084060540756ffc51584 *120e20c03124eb3b32bf21fffbb1a621ea3cf099059367ea2755aca485c3db3e0c319d36e2b9d2 *c51973fc74b91ee33c35a636475345924b5225259563556175d57bdd4cb5873b03c673cf3e4ba4 *18d0186172c64a361ca26a4811d3f886153f502b2ec650fbadb1c763923d387685c28ba8a3f61a *4038e37c09be9d766843ab769b8b95d7f68b8de4b1b4092888b12a9d6f8ca1047c79cefa37eae6 *42c190cead37fef126be4ad5c7b0618db5c9eb00b7ae50e4920f4c796296b70d67b6a91e62c34a *4a846ed21543546cc213aeec993af5e4ae2e79eb8f0bfeba0386c65baf71f7e64e66f665fa2ef9 *2da0c2e20bf0950f7f5ef1dacae8c54a3764ff3631e97b5b8c0c68d5fb6febf5ce67a6de11507b *796916f9b4238b93154807110acbcb76a1b3031a907cac13980033d8be9fb9c954e8e1489ce4c4 *ad91a0616f2d88c20f3867902778e274ff7b2100332843b461ed29b6e95a00aa30c31dfe6e83a1 *12defb3e1842ba81ae2426f982fe0ea20347f00f864eb4de7878c843c3d5467152dca10fa365b9 *0e62ee8345a3ccd1d8b33cbc392f3e2c01c6f49ea8465a41218bebbb228920e12bdb052021701c *911b8107c4f7c10f325f0ca348c45812cc8c210a658c8f1a5ce1c23532925644c8e306cfd73dda *84cf01e78324266161112e7631737f5c0fd2ba7544d2a9d020895c642353e927229c2293ae8c48 *29ff1838210194e295b654cce5f8d8184f7e9110942962e8c6608521c8c08c3ae8031a55a94c72 *11c13c6eaadc2da37502a78ce504d1fc612b71b9c95cea124e8ff1a31f7b094a411a31335730c2 *0d9208bd26f56f99ee7464372f02c42d92278f8c18d0805464cb2d6e319e6fc2441f413844f9fd *1298466c9515d0594a131c1318bb792744c965037f52b431e5e1674516c388090420001360c436 *fb29cf8c72b2a21e14e240c53942bb99e46e5f48e80d16ca12575c25a2362d970d1ad611219ab4 *a7160984090e70001380d4a726156264525ab471d6cd6e77cbcc18ae70841f3ccf20c7a4693b6f *aad55ae5f48f9341a946e067d49f9ac0031e3041208c1affd680662e9c5e4d15539bead4fb89ce *0a5395813aa1e708873a6dab7eb5950d42f2d62f8275a7603d2c40817a90b422f6b08605a75207 *1b5783d249626fd842148cb083aa5ab50fb949e35f438bd3c95666b0a67dab620d1288d3b276a9 *a495ab536964c4316056b330c82bf43caba8be8ab6b7388ded1e5e0b92820eb7b5a94aad09e860 *5cb81297a923a16c6ce94a5bbbfec00632b5aabcac025adf7277633668e9dd801b5be192b73262 *58c9e7040b48d23e1794e2052e5d45b7052b2861083790c175b1bb570575b7bfd433010c6cf083 *2128210a56f8c218e29b99f73298c1e73d88181a2ce1b95af67e637869148e3084eaded68cf141 *546ebe9155fffb9218751e5e090a5a00831b0cd80805b6c21610ac60f0de6fc22379b041226ce3 *192bf8c2f38d82128cb0e11bc0a005b88dcf13e4e50aedf2b6c44eae9e3c1a048ce0f4410d533a *f18953ac6219dc6007031e82118e5060035be10a5b10c317103c8635a7e17e5658c915ee978635 *af39cd62d8c215ac60852800f90842def00eee5b642363f9c449ee036eb43be227331aa2fa48c7 *37aa818c297bc2115ed141a133ade94d739ad33a988a233cb1646454e31be96872a353dd687d44 *f91b919ef4945de1894ad34e0db67e02ae1d88e94e5bd581b84eb2ad69176a512f1918a476753a *e4816a5533bbd9ce7e36b4a32ded6953bbdad6beb6680302003b addfile ./examples/menu.html hunk ./examples/menu.html 1 + + + + + + + + + + +