Objective Label 1.06: User's Manual

This manual is not up-to-date. Please refer to the DVI and postscript versions.

Contents

  1. Introduction
  2. Labeled and optional arguments
  3. Polymorphic variants
  4. Distribution modifications
  5. LablTk
  6. LablBrowser
  7. Installation

Introduction

O'Labl, for Objective Label, extends Objective Caml to labeled and optional parameters [F], and also adds polymorphic variants. The modifications to the language itself are minimal, but using labels will deeply change the aspect of programs. They are more readable, easier to maintain, and one can really understand the meaning of a function by looking at its type.

Particularly interesting is the LablTk library, based on François Rouaix's CamlTk interface [R], which allows one to write ML programs in a style very close to Tcl/Tk's.

LablBrowser, based on it, demonstrates the power of typeful programming in the presence of labels: the integrality of O'Labl libraries is browsable and searchable, as well as user's programs, on the basis of typing information only.

The O'Labl distribution contains a patch to modify O'Caml (Currently version 1.06. Check that the O'Caml version and the patch version match.), the library LablTk, and the module browser LablBrowser. See appendix A for installation.

In the following we suppose that you are at least familiar with a language of the ML family, preferably of the CAML branch.

Labeled and optional arguments

One of the goals of O'Labl is to show that labels and variants are not only useful, but also inexpensive: both in terms of the work necessary to extend the original compiler, and efficiency of the resulting code.

As a result, modifications to O'Caml were limited to a minimum, making this extension immediately usable by an O'Caml programmer. This section and the next one describe syntactic and semantic modifications to the language.

Labels, optionals and currying

Until now, no widely distributed functional language provided for labeled or optional arguments. This comes essentially from the fact these languages allow currying, and, as a result, partial application.

For instance, suppose we define (``name:'' denotes a label of name name.),

let rec map fun:f = function
    [] -> []
  | x :: l -> f x :: map fun:f l

We can use it fully applied as map fun:(fun x -> x+1) [1;2;3], but also partially applied map fun:(fun x -> x+1), as usual.

But what to do with the unlabeled partial application map [1;2;3]. Intuitively, we expect it to have type fun:(int -> 'a) -> 'a, otherwise there is no point in having labels. However, compiling this without changing semantics is not trivial.

When we add optional parameters, the relation with currying is even more complex. Take the function sort : ?order:('a -> 'a -> bool) -> 'a list -> 'a list. The ``?'' in front of ``order:'' means that this argument is optional. We can do it, since O'Caml has polymorphic comparison: we take (<) : 'a -> 'a -> bool as default. Still, we have a problem with determining when we should decide this argument was omitted. Intuitively, sort [1;4;3] should directly give [1;3;4] as result. But, how should we handle sort [1;4;3] order:(>)? The trivial extension results in a type error, where one would want arguments to commute. We need a more precise definition of ommission semantics.

Syntax

The original syntax of O'Caml is extended with the following production rules (cf. O'Caml's reference manual for the syntax of the rules).
typexpr ::= ...
  | [?]typexpr -> typexpr
  | [?]label:typexpr -> typexpr
expr ::= ...
  | expr labeled-expr+
  | fun labeled-simple-pattern+ [when expr] -> expr 
  | function labeled-pattern [when expr] -> expr
          {| labeled-pattern [when expr] -> expr}*
labeled-expr ::=
    [?]expr
  | [?]label:expr
labeled-pattern ::=
    pattern
  | label:pattern
  | ?pattern [[< expr >]]
  | ?label:pattern [[< expr >]]

``label:'' is a new lexical entity, ``[a-z][a-zA-Z0-']*:'' being its defining regular expression. As such, there is no restriction as which identifiers you may use as labels: keywords of the language are welcome, like ``fun:'' above.

Since heavy use of labels may make a program more verbose than necessary, some abbreviations are also permitted. They are all based on the expansion rule

:name --> name:name
and its optional version
?:name --> ?name:name
This rule being applied at the lexical level, it is valid in all contexts: patterns, expressions and types.

There are some interferences between labels and the original syntax of O'Caml at three levels:

Semantics

Note first that application is no longer a binary operation --- the original definition is expr expr --- but application of an expression to a list of labeled expressions (Notwithstanding its formal definition, O'Caml was already using this definition of application internally.). This is to avoid the interference between order and optionals: between arguments applied simultaneously on different labels, order is irrelevant.

Labeled arguments

In absence of optionals (ignore all the ``?''), semantics is easy. You can apply a function on any of its labels, and in any order. The labeled argument will be substituted for the first parameter with same label. That is:
#let f = map [1;2;3];;
val f : fun:(int -> 'a) -> 'a list
#f fun:(fun x -> x+1);;
- : int list = [2; 3; 4]

When you have several arguments on the same label (quite rare, except for the empty label), they are just applied in the order given.

#let f a:x a:y = x - y;;
val f : a:int -> a:int -> int
#f a:3 a:1;;
- : int = 2

Optional parameters

One can introduce default values in a function definition.

#let f x ?incr:y [< 1 >] = x + y;;
val f : int -> ?incr:int -> int
#f 1;;
- : int = 2

As explained above, we need some definite rule to decide when an argument was omitted. This is rule is in some way arbitrary, but it appears to do what one wants to do in most cases.

  1. When a function is passed as argument to another function, all its optional parameters are considered omitted.

    #let g = (fun x -> x) f;;
    val g : int -> int
    #g 3;;
    - : int = 4
    
  2. For application, optional labels match their non-optional counterpart.

    #f 1 incr:3;;
    - : int = 4
    #f incr:3;;
    - : int -> int
    
  3. After an application, all optional labels appearing at the head of the result type are considered omitted.

    #f 1;;
    - : int = 2
    #let g () ?:x [< 1 >] ?:y [< 1 >] () ?:z [< 1 >] = x * y * z;;
    val g : unit -> ?x:int -> ?y:int -> unit -> ?z:int -> int
    #g ();;
    - : unit -> ?z:int -> int
    #g () () x:3;;
    - : int = 3
    

Optionals as syntactic sugar

In fact default arguments are only syntactic sugar for simpler optional parameters. They are implemented as option types (type 'a option = None | Some of 'a).

# let f () ?:x = x;;
val f : unit -> ?x:'a -> 'a option
# f ();;
- : 'a option = None
# f () x:3;;
- : int option = Some 3

In order to allow some forms of meta-programming with optionals, ``?'' may also be used in applications, with two effects:

About call-by-value

ML is defined as a language with call-by-value semantics. This defines an order of evaluation for expressions (In O'Caml, this does not specify the order of evaluation of the arguments, nor whether the arguments should be evaluated before or after the function.), permitting the integration of side-effects in the language. However this definition is made with respect to classical lambda-calculus. The same definition with label-selective lambda-calculus (as defined in [A]) would be very hard to implement efficiently --- there should be different evaluation paths depending on the order the arguments were applied. As a result, what we get in O'Labl is call-by-value operating on the translation into classical lambda-calculus of the original program.

Usually, you will not see it: as soon as a closure gets all its necessary arguments, it is evaluated.

#let f () =
#  print_endline "Hello!";
#  fun :x :y -> x + y;;
val f : unit -> x:int -> y:int -> int
#f () y:1;;
Hello!
- : x:int -> int
#let g = f y:1 in g ();;
Hello!
- : x:int -> int

Both when ``()'' and ``y:1'' are applied simultaneously or separately, ``Hello!'' is printed as soon as ``()'' is passed. (However, the first form is more efficiently compiled.)

Things get a little strange when you use tracing.

#trace f;;
f is now traced.
#f () x:1;;
f <-- ()
Hello!
f --> <fun>
f* <-- x: 1
f* --> <fun>
- : y:int -> int = <fun>
#f () y:1;;
f <-- ()
Hello!
f --> <fun>
- : x:int -> int = <fun>

The function is correctly traced only when there is no ``gap'' in the parameters passed. In the second case, since x: precedes y:, the trace of y:1 is delayed until the resulting function is applied on x:. Since tracing is done by instrumenting the original function, and out-of-order application with a gap creates a closure around it, there is no easy way to get more accurate trace information.

If you are curious about what is exactly done by compilation, use olabl with option -dlambda : an intermediate form will be displayed.

Typing

Type checking is extended to allow these new constructs. We do not detail the modifications here, the formal definition can be found in [F].

Only one modification had to be made in an unrelated part of the type checker. The definition of value, used to restrict polymorphism to side-effect free expressions, was extended in the following manner:

This allows one to do some tricky things with optional parameters.

Another modification was done, in the typing of statement sequences, to avoid some stupid errors. When the type of the result of the expression preceding a semicolon is unknown, it is resolved as unit. When it is known, the old behaviour is kept, and you only get a warning when this is a partially applied function.

# fun x -> x; ();;
- : unit -> unit = <fun>
# fun (x : int) -> x; ();;
- : int -> unit = <fun>
# fun (x : int -> int) -> x; ();;
Warning: this function application is partial,
maybe some arguments are missing.
- : (int -> int) -> unit = <fun>

Interaction with objects

There are limitations on the use of labels and optionals when using them in combination with objects.

# class point :x :y =
    val mutable x = x
    val mutable y = y
    method move y:dy x:dx = x <- x + dx; y <- y + dy
    method omove ?y:dy [< 0 >] ?x:dx [< 0 >] =
       x <- x + dx; y <- y + dy
  end;;
class point x:(int) y:(int) =
  val mutable x : int
  val mutable y : int
  method move : x:int -> y:int -> unit
  method omove : ?y:int -> ?x:int -> unit
end
# let move_x10 p = p#move y:0 x:10;;
move_x10 : < move : x:int -> y:int -> 'a; .. > -> 'a = <fun>
# let omove_x10 (p : #point) = p#omove x:10;;
omove_x10 : #point -> unit = <fun>

move_x10 demonstrates how alphabetical reordering of labels allows one to use methods in a fully polymorphic way: the type matches that of the point class. Remark that for it to work well you should only apply methods completely (most often partial application of methods has very little meaning).

In omove_x10 we have to constraint p to be a subtype of point. Otherwise we do not know which arguments are optional and cannot compile it properly. This formulation is still general since any subtype of point may be used with this function.

Suggestions for labeling

Like for names, choosing labels for functions is not an easy task. A good labeling is a labeling which

We explain here the rules we applied when labeling the standard library.

To speak in an ``object-oriented'' way, one can consider that each function has a main argument, its object, and other arguments related with its action, the parameters. To permit the combination of functions through functionals, the object will not be labeled. Its role is clear by the function itself. The parameters are labeled with keywords reminding either of their nature or role. The role is to prefer, since the nature will often be given by the type itself. Obscure abbreviations should be avoided.

List.map : fun:('a -> 'b) -> 'a list -> 'b list
output : out_channel -> buffer:string -> pos:int -> len:int -> unit

When there are several objects of same nature and role, they are all left unlabeled.

List.iter2 : fun:('a -> 'b -> 'c) -> 'a list -> 'b list -> unit

Choosing the object contains some part of arbitrary, readability and usability being the real goal. In assoc the theoretical object would probably be the association list, but the following choice seems more natural. This is also coherent with mem.

List.assoc : 'a -> in:('a * 'b) list -> 'b
List.mem : 'a -> in:'a list -> bool

When there is no object, all arguments are labeled,

open_out : name:string -> out_channel
Sys.rename : old:string -> new:string -> unit

however, when there is only one argument, it is often left unlabeled.

Format.open_hvbox : int -> unit

All these are only suggestions, but one should keep in mind that the choice of labels is essential for readability. Omissions or bizarre choices will make the program difficult to maintain.

In the ideal, the right function name with right labels should be enough to understand the function's meaning. Since one can get this information with LablBrowser or olabl, the documentation is only used when a more detailed specification is needed.

Polymorphic variants

Here we introduce the syntax of polymorhic variants, informally discuss their use, and explain how they are typed.

Syntax

The already extended syntax is again extended to include polymorphic variants.
typexpr  ::= ...
  | ['a][variant-kind]
  | [('a,...)] #ident [as 'a]
  | [('a,...)] #ident[> ident+] [as 'a]
  | [('a,...)] #ident[ident+] [as 'a]
variant-kind ::=
    tag-type*
  | tag-type* .. [> ident+]
  | < tag-type+ [> ident+]
  | > tag-type+
tag-type ::= 
    ident
  | ident (typexpr)
expr ::= ...
  | `ident simple-expr
simple-expr ::= ...
  | `ident
pattern ::= ...
  | `ident simple-pattern
simple-pattern ::= ...
  | `ident

A variant kind (eventually preceded by a type variable it constrains) is written between square brackets (``['' and ``]'').

Variant expression and pattern are identifiers (either low- or upper- case) preceded by a backquote (```'') and eventually followed by an argument.

A variant kind can be seen as a triple (T, U, L). T is a set of bindings from tags to types (or 0 if the tag takes no argument), U the upper bound of the variant (a set of tags, A if there is no bound), and L its lower bound. Here are examples of the different forms and their meanings.

 
    Syntax             Meaning
(a) [a b(int)]         ({a : 0, b : int}, {a,b}, {a,b})
(b) [a b(int) .. > b]  ({a : 0, b : int}, A, {b})
(c) [< a b(int) > b]   ({a : 0, b : int}, {a,b}, {b})
(d) [> a b(int)]       ({a : 0, b : int}, A, {a,b})

There is a double subtyping relation between variant kinds, such that (a) < (c) < (b) and (a) < (d) < (b). Kinds of the form of (a) are static: they are minimal in the subtype hierarchy, and cannot change anymore through type unification. [..] is the other extremity of the hierarchy, the kind we know nothing about.

In a way similar to object types, ``#'' introduces abbreviations for subtypes.

     Abbreviation  Extended form
(a)  ab            [A(int) B]
(b)  #ab           [< A(int) B]
(c)  #ab[> A]      [< A(int) B > A]
(d)  #ab[A]        [A(int)]
These abbreviations make easy to write types and signatures. Forms (b) and (c) contain an hidden kind variable, and are also correctly generated by the typechecker. Form (d) allows one to define a subtype as a list of cases from its supertype.

Use

Basic use

Use of polymorphic variants is identical to sum types, except that you don't have to define them. As a result, the same variant tag may be used in many different variant kinds.
# [`on; `off];;
- : [> off on] list = [`on; `off]
# `number 1;;
- : [> number(int)] = `number 1
# let f = function `on -> 1 | `off -> 0 | `number n -> n;;
val f : [< number(int) off on] -> int = <fun>
# List.map fun:f [`on; `off];;
- : int list = [1; 0]
# function `A -> `B | x -> x;;
- : 'a[A B .. > B] -> 'a[A B .. > B] = <fun>

[> off on] list means that to match this list, you should at least be able to match `off and `on, without argument. [< number(int) off on] means that f may be applied to `off, `on (both without argument), or `number n where n is an integer. Both variant kinds appearing only once in the type, the implicit type variables they constrain are not shown.

In the last example, since there is a relation between input and output (introduced by the x -> x case), the type variable appears. The variant kind [A B .. > B] means that `A and `B should have no argument, and any match on the output should at least have a case for `B.

Recursive variants are also correctly inferred.

# let rec map f = function
      `nil -> `nil
    | `cons(a,l) -> `cons(f a, map f l);;
map : ('a -> 'b) ->
      'c[< cons('a * 'c) nil] ->
      'd[> cons('b * 'd) nil] = <fun>

Another interesting use of variants is in combination with objects: rather than statically define a sum type to represent the object state, you may use variants.

# class switch () =
    val mutable state = (`off : [on off])
    method set = state <- `on
    method reset = state <- `off
    method get = state
  end;;
class switch (unit) =
  val mutable state : [off on]
  method set : unit
  method reset : unit
  method get : [off on]
end

This is more readable than using a boolean, and less cumbersome than defining a sum type. This is particularly true when you think that a sum type would have to be exported with the class, if you want to access it from other modules.

Subtleties

You can see in the previous example that we annotate state with the explicit type [on off]. This is necessary, since there cannot be free type variables in an object.

But even when this is not compulsory, this is good style to constrain variant types. Not constraining them may cause errors. For instance, the following code is typed correctly, but not in the expected way:

# let test state =
    if state = `on then print_endline "on"
    else print_endline "off";;
val test : [> on] -> unit = <fun>

Indeed, you probably expected the type [on off] -> unit. But there is nothing in this definition to know that. This problem only appears when either you use polymorphic equality, or an open form of pattern matching (when there is a case with no constructor). As a result of these type annotations, and the use of type abbreviations, a polymorphic variant will often be less prolymorphic than it might. There are two ways to recover this lost polymorphism.

  1. Variant dispatching: this relies on the use of as clauses in pattern matching. The variable you write after as will get the type of its associated pattern, rather than the type of the matched expression.
    # function `a|`b as x -> (Some x,None)
             | `a|`c as y -> (None,Some y);;
    - : [< a b c] -> [> a b] option * [> a c] option = <fun>
    
    This form of dispatching allows one to describe delegation behaviours in terms of variants, and provides an alternative to objects for small data.
  2. Subtyping: like with object types, you may write explicit coercions for variant types. For instance, if x has type [on off], you may extend it to type [on off unknown] by writing (x :> [on off unknown]). See next subsection for details.

Variants vs. sum types

Polymorphic variants and defined sum types are very similar. This may bother you when you are to choose the data structures to use in a program.

Advantages Drawbacks/restrictions
No need to define them and to open signatures In most cases you will still need to define an abbreviation for your comfort
Better accuracy of types / subtyping Sometimes the type inferred is too general

For these reasons you will probably not use polymorphic variants for everything. In particular, sum types seem more appropriate for data structures shared throughout a program (when subtyping is not needed): you just have to group them in an header .mli file, opened from all other modules.

On the other hand, variants are appropriate for transient data structures. That is, simple data (flags, union types) used either locally or as parameter to functions. In particular, for functions called from out their defining module, using variants as parameters is cleaner: it avoids the grudge of prefixing arguments with the module name, and allows to share the same tags between different modules (particularly important if you are building a library, and do not want to use a C-like naming scheme).

Nothing opposes mixing both variants and sum types in the same data structure. Still, you shall be careful in making it easy to remember, by making clear what is defined as variant and what is defined as sum type.

Typing

We just explain here the basics of polymorhic variant typing. This supposes some knowledge of how works ML's type inference.

Variant kinds are an extension of the unification algorithm used by the typechecker. When you apply ``List.map fun:f : [< number(int) off on] list -> int list'' to ``[`on; `off] : [> off on] list'', the typechecker tries to computes the most general unifier, here [< number(int) off on > off on] and binds it to the variables which where constrained by each kind.

To compute this mgu we use the triple view (T,U,L) of variant kinds. When U is finite, T is restricted to its elements.

(T1, U1, L1) /\ (T2, U2, L2) = ((T1|(U1/\U2)) /\ (T2|(U1/\U2)), U1 /\ U2, L1 \/ L2)

There are two logical conditions for this equality to stand:

  1. L1 \/ L2 shall be included in U1 /\ U2.
  2. T1 /\ T2 checks the compatibility between the two assigments by unifying their types recursively: if it fails there is no mgu.

Since subtyping is obtained through unification, it may happen that you unify two unrelated constrained variables. Like with objects, this can be avoided by explicit coercions. In (expr :> [a b(int)]), The type of expr is unified with 'a[< a b(int)], while the type of the result is [a b(int)]. For instance, to pass an argument x : [off on] to a function f : [number(int) off on] -> int, you should write f (x :> [on off number('a)]).

There is a small difference between class coercions and variant kind coercions, which appears on recursive types: while abbreviated class subtyping is recursive, this is not the case with kinds. In (x :> 'a[nil cons(t * 'a)]), the type of x will be unified with [< nil cons(t * 'a[nil cons(t * 'a)])] rather than with 'a[< nil cons(t * 'a)]) (which would correspond to classes). This just appears to be the right thing to do, since the kind of recursion you have with variants is different in nature from the recursion of objects. You can still coerce between recursive types by using complete coercions, of the form (e : t1 :> t2).

Another constraint is enforced by variant kind unification: it checks that all tags present in the result variant will be compiled to different integers. This allows a very efficient compilation scheme, which makes polymorphic variants just as effective as sum types, as long as matches are of reasonable size: matching against a sum type works in constant time, but against polymorphic variants it is in log(n), where n is the number of cases (we cannot use the switch instruction).

Distribution modifications

Modifications were done at several levels: library interfaces; parsing, type-checking and first stage of compilation; small modifications to other tools. Please refer to O'Caml's reference manual for how to use the commands.

Libraries

The standard library, as well as part of the other libraries of the distribution, are ``labelized''. This means that labels were added on function parameters to make clearer their meaning. We do not give the types here, you should either look at the compiled interface files (.mli) or use LablBrowser.

Batch compiler

olablc replaces ocamlc. Both commands are completely compatible and use same command line switches.

The bytecode files (.cmo) can be ran by the same ocamlrun, but one should take care of not mixing compiled interface files (.cmi): they are not compatible, and reading a compiled interface produced by one compiler with the other would result in a ``xxx.cmi is not a compiled interface'' error.

Command line switches were added.

By using the -nolabels switch or renaming the compiler, all O'Caml programs and libraries can be compiled and used in O'Labl. They can be easily ``labelized'' by adding labels only in the interface: they are ignored when compiling the implementation, but can be used in O'Labl programs. For bootstrapping reasons, this is the way the standard library was labelized. This explains why it contains no optional arguments.

If you compile and install the native code compiler, olablopt will also replace ocamlopt. (cf. O'Caml's reference manual for differences between bytecode and native code compilers.)

Interactive toplevel

olabl replaces ocaml. Both commands are completely compatible and use same command line switches.

-nolabels is also available with olabl. This allows one to read O'Caml files in the toplevel, replacing completely ocaml. Again, you obtain the same effect by renaming olabl to ocaml.

Among other interesting switches, notice also -dlambda. This dumps the code after label compiling, allowing to compare labeled code with usual one.

Custom toplevels can be built using olablmktop.

Other tools

They are all available under names starting with olabl. olablcp, olablprof and olabldebug needed small changes for use with Objective Label, but olablrun, olabllex, olablyacc and olabldep are identical to their Objective Caml counterparts.

LablTk

LablTk41 is an easy-to-use and well integrated interface to the Tcl/Tk toolkit. It is more than the labelized version of OCamlTk41, the Tcl/Tk interface of O'Caml. Optional arguments as well as polymorphic variants were heavily used to make it much closer to Tcl's syntax, and almost type safe. See the (rather old) documentation for details, and read the examples for how to use it. labltktop is also good for experimenting.

Here are a few hints on how to compile and link with LablTk:

LablBrowser

LablBrowser is a source and compiled interface browser, written using LablTk. This is a necessary companion to the programmer.

Its functions are:

The name of the command is lablbrowser, and, as with the compiler, you may change the standard library directory by setting OLABLDIR, and extend the load path using -I options.

Viewer

This is the first window you get when you start LablBrowser. It displays the list of modules in the load path. Click on one to start your trip.

Module walking

Each module is displayed in its own window.

At the top, a scrollable list of the defined identifiers. If you click on one, this will either create a new window (if this is a sub-module) or display the signature for this identifier below.

Signatures are clickable. Double clicking with the left mouse button on an identifier in a signature brings you to its signature, inside its module box.

A single click on the right button pops up a menu displaying the type declaration for the selected identifier. Its title, when selectable, also brings you to its signature.

At the bottom, a series of buttons, depending on the context.

C-s lets you search a string in the signature.

File editor

You can edit files with it, if you like to live dangerously. Otherwise you can use it as a browser, making occasional corrections.

The Edit menu contains commands for jump (C-g), search (C-s), and sending the current selection to a sub-shell (M-x). For this last option, you may choose the shell via a dialog.

Essential functions are in the Compiler menu.

Shell

When you create a shell, a dialog is presented to you, letting you choose which command you want to run, and the title of the shell (to choose it in the Editor).

You may change the default command by setting the OLABL environment variable.

The executed subshell is given the current load path.

Bugs

Acknowledgements

We have to thank very heartfully the Caml team. All these extensions were possible thanks to the O'Caml/CamlTk system.

Installation

Installing O'Labl

From the O'Labl distribution, get ``ocaml-olabl-ver.diffs'', where ver is the newest version of O'Caml available. But read this before acting.

Starting from the raw O'Caml ver distribution, type

  1. % cp olabl-ver/boot/ocamlc boot/
  2. % patch -p1 < olabl-ver/ocaml-olabl-ver.diffs
  3. % ./configure
  4. % make world
  5. % make install
Look in O'Caml's documentation for other options you may use at step 3.

You can also make and install the native code compiler and its libraries:

% make opt
% make installopt

Installing LablTk and LablBrowser

Tcl 7.5/6 and Tk 4.1/2 should be installed on your system. Go to the labltk41 directory in the O'Labl distribution.
  1. First copy site.config and modify it for your computer, and then
    % ./configure --with-config=mysite.config
    This should identify correctly your configuration. If there is an error, see config.log. If all your attempts fail, copy Makefile.config.tmpl and labltklink.tmpl to Makefile.config and labltklink, and edit by hand.
  2. Then type
    % make all
  3. and to make examples in example directory, type
    % make example
  4. To make LablBrowser, type
    % make browser
  5. After successful compilation of everything, you may install the library and LablBrowser.
    % make install

    The following files are installed:

References

[AitKaci95]
Hassan Aït-Kaci and Jacques Garrigue. Label-selective lambda-calculus: Syntax and confluence. Theoretical Computer Science, 151:353-383, 1995.
[Furuse95]
Jun P. Furuse and Jacques Garrigue. A label-selective lambda-calculus with optional arguments and its compilation method. RIMS Preprint 1041, Research Institute for Mathematical Sciences, Kyoto University, October 1995.
[Remy89]
Didier Rémy. Typechecking records and variants in a natural extension of ML. In Proc. ACM Symposium on Principles of Programming Languages, pages 77-87, 1989.
[Rouaix95]
François Rouaix. The CamlTk Interface. INRIA, Rocquencourt, France, July 1995. Available at URL http://pauillac.inria.fr/camltk.