[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:
+
+
The first four lines of the module body
+ define a struct, or record, type,
+ called Counter. This type has three methods,
+ and will act as an interface to counter objects.
+
The rest of the module defines a class counter.
+ Instances of this class have an internal state consisting of a
+ single integer state variable n, initialised to 0 when
+ the instance is created. The effects on the state when methods
+ are invoked on this object is described. Finally, the
+ result statement declares that object creation
+ returns a Counter interface to the object.
+ Thus counter has type Class Counter.
+
To create an object of this class, one writes (within a method
+ or another class definition)
+
+ctr = new counter
+
+The variable ctr has type Counter, and the newly
+ created object can be updated by method calls ctr.incr and
+ ctr.decr. The state can be read by
+
+val <- ctr.value
+
+
Any method call has exclusive access to the state of the
+ object; there is no need for the programmer to protect calls
+ further.
+
The two action methods are invoked asynchronously,
+ while the value-returning request of course requires
+ synchronous communication.
+
The notation Counter{..} means "assemble an
+ object of type Counter from definitions in scope".
+ It would be possible, and maybe preferrable in this small example,
+ to define the methods within the result expression as follows:
+
+counter = class
+
+ n := 0
+
+ result
+ struct
+ incr = action n := n+1
+ decr = action n := n-1
+ value = request result n
+
+In more complex situations, the {..} is a useful convenience.
+
To see an example of use of counter, see EchoServer2.
+
+
+
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:
+
+The root definition now has two more components:
+
+
The (implicit) declaration and initialisation of the state
+ variable count, which will maintain line numbers.
+
The auxiliary procedure prompt, which writes
+ a prompt to the user and increases the line count.
+
+
+In addition, the callback and the initial action both call
+prompt, and a greeting phrase is added.
+
+Some additional details:
+
+
The keyword do signifies the start of a,
+ typically local, procedure, that may be called from other methods
+ as above.
+
show is a function that converts
+ the integer value count to a string; ++
+ denotes string concatenation. Both these are defined in
+ the Prelude, a library module which is implicitly imported by
+ all modules.
+
The user input string given to echo will include
+ the newline; hence so will the string echoed to stdout.
+ But to write the welcome phrase on a separate line, it will have
+ to end with an explicit newline.
+
The root object maintains state variable
+ count, which is initialised to 1 and increased for each
+ prompt written. Obviously, it would be possible to use
+ a counter object here, but in this simple program that
+ seems an overkill.
+
A more careful description of what the runtime system does
+ when the program is run is the following: it creates an object of type
+ Env,
+ applies function root to that object, creates an object
+ of the resulting class and invokes the resulting action.
+
+
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
+
+
+
+
The message to be printed once a second is maintained in state
+ variable current.
+
The callback installed with stdin changes
+ current.
+
The initial action not only installs save, it also
+ invokes the auxiliary action tick, which prints
+ current and schedules itself for later execution.
+
+
The scheduled execution time (the baseline) for each instance of tick is
+ one second after the baseline of the previous instance. Thus there
+ is no ackumulating drift in the program, even if a particular tick may be delayed in
+ execution.
+
+
+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:
+
+
The result action of the root definition just installs a
+ listening callback in the environment. Such a callback has type
+ Socket -> Class Connection where
+
+
a Socket object has selectors for the resources
+ from the environment
+ needed by the serving object: the remoteHost and
+ remotePort and the inFile and outFile
+ parts of the connection.
+
a Connection implements the services provided
+ by the server
+ to the environment: an initial action to call when the
+ connection is established, an action to call with
+ an error message when a
+ neterror occurs and a method to call when the
+ remote client wants to close the connection.
+
+
The echoing behaviour is achieved by installing,
+ when connection is established, the
+ echo method with the inFile of the socket.
+
Additionally, the server logs its connections and
+ errors, using the logging method
+ that it get as parameter (which logs to stdout).
+
+
+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:
+
+
The first line just states the name of the module.
+
Line 3 contains an import declaration; we will use resources from
+POSIX, a predefined library module that provides the types
+ needed to build programs for simple environment we described above.
+
+Module POSIX defines a struct type Env, with selectors
+corresponding to the resources available to the program in its interaction
+with the environment.
+Among these are stdin, which refers to the keyboard,
+and stdout, which refers to the screen.
+
+Module POSIX also acts as the default
+target environment for Timber programs.
+This target environment prescribes that a program
+must contain a root definition
+
+root :: Env -> Class Action
+
+
+
+In module Echo, this definition starts on line 5 and
+makes up the rest of the program.
+
+root must describe the initial behaviour of the program in its
+result action, which terminates the class definition.
+
+In addition, it may make auxiliary definitions; here of
+the function echo, which describes how the program
+reacts to an input string str.
+The resulting action just installs this function as
+a callback with env.stdin.
+
+
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:
+
+
stdout
+is a WFile and thus has a write method;
+
stdin is a RFile, and thus has an
+installR method.
+
+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:
+
+
The program makes use of two auxiliary modules
+ Data.Functional.List and RandomGenerator. The
+ former is a library module, while the latter is provided in the
+ examples directory.
+
The program complains if the user gives contradictory answers,
+ asks for the secret and explains the user's mistake.
+
There is no error handling: if an answer cannot be parsed as
+ two integers, the program crashes.
+
+
+
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:
+
+
The program uses a timer object tmr, which is
+ an instance of the primitive class timer. A timer
+ can be can be reset and sampled; in
+ the latter case it returns the Time elapsed since it was
+ last reset.
+
The program is a simple State machine, where
+ state changes are triggered in two ways:
+
+
The user strikes Return; the case statement in enter
+ describes the corresponding actions and state changes. Note that
+ a strike in the Holding state is a user error;
+ hence the user is accused of cheating.
+
Two seconds have elapsed in the Holding state and
+ the action that was scheduled at the previous keystroke is
+ invoked.
+
+
The Holding state carries one more piece of information in the
+ form of a Msg tag, created when the Go message was scheduled.
+ If the user cheats, that scheduled action must be aborted;
+ the message tag is needed as argument to the abort function.
+
The time displayed is formatted with two decimals, using
+ auxiliary function format.
+
Of course, the waiting time should not be fixed to two seconds but
+ vary a bit randomly; an easy but omitted extension with the help of a module for
+ generating random numbers.
+
This program should preferrably be executed in some simpler
+ environment with only a display, one or two buttons and perhaps some
+ sound-making device. The program would have to be modified
+ accordingly to import the proper environment module instead of POSIX
+ and to call the methods of that environment.
+
+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:
+
+
Echo. The archetypical reactive program: user input is
+ read line by line and echoed to the screen.
+
Counter. The quintessential stateful class; its instances
+ maintain an integer value that can be increased and decreased.
+
Echo2. Slight extension of Echo: the output
+ lines are decorated with line numbers, thus adding state to the
+ root definition.
+
Echo3. Another extension: The last input line is
+ repeatedly echoed once per second, showing use of Timber time
+ constructs.
+
EchoServer. Still a variation: Echoing user input
+ over the Internet.
+
EchoServer. A variation of the previous: limiting
+ the number of concurrently served clients.
+
Reflex. A simple reaction time tester.
+
MasterMind. A bit more complex: The user chooses a
+ secret in MasterMind and the program does the guessing.
+