[First verion of language summary sydow@chalmers.se**20080321145959] { adddir ./summary addfile ./summary/bindings.html hunk ./summary/bindings.html 1 + +
++Patterns occur in several syntactic contexts in Timber (e.g. in the left hand sides of bindings, lambda expressions +and case alternatives). Syntactically, patterns form a subset of expressions; a pattern is one of the following +
+At run-time, patterns are matched against values. Pattern-matching may succeed or fail; in the former case the result +is a binding of the variables in the pattern to values. The rules are as follows: +
+ In patterns the special "wildcard" variable _ may be used; in contrast to other variables, it is not bound + by pattern-matching. +
+ A consequence of the way pattern-matching is done is that patterns must be linear; no variable may occur more than once in + a pattern. + +
+Syntactically, bindings are divided into type signatures and equations. Equations are either function bindings, pattern bindings + or instance bindings for implicit struct types. + +
+ var (, var ) * :: qtype +
Here a qtype is a (possibly) qualified type. +
Examples + | +
---|
x, y, z :: Int |
map :: (a -> b) -> [a] -> [b] |
elem :: a -> [a] -> Bool \\ Eq a |
We present first the simplest form of function definition, a sequence of equations, and then how these may +be extended with where-clauses and with guards; these extensions may be combined. +
+var pat * = expr +
+The variable in each of the equations (the name of the function) and the number of patterns must be the same in all equations. +The order of equations is significant; when applying the function, pattern-matching is tried starting wih the first equation +until it succeeds; the function value is computed from right hand side of that equation, using the variable bindings obtained. +Within one equation, patterns are matched from left to right. +
+A binding may have attached a where-clause with a list of local bindings in layout-sensitive syntax
+var pat * = expr
+ where bind +
+
Example + | +
---|
formatLine n xs = concatMap f xs |
where f x = rJust n (show x) |
+var pat *
+ ( | (qual) +
+ = expr ) +
+
+In the most common case, a qual is a Boolean expression. After pattern-matching has succeeded, the guards are +evaluated in turn; the right hand side corresponding to the first true guard (if any) is used. +
Example + | +
---|
lookup x [] = Nothing |
| x == a = Just b |
| True = lookup x xs |
+More complicated guards that bind variables are possible, but omitted here. +
+pat = expr +
+where pat is not a variable (in which case the binding is, perhaps counter-intuitively, a function binding). +
+Pattern bindings bind the variables in pat by pattern-matching against the value of expr. +A pattern binding may not occur as a top-level declaration, but only as a local binding. +
Example + | +
---|
lookup' x ps = y |
where Just y = lookup x ps |
The pattern-binding in the where-clause will fail (and the function application give a run-time error), if +the result of calling lookup is Nothing. +
+implicit var :: type
+funBind
+
+The type signature of an instance of an implicit type is prepended by the keyword implicit. For instances, +a type signature is compulsory; only the function binding defining the instance is not sufficient, +
+The order between bindings in a sequence of bindings are not significant, with the following exceptions: +
+Function bindings are recursive. For pattern bindings certain limited forms of recursion are possible, in order +to build finite, cyclic data structures. To be described more... + addfile ./summary/default.html hunk ./summary/default.html 1 + +
++Default declarations come in two distinct forms. They share the keyword default and they both +affect instances for implicit struct types, but otherwise they serve quite different purposes. +
+ For a given implicit struct type T, several instances are typically defined. It is permitted to define + instances at overlapping types, such as e.g. T [a] and T [Int], where the latter type + is more specific than the former. +
+ During type-checking, the compiler + needs to insert instances as implicit arguments to functions that use of the selectors of T. The compiler infers + which instance type T t that is needed and chooses the most specific instance. However, it may happen that there + is no most specific type. The prelude defines intInt :: IntLiteral Int and intFloat :: IntLiteral Float and similarly for + Show. Neither of + this is more specific than the other. Thus a top-level definition such as +
s = show 1 ++ leads to problems; should + implicit arguments for Int or Float be inserted? There is no reason to prefer one to the other so s is + considered ill-typed. But the matter can be decided by inserting a default declaration; the prelude declares +
+default intInt < intFloat ++which means that the instance intInt is to be preferred to intFloat. Thus the Int instances +are chosen and s is "1" rather than "1.0". +
+A declaration +
+default tD :: T D ++where T is an implicit struct type and D is a data type produces automatically an instance following +the ideas of Hinze's and Peyton Jones' derivable type classes. The mechanism applies in some, rather restrictive, situations, +but these including commn cases like the Prelude's Eq and Ord, for which it is easy but tedious +to define instances for a new data type. +
+The method applies only to one-parameter implicit +types, for which the types of all selectors are simple, according to the following inductive definition: +
+Timber has a rich expression language and we divide +the description in three parts: +
Here we describe the Timber form of expression forms that have counterparts in most functional languages. +
These forms are special to Timber and provide the building blocks for + object-oriented programming. +
Every Timber program will include expressions from the previous two groups. In this + third group we describe more esoteric forms that may be ignored by the beginning Timber programmer. +
+Layout of program code is significant in Timber. In many cases, sequences of syntactic elements can be written in +tabular form, where each new item starts on a new line and in the same column as the beginning of the previous item. Multi-line +items are possible by intending subsequent lines; the end of the sequence is signalled by "outdenting", i.e. indenting +less, as in the example +
+ showSeq xs = concat (map showLine xss) + where prec = 100 + showLine x = map (showItem 10) + (comp prec xx) + + showItem n x = format n ('_' : g x) ++
+The definition of showSeq has a where-clause with a list of two local definitions (defining prec and +showLine). The definition of showLine spans two lines, indicated by indentation. The last definition, +of showItem, has another indentation level, thus is not part of the where-clause and is hence not +local to showSeq. Instead showSeq and showItem form another list of bindings. +
+It is possible to avoid layout-sensitive syntax by enclosing such sequences in braces and using semi-colon as +separator: let {x=1; y=f x 3} in g x y; this is generally not recommended. + +
+
Examples + | +
---|
x, counter, d'Dictionary, (+) |
+
Type of literal + | +Examples + | +
---|---|
Int | 37, 0, -123 |
Float | 1.23, 3E12, 0.4567E-6 |
Char | 'a', '3', '\n', '\t', '\\' |
String | "Hi", "Error\n" |
+Every occurrence of an integer literal except in patterns is during desugaring replaced by application of the function +fromInt to the literal. The Prelude defines +
+implicit struct IntLiteral a where + fromInt :: Int -> a ++and instances for Int (the identity function) and Float (conversion). +
+This device will make many functions that mention integer literals usable for both Int and Float arguments; +a simple example is +
+sum :: [a] -> a \\ Num a, IntLiteral a +sum [] = 0 +sum (x : xs) = x + sum xs ++
Examples + | Comments | +
---|---|
f 3 | Parentheses not needed |
g (x+2) | Parentheses necessary |
Just (f x) | Constructor Just applied to f x |
map f (g xs) | map f applied to g xs |
hMirror (x,y) | One argument, which is a pair |
+
Examples + | Desugared forms | +
---|---|
x+3 | (+) x 3 |
f x+3*x | (+) (f x) ((*) 3 x) |
3 `elem` xs | elem 3 xs |
+Precedence and associativity of operators is determined syntactically; see the name page for details.
+\ pat + -> expr +
+denoting anonymous functions. The sequence of patterns must be linear, i.e. may not include more than one occurrence +of any variable. +
Example + | +
---|
\x -> x+3 |
\ (Just x) d -> insert x 0 d |
+Pairs, triples etc are expressed using parenheses as delimiters and comma as separator. These are also desugered to +application: +
+
Examples + | Desugared forms | +
---|---|
(a,b) | (,) a b |
(f x,3+5,True) | (,,) (f x) ((+) 3 5) True |
3 `elem` xs | elem 3 xs |
+Here (,), (,,) etc are primitive constructors for the types of pairs, triples etc. +
List expressions are sequences delimited by square brackets and with comma as separators;[1,3,7] +is a list with three elements. This form is desugared to the primitive form of lists, which has as constructors +[] (the empty list) and : ("cons", which builds +a list with its first argument as first element ("head") and second argument as remainder ("tail")). +
+
Examples + | Desugared forms | +
---|---|
([1,3,7 | (:) 1 ((:) 3 ((:) 7 [])) |
[f x, p 3] | (:) (f x) ((:) (p 3) []) |
+ +
+let bind + in expr +
where the list of bindings is layout-sensitive. The bindings are recursive, i.e all the +names defined in the bind list are in scope in the right hand sides of these bindings (and, of course, +in the main expression). +
+
Example + | Comments | +
---|---|
let size = f 100 | f, defined below, is in scope |
f 0 = 0 | Pattern-matching allowed |
f x = g x (x+2) | |
in concat (map f xs) |
+
+[ type_constructor ] { field (, field )+ }
where field
+ has the form selector = expr .
+ The type_constructor is the name of a struct type. Since the struct type is uniquely determined
+by its fields, the type name is optional.
+
Examples + | +
---|
Point {x=3, y=1} |
{x=3, y=1} |
Counter {inc = inc, read = read} |
The examples presupposes type definitions +
+struct Point where + x, y :: Int + +struct Counter where + inc :: Action + read :: Request Int ++
+The last example is to emphasise that selectors (the inc and read in the left hand +sides of the fields) are in a separate namespace from variables (the right hand sides). Thus the equations +are not recursive; the example requires +that definitions of these variables are in scope. +
+type_constructor { [ field (, field )+] ..}
+The trailing .. indicates that the struct value should be stuffed, by adding fields +of the form x = x for each selector x that is not explicitly given a value in a field. +
+
Example + | +expands to + | +
---|---|
Counter {..} | Counter {inc = inc, read = read} |
Counter {read = readreq ..} | Counter {read = readreq, inc = inc} |
Point {x=0} | Point {x=0, y=y} |
+Obviously, because of subtyping, the type name cannot be omitted here. +
+struct bind +
+where the bindings have layout-sensitive syntax. +
+
Example + | +
---|
implicit showList :: Show [a] \\ Show a |
showList = struct |
show [] = "[]" |
show (x : xs) = '[':show x ++ preC (map show xs)++"]" |
+The list of bindings in this form of expression differs from all other occurrences of +lists of bindings in that they are not recursive. We are defining the selectors in a struct +but allow pattern matching equations in layout-sensitive form; occurrence of the same name as a +variable in the right and side must refer to some other definition in scope. This is particularly +common for implicit struct types, as here. See implicit types for +more explanatation. +
+case expr of alt + +
+where the sequence of alternatives is layout-sensitive. The simplest form of an alternative is +
+pat -> expr +
Example + | +
---|
case f a b of |
> [] -> 0 |
> > x : xs -> g x + h 3 xs |
+
+Classes in Timber should be thought of as in object-oriented programming: a class is a template, from which +we may create several objects. An object encapsulates its own copy of the state variables defined in the class. +
Actions and requests are methods that a class may expose to the outside; they may manipulate the local +state of objects. +
+Procedures are subroutines that may be called by actions and requests; they are typically not exposed +in interfaces. +
+The syntax of these constructs are similar; they are all built from sequences of statements: +
+In all cases, statement sequences have layout-sensitive syntax. See the statements page +for further descriptions. +
+In mathematics and in most programming languages, + and - denotes addition and subtraction; but what should +their types be? Of course, we want to be able to add both integers and floating-point numbers, but these two functions correspond to +completely different machine operations; we may also want to define arithmetic on new types, such as complex or rational numbers. +
+To better understand the problem, consider a function to add the elements of a list of integers to an accumulator. +Assuming that + only means integer addition we could define +
+add :: Int -> [Int] -> Int +add ack (x : xs) = add (x + ack) xs +add ack [] = ack ++
+As long as there are elements in the list, we add them to the accumulator and call the function recursively; when the list is empty the +ackumulator holds the result. +
But this function makes perfect sense also for floats (or rationals, or complex numbers, or ...) and we would like to use it at +those types, too. One could imagine an ad hoc solution just for the arithmetic operators, but we prefer a general solution. +
+A first step is to introduce the following struct type: +
+struct Num a where + (+), (-), (*) :: a -> a -> a ++
+An object of type Num Int has three fields, defining addition, +subtraction and multiplication, respectively, on integers. (Of course, we can construct an object of this type using any three functions +of the prescribed type, but the intention is to supply the standard arithmetic operators.) Similarly, an object of type Num Float +defines the corresponding operators for floating-point numbers. +
+Assume that we have +properly defined numInt :: Num Int. We can then define +
+add :: Int -> [Int] -> Int +add ack (x : xs) = add (numInt.(+) x ack) xs +add ack [] = ack ++
+Unfortunately, the first argument in the recursive call now looks horrible. We cannot accept to write integer addition in this way. But there is +at least something positive; we can generalize the type by giving the Num object as an argument: +
+add :: Num a -> a -> [a] -> a +add d ack (x : xs) = add d (d.(+) x ack) xs +add d ack [] = ack ++
+We can now use add for lists of any type of objects for which we can define the arithmetic operators, at the expense of passing an extra +argument to the function. +
+The final step that gives an acceptable solution is to let the compiler handle the Num objects: +
+implicit struct Num a where + (+), (-), (*) :: a -> a -> a + +add :: a -> [a] -> a \\ Num a +add ack (x : xs) = add (x + ack) xs +add ack [] = ack ++
+Num is now an implicit struct type. For such types, the selectors are used without the +dot notation identifying a struct value from which to select. Whenever a selector of an implicit type occurs in a function +body, the compiler +does the following: +
+This solution combines ease of use and flexibility with type security. A possible disadvantage is inefficiency; an extra parameter is passed +around. To address this, the user may add a specific type signature; if the user assigns the type Int -> [Int] -> Int to add, +giving up flexibility, the compiler will not add the extra parameter, instead inserting integer operations directly into the function body. +
+Several implicit struct types, including Num, are defined in the Prelude, together with instances for common cases. +
+The compiler must be able to select the proper object of an implicit type to use whenever a function with a qualified type is used; this choice +is guided by the context of the function application. In certain cases ambiguites can occur; these are resolved using default declarations. +
+We end by showing an instance of Num for rational numbers: +
+data Rational = Rat Int Int + +implicit numRat :: Num Rational +numRat = struct + Rat a b + Rat c d = Rat (a*d + b*c) (b*d) + Rat a b + Rat c d = Rat (a*d - b*c) (b*d) + Rat a b * Rat c d = Rat (a*c) (b*d) ++
+This definition must be improved by reducing the fractions using Euclid's algorithm, but we omit that. We just note that the arithmetic operators in +the right hand sides are at type Int; thus the compiler will insert the proper opertions from the instance numInt, avoiding +the overhead of extra parameters. +
+Also subtyping relations may be used as constraints in qualified types. As a simple example, consider the function +
+twice f x = f (f x) ++
+Obviously, twice has a polymorphic type. At first, it seems that the type should be (a -> a) -> a -> a. However,it can be assigned +the more general type +
+twice :: (a -> b) -> a -> b \\ b < a ++
+Types with subtype constraints will never be assigned by the compiler through type inference, but can be accepted in type-checking. + addfile ./summary/index.html hunk ./summary/index.html 1 + + +
++This document aims to provide a summary of the language constructs of Timber, including +syntax descriptions but with very little of motivation, explanation and examples. +
+It is intended to be useful for a reader who is exploring Timber and wants a reasonably +concise summary of the language. A Timber tutorial, with extensive motivation and examples, +will be a separate document. +
+Some syntactic constructions are described in simple BNF syntax, but this document does not give +complete formal syntax for Timber. In BNF descriptions, terminals are in +typewriter font, nonterminal in italics and meta symbols in red. + addfile ./summary/lex.html hunk ./summary/lex.html 1 +
++A Timber program may contain two kinds of comments: +
+A Timber program consists mainly of definitions that give meaning to names. There are six +separate namespaces in Timber: +
+Names are simple or qualified; the latter are used to disambiguate names defined in different modules. +
+Simple names come in two lexically distinct forms, identifiers and operators. +
+An identifier consists of a letter followed first by zero or more letters, digits and underscores and, finally, +zero or more single quotes. The initial letter must be upper case for constructors, type constructors and +module names, and must be lower case for variables, selectors and type variables. The following lexically correct +identifiers are keywords of the language and may not be used as names: +
+action after before case class data do +default else elsif forall if import implicit +in let module new of private request +result struct then type use where while ++
An operator is a sequence of one or more symbol characters. +The symbol characters are defined by enumeration: :!#$%&*+\<=>?@\^|-~. +An operator starting with : is a constructor; otherwise it is a variable. Only +variables and constructors have operator forms; the other four namespaces contain only +identifiers. The following lexically correct operators are keywords and may not be used +as names: +
+. .. :: := = \ \\ | <- -> ++
+An identifier may be used as an operator by enclosing it in backquotes; `elem` is an operator. +Conversely, an operator may be used as an identifier by enclosing it in parentheses; (+) is an identifier. + +
Examples: +
Names + | +Possible namespaces + | +
---|---|
Color, T3, T_3, T_3' | constructors, type constructors, module names |
x, env, myTable, a', x_1 | variables, selectors, type variables |
+, #=#, @@ | variables |
:, :++: | constructors |
x'3 | ILLEGAL; only trailing ':s allowed |
#3 | ILLEGAL; mixture of operator and identifier symbols. |
+The precedence and associativity of operators are determined by their syntax. The operators in the following table +are listed in decreasing precedence, i.e. an operator that appears in a later row binds less tightly. Function application, +denoted by juxtaposition, binds tighter than all operators. + +
Operators + | +Associativity + | +
---|---|
@ | Right |
^ | Right |
* / `div` `mod` | Left |
+ - | Left |
: ++ | Right |
== /= < > <= >= | None |
&& | Right |
|| | Right |
>> >>= | Left |
$ | Right |
+The operators in the table above are defined in the Prelude, but can be redefined in user modules, except for the following +three exceptions: +
+ In harmony with this, the empty list has the (lexically illegal) name []. +
+ This means that, if evaluation of a in +a && b gives False as result, the result of the complete expression is False and +b is +not evaluated (and, in particular, a runtime error or non-termination that would occur during evaluation of b is avoided). +
+Similarly, if the left operand to || evaluates to True, the result of the complete expression is +True without evaluating the right operand. +Thus, semantically speaking, these are not operators at all but special expression-forming constructs.
+Timber modules are used to manage namespaces. In this mechanism, simple names are extended to qualified forms, where the +simple name is suffixed by the name of the module where it is defined. +
A qualified module name is a sequence of simple module names interspersed with single quotes, such as +Data'Functional'List. This structure on module names is simply intended to indicate a suitable storage +structure of modules in a hierarchical file structure; this example module would be defined in file List.t +in folder Data/Functional relative to some installation dependent search path. +
+Imagine a module Dictionary, which defines among others the names insert and |->. An importing module may +refer to these names using the qualified forms insert'Dictionary and |->'Dictionary in order to avoid possible name conflicts. See the modules page for more information on import and use of other modules.The simple name that is the prefix of a qualified name decides if the +name is an operator or an identifier and if it is a constructor or not. + + addfile ./summary/menu.html hunk ./summary/menu.html 1 + +
+ + + + + + + + ++A Timber program consists of a collection of modules. One of these is the root module and contains the root +definition. The root definition must have a prescribed root type, that may depend on the target environment. +A Timber installation may support several target environments/platforms. +
+The other modules in the program provide auxiliary definitions, used by the root module and by other auxiliary modules. +The compilation unit in Timber is the module, so modules may be compiled individually (but see below for dependencies). + +
+module moduleName where
+ importDeclaration*
+ topLevelDeclaration*
+private
+ topLevelDeclaration*
+
+
+Here, as in many places of Timber syntax, indentation is significant. The import and top-level declarations must be indented at +least one step and be vertically aligned, i.e. the first character of each declaration must be in the same column. +An exception is the (common) case where there is no private part; then indentation can be omitted (and all declarations start in the +leftmost column). +
+A module has a simple name, which is an identifier starting with an +upper-case letter. Modules are conventionally stored in files of the same name with suffix .t, i.e. +module Dictionary is stored in Dictionary.t. Projects and Timber sites may also use hierarchical +file systems to organize module libraries; if Dictionary.t resides in dictionary Data/Object, the +fully qualified name of the module, used by clients, is Data'Object'Dictionary. Such qualified names are +relative to some installation-dependent notion of search paths. Module hierarchies in Timber have no other significance +than to support organizing and subsequently finding modules in a file system. +
+The module name is given in the header, as described above. + +
+A module may depend on other modules, i.e. use types or values defined in these modules. In a Timber program +the dependency graph between modules must be acyclic; no recursive dependencies are allowed. This means that +modules can be compiled in dependency order, i.e. when a certain module is compiled, all the modules it depends on have already +been compiled. The present distribution does not include tools to decide on a proper compilation sequence; the user must compile +modules in appropriate order. + +
+Following the header is a sequence of import/use declarations, i.e. declaration of the modules that the current module depends on. +There are two forms of such declarations: +
+Both forms of declaration give access to all exported entities from the named module; the difference is that in the latter case +one must use the qualified name of an imported entity, while in the former case the simple (unqualified) name is enough, unless name +clashes occur. +
+Name clashes are handled as follows: +
+ All the entities (types, defaults and values) defined in the sequence of public top-level declarations are exported, i.e. can + be referred to by importing/using modules. Entities defined in the private part are not exported and hence not visible to importing/using + modules. In particular, this means that the type environment of the public part must be closed, i.e. the type of an exported value + must not mention a type defined in the private part. Imported entities are not re-exported, i.e. the import relation is not transitive. + + addfile ./summary/simplestyle.css hunk ./summary/simplestyle.css 1 - +body { + font-size: 12pt; + font-family: helvetica, "lucida grande", sans-serif; + margin: 0; + padding: 2em; +} + +h1, h2, h3, h4, h5, h6 { + font-family: georgia, times, "times new roman", serif; +} + +p,a,ul,li,em,strong,span,div { + font-size: 1em; +} + +p { + width: 37em; +} + +ul, ol { + width: 35em; + margin: 1em 0; +} + +li + li { + margin-top: 1em; +} + +img { + border: 0; +} + +pre { + width: inherit; + overflow-x: auto; +} + +a:link, a:visited, a:active { + color: #1C5380; + padding: 0.1em 0.2ex 0 0.1em; +} + +a:visited { + color: #584781; +} + +a[href]:hover { + color: #111; +} + +a[href^=http] { + background: transparent url(data:image/gif;base64,R0lGODlhCQAJAJEAAP///wAAAP///wAAACH5BAUUAAIALAAAAAAJAAkAAAIXlI8ZK8sdGpggWhrAyXVGSVUGh42OIxQAOw%3D%3D) no-repeat scroll right center; + padding-right: 13px; +} + +a[href$=pdf]:after { + content: ' (pdf)'; +} + + +div.navbar h3, div.navbar h4 { + margin: 0.5em 0; + text-align: center; +} + +ul.menu { + border-right: 1px solid #ddd; + border-left: 1px solid #ddd; + border-top: 1px solid #f0f0f0; + margin: 3em 0; + padding: 0; + list-style-type: none; + width: 100%; +} + +ul.menu li { + padding: 0; + margin: 0.1em 0; +} + +ul.menu li a { + display: block; + padding: 0.2em 1em 0.1em 0.5em; + text-decoration: none; + background: #fafafa; + color: #222; + border-bottom: 1px solid #ddd; + border-top: 1px solid #fefefe; +} + +ul.menu li a:hover { + color: #000; + background: #FEF7ED; + padding: 0.2em 1em 0.1em 0.55em; +} + +ul.menu li a:active { + font-weight: bold; +} + +table { + border: 1px solid #eee; + font-size: 0.8em; +} + +th, td { + border: 0 !important; +} + +th { + font-weight: bold; + font-size: 1em; + border-top: 1px solid #fefefe; + border-bottom: 1px solid #f0f0f0; + background: #FEF7ED; +} + +tr { + background: #fafafa; + color: #222; +} + +tr:hover { + background: #FEF7ED; +} addfile ./summary/stmts.html hunk ./summary/stmts.html 1 + +
++Statements form the bodies of classes. Within the sequence of statements forming a class definition, there may (and indeed, typically +will) also occur definitions of actions and requests, which themselves have statement sequences as their bodies. +
+Statements will typically have side-effects, affecting the state of objects or the external world. This implies that the order of statements within +a sequence is important. Also, for the statement forms that bind variables, the binding affects only the rest of the sequence. +
+The available statement forms are: +
+ svar := expr +
+ Here svar is a state variable. These have the same syntax as ordinary variables and share namespace, but + there are no rules for shadowing, so a state variable must be distinct from all ordinary variables in scope (and from other, + already defined state variables in scope). The variable + being defined may not occur in the right hand side. Initialisation implicitly declares this variables as part of the state of objects + instantiated from this class. +
These have the same syntax as bind lists in general; they are recursive and within one binding group + order is insignificant (with the + exceptions detailed at the end of the bindings page), but the bindings are only in scope + in the rest of the statement sequence. +
In addition to local bindings as they are used in general, a particularly important case is definitions of actions + and requests (which can only be defined in the statement sequence f a class). +
+ var = new expr +
+ The expr must evaluate to a class; the effect is that a new object is created, its state initialized and its + interface bound to var +
result expr
+ In the sequence of statements of a class, this must be last statement. It defines the interface of the class, i.e. how + the variable referring to an object may interact with it. +
Within an action or a request, the result statement indicates termination of the method and the value returned (for + requests; for actions the result is (), the dummy value of type ()). +
+ The forms of statements up to now are the only forms that may occur in the statement sequence at the outermost level of a class; + creating an object + may only involve initiating the state, creating other objects and returning the proper interface. The remaining forms + occur only within actions and requests. +
+svar (! expr )*:= expr
+The left hand side is here either a state variable or an array L-value (when the svar is an array). Array indexing +is denoted by the ! operator; several indexing operations may occur for multidimensional arrays. The right hand side may +mention this and other state variables.
+pat <- expr
+Here the right hand side must evaluate to a request or procedure; the statement expresses a call of this method and matching +the pattern against the returned value. +
+The alternative form
+expr +
+may also denote a request or procedure call where the pattern matching is omitted or an action call (which does no return a value). +
+if expr then
+ stmts
+elsif expr then
+ stmts
+else
+ stmts
+
+The elsif may occur zero or more times; the else part zero or one time. +
+case expr of
+ pat1 -> stmts1
+ pat2 -> stmts2
+ ...
+
+The alternatives may use guards and/or where clauses just as in function bindings. +
+forall (qual ) + do
+ stmts
+
+Here the simplest form of qual is var <- expr, where expr evaluates +to a list. The statement sequence in the body will be executed once for each eement of the list, with var bound to +that element. +
+struct Counter where + inc :: Action + read :: Request Int + reset :: Action + +counter = class + s := 0 + inc = action + s := s+1 + read = request + result s + reset = action + s := 0 + result Counter {..} ++ addfile ./summary/toplevel.html hunk ./summary/toplevel.html 1 + + +
+The body of both the public and private parts of a module is a sequence of +top-level declarations. These declarations comprise +
+Values in Timber are classified into types. The integer value 7 has type Int, a fact that is expressed +in Timber as 7 :: Int, so :: is read "has type". One seldom adds such explicit type information to expressions +in Timber code, but it is allowed to do so. More common is to supply type signatures as documentation to +top-level definitions, but also these can be omitted, leaving to the Timber compiler to infer types. +
+Timber also has type constructors, which can be thought of as functions that take types as arguments and give a type as
+result. An example is the primitive type constructor Request, which takes a type a as an argument and constructs
+the type Request a of methods (in the object-oriented sense) returning a value of type a.
+
+Kinds and kind declarations
+
+Timber types and type constructors are classified by their kind. All types have kind *, while +type constructors that expect one type type argument (such as e.g. Request) have +kind * -> *. In general, a kind is either * or k1 -> k2 where k1 and k2 are +kinds. A type constructor of kind k1 -> k2 expects an argument of kind k1; the result is then a type (constructor) +of kind k2. +
+The programmer may declare the kind of a type constructor in a top-level kind declaration:
+con :: kind +
+This is particularly useful when defining abstract data types; in the public part of a module one declares the kind of +an abstract type and the signatures of the operators; the actual type definition and equations are given in the private part. + +
Examples + | Comments | +
---|---|
Stack :: * -> * | Stacks with elements of arbitrary type |
Dictionary :: * -> * -> * | Dictionaries storing info about keys |
+We first describe the primitive types of Timber. One should realize that in Timber code, it is always clear from the context whether +an expression denotes a type or a value, so some types use the same syntax for type expressions as for +values without confusion. (A beginner might disagree about the last two words.) + +
+As part of the language, the following primitive types are provided: +
+Literals of types Int and Float are as in most programming languages; integer constants can be +given in octal or hexadecimal formed if prefixed by 0o and 0x, respectively. +
+Time values are expressed using the primitive functions sec, millisec, microsec and nanosec, +which all take an integer argument and return a Time value. Of course, millisec 1000 and sec 1 denote +the same value. +
+Character literals are written within +single quoutes as in 'a' or '3'; common escaped characters are '\n' and '\t' for newline and tab, respectively. (Many other forms of +character literals omitted.) +
+The following types and type constructors are also primitive in the language. +
The type [a], for any type a, contains finite lists of values of type a. + The list [3, 6, 7, 1] has type [Int] and [[3, 2], [4, -1, 7]] has type [[Int]] + (however, see the overloading page for more general types of these lists). +
+For arbitrary types a1,a2,...an, we can form the tuple type (a1, a2, ..., an). +Values use the same notation so (True,'a') has type (Bool,Char). +
+For any type a, the type Array a consists of a sequence of a values, organized so that one can access all values +by index in constant time. Arrays are particularly useful as state variables in objects, where they may also be +updated in imperative style.
For any two types a and b, a -> b is the type of functions from a to b. +-> associates to the right, so a -> b -> c parses as a -> (b -> c). +
+This type could be defined in Timber as +
+data Either a b = Left a | Right b ++
+It is only primitive because of its role in generating default instances.
+Action is the type of asynhronous methods. An object may offer an Action in its interface; a client who has access to this interface +may send the object an action message with appropriate arguments. The message will at a later point in time execute the action, with +exclusive access to the object's state.
+For any a, Request a is the type of synchronous methods that return a value of type a. An object +may offer a Request in its interface; a client who has access to this interface may then send a request message with appropriate +arguments and wait for the result. Since all methods require exclusive access to the state of the receiving object during execution, cycles of requests lead to deadlock.
For any two types s and a, Cmd s a is the type of procedures that can execute in a +state s and return a value of type a. +
+We can now form complex types such as + +
Examples + |
---|
Int -> Int -> Bool |
[Int] -> Int |
(a -> Bool) -> [a] -> [a] |
+The two first examples are monomorphic; they involve only known types and type constructors. The third is polymorphic; +it involves the type variable a (a type variable since it starts with a lower-case letter), that stands for an +arbitrary type. A function possessing this type can be used at any type obtained by substituting a type for a. +
+The type variable a is implicitly bound in such a type expression; one should think of an implicit "for all a"
+quantification prepended to the type expression.
+Data types
+
+The programmer may introduce new ways of constructing data by defining data types. The simplest case is enumeration types like +
+data Day = Mon | Tue | Wed | Thu | Fri | Sat | Sun ++The type Day contains the seven constructor values that are enumerated in the right hand side. +
+The constructors may have arguments, as in +
+data Temp = Fahrenheit Int | Celsius Int ++
+Values in type Temp are e.g., Fahrenheit 451 and Celsius 100. There may be one, two or more alternatives +and a constructor may have more than one argument. A data type for a web log entry might be +
+data Entry = Entry IPAddress Date URL Method Int ++
+where a value of type Entry might be +
+Entry "123.456.789.000" (May 29 2007) "http://www.abc.def" GET 321 ++
+given suitable type definitions for the other types involved. Note that the type and the constructor have the same name; this is +OK since types and constructors live in different namespaces. +
+We may also define parameterised data types: +
+data Tree a b = Nil | Branch (Tree a b) a b (Tree a b) ++
+Tree thus has kind * -> * -> * and a value of type Tree String Int is a binary tree with a String and an Int stored in each internal node. +
+Two different data types may not use the same constructor name; with the above definition, no other data type in the same module can +use constructor Nil. For data types in imported modules there is no problem if they use Nil; only that the +qualified name must be used for the imported constructor. + +
+Struct, or record, types collect values bound to named selectors. Declarations have the syntax +
+struct con var * where
+ sig+
+
+ +
Examples + |
---|
struct Point where |
x, y :: Int |
struct Dictionary a b where |
insert :: a -> b -> Action |
lookup :: a -> Request (Maybe b) |
+An example value of type Point is Point {x=3, y=7}. The order between the fields is not significant, so +Point {y=7, x=3} is the same value. Similarly as for constructors, two different struct types in the +same module may not use the same selector name. +Thus a struct value is uniquely defined by the collection of selectors and the type name can be omitted from the value; {x=3, y=7} is again the same value. +
+If p :: Point, the selectors are accessed using dot notation, so the two integer coordinates are +p.x and p.y, respectively. +
+A struct type may have any number of selectors and the types of selectors are arbitrary. A struct type may also be parameterised +as shown by Dictionary, a type suitable as an interface to an object that acts as a dictionary, storing information of type b about keys +of type a. (The result type Maybe b for lookup is intended to capture the possibility that the given +key is not stored in the dictionary; the prelude defines data Maybe a = Nothing | Just a.) + +
+The user may introduce new names for existing types: +
+type Age = Int +type IPAddress = String +type List a = [a] +type Pair a b = (a,b) ++
+Such definitions do not introduce new types; they can only be helpful to improve program readability. They may not be recursive and +can not be partially applied (i.e., Pair Int is not a legal type constructor). The prelude introduces one type synonym: +
+type String = [Char] ++
+Struct types and data types may be defined in subtype hierarchies. As an example, we can extend Point: +
+struct Point3 < Point where + z :: Int ++
+We define Point3 to be a subtype of Point; for struct types this means that Point3 has all the selectors +of Point and possibly some more (in the example, one more: z). So we have {x=0, y=3, z=5} :: Point3. +A function that expects a Point as argument can be given a Point3 without problem, since all the function can do +with its argument is use the selectors x and y, which are present also in a Point3. +
+As another example we might split the dictionary type into two: +
+struct LookupDict a b where + lookup :: a -> Request (Maybe b) + +struct Dictionary a b < LookupDict a b where + insert :: a -> b -> Action ++
+In a program we may build a dictionary dict :: Dictionary a b and then send it to an unprivileged client typed as a +LookupDict; the client can then only lookup information, not insert new key/info pairs. +
+A struct type may have several supertypes; given a struct type +
+struct Object where + self :: OID ++where OID is a type that allows test for equality between objects, we could have defined +
+struct Dictionary a b < LookupDict a b, Object where + insert :: a -> b -> Action ++
+to get the same effect as before and, in addition, the possibility to test whether two dictionaries are the same (meaning same object, +not equivalent content). +
+We can also define hierarchies of data types, but these are completely separate from any hierarchy of struct types; a data type +can never be a sub- or supertype of a struct type. For data types we may add new constructors to get a supertype: +
+data CEntry > Entry = Corrupt ++
+Type CEntry adds another constructor to the type Entry defined above; a CEntry is either a proper +entry as above or Corrupt. A function that is defined to take a Entry as argument cannot accept a CEntry; +it may stumble on a Corrupt entry. The converse is OK; newly defined functions on CEntry values can happily +take an Entry; it will not have to use its Corrupt case. + +
+The following subtyping relations hold between primitive types:
+Class a < Cmd s a
+Request a < Cmd s a
+Action < Cmd s Msg
+
+
}