Error Handling
In OCaml, errors can be handled in several ways. This document presents most of the available means. However, handling errors using the effect handlers introduced in OCaml 5 hasn't been addressed yet. This topic is also addressed in the Error Handling chapter of the Real World OCaml book by Yaron Minsky and Anil Madhavapeddy (see references).
Errors as Special Values
Don't do that.
Some languages, most emblematically C, treat certain values as errors. For
instance, in Unix systems, here what is contained in man 2 read
:
read - read from a file descriptor
#include <unistd.h>
ssize_t read(int fd, void *buf, size_t count);
[...]
On error, -1 is returned, and
errno
is set to indicate the error.
Great software was written using this style. However, as expected return values can't be distinguished from values representing errors, nothing but the programmer's discipline ensures errors aren't ignored. This has been the cause of many bugs, some with dire consequences. This is not the proper way to deal with errors in OCaml.
There are three major ways to make it impossible to ignore errors in OCaml:
- Exceptions
option
valuesresult
values
Use them. Do not encode errors inside data.
Exceptions provide a means to deal with errors at the control flow level, while
option
and result
make errors distinct from normal return values.
The rest of this document presents and compares approaches towards error handling.
Exceptions
Historically, the first way of handling errors in OCaml is exceptions. The standard library relies heavily upon them.
The biggest issue with exceptions is that they do not appear in types. One has
to read the documentation to see that, indeed, List.find
or String.sub
are
functions that might fail by raising an exception.
However, exceptions have the great merit of being compiled into efficient machine code. When implementing trial and error approaches likely to back-track often, exceptions can be used to achieve good performance.
Exceptions belong to the type exn
, which is an extensible sum
type.
# exception Foo of string;;
exception Foo of string
# let i_will_fail () = raise (Foo "Oh no!");;
val i_will_fail : unit -> 'a = <fun>
# i_will_fail ();;
Exception: Foo "Oh no!".
Here, we add a variant Foo
to the type exn
and create a function that will
raise this exception. Now, how do we handle exceptions? The construct is try ... with ...
:
# try i_will_fail () with Foo _ -> ();;
- : unit = ()
Predefined Exceptions
The standard library predefines several exceptions, see
Stdlib
. Here are a few examples:
# 1 / 0;;
Exception: Division_by_zero.
# List.find (fun x -> x mod 2 = 0) [1; 3; 5];;
Exception: Not_found.
# String.sub "Hello world!" 3 (-2);;
Exception: Invalid_argument "String.sub / Bytes.sub".
# let rec loop x = x :: loop x;;
val loop : 'a -> 'a list = <fun>
# loop 42;;
Stack overflow during evaluation (looping recursion?).
Although the last one doesn't look as an exception, it actually is.
# try loop 42 with Stack_overflow -> [];;
- : int list = []
Among the predefined exceptions of the standard library, the following ones are intended to be raised by user-written functions:
Exit
can be used to terminate an iteration, like abreak
statementNot_found
should be raised when searching failed because there isn't anything satisfactory to be foundInvalid_argument
should be raised when a parameter can't be acceptedFailure
should be raised when a result can't be produced
Functions are provided by the standard library to raise Invalid_argument
and
Failure
using a string parameter:
val invalid_arg : string -> 'a
(** @raise Invalid_argument *)
val failwith : string -> 'a
(** @raise Failure *)
When implementing a software component which exposes functions raising exceptions, a design decision must be made:
- Use the preexisting exceptions
- Raise custom exceptions
Both can make sense, and there isn't a general rule. If the standard library exceptions are used, they must be raised under their intended conditions, otherwise handlers will have trouble processing them. Using custom exceptions will force client code to include dedicated catch conditions. This can be desirable for errors that must be handled at the client level.
Fun.protect
Using Because handling exceptions interrupts normal control flow, using them can
complicate some tasks requiring strictly ordered and coupled processes. For
these scenarios, the Fun
module of the standard library provides:
val protect : finally:(unit -> unit) -> (unit -> 'a) -> 'a
This function is meant to be used when something always needs to be done
after a computation is complete, whether it succeeds or fails. The unlabeled
function argument is called first, then the function passed as the
labeled argument finally
is called. protect
then returns the
same value as the unlabeled argument or raises the same exception that
function raised.
Note that functions passed to protect
take only ()
as a parameter. This
does not limit the cases where protect
can be used. Any computation f x
can
be wrapped in a function fun () -> f x
. As always, the body of the function
won't be evaluated until the function is called.
The finally
function is only expected to perform some side-effect, and should
not raise any exception itself. If finally
does throw an exception e
,
protect
will raise Finally_raised e
, wrapped to make it clear that the
exception is not coming from the protected function.
Let's demonstrate with a function that tries reading the first n
lines of a
text file (like the Unix command head
). If the file has fewer than n
lines,
the function must throw End_of_file
. In any case, the file descriptor must be
closed afterwards. Here is a possible implementation using Fun.protect
:
# let head_channel chan =
let rec loop acc n = match input_line chan with
| line when n > 0 -> loop (line :: acc) (n - 1)
| _ -> List.rev acc in
loop [];;
val head_channel : in_channel -> int -> string list = <fun>
# let head_file filename n =
let ic = open_in filename in
let finally () = close_in ic in
let work () = head_channel ic n in
Fun.protect ~finally work;;
val head_file : string -> int -> string list = <fun>
When head_file
is called, it opens a file descriptor, defines finally
and
work
, then Fun.protect ~finally work
performs two computations in order:
work ()
and then finally ()
, and has the same result as work ()
, either
returning a value or raising an exception. Either way, the file descriptor is
closed after use.
Asynchronous Exceptions
Some exceptions don't arise because something attempted by the program failed, but rather because an external factor is impeding its execution. Those exceptions are called asynchronous. These include:
Out_of_memory
Stack_overflow
Sys.Break
The latter is thrown when the user interrupts an interactive execution. Because they are loosely or not at all related with the program logic, it mostly doesn't make sense to track the place where an asynchronous exceptions was thrown, as it could be anywhere. Deciding if an application needs to catch those exceptions and how it should be done is beyond the scope of this tutorial. Interested readers may refer to Guillaume Munch-Maccagnoni's A Guide to recover from interrupts.
Documentation
Functions that can raise exceptions should be documented like this:
val foo : a -> b
(** [foo] does this and that, here is how it works, etc.
@raise Invalid_argument if [a] doesn't satisfy ...
@raise Sys_error if filesystem is not happy
*)
Stack Traces
To get a stack trace when an unhandled exception makes your program crash, you
need to compile the program in debug mode (with -g
when calling ocamlc
, or
-tag 'debug'
when calling ocamlbuild
). Then:
OCAMLRUNPARAM=b ./myprogram [args]
And you will get a stack trace. Alternatively, you can call, from within the program,
let () = Printexc.record_backtrace true
Printing
To print an exception, the module Printexc
comes in handy. For instance, the
function notify_user : (unit -> 'a) -> 'a
below calls a function, and if it
fails, prints the exception on stderr
. If stack traces are enabled, this
function will also display it.
let notify_user f =
try f () with e ->
let msg = Printexc.to_string e
and stack = Printexc.get_backtrace () in
Printf.eprintf "there was an error: %s%s\n" msg stack;
raise e
OCaml knows how to print its built-in exceptions, but you can also tell it how to print your own exceptions:
exception Foo of int
let () =
Printexc.register_printer
(function
| Foo i -> Some (Printf.sprintf "Foo(%d)" i)
| _ -> None (* for other exceptions *)
)
Each printer should take care of the exceptions it knows about, returning Some <printed exception>
, and return None
otherwise (let the other printers do the
job).
Runtime Crashes
Although OCaml is a very safe language, it is possible to trigger unrecoverable errors at runtime.
Exceptions Not Raised
The compiler and runtime makes a best effort for raising meaningful exceptions.
However, some error conditions may remain undetected, which can result in a
segmentation fault. This is especially the case for Out_of_memory
, which
is not reliable. It used to be the case for Stack_overflow
:
But catching stack overflows is tricky, both in Unix-like systems and under Windows, so the current implementation in OCaml is a best effort that is occasionally buggy.
This has improved since. Only linked C code should be able to trigger an undetected stack overflow.
Inherently Unsafe Functions
Some OCaml functions are inherently unsafe. Use them with care, not like this:
> echo "fst Marshal.(from_string (to_string 0 []) 0)" | ocaml -stdin
Segmentation fault ()
Language Bugs
When a crash isn't coming from:
- A limitation of the native code compiler
- An inherently unsafe function such as are found in modules
Marshal
andObj
it may be a language bug. It happens. Here is what to do when this is suspected:
- Make sure the crash affects both compilers: bytecode and native
- Write a self-contained and minimal proof-of-concept code which does nothing but triggering the crash
- File an issue in the OCaml Bug Tracker in GitHub
Here is an example of such a bug: https://github.com/ocaml/ocaml/issues/7241
Safe vs. Unsafe Functions
Uncaught exceptions cause runtime crashes. Therefore, there is a tendency to use the following terminology:
- Function raising exceptions: Unsafe
- Function handling errors in data: Safe
The main ways to write such safe error-handling functions are to use either
option
(next section) or result
(following section) values.
Although handling errors in data using those types may avoid the issues of error
values and exceptions, it requires extracting the enclosed value at every step,
which may lead to boilerplate code and comes with a runtime cost.
option
Type for Errors
Using the The option
module provides the first alternative to exceptions. The 'a option
data type represents either data of type 'a
- for instance, Some 42
is of type int option
- or the absence of data due to any error as None
.
Using option
it is possible to write functions that return None
instead of
throwing an exception. Here are two examples of such functions:
# let div_opt m n =
try Some (m / n) with
Division_by_zero -> None;;
val div_opt : int -> int -> int option = <fun>
# let find_opt p l =
try Some (List.find p l) with
Not_found -> None;;
val find_opt : ('a -> bool) -> 'a list -> 'a option = <fun>
We can try those functions:
# 1 / 0;;
Exception: Division_by_zero.
# div_opt 42 2;;
- : int option = Some 21
# div_opt 42 0;;
- : int option = None
# List.find (fun x -> x mod 2 = 0) [1; 3; 5];;
Exception: Not_found.
# find_opt (fun x -> x mod 2 = 0) [1; 3; 4; 5];;
- : int option = Some 4
# find_opt (fun x -> x mod 2 = 0) [1; 3; 5];;
- : int option = None
It tends to be considered good practice nowadays when a function can fail in
cases that are not bugs (i.e., not assert false
, but network failures, keys
not present, etc.) to return type such as 'a option
or ('a, 'b) result
(see
next section) rather than throwing an exception.
Naming Conventions
There are two conventions for naming pairs of functions with the same basic
behavior where one may raise an exception and the other returns an option. In
the above examples, the convention of the standard library is used: adding an
_opt
suffix to the name of the version of the function that returns an option
instead of raising an exception.
val find: ('a -> bool) -> 'a list -> 'a
(** @raise Not_found *)
val find_opt: ('a -> bool) -> 'a list -> 'a option
This is extracted from the List
module of the standard library.
However, some projects tend to avoid or reduce the usage of exceptions. In such
a context, the opposite convention is relatively common: the version of the
function that raises exceptions is suffixed with _exn
. Using the same
functions, that would give the specification:
val find_exn: ('a -> bool) -> 'a list -> 'a
(** @raise Not_found *)
val find: ('a -> bool) -> 'a list -> 'a option
Composing Functions Returning Options
The function div_opt
can't raise exceptions. However, since it doesn't return
a result of type int
, it can't be used in place of an int
. The same way
OCaml doesn't
promote integers
into floats, it doesn't automatically convert int option
into int
or vice
versa.
# 21 + Some 21;;
Error: This expression has type 'a option
but an expression was expected of type int
In order to combine option values with other values, conversion functions are
needed. Here are the functions provided by the option
module to extract the
data contained in an option:
val get : 'a t -> 'a
val value : 'a t -> default:'a -> 'a
val fold : none:'a -> some:('b -> 'a) -> 'b t -> 'a
get
returns the contents, or raises Invalid_argument
if applied to None
.
value
returns the contents, or its default
argument if applied to None
.
fold
returns its some
argument applied to the contents of the option, or its
none
argument if applied to None
.
As a remark, observe that value
can be implemented using fold
:
# let value ~default = Option.fold ~none:default ~some:Fun.id;;
val value : default:'a -> 'a option -> 'a = <fun>
# Option.value ~default:() None = value ~default:() None;;
- : bool = true
# Option.value ~default:() (Some ()) = value ~default:() (Some ());;
- : bool = true
It is also possible to perform pattern matching on option values:
match opt with
| None -> ... (* Something *)
| Some x -> ... (* Something else *)
However, sequencing such expressions leads to deep nesting which is often considered bad:
if you need more than 3 levels of indentation, you're screwed anyway, and should fix your program.
The recommended way to avoid that is to refrain from or delay attempting to access the content of an option value, as explained in the next sub section.
Option.map
and Option.bind
Using on Let's start with an example: imagine one needs to write a function returning
the hostname part of an email address
provided as a string. For instance, given the string
"gaston.lagaffe@courrier.dupuis.be"
it would return the string "courrier"
(one may have a point arguing against such a design, but this is only an
example).
Here is a questionable but straightforward implementation using exceptions:
# let host email =
let fqdn_pos = String.index email '@' + 1 in
let fqdn_len = String.length email - fqdn_pos in
let fqdn = String.sub email fqdn_pos fqdn_len in
try
let host_len = String.index fqdn '.' in
String.sub fqdn 0 host_len
with Not_found ->
if fqdn <> "" then fqdn else raise Not_found;;
val host : string -> string = <fun>
This may fail by raising Not_found
if the first the call to String.index
does, which could happen if there is no @
character in the input string,
signifying that it's not an email address. However, if the second call to
String.index
fails, meaning no dot character was found, we may return the
whole fully qualified domain name (FQDN) as a fallback, but only if it isn't
the empty string.
Note that generally String.sub
may throw Invalid_argument
. Fortunately, this
can't happen when calculating fqdn
. In the worst case, the @
character is
the last one, when fqdn_pos
is off range by one but fqdn_len
is null, and
that combination of parameters gives an empty string rather than an exception.
Below is the equivalent function using the same logic, but using option
instead of exceptions:
# let host_opt email =
match String.index_opt email '@' with
| Some at_pos -> begin
let fqdn_pos = at_pos + 1 in
let fqdn_len = String.length email - fqdn_pos in
let fqdn = String.sub email fqdn_pos fqdn_len in
match String.index_opt fqdn '.' with
| Some host_len -> Some (String.sub fqdn 0 host_len)
| None -> if fqdn <> "" then Some fqdn else None
end
| None -> None;;
val host_opt : string -> string option = <fun>
Although it qualifies as safe, its legibility isn't improved. Some may even claim it is worse.
Before showing how to improve this code, we need to explain how Option.map
and
Option.bind
work. Here are their types:
val map : ('a -> 'b) -> 'a option -> 'b option
val bind : 'a option -> ('a -> 'b option) -> 'b option
Option.map
applies a function f
to an option parameter, if it isn't None
let map f = function
| Some x -> Some (f x)
| None -> None
If f
can be applied to something, its result is rewrapped into a fresh option.
If there isn't anything to supply to f
, None
is forwarded.
If we don't take arguments order into account, Option.bind
is almost exactly
the same, except we assume f
returns an option. Therefore, there is no need to
rewrap its result, since it's already an option value:
let bind opt f = match opt with
| Some x -> f x
| None -> None
bind
having flipped parameter order with respect to map
allows its use as a
binding operator, which is a popular extension of
OCaml providing means to create “custom let
”. Here is how it goes:
# let ( let* ) = Option.bind;;
val ( let* ) : 'a option -> ('a -> 'b option) -> 'b option = <fun>
Using these mechanisms, here is a possible way to rewrite host_opt
:
# let host_opt email =
let* fqdn_pos = Option.map (( + ) 1) (String.index_opt email '@') in
let fqdn_len = String.length email - fqdn_pos in
let fqdn = String.sub email fqdn_pos fqdn_len in
String.index_opt fqdn '.'
|> Option.map (fun host_len -> String.sub fqdn 0 host_len)
|> function None when fqdn <> "" -> Some fqdn | opt -> opt;;
val host_opt : string -> string option = <fun>
This version was picked to illustrate how to use and combine operations on options allowing users to achieve some balance between understandability and robustness. A couple of observations:
- As in the original
host
function (with exceptions):- The calls to
String
functions (index_opt
,length
, andsub
) are the same and in the same order - The same local names are used with the same types
- The calls to
- There isn't any remaining indentation or pattern-matching
- Line 1:
- right-hand side of
=
:Option.map
allows adding 1 to the result ofString.index_opt
, if it didn't fail - left-hand side of
=
: thelet*
syntax turns all the rest of the code (from line 2 to the end) into the body of an anonymous function which takesfqdn_pos
as parameter, and the function( let* )
is called withfqdn_pos
and that anonymous function.
- right-hand side of
- Lines 2 and 3: same as in the original
- Line 4:
try
ormatch
is removed - Line 5:
String.sub
is applied, if the previous step didn't fail, otherwise the error is forwarded - Line 6: if nothing was found earlier, and if isn't empty,
fqdn
is returned as a fallback
When used to handling errors with catch statements, it requires some time to get
used the latter style. The key idea is avoiding or deferring looking directly
into option values. Instead, pass them along using ad hoc pipes (such as map
and bind
). Erik Meijer calls that style “following the happy path.” Visually,
it also resembles the “early return“ pattern often found in C.
One of the limitations of the option type is that it doesn't record the reason that
prevented having a return value. None
is silent, it doesn't say anything about
what went wrong. For this reason, functions returning option values should
document the circumstances under which they may return None
. Such
documentation is likely to resemble that required for exceptions using @raise
.
The result
type, described in the next section, is intended to fill this
gap: manage errors in data like option values and provide information on
errors like exceptions.
result
Type for Errors
Using the The result
module of the standard library defines the following type:
type ('a, 'b) result =
| Ok of 'a
| Error of 'b
A value Ok x
means that the computation succeeded and produced x
, a
value Error e
means that it failed, and e
represents whatever error
information has been collected in the process. Pattern matching can be used to
deal with both cases, as with any other sum type. However using map
and bind
can be more convenient, maybe even more than it was with option
.
Before taking a look at Result.map
, let's think about List.map
and
Option.map
under a changed perspective. Both functions behave as identity when
applied to []
or None
, respectively. That's the only possibility since those
parameters don't carry any data - unlike result
with its Error
constructor. Nevertheless, Result.map
is implemented similarly: on Error
, it
also behaves like identity.
Here is its type:
val map : ('a -> 'b) -> ('a, 'c) result -> ('b, 'c) result
And here is how it is written:
let map f = function
| Ok x -> Ok (f x)
| Error e -> Error e
The result
module has two map functions: the one we've just seen and another
one, with the same logic, applied to Error
Here is its type:
val map_error : ('c -> 'd) -> ('a, 'c) result -> ('a, 'd) result
And here is how it is written:
let map_error f = function
| Ok x -> Ok x
| Error e -> f e
The same reasoning applies to Result.bind
, except there's no bind_error
.
Using those functions, here is an hypothetical example of code using Anil
Madhavapeddy's OCaml YAML library:
let file_opt = File.read_opt path in
let file_res = Option.to_result ~none:(`Msg "File not found") file_opt in begin
let* yaml = Yaml.of_string file_res in
let* found_opt = Yaml.Util.find key yaml in
let* found = Option.to_result ~none:(`Msg (key ^ ", key not found")) found_opt in
found
end |> Result.map_error (Printf.sprintf "%s, error: %s: " path)
Here are the types of the involved functions:
val File.read_opt : string -> string option
val Yaml.of_string : string -> (Yaml.value, [`Msg of string]) result
val Yaml.Util.find : string -> Yaml.value -> (Yaml.value option, [`Msg of string]) result
val Option.to_result : none:'e -> 'a option -> ('a, 'e) result
File.read_opt
is supposed to open a file, read its contents and return it as a string wrapped in an option, if anything goes wrongNone
is returned.Yaml.of_string
parses a string and turns it into an ad hoc OCaml typeYaml.find
recursively searches for a key in a Yaml tree. If found, it returns the corresponding data, wrapped in an optionOption.to_result
performs conversion of anoption
into aresult
.- Finally,
let*
stands forResult.bind
.
Since both functions from the Yaml
module return result
data, it is
easier to write a pipe which processes that type all along. That's why
Option.to_result
needs to be used. Stages which produce result
must be
chained using bind
; stages which do not must be chained using some map
function to wrap their values back into a result
.
The map functions of the result
module allows processing of data or errors,
but the routines used must not fail, as Result.map
will never turn an Ok
into an Error
and Result.map_error
will never turn an Error
into an Ok
.
On the other hand, functions passed to Result.bind
are allowed to fail. As
stated before there isn't a Result.bind_error
. One way to make sense out of
that absence is to consider its type, it would have to be:
val Result.bind_error : ('a, 'e) result -> ('e -> ('a, 'f) result) -> ('a, 'f) result
We would have:
Result.map_error f (Ok x) = Ok x
- And either:
Result.map_error f (Error e) = Ok y
Result.map_error f (Error e) = Error e'
This means an error would be turned back into valid data or changed into another error. This is almost like recovering from an error. However, when recovery fails, it may be preferable to preserve the initial cause of failure. That behaviour can be achieved by defining the following function:
# let recover f = Result.(fold ~ok:ok ~error:(fun (e : 'e) -> Option.to_result ~none:e (f e)));;
val recover : ('e -> 'a option) -> ('a, 'e) result -> ('a, 'e) result = <fun>
Although any kind of data can be wrapped as a result
Error
, it is
recommended to use that constructor to carry actual errors, for instance:
exn
, in which case the result type just makes exceptions explicitstring
, where the error case is a message that indicates what failedstring Lazy.t
, a more elaborate form of error message that is only evaluated if printing is required- some polymorphic variant, with one case per possible error. This is very accurate (each error can be dealt with explicitly and occurs in the type), but the use of polymorphic variants sometimes make the code harder to read.
Note that some say the types result
and Either.t
are
isomorphic. Concretely, it means
it's always possible to replace one by the other, like in a completely neutral
refactoring. Values of type result
and Either.t
can be translated back and
forth, and appling both translations one after the other, in any order, returns
to the starting value. Nevertheless, this doesn't mean result
should be used
in place of Either.t
, or vice versa. Naming things matters, as punned by Phil
Karlton's famous quote:
There are only two hard things in Computer Science: cache invalidation and naming things.
Handling errors necessarily complicates code, making it harder to read and understand than simple code that behaves incorrectly or fails under exceptional conditions. The right tools, data, and functions can help you ensure correct behavior with minimal loss of clarity. Use them.
bind
as a Binary Operator
When Option.bind
or Result.bind
are used, they are often aliased into a
custom binding operator, such as let*
. However, it is also possible to use it
as a binary operator, which is very often writen >>=
. Using bind
this way
must be detailed because it is extremely popular in other functional programming
languages, especially in Haskell.
Assuming a
and b
are valid OCaml expressions, the following three pieces of
source code are functionally identical:
bind a (fun x -> b)
let* x = a in b
a >>= fun x -> b
It may seem pointless. To make sense, one must look at expressions where several
calls to bind
are chained. The following three are also equivalent:
bind a (fun x -> bind b (fun y -> c))
let* x = a in
let* y = b in
c
a >>= fun x -> b >>= fun y -> c
Variables x
and y
may appear in c
in the three cases. The first form isn't
very convenient, as it uses a lot of parentheses. The second one is often
preferred due to its resemblance with regular local definitions. The third
one is harder to read, as >>=
associates to the right in order to avoid
parentheses in that precise case, but it's easy to get lost. Nevertheless, it
has some appeal when named functions are used. It looks a bit like good old Unix
pipes:
a >>= f >>= g
looks better than:
let* x = a in
let* y = f x in
g y
Writing x >>= f
is very close to what is found in functionally tainted
programming languages which have methods and receivers such as Kotlin, Scala,
Go, Rust, Swift, or even modern Java, where it would look like:
x.bind(f)
.
Here is the same code as presented at the end of the previous section, rewritten
using Result.bind
as a binary opeator:
File.read_opt path
|> Option.to_result ~none:(`Msg "File not found")
>>= Yaml.of_string
>>= Yaml.Util.find key
>>= Option.to_result ~none:(`Msg (key ^ ", key not found"))
|> Result.map_error (Printf.sprintf "%s, error: %s: " path)
By the way, this style is called tacit
programming. Thanks to the
associativity priorities of the >>=
and |>
operators, no parenthesised
expression extends beyond a single line.
OCaml has a strict typing discipline, not a strict styling discipline; therefore, picking the right style is left to the author's decision. That applies error handling, so pick a style knowingly. See the OCaml Programming Guidelines for more details on those matters.
Conversions Between Errors
option
or result
Throwing Exceptions From This is done by using the following functions:
-
From
option
toInvalid_argument
exception, use functionOption.get
:val get : 'a option -> 'a
-
From
result
toInvalid_argument
exception, use functionsResult.get_ok
andResult.get_error
:val get_ok : ('a, 'e) result -> 'a val get_error : ('a, 'e) result -> 'e
To raise other exceptions, pattern matching and raise
must be used.
option
and result
Conversion Between This is done by using the following functions:
- From
option
toresult
, use functionOption.to_result
:val to_result : none:'e -> 'a option -> ('a, 'e) result
- From
result
tooption
, use functionResult.to_option
:val to_option : ('a, 'e) result -> 'a option
option
or result
Turning Exceptions into The standard library does not provide such functions. This must be done using
try ... with
or match ... exception
statements. For instance, here is
how to create a version of Stdlib.input_line
which returns an option
instead of throwing an exception:
let input_line_opt ic = try Some (input_line ic) with End_of_file -> None
It would be same for result
, except some data must be provided to the
Error
constructor.
Some may like to turn this into a higher-order generic function:
# let catch f x = try Some (f x) with _ -> None;;
val catch : ('a -> 'b) -> 'a -> 'b option = <fun>
Assertions
The built-in assert
instruction takes an expression as an argument and throws
the Assert_failure
exception if the provided expression evaluates to false
.
Assuming that you don't catch this exception (it's probably unwise to catch this
exception, particularly for beginners), this causes the program to stop and
print the source file and line number where the error occurred. An
example:
# assert (Sys.os_type = "Win32");;
Exception: Assert_failure ("//toplevel//", 1, 0).
Running this on Win32, of course, won't throw an error.
Writing assert false
would just stop your program. This idiom is sometimes
used to indicate dead code, parts of
the program that must be written (often for type checking or pattern matching
completeness) but are unreachable at run time.
Asserts should be understood as executable comments. They aren't supposed to fail, unless during debugging or truly extraordinary circumstances that absolutely prevent the execution from making any kind of progress.
When the execution reaches conditions which can't be handled, the right thing to
do is to throw a Failure
, by calling failwith "error message"
. Assertions aren't
meant to handle those cases. For instance, in the following code:
match Sys.os_type with
| "Unix" | "Cygwin" -> (* code omitted *)
| "Win32" -> (* code omitted *)
| "MacOS" -> (* code omitted *)
| _ -> failwith "this system is not supported"
It is right to use failwith
, other operating systems aren't supported, but
they are possible. Here is the dual example:
function x when true -> () | _ -> assert false
Here, it wouldn't be correct to use failwith
because it requires a corrupted
system or the compiler to be bugged for the second code path to be executed.
Breakage of the language semantics qualifies as extraordinary circumstances. It
is catastrophic!
Concluding Remarks
Properly handling errors is a complex matter. It is cross-cutting concern, touches all parts of an application, and can't be isolated in a dedicated module. In contrast to several other mainstream languages, OCaml provides several mechanisms to handle exceptional events, all with good runtime performance and code understandability. Using them properly requires some initial learning and practice. Later, it always requires some thinking, which is beneficial because proper error management shouldn't ever be overlooked. No error handling mechanism is always better than the others, and choosing one to use should be a matter of fitting the context rather than that of taste. But opinionated OCaml code is also fine, so it's a balance.
External Resources
- “Exceptions” in ”The OCaml Manual, The Core Language”, chapter 1, section 6, December 2022
- Module
option
in OCaml Library - Module
result
in Ocaml Library - “Error Handling” in “Real World OCaml”, part 7, Yaron Minsky and Anil Madhavapeddy, 2ⁿᵈ edition, Cambridge University Press, October 2022
- “Add "finally" function to Pervasives”, Marcello Seri, GitHub PR, ocaml/ocaml/pull/1855
- “A guide to recover from interrupts”, Guillaume Munch-Maccagnoni, parf the
memprof-limits
documentation
Help Improve Our Documentation
All OCaml docs are open source. See something that's wrong or unclear? Submit a pull request.