Standard ML Programming/Printable version


Standard ML Programming

The current, editable version of this book is available in Wikibooks, the open-content textbooks collection, at
https://en.wikibooks.org/wiki/Standard_ML_Programming

Permission is granted to copy, distribute, and/or modify this document under the terms of the Creative Commons Attribution-ShareAlike 3.0 License.

Types

Standard ML has a particularly strong static type system. Unlike many languages, it does not have subtypes ("is-a" relationships) or implicit casts between types.

Static typing edit

Internally, all data in a computer is made up of bits (binary digits, either 0 or 1), which are grouped into bytes (minimally addressable groups of bits — eight bits in all modern machines), and usually in turn into words (groups of bytes that the CPU can treat as a single unit — nowadays usually either four bytes, i.e. 32 bits, or eight bytes, i.e. 64 bits).

However, it is fairly unusual that a program is intended to operate on bits, bytes, and words per se. Usually a program needs to operate on human-intelligible, abstract data-types: integers, say, or real numbers, or strings of characters — or all of these. Programs operate on bits and bytes mainly because these are how computers implement, or represent, these data-types. There are a variety of ways that programming languages address this discrepancy:

  • A language can provide no data-type abstractions, and require programmer code to deal explicitly in bits and bytes. It may provide operations intended for certain abstract data-types (such as addition of 32-bit integers), but leave it entirely up to program code to ensure that it only uses those operations on bytes representing those types. This approach is characteristic of assembly languages and, to some extent, C.
  • A language can provide exactly one data-type abstraction, used by all programmer code. This approach is characteristic of shell-scripting languages, which frequently operate almost exclusively on strings of characters.
  • A language can assign a type to each fragment of data (each value), and store that type assignment together with the value itself. When an operation is attempted on a value of an inappropriate data-type, the language either automatically converts it to the appropriate type (e.g., promoting an integer value to an equivalent value of a real-number type), or emits an error. This approach, where type information exists only at run-time, is called dynamic typing, and is characteristic of languages like Lisp, Python, Ruby and others.
  • A language can assign a type to each fragment of code (each expression). If a bit of code applies an operation to an expression of an inappropriate data-type, the compiler either infers additional code to perform the type conversion, or emits an error. This approach, where type information exists only at compile-time, is called static typing, and is characteristic of languages like Standard ML, OCaml, Haskell and others.

Most languages do not adhere strictly to one of the above approaches, but rather, use elements of more than one of them. The type system of Standard ML, however, uses static typing almost exclusively. This means that an ill-typed program will not even compile. (ML programmers consider this a good thing, as it allows many programming errors to be caught at compile-time that a dynamically-typed language would catch only at run-time.) To the extent that Standard ML does support dynamic typing, it is within the static-typing framework.

Strong typing edit

The term strong typing is used in a wide variety of different ways (see the Wikipedia article “Strongly typed programming language” for a fairly thorough listing); nonetheless, it is fair to say that the Standard ML type system provides strong typing by almost all definitions. Every expression in an SML program has a specific type at compile-time, and its type at run-time is never in contravention of this. All type conversions are explicit (using functions such as real, which accepts an integer and returns an equivalent real number), and take the form of meaningful translations rather than mere re-interpretations of raw bits.

Basic types edit

There are a number of basic types that may be thought of as "built in", firstly in that they're predefined by the Standard ML Basis library (so that Standard ML programs do not need to define them), and secondly in that the language provides literal notations for them, such as 34 (which is an integer), or "34" (which is a string of characters). Some of the most commonly used are:

  • int (integer), such as 3 or ~12. (Note that a tilde ~ is used for negative numbers.)
  • real (floating-point number), such as 4.2 or ~6.4.
    • Standard ML does not implicitly promote integers to floating-point numbers; therefore, an expression such as 2 + 5.67 is invalid. It must be written either as 2.0 + 5.67, or as real(2) + 5.67 (using the real function to convert 2 to 2.0).
  • string (string of characters), such as "this is a string" or "". (The latter is the empty string, which contains zero characters.)
  • char (one character), such as #"y" or #"\n". (The latter denotes the newline character, ASCII code 10.)
  • bool (Boolean value), which is either true or false.

The following code snippet declares two variables:

val n : int = 66
val x : real = ~23.0

