[Improvements to web documentation
sydow@chalmers.se**20081112155834] {
hunk ./web/MasterMind_descr.html 7
-MasterMind is a board game with two players; in this
+MasterMind is a board game with two players; in this
hunk ./web/MasterMind_descr.html 34
-
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 makes use of two library modules
+ Data.Functional.List and RandomGenerator. These
+ are parts of the (presently very experimental) Timber library.
hunk ./web/Primes_descr.html 20
-module Primes where
+module Primes where
hunk ./web/Primes_descr.html 22
-import POSIX
+import POSIX
hunk ./web/Primes_descr.html 24
-root env = class
+root env = class
hunk ./web/Primes_descr.html 33
- where loop n = do
+ where loop n = do
hunk ./web/Primes_descr.html 35
- if p*p > k then
- result True
- elsif k `mod` p == 0 then
- result False
- else loop (n+1)
+ if p*p > k then
+ result True
+ elsif k `mod` p == 0 then
+ result False
+ else loop (n+1)
hunk ./web/Primes_descr.html 41
- checkFrom k = do
+ checkFrom k = do
hunk ./web/Primes_descr.html 43
- if p then
+ if p then
hunk ./web/Primes_descr.html 46
- if k < limit then checkFrom (k+1)
+ if k < limit then checkFrom (k+1)
hunk ./web/Primes_descr.html 48
- result action
+ resultaction
hunk ./web/Primes_descr.html 63
+
+
+
hunk ./web/Primes_descr.html 69
-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.
-
+all elements are initialised to the value of the second argument).
+
hunk ./web/Primes_descr.html 73
-procedure checkFrom. The iterative check is expressed using
+procedure checkFrom. This check is expressed using
hunk ./web/Primes_descr.html 76
+It would be possible to omit checkFrom altogether, using
+iteration directly in the main action:
+
+ resultaction
+ primes!0 := 2
+ count := 1
+ forall k <- [3..limit] do
+ p <- isPrime k
+ if p then
+ primes!count := k
+ count := count + 1
+ env.stdout.write (show count++"\n")
+ env.exit 0
+
+The choice between these alternatives is a matter of style; from
+ an efficiency point of view the alternatives are essentially
+ equivalent (the compiler transforms the tail recursive procedure to
+ iteration).
+
+
+ finally, we note that the correctness of the program depends on two mathematical facts:
+
+
To limit the size of the array, the program uses the moderately clever bound that the number
+of primes up to n is at most n `div` log3 n.
+
hunk ./web/Primes_descr.html 104
-none is found, k is prime.
+none is found, k is prime. Thus it is important, if
+ k
+ is actually a prime, that a prime p with p*p > k
+ exists to terminate the search. By Bertrand's postulate, much more
+ is
+ true: there is a prime with 2*p > k.
+
hunk ./web/bindings.html 36
-
Mathing (p) against a value is the same as matching p against the same value.
+
Matching (p) against a value is the same as matching p against the same value.
hunk ./web/bindings.html 48
- or instance bindings for implicit struct types.
+ or instance bindings for type classes.
hunk ./web/bindings.html 146
-instancevar::typewhere
- bind*
+instancevar::type
+var = expr
hunk ./web/bindings.html 149
-This is just a notational short-hand for an instance declaration of some variable and the binding
-of that variable to a struct expression.
+The type signature of an instance of a type class is prepended by the keyword instance. For instances,
+a type signature is compulsory; it is not sufficient to give only the binding defining the instance.
hunk ./web/bindings.html 152
+This basic form is to emphasise that an instance is just a struct value that is declared to be used as implicit argument,
+inserted by the compliler. Two alternative syntactic forms are also available:
+
+
An instance declaration combined with a binding of the typed variable:
hunk ./web/bindings.html 157
-instancevar::type
-var = struct
- bind*
+instancevar::type = expr
hunk ./web/bindings.html 159
+
+
An instance declaration where the struct value is specified by a list of bindings:
+
+instancevar::typewhere
+ bind+
+
+
+
hunk ./web/bindings.html 170
-With the exception of struct expressions,
+With the exception of struct expressions and the second alternative form for instances
+(which is immediately desugared to a form with a struct expression),
hunk ./web/default.html 11
-affect instances for implicit struct types, but otherwise they serve quite different purposes.
+affect instances for type classes, but otherwise they serve quite different purposes.
hunk ./web/default.html 14
- For a given implicit struct type T, several instances are typically defined. It is permitted to define
+ For a given type class T, several instances are typically defined. It is permitted to define
hunk ./web/default.html 19
- needs to insert instances as implicit arguments to functions that use of the selectors of T. The compiler infers
+ needs to insert instances as implicit arguments to functions that use the selectors of T. The compiler infers
hunk ./web/default.html 40
-where T is an implicit struct type and D is a data type produces automatically an instance following
+where T is a type class and D is a data type produces automatically an instance following
hunk ./web/default.html 45
-The method applies only to one-parameter implicit
-types, for which the types of all selectors are simple, according to the following inductive definition:
+The method applies only to one-parameter
+type classes, for which the types of all selectors are simple, according to the following inductive definition:
hunk ./web/default.html 49
-
the type parameter of the implicit struct type is simple.
+
the type parameter of the type class is simple.
hunk ./web/default.html 59
-In addition to the above mechanism, default instances can be defined for implicit types Show and Parse (defined in the Prelude), but as yet only for enumeration types (pending decisions on proper definitions of predefined implicit types for
+In addition to the above mechanism, default instances can be defined for type classes Show and Parse (defined in the Prelude), but as yet only for enumeration types (pending decisions on proper definitions of predefined type classes for
hunk ./web/examples.html 24
-This is generalized in the expected way to other programs; in
-particular, the --make option makes sure that all
+
+In particular, the --make option makes sure that all
hunk ./web/expr.html 114
-
-Precedence and associativity of operators is determined syntactically; see the name page for details.
+
Precedence and associativity of operators is determined syntactically; see the name page for details.
hunk ./web/expr.html 253
-
implicit showList :: Show [a] \\ Show a
+
instance showList :: Show [a] \\ Show a
hunk ./web/expr.html 312
-To be written.
+Here we just summarize for the Haskell programmer expression forms that are available also in Timber and with the same syntax:
+
+
Conditional expressions (if-expressions).
+
Explicitly typed expressions.
+
Operator sections.
+
Arithmetic sequences.
+
List comprehensions.
+
hunk ./web/haskell.html 37
-request default instances of some implicit types.
+request default instances of some type classes.
addfile ./web/inet.html
hunk ./web/inet.html 1
+
+
+Network programming
+
+
+
+
+
Network programming
+
+The POSIX environment provides basic support for network programming
+over TCP sockets. We repeat part of module POSIX:
+
+module POSIX where
+
+...
+
+data Host = Host String
+data Port = Port Int
+
+struct Internet where
+ tcp :: Sockets
+
+struct Socket < Closable where
+ remoteHost :: Host
+ remotePort :: Port
+ inFile :: RFile
+ outFile :: WFile
+
+struct Connection < Closable where
+ established :: Action
+ neterror :: String -> Action
+
+struct Sockets where
+ connect :: Host -> Port ->
+ (Socket -> Class Connection) -> Request()
+ listen :: Port ->
+ (Socket -> Class Connection) -> Request Closable
+
+instance showHost :: Show Host
+showHost = struct
+ show (Host nm) = nm
+
+
+Typically, a network program consists of two program parts, a client
+and a server, executing on different hosts, connected to
+the internet. The parts communicate over a socket, an
+abstraction of a communication channel. A socket has selectors to give
+the host and port of the remote peer and two files, an RFile
+for reading and a WFile for writing. The main body of both the
+server and the client is a function of type Socket -> Class Connection.
+This function has access to a socket and must define methods
+describing how to handle the events a network program must react to:
+ an established message when the cnnection has been established, a
+neterror message in case of problems and a close
+message from the remote peer.
+
+The client tries to connect to a server by specifying a
+host and a port; the server just specifies a port on which to
+listen. Whenever a client connects to a host on a port
+and there is a server listening on that port, a socket is created
+for each party with files set up for communication and an
+established
+message is sent to both parties. Typically, code in the body of
+established will register callbacks with the
+infiles.
+
hunk ./web/posix.html 27
-struct File where
- close :: Request ()
- seek :: Int -> Request Int
-
-struct RFile < File where
- read :: Request String
-
-struct WFile < File where
- write :: String -> Request Int
-
hunk ./web/posix.html 29
- argv :: [String]
+ argv :: Array String
hunk ./web/posix.html 34
- installR :: RFile -> Action -> Request ()
- installW :: WFile -> Action -> Request ()
+ getTime :: Request Time
+ inet :: Internet
+
+struct Closable where
+ close :: Request ()
+
+struct File < Closable where
+ seek :: Int -> Request Int
+
+struct RFile < File where
+ read :: Request String
+ installR :: (String -> Action) -> Request ()
+
+struct WFile < File where
+ write :: String -> Request Int
+ installW :: Action -> Request ()
+
+data Host = Host String
+data Port = Port Int
+
+struct Internet where
+ tcp :: Sockets
+
+struct Socket < Closable where
+ remoteHost :: Host
+ remotePort :: Port
+ inFile :: RFile
+ outFile :: WFile
+
+struct Connection < Closable where
+ established :: Action
+ neterror :: String -> Action
+
+struct Sockets where
+ connect :: Host -> Port ->
+ (Socket -> Class Connection) -> Request()
+ listen :: Port ->
+ (Socket -> Class Connection) -> Request Closable
+
+instance showHost :: Show Host
+showHost = struct
+ show (Host nm) = nm
+
hunk ./web/posix.html 88
-writing and install listeners on files; see below for more on these.
-Within a definition
+writing, etc. Within a definition
hunk ./web/posix.html 105
-when input is available or output is possible. This is the role of the listeners; a call
+when input is available or output is possible. This is the role of listeners
+or callbacks; a call
hunk ./web/posix.html 109
-env.installR env.stdin inpHandler
+env.stdin.installR inpHandler
hunk ./web/posix.html 113
-is available (i.e. the user strikes return), the runtime system calls the listener. So, in
-this case inpHandler will typically start by reading stdin.
+is available (i.e. the user strikes return), the runtime system calls the listener with
+the input line as argument.
+
+The method getTime returns a Time value, representing the time elapsed since
+the Epoch. One main use of this method is that its least significant part can
+serve as random generator seed.
+
The selector inet provides support for network programming, described on
+a separate page.
}