Recursion and Dynamic Data-structures in Bounded Space: Towards Embedded ML Programming Extended Abstract
John Hughes Lars Pareto Department of Computing Science Chalmers University; S 412 96 Goteborg frjmh,
[email protected]
1 Introduction During the last decade, declarative programming has found its way to large-scale industrial practice: Erlang [AVW93] is used by Ericsson to program telecommunication systems; Lustre [HCRP91] by Aerospatiale (among others) for embedded systems programming. Aimed at dierent domains, these two languages are dierent in nature. Erlang is rich, but not very safe: it is a general purpose programming language extended with constructs for concurrency, but does not prevent a program from crashing | it's not even statically typed. Lustre is safe but very restricted: it guarantees that all programs terminate and that they do not run out of space, but then, all computations must be expressed using booleans, numbers, streams and operations on these | not even function de nitions are allowed. These languages might be sucient for their intended domains, but it is not hard to think of applications where they are not: picture an embedded program that maintains a few lookup-tables. In Lustre, such a computation cannot conveniently be expressed. In Erlang it can, but at the cost of a potential abortion at run-time | that a program eventually computes a result is a fundamental requirement on any embedded program. We propose a programming language that guarantees termination and execution in constant space and that allows user-de ned recursive functions and dynamic datastructures. Our approach is to use a type and eect system with 1) a built in induction principle to guarantee that recursive programs terminate, with 2) a notion of sizes for data-types to allow manipulation of dynamic data-structures (such as lists) in constant space; that 3) maintains an upper bound on the height of the run-time stack to guarantee that a program never runs out of stack space, and that 4) maintains an upper bound on the memory allocations to guarantee that a program never runs out of heap space. The technique for termination proofs (1) and the notion of sizes (2) are immediately inherited from our previous work on sized types [HPS96, Par98], which does not address the bounded space problem. The techniques for memory allocation (4) are based on Tofte's and Talpin's work on region inference [TT97], which takes storage use into account, but which cannot give space bounds for recursive data-structures. The use of a type and eect system to compute an upper bound for the run-time stack (3) is novel. In the next section, we will introduce our working language MML (embedded ML): a strict, rst order, purely
functional language with explicit regions; we start by motivating our approach (sec. 2.1), and then give an informal introduction to regions and to what programming in the language looks like (sec. 2.2 and 2.3). The technical part of the paper de nes the syntax (sec. 2.4), the semantics (sec. 3), and the type system (sec. 4) of MML. The technical part is followed by a discussion of the correctness of the type system (sec. 5.1 and 5.2), of the implementation aspects of MML (sec. 5.3 and 5.4), of three candidate language extensions (sec. 5.5, 5.6, and 5.7), and of three possible widenings of our approach (sec. 5.8, 5.9, and 5.10).
2 A Functional Language with Explicit Regions 2.1 Implicit vs. Explicit Storage Management
One praised aspect of functional programming is that it entirely relieves the programmer from specifying where in memory any run-time values should reside | storage issues are left to the compiler and to the run-time-system. Coincidentally, a long cursed aspect of functional programming has been that programs use far too much memory and that its hard for the programmer to mend this | functional compilers and run-time systems seem not able to solve these storage issues in a satisfying way. A valid question, thus, is whether traditional functional language designs have taken the abstraction from storage management too far? Will there not always be cases where the programmer can do a better job than the compiler, and in which he is willing to undertake this eort? Is a programming language that does not abstract away from storage management necessarily a lesser language? The ML Kit project at Diku has convincingly demonstrated that SML can be given a semantics that also takes storage management into account, that the programmer who understands these can tune his programs to use signi cantly less space than before, and that the traditional advantages of high-level programming by no means are lost by giving the programmer control over the storage management [TBE+ 97]. Undeniably, advances in compiler technology will reduce the potential win of this approach, but we shall proceed under the assumption that programmers | at least in the near future | are cleverer than the compilers they use. In the ML Kit, storage management is implicit. The source language, SML, is automatically translated into a compiler intermediate language with constructs for storage management. It is an understanding of this intermediate
language, and of the translation process that gives the programmer the desired control. Our approach, instead, is to make storage management explicit. Our source language, essentially, is a sugared version of the ML Kit's intermediate language. This is because our proposed language relies on type checking rather than type inference, and because the storage management is explicit in our types: it is easier to formulate types for source programs than for programs derived from such. If type inference should turn out to be feasible, this approach has to be reexamined.
Here, the function f creates a pair in an arbitrary region speci ed by the region parameter r; the function g computes the sum of a pair stored in an arbitrary region | note that no region parameter is necessary for this. Regions cannot, however, be constructed, decomposed or compared: the only way to introduce a region is by the letreg-construct; the only way to use a region (except for passing it around) is as a storage designator in a tuple- or constructor expression.
2.2 Programming with Regions
Consider the program len xs = case xs of nil ! 0; cons x xs0 ! 1 + len xs fall n r = cons n ( case n of 0 ! nil r; x + 1 ! fall x r) r letreg x#43 + 1 in len(fall 4 x) which presents two typical programming slips, that would both lead to a crash. In the 0de nition of len, the recursive call is given xs rather than xs , causing the run-time stack to grow out of hand; in the letreg-declaration the programmer has correctly remembered that it takes 3 words to store a cons cell, and one word to store nil; what he has overlooked is that the list returned by fall 4 x | or not returned in this case | has a length of ve rather than four. This leads to an overfull region. Let us look at how the type system of MML prevents errors of these kinds. We start by looking at the basic notion of sized types. First of all, every inductively de ne value is associated with a size that denotes the number of iterations necessary to de ne it, e.g., the natural number 1 (which denotes succ zero) has size two; the list nil has size one. Moreover, every inductively de ned type is associated with a size that gives an upper bound on the sizes of the values in the type, e.g., the type List3 Nat2 contains the elements nil; 0: nil; 1: nil; 0:0: nil; : : : ; 1:1: nil, but neither 2: nil, nor 0 : 0 : 0 : nil. (Refer to [Par98] for the de nition of sized types.) The type of the intended list length function above would typically be len :: 8ka : Listk a ! Natk with = 5k and with the following interpretation: given a list of size k, len will return a natural number of size k; the stack eect , i.e, the temporary us of stack-space during any execution of len, is 5 times k words. (Five, because, at each recursive call, the values of x, xs0 , 1, and xs0 again, as well as a return address, will reside on the run-time stack | this will be evident when we introduce the abstract machine semantics below.) The termination-proof-technique employed by the type system is composed of a base case, which we will discuss in the technical part of the paper, and an inductive case, which, for len, reduces to showing that len00 xs = case xs of nil ! 0; cons x xs0 ! 1 + len0 xs
Regions can be thought of as short-lived heaps that are introduced and disposed of by the programmer. A region is empty at its point of creation, successively lled with values during its lifetime, and discarded in one go when disposed. In contrast to heaps, regions are never garbage-collected: neither during their lifetimes, nor when they cease to exist. Conceptually, regions can be either unbounded or bounded, which means that they either can or cannot store arbitrarily many values of arbitrary size. Bounded regions are associated with a region size that denotes the number of machine words occupied by a region; this size is constant during the lifetime of a region. In MML, a bounded region is introduced by the construct letreg x#e in e0
which creates a region of the size determined by the expression e (a number), binds a reference to this region (a name) to the variable x, evaluates e0 in the current environment extended with this binding, and which, nally, discards the 0 . Clearly, the value of region before returning the value of e e0 must not be stored in this region | the region is merely to be used by the computations that produce this value. Two kinds of values | tuples and constructors | can be stored in regions, and these values can only be stored in regions. To specify in which region a value should be stored tuple- and constructor-expressions are augmented with region parameters. Other values, such as numbers, are not stored in regions, but on the stack, and do, thus, not need any such extra parameters. For example, the program to store the pair (1; 2) in a region accessible by x, and to compute the sum of the elements of this pair (which can be retrieved with the projection operators 1 and 2 ) is letreg x#2 in let a = (1; 2)x in 1 a + 2 a The annotation on the region size indicates that the expression is a region size expression and not an ordinary natural number. This distinction is necessary, because these two classes of numbers have dierent types | we shall return to this below. The size of the region above region is taken to be 2 because two words are necessary to store a pair. Regions in MML are rst class values: they can be passed to functions and also be returned. The above program, for example, can be rewritten to: f x y r = (x; y)r g p = 1 p + 2 p letreg x#2 in let a = f 1 2 x in g a
2.3 Region Types
is typable under the type assignment len0 :: Listk a ! Natk with = 5k len00 :: Listk+1 a ! Natk+1 with = 5 (k + 1)
But this is not possible, for the variable xs cannot both have size k and size k +1 which this non-proof would require. The program is rejected on this ground. If we correct the bug by replacing the second occurrence of xs, with xs0 , this veri cation step will succeed. To see how the second bug is detected by the type system, we introduce a type for fall fall :: 8kr : Natk r ! Listk+1 (Natk ) r with = 5k; r += 3k + 1 which causes no problems. By coincidence, the stack eect is again 5k: at each recursive call, the values of n, x, x, r, plus a return address will have been pushed onto the stack. The type of fall also has a put eect (r += 3k +1) telling us that the function will store at most 3k + 1 words in region r. (Three, because every cons-node occupies one word each for the constructor-name, the head, and for the tail.) Returning to our fallacious program, let be the type of the region bound to x by the letreg-construct, and note that 4 has type Nat5 , the type of fall gives that the expression fall 4 x has type List6 Nat5 with the stack eect = 25 and the put eect += 16. These eects will be propagated through len, so the body of the letreg-expression will also have the put eect + = 16. The type system rejects the program because 16 6 4 3 + 1. To x the problem, the programmer simply has to increase the region size by three. The type of the corrected program, is Nat5 with = 27; = 17 Notice that this type has no put eects: put-eects concern regions in scope, and at the top-level of a program, there are no regions in scope. Instead, the program has a store eect that gives the maximum size of the store during its evaluation. Notice that this store-eect is one word larger than the put-eect of the let-expressions body, and also, that the stack-eect of the program is two words larger than of this body. To understand why, we need to take a look at the run-time system. The run-time system of MML maintains two stacks: a value stack in the style of traditional implementations of strict languages, and a region stack in style of the ML Kit, and on which letreg-expressions will push and pop region frames | run-time representations of regions. A region of size s is represented by s machine words in sequence preceded by a region oset that divides the region into an occupied and a free part. This oset will be 0 at the creation of a region, and successively increased by the allocations in that region by the number of words required to store a value. The oset is never decreased. For example, writing for an unde ned value and w w for sequences of machine words, the region frame of our very rst example would be 0 when pushed onto the region stack, and 2 1 2 just before being popped o it. This explains why the store eect of a letreg-expression is that of its body's put-eect plus one. As for the stack eect, we need one word to store on the stack and another to store the region size. This size is put on the stack by the region size expression, and used to increase the region stack pointer when a region is pushed onto the stack and to decrease it when the region is popped o the stack. This explains why the stack eect of a letregexpression is that of its body plus two. As mentioned above, region size expressions are not ordinary natural numbers (hence the annotations). This distinction is required by the type system, which, at letregs,
needs to know the region size exactly. As the type Natk only give bounds on sizes, we need a dierent type, Sizek , that gives us this. To avoid overloading, we use a dierent syntax for region size expressions and write n , e + e, etc., as in 1+ 2 :: Size3 1 :: Size1 Types with this precision will, of course, impose severe restrictions on the programs that compute with their elements; one cannot, for example, use a case expressions to return different sizes. Fortunately, such computations do not have to be very expressive. What we typically want to express is how the put eect of a function depends on the arguments of this function, i.e, the dependency that also appears in the type of a function. Now, these dependencies are themselves severely restricted: to make type checking decidable, size expressions are con ned to linear functions. As long as we can express such, programming with sizes is permissive enough. Let us illustrate the use of computations with sizes by showing how our main example can be made more readable through the use of a function fall0 to compute the put eect of fall: len :: 8ka : Listk a ! Natk with = 5k len xs = case xs of nil ! 0; cons x s ! 1 + len s
fall :: 8kr : Natk r ! Listk+1 (Natk ) r with = 5k; r += 3k + 1 fall n r = cons n ( case n of 0 ! nil r; x + 1 ! fall x r) r fall00 :: 8k : Sizek ! Size3k+1 fall s = 3s + 1 letreg x#fall0 5 in len(fall 4 x)
2.4 The Syntax of MML
We move on to formalise our development so far, and start with MML's syntax: P ::= g g e g ::= d d d ::= f x x = e e ::= n x c e e e e e f e e let x = e in e n e e letreg x#e in e (e; : : : ; e)e n e case e of 0 ! e [] x + 1 ! e case e of a a ::= + ? a ::= c x x ! e
n 2 Nat x 2 Var c 2 Con f 2 FunVar A program (P ) consists of a sequence of groups of mutually recursive function de nitions (g) followed by an expression. Such groups, in turn, are sequences of basic function de nitions (d) that take the form f x x = e. The top-level of a program is the only place where function de nitions are allowed: there are no lambda expressions or other means of de ning a function within an expression.
The form of an expression (e) is more-or-less standard, but with occasional twists calling for our attention: Numbers (n) and variables (x) are standard. Notice the restriction to natural numbers. Constructor expressions (c e1 en e) consist of n argument expressions, in the style of Haskell, plus an additional region expression. Constructors cannot be partially applied. The arithmetic operators () are restricted to addition, subtraction, and multiplication. Function calls (f e1 en ) are standard. Partial application is not allowed. Let expressions (let x = e in e0 ) are monomorphic, and must be non-recursive (lacking expressions of function type, the language has no need for a polymorphic let). Size expressions (n and e1 e2 ) are nothing but annotated arithmetic expressions. The letreg, pairing, and projection constructs (letreg x#e in e0 , (e1 ; : : : ; en )e , and n e) have already been covered. There are case expressions of two forms: for natural numbers (case e of 0 ! e1 [] x + 1 ! e2 ) and for constructor expressions (case e of a1 an ), that is, one rule for unboxed values (values stored on the run-time stack) and one rule for boxed values (values stored in a region). Our forthcoming development bene ts from keeping these constructs apart. Constructor alternatives (a) are restricted to simple patterns (c x1 xn ) with one variable for each constructor parameter, not counting the region parameter. * The syntax of MML's types, ::= 8k : 8t : 8 : p; ::= ;! ! ::= t [ ] Nats Sizes ::= Tss p ::= f 7! n; : : : ; 7! ng s ::= ! i i ::= k n n i i + i
rather than 1 n n1 ; f7!!n2 g; n3 . Constructor types (1 n ! ) have the same shape as function types, but for the absence of eects. This is because the eects of a constructor application are uniquely determined by its arity and the eects of its arguments. A basic type ( ) can be: A standard type variable (t). A region variable (). These play two roles: they are used as a variables in region polymorphic functions, and as unit-types for the actual region identi ers used as run-time | we shall return to this matter below. A tuple type ([ 1 n ] ), which is composed from element-types, as usual, but here also from a region variable that speci es where the tuple is stored. The built-in types for natural numbers (Nats ) or sizes (Sizes ), which have been covered above. A constructor type (). These are introduced by datatype declarations. The general form of a constructor type is Ts1 sn 1 m , where the rst size parameter s1 gives the size of the type, and where s2 sn and 1 m are actual size and type parameters (refer to [Par98] for details) the last parameter plays the same role as in tuple types. A size expression (s), which is either the limit ordinal literal (!), or a positive integer expression (i). Such an expression, in turn, is either a variable (k), a constant (n), a linear multiplication (n i), or an addition (i + i). This form of size expressions is inherited from the theory of sizedtypes, which requires that: 1) all size expressions are strictly monotonic in all their size variables, and that 2) all size expressions are linear in each size variable [Par98]. *
k 2 SizeVar t 2 TypeVar 2 RegVar ; ; n 2 Nat
also invites to a few remarks: There are three kinds of polymorphism: in size- (8k), type- (8t), and region-variables (8). Polymorphism is restricted to function or constructor types ( ). p; ) take the form of Function types (1 n ;! a mapping from a tuple of types rather than from a type; this is to manifest that our language is rst order. Function arrows are labelled with the three kinds eects discussed above: stack eects () which are natural numbers; put effects (p) which are mappings from region variables to natural numbers (f1 7! n1 ; : : : ; n 7! nk g); store eects () which are also natural numbers. In the informal development above, we used a sugared syntax for our function types and wrote 1 n ! with = n1 ; += n2 ; = n3
To simplify our development, we restrict MML to prede ned type declarations under the assumption that an extension to user de ned ones is straightforward. The syntax for declarations is: D ::= 8k : D 8t : D 8 : D " " ::= = r r ::= c j j c A declaration (D) is a, possibly quanti ed, equality (") between a constructor type () and a right-hand-type (r); a right hand type is a sequence of tagged type-sequences, each with a trailing region type (c 1 n ). We write D for the set of prede ned declaration, and take this set to be D = f 8 k a r : Listk+1 a r = nil r j cons a (Listk a r) r g
3 The Semantics of MML 3.1 Choosing a Semantic Framework
The role of our language semantics is manifold, and we must carefully design the semantics with respect to all its intended uses: 1) the semantics are used to reason about a type system with stack and store eects, so some notion of a stack and a store must be provided; 2) the semantics serve as a speci cation for compilers, so it must be designed with language implementation techniques in mind; 3) the
model is used in numerous proofs, so it must be mathematically tractable; 4) to fully understand MML's type system, programmers will need to refer to the semantics, so their formulation should, preferably, not be too mathematically intricate. Under these requirements, semantics by an abstractmachine in the style of Landin [Lan64] has turned out to be a suitable choice. By adding a store and a few new instructions to his SECD-machine, and by coalescing its dump and stack, we get a semantic model that satis es all of the requirements (1{4) above.
3.2 The Abstract Machine
An abstract machine is a transition system between machine states M , which, in MML, take this form: M ::= hV; S; E; C i V ::= v : V v v ::= n a c CES a ::= o S ::= f 7! R; : : : ; 7! Rg R ::= fo 7! v; : : : ; o 7! vgn E ::= fx 7! v; : : : ; x 7! vg C ::= : C callf retn sretCnES end ::= e e []x e = ()n n cn
a a x:e fgx e o 2 Nat 2 RegVar A machine state (M ) consists of a value stack (V ) that represents the run-time stack of a language implementation, a store (S ) that represents the region stack, an environment (E ) that maps program variables to values, and which has no immediate run-time representation, and an instruction sequence (C ) that represents the machine instructions in an executable program. A value (v) is either a natural number (n), an address (a) which points to either a tuple or a constructor in the store, a region identi er () which can be thought of as a reference to a region, a constructor tag (c), or a continuation CES , which corresponds to a return address in an actual implementation. An address (a) is a pair of the form o where is a region identi er and o an oset in that region (o is a natural number). A store (S ) is a mapping f1 7! R1 ; : : : ; k 7! Rk g from region variables to regions (R), which in turn are xed-size mappings fo1 7! v1 ; : : : ; ok 7! vk gn from osets to values, where k must not exceed n. The value in a store S pointed to by an address o can thus be expressed as S ()(o), or using the syntactic abbreviation S (o ) S ()(o). We write S + f 7! Rg to extend a store with region R identi ed by ; to make our manipulation of stores more concise, we introduce the syntactic abbreviation S + fo 7! vg S + f 7! S () + fo 7! vgg. An instruction sequence (C ) consists of one or more atomic instructions () followed by a control- ow instruction. These instructions will be discussed together with the transition rules of the abstract machine to which we devote the remainder of this section.
3.3 Numbers and Variables
Every expression e constitutes an atomic instruction that, when executed, will leave one value on the value stack; execution of an instruction will remove it from the instruction sequence, and the succeeding instruction will determine which transition to apply next. This basic rewrite process is illustrated by the transition rules for numbers and variables: hV; S; E; n : C i ! hn : V; S; E; C i hV; S; E; x : C i ! hE (x): V;S; E; C i
3.4 Constructors
The execution of an instruction is typically divided into a sequence of sub-computations that, together, form the desired result. To execute a constructor expression, for example, we rst execute all argument expressions, which will leave a value for each instruction on the stack; then, we execute an instruction that, using these values, will write the machine representation of the constructor to the store, and that will leave the address to this machine representation on the value-stack: hV; S; E; c e1 en e : C i ! hV; S; E; e1 : : en : e : cn : C i h : vn : : v1 0: V; S; E; cn : C i ! ho : V; S 0 ; C i; o = jS ()D j S S + fo 7! cg + f(o + i) 7! vi g Here, by S ()D we mean the domain of the region bound to in S , and by jS ()D j the number of elements in this set: this gives a fresh oset in the designated region (assuming that all binding osets in S () have been introduced in this way). A constructor value is simply represented as the constructor tag followed by the argument values. The address left on the value stack will point to the rst word of this sequence. Not only does a rewrite rule remove an instruction from the instruction sequence, but it may also insert new ones (as in the rst rule above). These insertions, however, do not occur at run-time, but at compile time: they represent the translation schemas of the compiler.
3.5 Arithmetic Operators
For every operator on expressions, , we introduce the corresponding operation on values; this lets us express all transition rules for arithmetic expressions as hV; S; E; e1 e2 : C i ! hV; S; E; e1 : e2 : : C i hn2 : n1 : V; S; E; : C i ! hn1 n2 : V; S; E; C i
3.6 Function Calls
At the abstract machine level, a function call can be divided into 1) creation of a continuation to use the computed value, 2) evaluation of the function's arguments, 3) creation of an environment that maps the formal variables of the function to the actual values of the call, 4) execution of the function's body in this environment, 5) removal of actual parameters from the stack, and 6) execution of the continuation. The rules to accomplish this process are: hV; S; E; f e1 en : C i ! hCES : V; S; E; e1 : : en : callf i hvn : : v1 : CES : V; S; E 0 ; callf i ! hvn : : v1 : CES : V; S; fxi 7! vi g; ef : retn i hv : vn : : v1 : CES : V; S; E 0 ; retn i ! hv : V; S; E; C i; S 0 S 0
0
0
When executed, a call-expression-instruction (the rst rule) pushes a continuation on the stack, and places the argument expressions plus a call instruction, callf , in the instruction sequence. The continuation, CES , consists of the instruction sequence following the call plus the environment and the store at the call; the continuation must carry both the environment and the store, because the environment maps variables to values, and values can be addresses. To capture the store in this way is, of course, not realistic in an implementation, so we play the following trick: we only allow continuations to be reinstalled in machine states with a store larger than that of the continuation (the side condition of the third rule above). In our semantics, this will always be the case so a language implementor can forget about this condition; we need it, however, for our proofs. The execution of a call-instruction (the second rule) creates the new environment and places the called function's body plus a return instruction in the instruction sequence. To allow the environment to be implemented using indirect addressing relative the top of the stack (a standard technique), we leave the actual parameters on the stack | remember that a language implementor is not free to put temporary values on the stack, or he would violate the correctness of the type system. We do not, however, make this indirect addressing explicit in the de nition of E as this would complicate our proofs. Return instructions (the third rule) are parameterised on the number of arguments that the return-value should be slid over at the return (sliding is another standard language implementation technique). In addition to the slid arguments, the return instruction removes the continuation from the stack and reinstalls its instruction sequence and environment.
3.7 Let-Bindings
The Execution of a let-expressions resembles a function call in many ways; it involves 1) computation of an argument, 2) creation of an environment that binds this value to a variable, 3) creation of a continuation, 4) execution of an expression in the new environment, 5) sliding, and 6) reinstallation of a continuation. The most notable dierence is that, in a function call, the continuation is a dynamic object (i.e., it will be present at run-time), whereas, in a let expression, a continuations is a static object (i.e., it will only be present at compile time): hV; S; E; let x = e in e0 : C i ! hV; S; E; e : x:e0 : C i hv : V; S; E; x:e : C i ! hv : V; S; E + fx 7! vg; e : sretC1 ES i hv : vn : : v1 : V; S; E 0 ; sretCnES i ! hv : V; S; E; C i; S 0 S Here, the instruction x:e provides, \in-line" functions, and the instruction sretCnES static-returns. Note the body of a lambda-instruction is an expression, not an instruction, so nested lambda expressions can never arise. 0
3.8 Sizes
Size expressions have the same meanings as ordinary arithmetic expressions, the distinction is only present in the type system: hV; S; E; n : C i ! hV; S; E; n : C i hV; S; E; e1 e2 : C i ! hV; S; E; e1 e2 : C i
3.9 Letreg
Letreg expressions, in turn, resemble let-expressions, but there are two important dierences: 1) the life and death of a new region is involved in their executions; 2) the expression computed rst will not itself be bound to the introduced variable, but used to determine the size of the created region | what is bound is a reference to this region. The rewrite rules are: hV; S; E; letreg x#e in e0 : C i ! hV; S; E; e : fgx e0 : C i hn : V; S; E; fgx e : C i ! h : n : V; S 0 ; E 0 ; e : = : sretC2 ES i; 2= SD S 0 S + f 7! fgn g; E 0 E + fx 7! g
hv : : n : V; S; E; = : sret2CE S i ! hv : : n : V; S n; fg; sret2CE S i By SD above, we mean the domain of S , and by S n we mean f0 7! R 2 S j 0 = 6 g. The rewrite scheme involves two new instructions: the region creation instruction fgx , and the region destruction instruction =. 0 0
0 0
Note that the region size is kept on the value stack during the whole execution of a letreg-construct; this is to allow the region stack to be implemented using a region stack-pointer that is increased to allocate memory for a region frame and decreased to reclaim this memory.
3.10 Tuples and Tuple Projections
The tuple construction process is almost identical to that of constructors; the absence of leading constructor name in the representation being the only dierence: hV; S; E; (e1 ; : : : ; en )e : C i ! hV; S; E; e1 : : en : e :()n : C i h : vn : : v1 : V; S; E; ()n : C i ! ho : V; S 0 ; E; C i; o = jS ()D j S 0 S + f(o + i ? 1) 7! vi g Given this representation, projection of a tuple onto one of its coordinates is trivial: hV; S; E; i e : C i ! hV; S; E; e : i : C i ho : V; S; E; i : C i ! hS ()(o + i ? 1): V; S; E; C i New, are the instructions ()n and i .
3.11 Case Expressions
The execution of a case expressions essentially follows that for a let-expression, except for some added control ow, and a decrement or decomposition of the tested expression. For numeric case, the transition rules are hV; S; E; case e of 0 ! e1 [] x + 1 ! e2 : C i ! hV; S; E; e : e1 []x e2 : C i h0: V; S; E; e1 []x e2 : C i ! hV; S; E; e1 : C i hv : V; S; E; e1 []x e2 : C i ! hv ? 1: V; S; E 0 ; e2 : sretC1 ES i E 0 E + fx 7! v ? 1g where the branching instruction e1 []x e2 is new. The rules for constructor-case, hV; S; E; case e of a a : C i ! hV; S; E; e : a a : C i ho : V; S; E; fci xi1 xini ! ei g : C i ! hvnk : : v1 : V; S; E 0 ; ek : sretCnES k i ck = S (o ); vj S ((o + j ) ); E 0 E + fxkj 7! vj g
are essentially the same: the case-alternative instruction a1 an , which we also write as, fci xi1 xini ! ei g is a generalisation of e1 []x e2 : the test refers to the store rather than to the stack; decomposition, like in the rule for tuple-projection, has replaced the decrement.
4 A Type System with Space Eects A type and eect system is a type system that, in addition to a type, associates a collection of observable side eects with each node in the derivation tree. In MML, there are three kinds of eects: stack eects (), put eects (p), and store eects (). In this section, we shall formulate the type system that lets us infer these eects; we start with a few standard de nitions and then proceed to the actual rules. A type assignment ? is a set of basic typing statements of the form x :: ; a function type assignment F is a set of function typing statements of the0 form0 f :: . 0By ?; x :: we refer to the set fx :: g [ f x :: 2 ? j x 6= xg, and similarly for F; f :: . A typing judgement is a 7-tuple of the form ? `F e :: ! ; p; where e, , , p, and are given by the grammar in section 2.4. A typing judgement is said to be valid if it is derivable using the inference rules of the type system. A subtyping judgement is a pair of the form 1 B 2 , read as 1 is a subtype of 2 , or of the form B 0 read out similarly. A subtyping judgements is valid if it can be derived using the subtype inference rules of the type system. We require any collection of type- and subtype-inference rules to satisfy the following property: if ? `F e :: ! ; p; and B 0 are valid, then so is ? `F e :: 0 ! ; p; . Eects posses a natural order, so there is no need for a notion of sub-eects: for and this order is that of natural numbers; for put eects, let pD denote the domain of p, take p(0) to be 0 if0 2= pD , and de ne p p0 as 8 2 (pD [ p D ) : p() p (). A system of inference rules is syntax directed if the structure of a derivation tree for a judgement is uniquely determined by the form of the judgement. We proceed to de ne syntax directed type- and subtypeinference rules of MML.
4.1 Typing Numbers
As we have already seen, the size of a natural number is one plus its value; this is because we want Nat0 to denote the empty set. The execution of a number-instruction n will push one element on the value stack, so = 1; there are no side eects in the store, so p = ; and = 0: ? `F n :: Natn+1 ! 1; fg; 0 The most precise type we can assign to a number n is Natn+1 , but because the size parameter of Nat is an upper bound on the numbers that might have this type, we can also give n any type Nats such that n + 1 s. The subtype inference rule for naturals is Nats1
B Nats2 s1 s2
4.2 Typing Variables
The inference rule for variables is analogous to that for numbers: ?; x :: `F x :: ! 1; fg; 0
4.3 Typing Constructors From the set of declarations D, one can easily derive a set of constructor type assumptions C. For our prede ned dec-
larations we get C = fnil :: 8 a r : r ! List1 a r; cons :: 8 k a r : a Listk a r r ! Listk+1 a rg Constructors being assigned type schemes, we need an instantiation relation, 8kt : 4 [s=k ][=t][ =] in which k is a shorthand for k1 kn , etc., and [s=k ] for the simultaneous substitution of si for ki in . The inference rule for constructors, 4 c :: 2 C c :: is used in the inference rule for constructor expressions: P F +1 Fni=1 (i ? 1 + i ); p i pi + f 7! 1 + ng; i i c :: 1 n ! i0 B i (8i) ? `F ei :: i0 ! i ; pi ; i (8i) ? `F e :: ! n+1 ; pn+1 ; n+1 ? `F c e1 en e :: ! ; p; The interesting parts of this rule are the eects: When e1 is evaluated, no value has been pushed on the stack, when e2 is evaluated one expressions has been pushed, etc., hence the de nition of . The put eect p is the cumulative put-eect of all subexpressions, plus the eect of writing 1 + n values to (1 for the c, and n for the vi 's | recall the representation of a constructor). Let pR denote the range of the eect p; the sum of two eects is p + p0 = f p() + p0 () j 2 (pR [ p0 R ) g The store eect is simply the maximum store eect of any sub-expression. The subtype relation for constructors is si B s0i (8i) i B i0 (8i) s s 0
Ts1 sk 1 m B Ts1 sk 10 m0 0
0
s1 B s2
1
Notice that, declarations lacking function types (basic types
do not contain function types), constructor types are al-
ways covariant in their parameters, but never contravariant.
4.4 Typing Arithmetic Operators
In the inference rules for the arithmetic operators, ? `F e1 :: Nats1 ! 1 ; p1 ; 1 ? `F e2 :: Nats2 +1 ! 2 ; p2 ; 2 ? `F e1 + e2 :: Nats1 +s2 ! 1 t (1 + 2 ); p1 + p2 ; 1 t 2 ? `F e1 :: Nats1 ! 1 ; p1 ; 1 ? `F e2 :: Nats2 ! 2 ; p2 ; 2 ? `F e1 ? e2 :: Nats1 ! 1 t (1 + 2 ); p1 + p2 ; 1 t 2 ? `F ei :: Natsi ! i ; pi ; i (8i) ? `F e1 e2 :: Nat! ! 1 t (1 + 2 ); p1 + p2 ; 1 t 2
2
the interesting parts are not the eects, but the dependencies between the operand-type sizes and those of the resulttypes: In an addition, the second operand-type must have a size greater than one, and the size of the resulting type will be the sum of the operands sizes minus one. In a subtraction, because sized types give upper bounds on the sizes of the elements in the type, all we conclude is that the size of the result is not greater than that of the left operand. In a multiplication, the type of the result is Nat! , which is the type of all natural numbers. Recall that size expressions (s) are restricted to linear expressions, so Nat! is the best type we can give arbitrary multiplications. (One could introduce specialised rules for the cases when one argument has a constant size, but then, our type system would no longer be syntax-directed. We refrain from this.)
4.5 Typing Function Calls
The rule for function type instantiation,
4 ? `F f :: f :: 2 F looks up the type scheme of a function in the function type assignment of the judgement. The type inference rule for function calls, ? `F f :: 1 n n+1 ; pn!+1; n+1 ? `F ei :: i0 ! i ; pi ; Fi (8i) i0 B P i (8i) F +1 ? `F f e1 en :: ! 1 + ni=1 (i ? 1 + i ); i pi ; i i is straightforward: the eects of the function are treated as those of its arguments.
4.6 Typing Let-Bindings
The typing of let-bindings, too, is entirely straightforward: ? `F e :: ! ; p; ?; x :: `F e0 :: 0 ! 0 ; p0 ; 0 ? `F let x = e in e0 :: 0 ! t (1 + 0 ); p + p0 ; t 0
4.7 Typing Sizes
For sizes, as for naturals, the interesting parts are not the eects, but the types. For constant sizes, the size of the type has the same value as the constant (a dierence compared to naturals): ? ` n :: Sizen ! 1; fg; 0 Because 0 has size 0, the size of an addition is the sum of the sizes of the operands: ? `F ei :: Sizesi ! i ; pi ; i (8i) ? `F e1 + e2 :: Sizes1 +s2 ! 1 t (1 + 2 ); p1 + p2 ; 2 t 2 The size of a subtraction may well be less than the size of the rst operand ? `F e1 :: Sizes1 +s2 ! 1 ; p1 ; 1 ? `F e2 :: Sizes2 ! 2 ; p2 ; 2 ? `F e1 ? e2 :: Sizes1 ! 1 t (1 + 2 ); p1 + p2 ; 1 t 2 c.f., the corresponding rule for naturals.
The syntax of size expressions restricts multiplication to multiplication by a constant (n i). We express our typing rule for multiplication of sizes accordingly: ? `F e1 :: Sizen ! 1 ; p1 ; 1 ? `F e2 :: Sizes ! 2 ; p2 ; 2 ? `F e1 e2 :: Sizens ! 1 t (1 + 2 ); p1 + p2 ; 1 t 2 Every size is a subtype of itself, Sizes B Sizes
but there is no subtype relationship between types with sizes that are dierent.
Sizesi
4.8 Typing Letreg
Any excesses in space use are eectively trapped at the letreg rule. It checks that the put eect of the region it introduces is less than or equal to the size assigned to the region: 2= FV (?; ); p0 () s ? `F e :: Sizes ! ; p; ?; x :: `F e0 :: ! 0 ; p0 ; 0 ? `F letreg x#e in e0 :: ! t (2 + 0 ); p + p0 n ; t (s + 1 + 0 ) The put eect of the local region should not visible outside the letreg-expression, so it is removed from the eect set p0 . To account for the space needed by the region's region frame, the size of the region plus one0 (for the region frame's oset) is added to the store-eect of the sub-expression e0 in which the region is alive. The side condition 2= FV (?; ) stops us from malicious de-allocations, i.e, deallocations that would introduce dangling pointers, as, for example, in let a = letreg x#3 in (1; 1)x in 1 a + 2 a
4.9 Typing Tuples and Tuple Projections
The typing rules for tuples and tuple projections are trivial: P F +1 Fni=1 (i ? 1 + i ); p i pi + f 7! ng; i i ? `F ei :: i ! i ; pi ; i (8i) ? `F e :: ! n+1 ; pn+1 ; n+1 ? `F (e1 ; : : : ; en )e :: [ 1 n ] ! ; p;
? `F e :: [ 1 n ] ! ; p; ? `F i e :: i ! ; p; The subtyping-rule for tuples is i B i0 (8i) [1 n ] B [1 n ]
4.10 Typing Case Expressions
Two aspects of the numeric case rule, 0 t 1 t (1 + 2 ); p p0 + (p1 t p2 ); Fi i ? `F e :: Nats+1 ! 0 ; p0 ; 0 ? `F e1 :: 1 ! 1 ; p1 ; 1 ?; x :: Nats `F e2 :: 2 ! 2 ; p2 ; 2 i B (8i) ? `F case e of 0 ! e1 [] x + 1 ! e2 :: ! ; p; are worth notice: 1) The binding of the pattern-variable in the second branch (x) requires one word of stack space. The
rule accounts for this by adding one to the stack eect of the expression in the second branch. 2) The potential eects of the two branches have to be merged in some way; we do so by taking their least upper bound: p t p0 = f p() t p0 () j 2 (pR [ p0 R ) g The typing rule for constructor-case is, essentially, a generalisation of that for numeric-case: 0 t Fni=1 (ni + i ); p p0 + Fni=1 pi ; Fi i D 4 = c1 1 j j cn n ; D2D ? `F e :: ! 0 ; p0 ; 0 ?; xi1 :: i1 ; ; xini :: ini `F ei :: i ! i ; pi ; i (8i) i B (8i) ? `F case e of c1 x1 ! e1 cn xn ! en :: ! ; p; The instantiation relation for type equalities used here is de ned by 8kt : " 4 "[s=k ][=t][ =] 0
4.11 Typing Function De nitions
It remains to relate the function type assignment F, that occurs in the typing judgements for expressions, to the function de nitions of a program. For this purpose, we introduce four new kinds of judgements: F ` d :: for basic function de nitions, F ` g ) F for recursive groups of such, g ) F for sequences of such groups, and P :: ! ; p; for programs. The inference rule for the rst kind of judgements, x1 :: 1 ; : : : ; xn :: n `F e :: ! ; p; p; F ` f x1 xn = e :: 1 n ;! is trivial, but the one that uses it, i [k] 8ki ti i :i [k]; FV (8k:i [k]) = ;; i0 B i [k+1] (8i) F; f1 :: 1 [k]; : : : ; fn :: n [k] ` fi xi = ei :: i0 (8i) i [0] = U (8i) F ` ffi xi = ei g ) F; f1 :: 8k : 1 [k]; : : : ; fn :: 8k : n [k] is more involved. To guarantee termination, the rule has the same built in induction principle as the letrec-rule of the sized type system (we refer the reader to [HPS96, Par98] for details): The last premise of the rule (i [0] = U) states that a type must be universal, which, for MML, means that it must be derivable using =U =U =U 8k : = U 8t : = U 8 : = U Z
Z
Z
i = E (8i) p; =U 1 n ;!
The last rule, here, states that a function type is universal if one of its domain types are empty, which, for MML, means derivable using the rules i = E Nat0 = E [ 1 n ] = E (8i)
si = 0 (8i 2 A) i = E (8i 2 B ) hA; B i 2 T =E T s = E
This last rule assumes that=Eevery type constructor T is associated with a constant T 2 }(}(N) }(N)) that speci es conditions on the constructor parameters under which the constructor type is empty. These constants can be derived from the declaration of a type (refer to [Par98] for the technique). In this paper, our only constructor type is List, which is associated with the constant List=E = fhf1g; ;ig. The rst premise in the rule for empty constructor types uses a judgement s = 0, which is valid if it can be derived using i=0 i1 = 0 i2 = 0 n=0 0=0 ni=0 ni=0 i1 + i2 = 0 * The second premise in the rule for mutual recursion (FV (?; )) states that the type schemes introduced by the rule must not contain free variables; this is to preserve the invariant \F contains no free variables" which makes the usual side condition for generalisation | a generalised variable must not occur in the type assignment | trivial. 0 The third premise in the rule for mutual recursion(i B i [k+1]) uses subtyping for function types, 0 ; p p0 ; 0 i0 B i (8i) B 0 p; p; 0 B 10 n0 ; ! 1 n ;! 0
0
0
which is contravariant in the argument types and covariant in the result type as usual.
4.12 Typing Programs
The last two type inference rules, for sequences of recursive de nitions, [ ] ` g1 ) F1 Fn?1 ` gn ) Fn g1 gn ) Fn and for programs, g ) F [ ] `F e :: ! ; p; g e :: ! ; p; are trivial. Z
Z
Z
Z
5 Discussions 5.1 Correctness of the Type System
Except for a handful of seemingly correct lemmas, the following property of MML has been proved: if a program is well-typed with the stack eect and the store eect , then the program will use at most + words of memory (not counting the words necessary to store the program, nor the machine registers). The rst step of this proof is to introduce a notion of size for machine states, written jM j, which is de ned as the height of the stack plus the sum of the sizes of all regions: jhV; S; E; C ij = jV j + jS j jv1 : : vn j = nP jS j = 2SD jS ()j jfo1 7! v1 ; : : : ; ok 7! vk gn j = n + 1
The size of a region f: : : gn is n + 1, because of the size of a region-frame is one word larger than the size of the region it holds. Environments (E ) and instruction sequences (C ) are compile time objects, and are thus not included in the size. The second step is to introduce a type system for machine states, in which both the stack and the store are assigned types. The syntax for the types in this system is ::= ::= V : V V ::= C C ::= 7?;! ::= f 7! ; : : : ; 7! g
2 Nat 2 Nat A machine type () consists of a stack-type () and a store-
type (), where a stack-type is a sequence of value types (V ) which in turn are either basic types ( ) or continuation types (C ). A continuation type is of the form 1 7?;! 2 , where 1 is the type of the machine that the continuation expects, 2 the type of the machine that it returns, and , the absolute stack- and store eects. (The eects and are relative eects.) A store-type () is a mapping f1 7! 1 ; : : : ; n 7! n g from region-variables (i ) to numbers (i ); the number i denotes the allocation in region i. The third step of the proof is to de ne the notion of a well-typed machine state, for which we introduce ve new typing-judgements: for stacks (S ` V :: ), for stores (S :: ), for environments (S ` E :: ?), for instruction sequences (? ` C :: 7?;! ), and for machine states (M :: ! ; ). We omit the inference rules for the rst four judgements (these belong to the full paper), and just look at the rule for a well-typed machine state: 0 0 ; S ` V :: 0 S :: 0 S ` E :: ? ? ` C :: 0 0 7?;! hV; S; E; C i :: ! ; A typing M :: ! ; tells us that the machine state M , when executed, will reduce to a state of type (c.f., a typing e :: Nat! , which tells us that e will reduce to a natural number.) The fourth step of the proof is to show that the size of a well typed machine state is less than or equal to the sum of its stack and store eects, i.e, if M :: ! ; is valid, then jM j + . The fth step is to prove subject reduction, i.e, if M :: ! ; is valid and M ! M 0 , then M 0 :: ! ; . Together with a notion of initial machine states, the last two statements let us infer the desired result: let M0 be the initial machine state for the expression e; if g e :: ! ; p; is valid and M0 ! ! Mn , then 8i : jMi j + . 0
5.2 Termination
0
The statement of the last section tells us that a well typed program runs in constant space, but does not mention termination. However, MML's type system being a strengthening of the sized type system (which does guarantee termination)
we have strong reasons to expect that the desired termination proof can be established. This approach includes the development of a denotational model for MML, and a proof that our abstract machine correctly implements this model. Another approach would be to re-develop the theory of sized types in an operational setting.
5.3 Implementation of the Type System
The type system described in this paper has not been implemented, but we have strong reasons to expect an implementation to be straightforward: it's predecessor, the sized-type system, has been given an ecient implementation [Par98], and there is no evident reason why our extended type system could not be implemented using the same techniques. What has been added to the sized type system are the three classes of eects, which will give raise to three new kinds of constraint-systems. The potential complication of the extension is that these new constraint-systems would turn out to be hard to solve. The implementation of the sized type system reduces type-constraints to Presburger-Arithmetic formulae, F ::= True False i = i i i i < i
8k:F
9k:F
F ^F
F _F
where i are size expressions as usual. Similar reductions should apply to our new constraints: we expect stack eects, put eects, and store eects all to be reducible to terms F . Like in the implementation of the sized type system, we can then use the omega test [Pug92], to check the generated formulas for truth. Although this means a hyperexponential worst case complexity of our implementation, we shall, in spirit of the sized type system, worry little about this until a program that triggers this complexity has been found.
5.4 Implementation of the Run-Time System
The run-time system of MML has not been implemented either, but we expect such an implementation to be straightforward too: the abstract machine has been designed with conventional compiler implementation techniques in mind. Let us look at the intended run-time representation of machine states hV; S; E; C i: The value stack (V ) is implemented using the CPU's stack-pointer as usual, and the store (S ) using a separate region stack pointer as described in sec. 2.3. The environment (E ) of a machine state mirrors values stored on the run-time stack, but has no run-time representation in addition to this. The instruction sequence (C ) is represented by a program counter that points into a sequence of CPU-instructions which has been generated by the compiler. (We expect the necessary compilation scheme to be standard, and will not consider it further.) To avoid tagging, a value (v) is represented using one machine word only: a number (n) is represented by an unsigned integer; an address (o ) by a pointer that points directly to the tuple- or constructor-representation that the address represents; a region () by a pointer to a region frame; a constructor tag (c) by an integer constant; a continuation (CES ) by pointer into the CPU-instruction sequence. (There is no run-time representation for environments in continuations,
nor for their stores | recall our discussions above and in sec. 3.6). * To verify that a compiler actually can be implemented along these lines | we might have overlooked something in our design of the abstract machine | is future work.
5.5 Tail Recursion
A well known technique to make recursive programs use less space is to distinguish tail calls from arbitrary function calls, and to exploit that tail-calls can be implemented more ef ciently. This technique is of particular importance in the context of embedded programming, so in this section we shall study how it can be added to MML. The idea of the technique is to avoid chains of continuations in which a continuation just passes its parameter on to the next. To avoid such chains is to save stack-space, because continuations are represented using the stack. Some of the function calls that give raise to such chains can be syntactically identi ed using a notion of tail expressions : the body of a function de nition is a tail expression; if a case-expression is a tail-expression, then so are the expressions of its branches. Function calls that are tail expressions are the ones we want to avoid. For this purpose, we add a new syntactic construct for tail calls to MML, and refurbish the grammar to allow such calls if they are tail expressions: P ::= g g e g ::= d d d ::= f x x = b b ::= fn e e case e of 0 ! b [] x + 1 ! b e Tail calls (fn e e) are distinguished from ordinary function calls by the presence of an environment-size n that is used to discard the environment in which the tail-call occurs. For example, in the tail recursive version of fac, fac a n = case n of 0 ! a [] x + 1 ! fac3 (n a) x the environment size is 3, for, at the call, the environment binds a, n, and x. We make tail-calls explicit for the same reason as we made storage management explicit: it is easier to formulate types for source programs than for programs derived from such; moreover, we expect this syntactic distinction to make programmers more tail-recursion aware. To give meaning to our new construct, we extend the callinstruction of the abstract machine with an environment-size to become callnf , and then introduce two new rules:
hV; S; E; fk e1 en : C i ! hV; S; E; e1 : : en : callkf i hvn : : v1 : v10 : : vk0 : CES : V; S; E 0 ; callkf i ! hvn : : v1 : CES : V; S; fxi 7! vi g; bf : retn i Here, the number n in the second rule is the arity of the function f , which we, as with its body, take to be globally 0
0
known.
We must also extend our rule for ordinary function calls with respect to our extended instruction: hV; S; E; f e1 en : C i ! hCES : V; S; E; e1 : : en : call0f i To type programs with tail-calls, we introduce a new judgement, ? `Fn b :: ! ; p; , that accounts for the number of variables (n) in the environment. The inference rule for tail calls, Fni=1 (i ? 1 + i ) t (n + ? k) ? `F f :: 1 n n+1; pn!+1; n+1 ? `F ei :: i0 ! i ; pi ; i (8i)P i0 F B i (8i) k ? `F fk e1 en :: ! ; i pi ; i i requires that the environment-size of the call matches that of the judgement. The rule is the same as for ordinary calls, except for the stack eect, which now accounts for the removed environment and for the re-use of the continuation created by the preceding call. The typing rule for numeric case expressions, 0 t 1 t (1 + 2 ); p p0 + (p1 t p2 ); Fi i ? `F e :: Nats+1 ! 0 ; p0 ; 0 ? `Fn b1 :: 1 ! 1 ; p1 ; 1 ?; x :: Nats `Fn+1 b2 :: 2 ! 2 ; p2 ; 2 i B (8i) ? `Fn case e of 0 ! b1 [] x + 1 ! b2 :: ! ; p; has been extended with the new judgement, and to account for the extended environment in the second branch of a numeric case. A new rule for expressions, states that well typed expressions are also well typed tail-expressions regardless of the environment's size: ? `F e :: ! ; p; ? `Fn e :: ! ; p; Finally, we introduce a rule for our new form of basic function de nitions: x1 :: 1 ; : : : ; xn :: n `Fn b :: ! ; p; p; F ` f x1 xn = e :: 1 n ;! With these rules, we can give fac the type ;;;0 fac :: 8k : Nat! Natk 3! Nat!
i.e, the relative stack eect is three words regardless of the sizes of the arguments. * The cost of adding tail recursion to our language is solely on the theoretical side: 1) the distinction between bodyexpressions b and ordinary expressions e make the subject reduction proof unwieldy, as it shows up all over the proof; 2) a stronger notion of well typed machine states that also take the size of the environment into account is required. To rework the subject reduction proof for the extended language is future work.
5.6 Unbounded Regions
The letreg construct of MML requires the programmer to express how large every region should be. This extra burden can be eliminated by extending the language with unbounded regions, as used by the run-time system of the ML Kit [TBE+ 97]. The idea is to implement a region as a linked list of region pages: at the creation of a region, or whenever a region page is full, a new page is allocated from a pool of un-used pages; when a region is discarded, the linked list is returned to this pool. It is possible to extend our type system to guarantee execution in bounded space for this model too; we shall brie y look at how. First of all, we need a construct for unbounded regions: letreg x = e in e0 We also need a cost function, cost : N ! N, that gives the cost of allocations in unbounded regions. Suppose that our region pages occupy 103 words each: hundred words for storage, one word for a region oset, and two words for linking information. Suppose also, that the largest constructoror tuple-representation that can arise is seven words long. Then, cost(n) = 103 (div(n; 100 ? (7 ? 1))) Here, the storage capacity of a page is reduced by 7 ? 1 to account for the worst case in which every region page is introduced by an attempt to allocate a tuple (or constructor) of maximum size in a region that has room for it, but for one word. We need, also, a notion of page-eects, , which denote the use of page-space by any invisible regions in an expression (c.f. the eect ). To infer such eects, we need new rules. For addition, ? `F e1 :: Nats1 ! p1 ; 1 ? `F e2 :: Nats2 +1 ! p2 ; 2 ? `F e1 + e2 :: Nats1 +s2 ! p1 + p2 ; 1 t 2 the new rule is analogous to the corresponding rule for storeeects . The rule for unbounded regions ?; x :: `F e :: ! ; p; ? `F letreg x in e :: ! p n ; cost(p()) + 2= FV (?; ) is analogous to that for bounded regions. * For presentational reasons, bounded regions have been made an extension to MML rather than an intrinsic part of the language.
5.7 Streams
The most striking limitation of MML is the lack of constructs for input output; another limitation is the lack of constructs for concurrency. Without such, embedded ML is not much of an embedded programming language. We intend, however, to overcome these limitations by adding streams. This allows for input output using synchronous stream-IO, and for concurrency using stream transformation functions | these are sucient idioms for,
at least, basic embedded programming programming problems [Par98]. One standard technique to represent streams in a strict functional language is by the language constructs delay and force that allow function calls to be suspended (see, for example, [Hen80], for a discussion of these). It remains as future research to study how these constructs can best be added to MML, and whether our type system can be extended to guarantee bounded-space execution for programs that use these.
5.8 Real Time
Not only does a region based run-time model let us prove that a program runs in constants space, but it also paves the way for functional programming with hard real-time constraints: it eliminates the problem of garbage collection present in traditional implementations of functional languages. We expect that we, in a way similar to our use of sized types to guarantee execution in bounded space, will be able to use sized types to guarantee execution in bounded time.
5.9 Higher Order Functions
One of the main strengths of functional programming languages is the presence of higher order functions; this, however, is not their only strength. Strong typing, datastructures with pattern-matching, referential transparency, and clean semantics are other strengths. Our approach in the design of MML has been not to introduce higher order functions too early, but to rst see how strong properties we can prove for a rst order language. Once we know this, we can try to re-establish these properties for a higher-order language. If this should turn out to be hard, one has to weigh rst-order programming in a strong language against higher order programming in a language that is weaker.
5.10 Type Inference
Once we know that a type checking for MML is feasible, an immediate questions is whether type inference is feasible too? We reduce the question to whether type inference is possible for sized types. Little regard has been payed to this problem, mainly because type inference for size types involves the seemingly hard problem of nding minimal solutions to systems of integer inequalities with functions as un-knowns. This, certainly, is an interesting problem, but as far as the authors can see, it is an integer-programming problem [Sch86] more than a problem in programming language design.
Acknowledgements We would like to thank Fritz Henglein who ignited this work and Mads Tofte who encouraged us to take it further. Thanks, also, to Jrgen Gustavsson for helpful discussions on abstract machine semantics.
References [AVW93] Joe Armstrong, Robert Virding, and Mike Williams, Concurrent programming in erlang, Prentice Hall, 1993.
[HCRP91] N. Halbwachs, P. Caspi, P. Raymond, and D. Pilaud, The synchronous data ow programming language Lustre, Proc. IEEE 79 (1991), no. 9, 1305{1320. [Hen80] Peter Henderson, Functional programming; application and implementation, Prentice Hall, 1980. [HPS96] John Hughes, Lars Pareto, and Amr Sabry, Proving the correctness of reactive systems using sized types, Conference Record of POPL '96: The 23rd ACM SIGPLAN-SIGACT Symposium on Principles of Programming Languages (St Petersburg, Florida) (Guy L. Steele Jr, ed.), vol. 23, ACM, January 1996. [Lan64] P. J. Landin, The Mechanical Evaluation of Expressions, Computer Journal 6 (1964), no. 4, 308{320. [Par98] Lars Pareto, Sized types, Licentiate thesis, Chalmers University of Technology, 1998. [Pug92] William Pugh, A practical algorithm for exact array dependence analysis, Communications of the ACM 35 (1992), no. 8, 102{114. [Sch86] A. Schrijver, Theory of linear and integer programming, Wiley, 1986. + [TBE 97] Mads Tofte, Lars Birkedal, Martin Elsman, , Niels Hallenberg, Tommy Hjfeld Olesen, Peter Sestoft, and Peter Bertelsen, Programming with regions in the ML Kit, Tech. Report DIKU-TR-97/12, Dept. of Computer Science, University of Copenhagen, 1997, (http://www.diku.dk/research-groups/ topps/activities/kit2). [TT97] Mads Tofte and Jean-Pierre Talpin, Region-based memory management, Information and Computation 132 (1997), no. 2, 109{176.