After this snippet, n has type int and the value 66; x has type real and the value -23. Note that, unlike in some languages, these variable bindings are permanent; this n will always have the value 66 (though it's possible that other, unrelated variables, elsewhere in the program, will also have the name n, and those variables can have completely different types and values).

Type inference edit

In above examples, we provided explicit type annotations to inform the compiler of the type of a variable. However, such type annotations are optional, and are rarely necessary. In most cases, the compiler simply infers the correct type. Therefore, the following two code snippets are equivalent:

val s : string = "example"
val b : bool = true
val s = "example"
val b = true

In examples below, we occasionally provide type annotations as a form of documentation; this has the nice property that the documentation's correctness is enforced, in that compiler will report an error if any type annotations are incorrect. In other cases we may include ordinary comments, of the form (* this is a comment *); this is a more flexible form of documentation, in that it can include any sort of text (rather than just type information), but of course its accuracy cannot be enforced by the compiler.

Tuples edit

Types, including the above basic types, can be combined in a number of ways. One way is in a tuple, which is an ordered set of values; for example, the expression (1, 2) is of type int * int, and ("foo", false) is of type string * bool. There is also a 0-tuple, (), whose type is denoted unit. There are no 1-tuples, however; or rather, there is no distinction between (for example) (1) and 1, both having type int.

Tuples may be nested, and (unlike in some mathematical formalisms), (1,2,3) is distinct from both ((1,2),3) and (1,(2,3)). The first is of type int * int * int; the other two are of types (int * int) * int and int * (int * int), respectively.

expression type notes
() unit the 0-tuple
(3, "yes", "yes") int * string * string a 3-tuple (ordered triple)
(3, "yes", true) int * string * bool a 3-tuple (ordered triple)
((1, 2), 3) (int * int) * int a 2-tuple (ordered pair), whose first element is another 2-tuple

The following code snippet declares four variables. On the right side the environment after execution is shown. Notice the use of pattern matching to assign types and values to a and b and the use of projection in the assignment of also_a. This allows for a very convenient notation.

val pair = ("a", "b")
val (a, b) = pair
val also_a = #1 pair
identifier value type
pair ("a", "b") string * string
a "a" string
b "b" string
also_a "a" string

Records edit

Another way to combine values is in a record. A record is quite like a tuple, except that its components are named rather than ordered; for example, { a = 5.0, b = "five" } is of type { a : real, b : string } (which is the same as type { b : string, a : real }).

In fact, in Standard ML, tuples are simply a special case of records; for example, the type int * string * bool is the same as the type { 1 : int, 2 : string, 3 : bool }.

Functions edit

A function accepts a value and normally returns a value. For example, the factorial function we defined in the introduction:

fun factorial n =  if n < 1  then 1  else n * factorial (n - 1)

is of type int -> int, meaning that it accepts a value of type int and returns a value of type int.

Even if a function doesn't return a value at run-time — for example, if it raises an exception, or if it enters an infinite loop — it has a static return type at compile-time.

As with other types, we can provide explicit type annotations:

fun factorial (n : int) : int = if n < 1  then 1  else n * factorial (n - 1)

should we choose.

Tuples as arguments edit

Although a Standard ML function must accept exactly one value (rather than taking a list of arguments), tuples and the above-mentioned pattern matching make this no restriction at all. For example, this code snippet:

fun sum (a, b) = a + b
fun average pair = sum pair div 2

creates two functions of type int * int -> int. This approach may also be used to create infix operators. This code snippet:

infix averaged_with
fun a averaged_with b = average (a, b)
val five = 3 averaged_with 7

establishes averaged_with into an infix operator, then creates it as a function of type int * int -> int.

And since a tuple is an ordinary type, a function can also return one. In this code snippet:

fun pair (n : int) = (n, n)

pair is of type int -> int * int.

Polymorphic data type edit

In this code snippet:

fun pair x = (x, x)

the compiler has no way to infer a specific type for pair; it could be int -> int * int, real -> real * real, or even (int * real -> string) -> (int * real -> string) * (int * real -> string). Fortunately, it doesn't need to; it can simply assign it the polymorphic type 'a -> 'a * 'a, where 'a (pronounced "alpha") is a type variable, denoting any possible type. After the above definition, pair 3 and pair "x" are both well-defined, producing (3, 3) and ("x", "x") (respectively). A function can even depend on multiple type variables; in this snippet:

fun swap (x, y) = (y, x)

swap is of type 'a * 'b -> 'b * 'a. All or part of this can be indicated explicitly:

fun swap (x : 'a, y : 'b) : 'b * 'a = (y, x)

Functions as arguments, and curried functions edit

A function can accept another function as an argument. For example, consider this code snippet:

fun pair_map (f, (x, y)) = (f x, f y)

This creates a function pair_map of type ('a -> 'b) * ('a * 'a) -> ('b * 'b), which applies its first argument (a function) to each element of its second argument (a pair), and returns the pair of results.

Conversely, a function can return a function. Above, we saw one way to create a two-argument function: accept a 2-tuple. Another approach, called currying, is to accept just the first argument, then return a function that accepts the second:

fun sum i j = i + j
val add_three = sum 3
val five = add_three 2
val ten = sum 5 5

This creates a function sum of type int -> int -> int (meaning int -> (int -> int)), a function add_three of type int -> int that returns three plus its argument, and integers five and ten.

Type declarations edit

The type keyword may be used to create synonyms for existing data-types. For example, this code snippet:

type int_pair = int * int

creates the synonym int_pair for the data-type int * int. After that synonym has been created, a declaration like this one:

fun swap_int_pair ((i,j) : int_pair) = (j,i)

is exactly equivalent to one like this:

fun swap_int_pair (i : int, j : int) = (j,i)

As we shall see, this is mainly useful in modular programming, when creating a structure to match a given signature.

Datatype declarations edit

The datatype keyword may be used to declare new data-types. For example, this code snippet:

datatype int_or_string = INT of int | STRING of string | NEITHER

creates an entirely new data-type int_or_string, along with new constructors (a sort of special function or value) INT, STRING, and NEITHER; each value of this type is either an INT with an integer, or a STRING with a string, or a NEITHER. We can then write:

val i = INT 3
val s = STRING "qq"
val n = NEITHER
val INT j = i

where the last declaration uses the pattern-matching facility to bind j to the integer 3.

Conceptually, these types resemble the enumerations or unions of a language such as C++, but they are completely type-safe, in that the compiler will distinguish the int_or_string type from every other type, and in that a value's constructor will be available at run-time to distinguish between the type's different variants (the different arms/branches/alternatives).

These data-types can be recursive:

datatype int_list = EMPTY | INT_LIST of int * int_list

creates a new type int_list, where each value of this type is either EMPTY (the empty list), or the concatenation of an integer with another int_list.

These data-types, like functions, can be polymorphic:

datatype 'a pair = PAIR of 'a * 'a

creates a new family of types 'a pair, such as int pair, string pair, and so on.

Lists edit

One complex data-type provided by the Basis is the list. This is a recursive, polymorphic data-type, defined equivalently to this:

datatype 'a list = nil | :: of 'a * 'a list

where :: is an infix operator. So, for example, 3 :: 4 :: 5 :: nil is a list of three integers. Lists being one of the most common data-types in ML programs, the language also offers the special notation [3, 4, 5] for generating them.

The Basis also provides a number of functions for working with lists. One of these is length, which has type 'a list -> int, and which computes the length of a list. It may be defined like this:

fun length nil = 0
|   length (_::t) = 1 + length t

Another is rev, of type 'a list -> 'a list, which computes the reverse of a list — for example, it maps [ "a", "b", "c" ] to [ "c", "b", "a" ] — and may be defined like this:

local
  fun rev_helper (nil, ret) = ret
  |   rev_helper (h::t, ret) = rev_helper (t, h::ret)
in
  fun rev L = rev_helper (L, nil)
end

Exception declarations edit

The built-in type exn (exception) resembles the types created by datatype declarations: it has variants, each with its own constructor. However, unlike with those types, new variants, with new constructors, can be added to the type, using exception declarations. This code snippet:

exception StringException of string
val e = StringException "example"
val StringException s = e

creates a constructor StringException of type string -> exn, a variable e of type exn, and a variable s of type string (its value being "example").

The exn type is unique in this regard; a type created within a program cannot be "added to" in this way.

References edit

All of the above describe immutable forms of storage; for example, once a tuple is created, it cannot be changed (mutated). After this statement:

val x = (3, 4)

there is no way to change the value of x to be, say, (3, 5). (It is possible to create an entirely new x, that "shadows" the old one and has a completely different value — or even a completely different type — but that merely hides the old x, and won't affect any other values referring to it.)

The initial basis also provides mutable storage, in the form of references. In some ways, references behave as though they were defined like this:

datatype 'a ref = ref of 'a

For example, the following code snippet:

val reference : int ref = ref 12
val ref (twelve : int) = reference

binds the variable reference to a reference containing the value 12, and binds the variable twelve to the value 12.

However, the above snippet merely specifies the initial contents of the reference; the contents can be changed. This code snippet:

val () = reference := 13
val ref (thirteen : int) = reference

uses the built-in := function to modify the contents of reference. It then binds the new variable thirteen to the new value.

The Standard ML Basis Library defines a convenience function ! that retrieves the contents of a reference. It may be defined like this:

fun ! (ref x) = x

and is used like this:

val () = reference := 14
val fourteen = ! reference

Equality types edit

Above, the concept of polymorphic types was discussed, and we have seen examples such as 'a * 'b -> 'b * 'a and 'a list. In these examples, the type applies to all possible types 'a and 'b. There also exists a slightly more restrictive type of polymorphism, which is restricted to equality types, denoted ''a, ''b, and so on. This type of polymorphism is generated by the polymorphic equality operator, =, which determines if two values are equal, and which has the type ''a * ''a -> bool. This means that both of its operands must be of the same type, and this type must be an equality type^ .

Of the "basic types" discussed above — int, real, string, char, and bool — all are equality types except for real. This means that 3 = 3, "3" = "3", #"3" = #"3", and true = true are all valid expressions evaluating to true; that 3 = 4, "3" = "4", #"3" = #"4", and true = false are all valid expressions evaluating to false; and that 3.0 = 3.0 and 3.0 = 4.0 are invalid expressions that the compiler will reject. The reason for this is that IEEE floating point equality breaks some of the requirements for equality in ML. In particular, nan is not equal to itself, so the relation is not reflexive.

Tuple and record types are equality types if and only if each component type is an equality type; for example, int * string, { b : bool, c : char }, and unit are equality types, whereas int * real and { x : real } are not.

Function types are never equality types, since in the general case it is impossible to determine whether two functions are equivalent.

A type created by a datatype declaration is an equality type if every variant is either a null constructor (one without an argument) or a constructor with an equality-type argument, and (in the case of polymorphic types) every type argument is an equality type. For example, this code snippet:

datatype suit = HEARTS | CLUBS | DIAMONDS | SPADES
datatype int_pair = INT_PAIR of int * int
datatype real_pair = REAL_PAIR of real * real
datatype 'a option = NONE | SOME of 'a

creates the equality types suit (null constructors only), int_pair (only one constructor, and its argument is the equality type int * int), and int option (one null constructor, and one constructor with the equality-type argument int), not to mention char option and string option and so on. It also creates the non-equality types real_pair (a constructor with argument of non-equality type real * real), real option, (int -> int) option, and so on.

A recursive type is an equality type if possible, and not otherwise. For example, consider the above-mentioned polymorphic type 'a list:

datatype 'a list = nil | :: of 'a * 'a list

Certainly real list is not an equality type, both because its type argument is not an equality type, and because real * real list (the type of ::'s argument) cannot be an equality type. However, there is no reason that int list cannot be an equality type, and so it is one. Note that this equality typing is only within a type; something like (nil : int list) = (nil : char list) would be invalid, because the two expressions are of different types, even though they have the same value. However, nil = nil and (nil : int list) = nil are both valid (and both evaluate to true).

The mutable type 'a ref is an equality type even if its component type is not. This is because two references are said to be equal if they identify the same ref cell (i.e., the same pointer, generated by the same call to the ref constructor). Therefore, for example, (ref 1) = (ref 1) and (ref 1.0) = (ref 1.0) are both valid — and both evaluate to false, because even though both references happen to point to identical values, the references themselves are separate, and each one can be mutated independently of the other.

However, a code snippet such as this one:

datatype 'a myref = myref of 'a ref

does not generate an equality type real myref, because its type argument is not an equality type — even though its sole constructor accepts an argument of an equality-type. As noted above, polymorphic types created with datatype declarations can only be equality types if their type arguments are, and though the built-in references are exempt from this restriction, they cannot be used to circumvent it. If it is desired that myref types always be equality types, one must use this approach:

datatype ''a myref = myref of ''a ref

which forbids real myref entirely (since the equality-type variable ''a cannot represent the non-equality type real).


Expressions

Tokens edit

A Standard ML program consists of a sequence of "tokens"; these may be thought of as the "words" of the language. Some of the most common token types are:

token type examples
special constants 2 , ~5.6 , "string" , #"c"
alphanumeric identifiers x, mod, 'a
symbolic identifiers + , - , * , /
keywords val , = , ( , )

Arithmetic expressions edit

Arithmetic expressions are similar to those in many other languages:

3 + 4
3.0 / 4.0
(2 - 3) * 6

However, a few points bear note:

  • Unary negation is expressed using the tilde ~ rather than the hyphen -; the latter is used only for binary subtraction. For example, three minus negative-two is written 3 - ~2 or 3 - ~ 2.
  • Though the operators are "overloaded" to support multiple numeric types — for example, both 3 + 4 and 3.0 + 4.0 are valid (the former having type int, the latter type real) — there is no implicit promotion between types. Therefore, an expression such as 3 + 4.0 is not valid; one must write either 3.0 + 4.0, or real 3 + 4.0 (using the basis function real to convert 3 to 3.0).
  • Integer division is expressed using the special operator div rather than the solidus /; the latter is used only for real-number division. (And since there is no implicit promotion between types, an expression such as 3 / 4 is not valid; one must write either 3.0 / 4.0 or real 3 / real 4.) There is also a modulus operator mod; for example, seventeen divided by five is three-remainder-two, so 17 div 5 is 3 and 17 mod 5 is 2. (More generally, if q is a positive integer, then d = p div q and m = p mod q are integers such that p = d * q + m, m >= 0, and m < q. If q is a negative integer, then p = d * q + m, m <= 0, and m > q.)

Function calls edit

Once a function has been declared:

fun triple n = 3 * n

it is called simply by following the function-name with an argument:

val twelve = triple 4

In the general case, parentheses are not necessary, but they are frequently necessary for grouping. Also, as we saw in the chapter on types, tuples are constructed using parentheses, and it is not uncommon to construct a tuple as a function argument:

fun diff (a, b) = a - b
val six = diff (9, 3)

Function calls have very high precedence, higher than any infix operator; so, triple 4 div 5 means (3 * 4) div 5, which is 2, rather than 3 * (4 div 5), which is 0. Also, they are left-associative; f x y means (f x) y (where f takes x as its argument and returns a function that accepts y as its argument), not f (x y).

Infix function calls edit

A binary function — that is, a function whose parameter type is a 2-tuple type — can be turned into an infix operator:

fun minus (a, b) = a - b
val three = minus (5, 2)
infix minus
val seven = 4 minus ~3
val two = op minus (20, 18)

An infix operator can have any precedence level from 0 to 9, 0 (the default) being the lowest precedence, 9 being the highest. The Standard Basis provides these built-in infix specifications:

infix  7  * / div mod
infix  6  + - ^
infixr 5  :: @
infix  4  = <> > >= < <=
infix  3  := o
infix  0  before

Notice that in the third line, :: and @ are made infix using infixr rather than infix. This makes them right-associative rather than left-associative; whereas 3 - 4 - 5 means (3 - 4) - 5, 3 :: 4 :: nil means 3 :: (4 :: nil).

An identifier can actually be declared infix even before it refers to a specific function:

infix pow
fun x pow y = Math.pow (x, y)
val eight = 2.0 pow 3.0

Note that in this case, the infix notation is already used in declaring the function. Another way of doing this is by using op in the function declaration, which works regardless if the function has already been declared infix or not:

fun op pow (x, y) = Math.pow (x, y)

The preferred style is usually to not do this, but it can be useful if the declaration happens in a setting where it is not certain whether the function has been declared infix or not, or when use might be called on a file containing such a function declaration more than once, where the function is declared as infix after its definition. It can also be a way of signalling that the function might be declared as infix later on, possibly in another file, in which case it can be useful to ensure that the order of parsing the files does not matter.

Boolean and conditional expressions edit

Comparisons edit

As we saw in the chapter on types, the bool (boolean) type has two values, true and false. We also saw the built-in polymorphic equality operator =, of type ''a * ''a -> bool. Closely related is the inequality operator <>, also of type ''a * ''a -> bool, which returns true when = would return false, and vice versa.

The < (less than), > (greater than), <= (less than or equal to), and >= (greater than or equal to) operators are overloaded to be usable with a variety of numeric, character, and string types (but as with the arithmetic operators, both operands must have the same type).

Operations on booleans edit

Three main functions operate on boolean values:

  • The function not, of type bool -> bool, maps true to false and vice versa.
  • The infix operator andalso, of type bool * bool -> bool, maps (true, true) to true, and all other possibilities to false. This is know as a short circuit operator; if its first operand is false, then it will return false without evaluating its second operand.
  • The infix operator orelse, of type bool * bool -> bool, maps (false, false) to false, and all other possibilities to true. Like andalso it is a shortcutting operator, but in the opposite direction: if its first operand is true, then it will return true without even evaluating its second operand.

Conditional expressions edit

One major use of boolean values is in conditional expressions. An expression of this form:

if boolean_expression then expression_if_true else expression_if_false

evaluates to the result of expression_if_true if boolean_expression evaluates to true, and to the result of expression_if_false if boolean_expression evaluates to false. As with the shortcutting operators, the unneeded expression is not evaluated. This allows conditional expressions to be used in creating recursive functions:

fun factorial x = if x = 0 then 1 else x * (factorial (x - 1))

It also allows for conditional side effects:

if x = 0 then print "x = 0" else print "x <> 0"

Note that, since conditional expressions return a value, the "then" and "else" branches are both required to be present, and to have the same type, though they do not have to be particularly meaningful:

if x = 0 then print "x = 0" else ()

Case expressions and pattern-matching edit

Functions may be composed of one or more rules. A rule consists of its function-name, an argument pattern and its expression. When the function is called the argument values will be matched to the patterns in top down order. Functions using pattern-matching are very similar to case expressions. In fact you can transform any case construct into a function. For example this snippet

case compare(a,b) of
 GREATER => 1
 LESS => 2
 EQUAL => 3

is semantically equal to

fun case_example_function GREATER = 1
  | case_example_function LESS = 2
  | case_example_function EQUAL = 3;
case_example_function compare(a,b);

The first matching rule will get its expression evaluated and returned. That means if the patterns are overlapping (multiple patterns match a given argument value) one must keep in mind that only the first matching rule gets evaluated.

fun list_size (nil) = 0
 |  list_size (_::xs) = 1 + str_len xs;

The functions pattern is called exhaustive if there is a matching pattern for all legal argument values. The following example is non-exhaustive.

fun list_size ([a]) = 1
 |  list_size ([a,b]) = 2;

Any empty list or lists of size>2 will cause a Match-exception. To make it exhaustive one might add a few patterns.

fun list_size ([a]) = 1
 |  list_size ([a,b]) = 2
 |  list_size (nil) = 0
 |  list_size (_) = 0;

Lists of size>2 will return 0 which does not make a lot of sense but the functions pattern is now exhaustive.

Exceptions edit

Exceptions are used to abort evaluation. There are several built in exceptions that can be thrown using the raise keyword, and you can define your own using the exception keyword. Exceptions can have messages attached to them by writing of in the declaration and they are used much like datatype constructors. An exception can be caught using the handle keyword. Example:

exception Exc of string;
fun divide (_, 0) = raise Exc("Cannot divide by zero")
  | divide (num, den) = num div den
val zero_or_infinity = divide (0, 0)
  handle Exc msg => (print (msg ^ "\n"); 0)

This will print "Cannot divide by zero" and evaluate zero_or_infinity to 0 thanks to the handle clause.

Built in exceptions include Empty, Domain and Fail(msg).

Lambda expressions edit

A lambda expression is an expression that can be evaluated into a function without the function being bound to an identifier, a.k.a. an anonymous function, function constant or a function literal. Such a function can be defined in Standard ML using the fn keyword. This is particularly useful for higher order functions, i.e. functions that take other functions as arguments, such as the built in map and foldl functions. Instead of writing:

fun add_one x = x + 1
val incremented = map add_one [1, 2, 3]

You could simply write

val incremented = map (fn x => x + 1) [1, 2, 3]

Note that the => operator is used instead of =. The fn keyword can be used in place of fun, including pattern matching and even recursion (if the rec keyword is used):

val rec fact = fn 1 => 1 | n => if n > 1 then n * fact(n - 1) else raise Domain

Be aware that it is often considered better style to use the fun keyword.

Let expressions edit


Examples and Exercises

Values and Functions edit

  • Indicate the identifiers, keywords, and special constants in the following piece of code. What is the value of the second a?
 val a = 5
 val b = 9
 val a = 2*a+b;
  • Construct a tuple with 4 positions and 3 components.
  • What is the type of t?
 fun f a = 2
 val t = (true,f,f 1);
  • Write a function that returns the value 2 for the arguments 0, 1 and 2 and returns 3 for all other arguments.
  • Write a function that returns -1 for all negative and +1 for all positive arguments and 0 for the argument 0.
  • Create a function min(a:int,b:int) that returns the smaller one of its 2 arguments. Do the separation of the argument values in 3 different ways. Using a Cartesian argument-pattern, using a projection and using a local declaration.

(solutions to this chapter are here)

Recursion edit

  • Create a function power9(x) that calculates the 9th power of x. Preferably using as few multiplications as possible.
  • Calculate the greatest common denominator from 2 positive integer arguments.
  • Calculate mul(n,z)=n*z without using the * operator for   and  
  • Calculate power2(n) by only using addition and resursion. (hint: it is possible to rewrite the square function as a summation of natural numbers.)

(solutions to this chapter are here)


Solutions

Values and Functions edit

Problem: Indicate the identifiers, keywords, and special constants in the following piece of code. What is the value of the second a?

 val a = 5
 val b = 9
 val a = 2*a+b;

The identifiers are a, b, *, and +. The keywords are val, =, and ;. The special constants are 5, 9, and 2. The value of the second a is 19.

Problem: Construct a tuple with 4 positions and 3 components.

 (1,1,2,3)

is a simple one but this one is also valid

 (1,false,(3,2),1)

Problem: What is the type of t?

 fun f (a:int) = 2
 val t = (true,f,f 1);

Well the answer is

 bool * (int -> int) * int

Problem: Write a function that returns the value 2 for the arguments 0, 1 and 2 and returns 3 for all other arguments.

fun example(0) = 2
  | example(1) = 2
  | example(2) = 2
  | example(_) = 3;

or

fun example(x:int) = if (x>2) then 3 else if (x<0) then 3 else 2;

Problem: Write a function that returns -1 for all negative and +1 for all positive arguments and 0 for the argument 0.

fun example(x:int) = if (x=0) then 0 else if (x<0) then ~1 else 1;

One might try to use pattern matching like in the example above but "~" is an operator and thus can not be used in an argument pattern.

Problem: Create a function min(a:int,b:int) that returns the smaller one of its 2 arguments. Do the separation of the argument values in 3 different ways. Using a cartesian argument-pattern, using a projection and using a local declaration.

Using a cartesian argument-pattern

fun min(a,b) = if (a<b) then a else b;

Using a projection. Here we have to note the argument type as a 2-tuple of int*int. The value t will hold the whole tuple and thus for comparation it must be split up again.

fun min(t:int*int) = if (#1t < #2t) then #1t else #2t;

Using a local declaration.

fun min(t:int*int) = let val (a,b)=t in if (a<b) then a else b end;

Recursion edit

Problem: Create a function power9(x) that calculates the 9th power of x. Preferably using as few multiplications as possible.

The straight forward way to do this is could be:

fun power9(x) = x*x*x*x*x*x*x*x*x;

But thats no clever way and it also uses lots of multiplication. We could use local declarations inside the function to shorten the code and make it more readable.

 fun power9(x) = 
 let
   val a=x*x 
   val b=a*a 
 in 
   b*b*x 
 end;

or we could use helper-functions to calculate the partial products.

fun power2(x) = x*x;
fun power4(x) = power2(x)*power2(x);
fun power9(x) = power4(x)*power4(x)*x;

But that still isnt really smart. We would have to write lots of code for a function like power66(). The following code uses recursive function calls to calculate the n-th power of x.

fun power(x,n) = if (n=0) then 1 else power(x,n-1)*x;

which could be rewritten as

fun power(x,0) = 1
  | power(x,n) = power(x,n-1)*x;

Problem: Calculate the greatest common denominator from 2 positive integer arguments.

Using euclids algorithm we construct the recursive function

fun gcd(a,0) = a
  | gcd(a,b) = gcd(b,a-b*(a div b));

Problem: Calculate mul(n,z)=n*z without using the * operator for   and  

fun mul(n:int, z:int) = if (n=1) then z else z + mul(n-1,z);
fun h(a:int, n:int, z:int) = if (n=1) then z + a else h(a+z,n-1,z);
fun mul(n:int, z:int) = h(0,n,z);

Problem: Calculate power2(n) by only using addition and resursion. (hint: it is possible to rewrite the square function as a summation of natural numbers.)

The sum to be calculated is   which is the sum on the n first odd Elements of  . Or on other words  .

fun power2(1) = 1
  | power2(n) = n+n-1 + power2(n-1);