Previous Contents Next
Chapter 7 Language extensions

This chapter describes the language features that are implemented in Objective Caml, but not described in the Objective Caml reference manual. In contrast with the fairly stable kernel language that is described in the reference manual, the extensions presented here are still experimental, and may be removed or changed in the future.

7.1 Streams and stream parsers

Objective Caml comprises a library type for streams (possibly infinite sequences of elements, that are evaluated on demand), and associated stream expressions, to build streams, and stream patterns, to destructure streams. Streams and stream patterns provide a natural approach to the writing of recursive-descent parsers.

Streams are presented by the following extensions to the syntactic classes of expressions:



expr ::= ...
  | [< >]
  | [< stream-component  { ; stream-component } >]
  | parser [pattern]  stream-matching
  | match expr with parser  [pattern]  stream-matching
stream-component ::= ' expr
  | expr
stream-matching ::= stream-pattern  [pattern] ->  expr  { | stream-pattern  [pattern] ->  expr }
stream-pattern ::= [< >]
  | [< stream-pat-comp  { ; stream-pat-comp  [ ?? expr ] }>]
stream-pat-comp ::= ' pattern  [ when expr ]
  | pattern =  expr
  | ident

Stream expressions are bracketed by [< and >]. They represent the concatenation of their components. The component ' expr represents the one-element stream whose element is the value of expr. The component expr represents a sub-stream. For instance, if both s and t are streams of integers, then [<'1; s; t; '2>] is a stream of integers containing the element 1, then the elements of s, then those of t, and finally 2. The empty stream is denoted by [< >].

Unlike any other kind of expressions in the language, stream expressions are submitted to lazy evaluation: the components are not evaluated when the stream is built, but only when they are accessed during stream matching. The components are evaluated once, the first time they are accessed; the following accesses reuse the value computed the first time.

Stream patterns, also bracketed by [< and >], describe initial segments of streams. In particular, the stream pattern [< >] matches all streams. Stream pattern components are matched against the corresponding elements of a stream. The component ' pattern matches the corresponding stream element against the pattern; if followed by when, the match is accepted only if the result of the guard expression is true. The component pattern =  expr applies the function denoted by expr to the current stream, then matches the result of the function against pattern. Finally, the component ident simply binds the identifier to the stream being matched.

Stream matching proceeds destructively: once a component has been matched, it is discarded from the stream (by in-place modification).

Stream matching proceeds in two steps: first, a pattern is selected by matching the stream against the first components of the stream patterns; then, the following components of the selected pattern are checked against the stream. If the following components do not match, the exception Stream.Error is raised. There is no backtracking here: stream matching commits to the pattern selected according to the first element. If none of the first components of the stream patterns match, the exception Stream.Failure is raised. The Stream.Failure exception causes the next alternative to be tried, if it occurs during the matching of the first element of a stream, before matching has committed to one pattern.

The streams hold the count of their elements discarded. The optional pattern before the first stream pattern is bound to the stream count before the matching. The one after each stream pattern (optional, too) is bound to the stream count after the matching.

The exception Stream.Error has a string parameter coming from the optional ?? expr after the stream pattern components (its default is the empty string). This expression is evaluated only in case of error.

See Functional programming using Caml Light for a more gentle introductions to streams, and for some examples of their use in writing parsers. A more formal presentation of streams, and a discussion of alternate semantics, can be found in Parsers in ML by Michel Mauny and Daniel de Rauglaudre, in the proceedings of the 1992 ACM conference on Lisp and Functional Programming.

7.2 Range patterns

In patterns, Objective Caml recognizes the form ' c ' .. '  d ' (two character literals separated by ..) as shorthand for the pattern
' c ' | '  c1 ' | '  c2 ' | ... | '  cn ' | '  d '
where c1, c2, ..., cn are the characters that occur between c and d in the ASCII character set. For instance, the pattern '0'..'9' matches all characters that are digits.

7.3 Assertion checking

Objective Caml supports the assert construct to check debugging assertions. The expression assert expr evaluates the expression expr and returns () if expr evaluates to true. Otherwise, the exception Assert_failure is raised with the source file name and the location of expr as arguments. Assertion checking can be turned off with the -noassert compiler option.

As a special case, assert false is reduced to raise (Assert_failure ...), which is polymorphic (and is not turned off by the -noassert option).

7.4 Deferred computations

The expression lazy expr returns a value v of type Lazy.t that encapsulates the computation of expr. The argument expr is not evaluated at this point in the program. Instead, its evaluation will be performed the first time Lazy.force is applied to the value v, returning the actual value of expr. Subsequent applications of Lazy.force to v do not evaluate expr again.

The expression lazy expr is equivalent to ref(Lazy.Delayed(fun () -> expr)). For more information, see the description of module Lazy in the standard library (section 19.14).

7.5 Record copy with update

The expression { expr with  lbl1 =  expr1 ; ... ;  lbln =  exprn } builds a fresh record with fields lbl1 ...  lbln equal to expr1 ...  exprn, and all other fields having the same value as in the record expr. In other terms, it returns a shallow copy of the record expr, except for the fields lbl1 ...  lbln, which are initialized to expr1 ...  exprn. For example:
        type point = { x : float; y : float; z : float }
        let proj p = { p with x = 0.0 }
        let proj p = { x = 0.0; y = p.y; z = p.z }
The two definitions of proj above are equivalent.

7.6 Local modules

The expression let module module-name =  module-expr in  expr locally binds the module expression module-expr to the identifier module-name during the evaluation of the expression expr. It then returns the value of expr. For example:
        let remove_duplicates comparison_fun string_list =
          let module StringSet =
            Set.Make(struct type t = string
                            let compare = comparison_fun end) in
          StringSet.elements
            (List.fold_right StringSet.add string_list StringSet.empty)

Previous Contents Next