[extended version of language summary
sydow@chalmers.se**20080326153339] {
addfile ./summary/haskell.html
hunk ./summary/haskell.html 1
+
+
+Timber for Haskell programmers
+
+
+
+
+
Timber for Haskell programmers
+
+Much of Timber syntax is taken from Haskell, so the Haskell programmer glancing
+through Timber code will feel at home. This page summarizes instead the most important
+differences between Timber and Haskell.
+
+
+
Timber has strict semantics, not lazy as Haskell. This has a major impact on the
+ programming styles of the two languages.
+
Timber has a correspondence to Haskell type classes, but with a different name and
+ different syntax of declarations. A main reason for this change is that the word class
+ in Timber is used to denote the well-known concept from object-oriented programming. For overloading,
+ one can define a Timber struct type to be implicit. Instances of such types are
+ just named values of the type, tagged as implicit. The following excerpt from
+ the Prelude illustrates the concept.
+
+implicit struct Eq a where -- this is the "type class"
+ (==),(/=) :: a -> a -> Bool
+
+
+implicit eqUnit :: Eq () -- here is a named instance
+eqUnit = struct
+ _ == _ = True
+ _ /= _ = False
+
+
+One cannot attach a deriving-clause to a data type definition. Instead, one can separately
+request default instances of some implicit types.
+
In addition to data types, Timber has a dual notion of struct types. For both data and struct types there is a notion
+ of subtyping with inclusion polymorphism.
+
Qualified types have another syntax in Timber. To illustrate, here is the definition of the function elem
+ from the Prelude:
+
+elem :: a -> [a] -> Bool \\ Eq a
+elem x [] = False
+elem x (y : ys) = x == y || elem x ys
+
+
+ Note: A call to elem will evaluate both arguments
+ completely (because the language is strict), but will not traverse its second argument
+ further when an equality becomes True (because the disjunction "operator" || is non-strict
+ in its right operand).
+
In Timber one can express monadic computations using do-notation, but this is reserved for a particular primitive
+ monad Cmd s of commands operating on a state s. It is possible to define the concept of a general
+ monad as in Haskell, but the do-notation is not available for general monads.
+
The Command monad provides powerful constructs for object-oriented programming, with objects encapsulating a local
+state and methods manipulating this state. This is done while retaining the pure nature of the language; a computation with
+such side-effects is clearly indicated by a monadic type (and can hence not be used in a non-monadic context).
+
+Further, methods execute concurrently, but with exclusive access to the state of the object; thus Timber is also a concurrent
+language with some real-time constructs.
+
The main program of a Timber program is not of type IO () (this type does not exist in Timber), but their must
+be a designated root module with a root definition; the type of this depends on the target environment. In the present
+distribution, only a rudimentary POSIX environment is provided.
+
The type system of Timber implements many of the non-standard features that are implemented as extensions in GHC. See
+more details on the page that discusses advanced features of the type system.
+
hunk ./summary/implicit.html 11
-In mathematics and in most programming languages, + and - denotes addition and subtraction; but what should
+In mathematics and in most programming languages, + and - denote addition and subtraction; but what should
hunk ./summary/implicit.html 19
-add ack (x : xs) = add (x + ack) xs
-add ack [] = ack
+add acc (x : xs) = add (x + acc) xs
+add acc [] = acc
hunk ./summary/implicit.html 24
-ackumulator holds the result.
+accumulator holds the result.
hunk ./summary/implicit.html 43
-add ack (x : xs) = add (numInt.(+) x ack) xs
-add ack [] = ack
+add acc (x : xs) = add (numInt.(+) x acc) xs
+add acc [] = acc
hunk ./summary/implicit.html 51
-add d ack (x : xs) = add d (d.(+) x ack) xs
-add d ack [] = ack
+add d acc (x : xs) = add d (d.(+) x acc) xs
+add d acc [] = acc
hunk ./summary/implicit.html 64
-add ack (x : xs) = add (x + ack) xs
-add ack [] = ack
+add acc (x : xs) = add (x + acc) xs
+add acc [] = acc
addfile ./summary/java.html
hunk ./summary/java.html 1
+
+
+Timber for Java programmers
+
+
+
+
+
Timber for Java programmers
+
+Timber can be seen as an object-oriented programming language with
+many familiar features, but also some less familiar. This page summarizes
+both similatities and differences.
+
+
+The Timber compilation unit is a module. Within such a module one
+defines e.g. types, functions and classes. So there are many other
+entities in Timber than classes and objects.
+
The correspondence to a Java interface is a Timber
+ struct type. Here is an interface suitable for a smple counter object:
+
+struct Counter where
+ incr :: Action
+ reset :: Action
+ read :: Request Int
+
+
+A class that implements this interface provides two actions
+ (asynchronous methods, that do not return results): incr
+ to increment the local integer state by one, and reset to
+ reset the state to zero. To query the state, we use the request
+ (synchronous, value-returning method) read, which simply returns
+ the value of the state.
+
+ A Timber class consists of
+
+
Declaration and initialisation of local state variables;
+
Declarations of methods, i.e. actions and requests, that
+ access and update the state.
+
Possibly local, auxiliary, definitions.
+
Specification of a result, which typically is one or more
+ interfaces that the class implements.
+
+Here is a counter class:
+
+counter initVal = class
+ val := initVal
+
+ incr = action
+ val := val + 1
+
+ reset = action
+ val := 0
+
+ read = request
+ result val
+
+ result Prog {..}
+
+
+ The class itself starts with the keyword class. We see
+ the initialisation of the state variable val to initVal,
+ the three method declaration and finally the result specification;
+ here Prog {..} means: asemble a value of type Prog
+ from definitions in scope.
+
+ Note that there is no constructor method within the class. Within
+ the methods of another class we may write
+
+ c1 = new counter 0
+ c2 = new counter 10
+
+ to create two counter objects, with initial value 0 and 10, respectively.
+
Timber has parametric polymorphism, so the kind of generics
+ introduced in Java 1.5 is naturally supported.
+
Timber provides powerful ways to define new
+ value-oriented data types and functions on these, without attempts to
+ force this into an (often ill-suited) object paradigm. A consequence is
+ that Timber classes have no static variables or methods; such entities
+ are naturally defined as values and functions outside classes.
+
+ All types in Timber are first-class, which makes it possible to use classes
+ and methods as parameters to functions, as function values, as elements in
+ data structures etc leading to new programming patterns.
+
Timber does have subtyping between struct types and inclusion polymorphism
+ but does not support inheritance. The first-order nature of the language
+ makes it possible to find other ways to express most useful occurrences of
+ inheritance.
+
+ Methods always execute with exclusive access to the state of objects; thus
+ they can execute concurrently, leading to a very simple cocurrency model for
+ Timber.
+
+
+Timber is intended to be usable in many different
+situations, ranging from embedded systems to
+standard desktop applications. The interfaces
+between the Timber program and the external environment
+is very different in these cases.
+
+Thus a Timber application must be built for a particular target
+environment. This distribution provides only one environment,
+the POSIX environment. Also this is incomplete
+and allows only programs reading from and writing to
+stdin and stdout. A more complete
+version will be provided in a future release.
+
+The root module of a program targeted for this environment must
+import POSIX and contain
+a definition root :: RootType.
+
+Here the type Env collects the services that the environment
+provides to the program: the program can access command line arguments
+through argv, the standard input and output streams
+as stdin and stdout and call a function exit
+to terminate the program with a status indication. Within a definition
+
+root env = ...
+
+these services are accessed using dot notation as env.argv etc.
+
+Files support two methods:
+
+
read, which returns a string of the bytes that are available
+ in the file at the time of the call. Thus read does not
+ block waiting for user input; if no input is available, the empty string is returned.
+ Input is line-buffered, so no input is available until the user strikes return.
+
write takes a string as argument and tries to write it to the file;
+ the returned value is the suffix of the argument string that was not written; for
+ stdout this should be the empty string.
+ and write.
+
+
+The type Prog collects the services that the program offers to the
+environment, i.e. the methods it reacts to.
+Execution of a program proceeds as follows. The runtime system is responsible
+for initialisation: it creates
+an environment object with interface env :: Env, applies root to env and
+creates an object of the resulting class; let us call the resulting
+interface p :: Prog. The run-time system sends a p.start message;
+execution of this message may
+lead to creation of more objects, scheduling of future actions etc.
+
+After this initial computation the program comes to rest and
+reacts to events:
+
+
Whenever the user strikes the return key,
+a p.io message is sent, leading to a new burst of activity.
+
Also timer events, scheduled using the after construct,
+ will be reported to the program, leading to execution of
+ the scheduled actions.
+
+
hunk ./summary/stmts.html 43
- In the sequence of statements of a class, this must be last statement. It defines the interface of the class, i.e. how
+ In the sequence of statements of a class, this must be the last statement. It defines the interface of the class, i.e. how
hunk ./summary/stmts.html 68
-may also denote a request or procedure call where the pattern matching is omitted or an action call (which does no return a value).
+may also denote a request or procedure call where the binding is omitted or an action call (which does no return a value).
+
+
After and before statements.
+
+afterexprexpr
+beforeexprexpr
+Here the first expr must be a time interval and the second an action; the latter is given a new baseline (the after case)
+or deadline (the before case).
hunk ./summary/stmts.html 101
-to a list. The statement sequence in the body will be executed once for each eement of the list, with var bound to
+to a list. The statement sequence in the body will be executed once for each element of the list, with var bound to
hunk ./summary/types.html 72
-
Primitive composite types
+
Primitive type constructors
hunk ./summary/types.html 74
-The following types and type constructors are also primitive in the language.
+The following type constructors are also primitive in the language.
hunk ./summary/types.html 104
-For any a, Request a is the type of synchronous methods that return a value of type a. An object
+For any type a, Request a is the type of synchronous methods that return a value of type a. An object
hunk ./summary/types.html 108
-state s and return a value of type a.
+state s and return a value of type a.
+
Object references.
+For any type a, Ref a is the type of references to objects with interface a.
hunk ./summary/types.html 273
-
+Ref a < OID.
}