Module Relude_IO

Relude.IO contains a type t('a, 'e) and related functions for representing and controlling the execution of side effects.

What is IO?

Side effects are a normal part of building a useful program. Side effects cover everything from reading user input to making HTTP requests to drawing output on the screen. Really, a side effect is any change (in application state or in the universe) that can be observed outside of a function other than that function's returned value.

While side effects are important for building a program that actually does something, they are inherently impure. This is obviously at odds with writing pure code. IO seeks to restore this purity by describing these effects (and transformations on top of these effects) as data. Doing so allows us to be much more precise about when our effects actually run, and we can more easily reuse, reason about, and confidently refactor these descriptions of effects.

IO can represent any type of synchronous or asynchronous side effect that can either produce a value (in the success channel 'a) or an error (in the error channel 'e). The main purpose of IO is to make side-effectful code referentially transparent. When you construct an IO, in most cases you are just suspending the execution of a side effect, rather than allowing it to execute immediately.

In the case of a synchronous effect like a Js.log(...), which writes to the console, or getCurrentDate(), which reads the current clock time from the system, or Math.random(), which generates a random number out of the blue, it simply makes the action lazy, using a thunk like unit => effect.

In the case of asynchronous side effects, the execution of the effect is suspended until the IO is run using unsafeRunAsync. Because IO can represent both synchronous and asynchronous side effects, the end result of executing an IO must always be handled via a callback, as if the effect were async.

Why is running an IO considered unsafe?

An IO value represents a "description" or "recipe" of one or more side effects to perform. When you run an IO, all of the suspended effects are executed, and all of the side effects will occur. Naming the run function unsafeRunAsync is intended to warn you that invoking the function will execute your side effects.

Describing these functions as "unsafe" is a convention in the FP community for performing IO effects:

Relation to Js.Promise

If you are coming from the JavaScript world, don't be afraid of IO - in many ways, you can basically just think of it as a construct similar to Promise, with the following key differences:

Eager vs lazy

Promise is eagerly-executed and IO is lazily-executed. When you construct a Promise, its execution is immediately started, and it will invoke its success or failure callbacks whenever it finishes. IO is lazily-executed, so it will not do anything until you "run" the IO using unsafeRunAsync, which provides you with the resulting value or error using a callback from result('a, 'e) => unit.

As a result, functions that return a Promise are inherently impure (they've already started performing an effect), while functions that return IO are not (they've returned a data structure describing how an effect will be performed in the future).

Memoization

Promise memoizes its result value, and IO does not. This means that once a Promise is resolved or rejected, it will hold onto the resulting value or error, and any future uses of then or catch will produce that same value or error, rather than re-running the Promise and producing a new value or error.

IO doesn't have built-in memoization of the value, so re-running an IO will cause all the effects to be re-run, and a new value (or error) will be produced.

Error handling

A Promise can fail (be rejected) with any type of value, and in JavaScript, the only way to tell what type of error occurred is to inspect the error value and/or its type at runtime. For this reason, the BuckleScript bindings choose to represent a Promise error as an opaque type. Opaque types require runtime inspection or unsafe casting before they can be used.

IO.t('a, 'e) uses the 'e type parameter to let you express to the type system whatever type of error makes most sense for your needs. In some cases, you may not care about the details of the error and can choose to use an opaque type or unit. In other cases, you may wish to pass along custom errors that carry lots of extra information. Either way, the choice is yours, and that flexibility makes errors much easier to work with,

More about "effects"

The word "effect" is a bit overloaded in the functional programming world. We often hear about "side effects," and this term is typically referring to things like writing to stdout, making a network call, getting the system time, generating a random number - these are all things that either send information to the outside world, or pull information in from the outside world. They are called "side effects" because the function has an effect on the system beyond its input arguments and output return value - it does something that is not represented by the input and output types.

Another place in functional programming where the term "effect" appears is when we talk about data types like option('a) or result('a, 'e). These types of values are often called "effectful" values, because they represent some sort of additional "effect" that may have occurred. For example if you have a function a => b, assuming it's a pure function, the only possible value you can get out of the function is a value of type 'b - there's no way to represent a failure, an asynchronous computation, or a case where the function can't produce a value. If instead the function is 'a => option('b), the function can now either produce a value of type 'a, or fail to produce a value (None).

This behavior is often called the "effect" of producing a value with the possibility of not being able to produce a value. For 'a => result('b, 'e), we have the "effect" of either producing a value or an error. Js.Promise is another effectful value in that it has the "effect" of asynchronous computation (a value will be produced at some time later), and the "effect" of possible failure. In terms of IO, this is important because not only can IO suspend actual "side effects" (like stdout/network/etc.), but it can also represent the types of "effects" like option('a), result('a, 'e), Js.Promise.t, etc.

All of these types of "effectful" values can be converted to an IO, so that you can easily compose all of these different effects in a single expression. When you try to write code in the monadic style (e.g. using chained flatMap or >>= operations), it can be quite convenient to be able to deal with various types of side effects and "functional effects" using a single Monad.

Further reading

This type is inspired by and based on the recent work that has gone into the concept of bi-functor IO in the FP community:

type t('a, 'e) =
| Pure('a) : t('a'e)
| Throw('e) : t('a'e)
| Suspend((unit => 'a)) : t('a'e)
| SuspendIO((unit => t('a'e))) : t('a'e)
| Async(((Pervasives.result('a'e) => unit) => unit)) : t('a'e)
| Map(('r => 'a), t('r'e)) : t('a'e)
| Apply(t('r => 'a'e), t('r'e)) : t('a'e)
| FlatMap(('r => t('a'e)), t('r'e)) : t('a'e)
;

IO is a bi-functor effect type that supports both synchronous and asynchronous effects, with explicit error handling.

This is inspired by the following libraries/articles:

  • John De Goes - http://degoes.net/articles/only-one-io and http://degoes.net/articles/bifunctor-io
  • ZIO/Scalaz 8 IO (Scala) - https://github.com/zio/zio
  • cats-bio (Scala) - https://github.com/LukaJCB/cats-bio
  • purescript-aff discussion (Purescript) - https://github.com/slamdata/purescript-aff/issues/137
let pure: a e. 'a => t('a'e);

IO.pure constructs an IO from the provided value. However, the fact that you are able to provide a value suggests that the effect has already run.

In many cases, it's preferable to use suspend, especailly for values that are expensive to construct or may produce observable effects.

let pureWithVoid: a. 'a => t('a, Relude_Void.t);

IO.pureWithVoid Wraps a non-failing, strictly-evaluated value in an IO. Unlike the normal pure function, this version uses Void.t in the error channel to indicate that no unhandled error exists.

As with pure, you should prefer suspend for values that are expensive to construct or may have side-effects.

let unit: e. t(unit, 'e);

IO.unit represents an IO that successfully resolves to ().

let unitWithVoid: t(unit, Relude_Void.t);

IO.unitWithVoid represents an IO that successfully resolves to (). Unlike IO.unit, this function indicates that it has no unhandled errors by using Void.t in the error channel.

let throw: a e. 'e => t('a'e);

IO.throw wraps a strictly-evaluated error value in an IO.

Prefer suspendThrow (or variants) for values that are expensive to construct or may have side-effects.

let throwWithVoid: e. 'e => t(Relude_Void.t, 'e);

IO.throwWithVoid wraps a strictly-evaluated error value in an IO, indicating that no success can exist with a Void.t type in the success channel.

let suspend: a e. (unit => 'a) => t('a'e);

IO.suspend wraps a lazily-evaluated value in an IO.

let suspendWithVoid: a. (unit => 'a) => t('a, Relude_Void.t);

IO.suspendWithVoid wraps a lazily-evaluated value in an IO. This function cannot fail, as indicated by the Void.t type in the error channel.

let suspendThrow: a e. (unit => 'e) => t('a'e);

IO.suspendThrow wraps a lazily-evaluated error in an IO

let suspendIO: a e. (unit => t('a'e)) => t('a'e);

IO.suspendIO wraps a lazily-evaluated IO value in an IO.

This can be useful if you are dealing with an effectful value that is normally eagerly or strictly evaluated, like a result or option or Js.Promise. In this case, you would typically convert the effectful value into an IO using a function like pure or throw, but doing this strict conversion inside a suspendIO function makes the conversion lazy.

let async: a e. ((Pervasives.result('a'e) => unit) => unit) => t('a'e);

IO.async creates an async IO value that is run by invoking a callback result('a, 'e) => unit.

This is useful for lifting other types of async effects into IO, like Js.Promise or a Node.js-style callback API.

let fromOption: a e. (unit => 'e) => option('a) => t('a'e);

IO.fromOption onverts an option('a) to an IO.t('a, 'e) by providing a callback to use when the option is None.

Because the option is already evaluated, no effort is made to suspend any effects.

let fromResult: a e. Pervasives.result('a'e) => t('a'e);

IO.fromResult converts a result('a, 'e) to an IO.t('a, 'e).

Because the result is already evaluated, no effort is made to suspend any effects.

let map: a b e. ('a => 'b) => t('a'e) => t('b'e);

IO.map applies a function 'a => 'b on an IO.t('a, 'e) to produce an IO.t('b, 'e).

let (<$>): ('a => 'b) => t('a'c) => t('b'c);
let (<#>): t('a'b) => ('a => 'c) => t('c'b);
let tap: a e. ('a => unit) => t('a'e) => t('a'e);

Applies a side-effect function 'a => unit on an IO.t('a, 'e), and propagates the 'a value unchanged.

This is useful for doing things like logging the value inside the IO.

let apply: a b e. t('a => 'b'e) => t('a'e) => t('b'e);

Applicative apply function

let (<*>): t('a => 'b'c) => t('a'c) => t('b'c);
let flatMap: a b e. ('a => t('b'e)) => t('a'e) => t('b'e);

IO.flatMap pplies an effectful function 'a => IO.t('b, 'e) on the 'a value inside the IO to produce an IO.t('b, 'e).

let bind: a b e. t('a'e) => ('a => t('b'e)) => t('b'e);

IO.bind is flatMap with the argument order reversed. It's also an alias for the >>= "bind" operator.

let (>>=): t('a'b) => ('a => t('c'b)) => t('c'b);
let cond: a e. ('a => bool) => 'a => 'e => t('a'e) => t('a'e);

IO.cond applies the provided predicate function to the success value in the IO. If the condition is satisfied, the provided 'a value is lifted into the IO and returned. If the condition fails, the provided 'e value is lifted into the IO and returned. If the IO was already an error, the predicate function isn't run and the existing error is preserved.

let condError: a e. ('a => bool) => 'e => t('a'e) => t('a'e);

IO.condError tests the success value against a provided predicate, as cond does. Unlike cond, if the predicate passes, the existing 'a is returned. If the condition does not pass, the new error is used instead.

let unsafeRunAsync: a e. (Pervasives.result('a'e) => unit) => t('a'e) => unit;

IO.unsafeRunAsync runs the IO.t('a, 'e) to produce a final result('a, 'e), which is provided to the caller via a callback of type result('a, 'e) => unit.

This function should be run "at the edge of the program" to evaluate the suspended side-effects in the IO and produce either an error of type 'e or a successful value of type 'a. Ideally, in simple apps, this execution happens at the end of your main function, but when using IO inside existing frameworks that don't natively support IO, the most appropriate place may be inside the context of a reducer side effect or a web app controller function.

The function uses the term "unsafe" because calling this function causes all of the suspended side effects to actually be executed. It is not "unsafe" in that it can throw an exception - it is just a convention in FP libraries to denote these types of functions as unsafe.

let unsafeRunAsyncPar2: a b e. (Pervasives.result('a'e) => Pervasives.result('b'e) => unit) => t('a'e) => t('b'e) => unit;

Runs two IOs in parallel, and invokes the given done callback when all complete

Note that applicative uses of IO (apply/map2/map3/traverse/etc.) will run the IOs in parallel, so it's rarely necessary for the end-user to call this directly.

let unsafeRunAsyncPar3: a b c e. (Pervasives.result('a'e) => Pervasives.result('b'e) => Pervasives.result('c'e) => unit) => t('a'e) => t('b'e) => t('c'e) => unit;

Runs three IOs in parallel, and invokes the given done callback when all complete.

Note that applicative uses of IO (apply/map2/map3/traverse/etc.) will run the IOs in parallel, so it's rarely necessary for the end-user to call this directly.

let compose: a b c e. t('b => 'c'e) => t('a => 'b'e) => t('a => 'c'e);

Creates a new IO value that contains the composition of functions from two input IO values. Composition is done from right-to-left with this function - see andThen for left-to-right.

let composePure: a b c e. ('a => 'b) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Pure('a => 'b)

let composeThrow: a b c e. 'e => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Throw

let composeSuspend: a b c e. (unit => 'a => 'b) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Suspend

let composeSuspendIO: a b c e. (unit => t('a => 'b'e)) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side SuspendIO

let composeAsync: a b c e. ((Pervasives.result('a => 'b'e) => unit) => unit) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Async

let composeMap: a b c r0 e. ('r0 => 'a => 'b) => t('r0'e) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Map

let composeApply: a b c r0 e. t('r0 => 'a => 'b'e) => t('r0'e) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side Apply

let composeFlatMap: a b c r0 e. ('r0 => t('a => 'b'e)) => t('r0'e) => t('b => 'c'e) => t('a => 'c'e);

compose specialization for a left-hand-side FlatMap

let (<<<): t('a => 'b'c) => t('d => 'a'c) => t('d => 'b'c);

Operator for IO's compose right-to-left composition function

This uses triple <<< to disambiguate from function compose <<

let andThen: a b c e. t('a => 'b'e) => t('b => 'c'e) => t('a => 'c'e);

Flipped version of compose for left-to-right usage

let (>>>): t('a => 'b'c) => t('b => 'd'c) => t('a => 'd'c);

Operator for IO's andThen left-to-right composition function

This uses triple >>> to disambiguate from function andThen >>

let mapError: a e1 e2. ('e1 => 'e2) => t('a'e1) => t('a'e2);

Same as map, but operates on the error channel.

let tapError: a e. ('e => unit) => t('a'e) => t('a'e);

Same as tap, but operates on the error channel.

let catchError: a e1 e2. ('e1 => t('a'e2)) => t('a'e1) => t('a'e2);

Handles an error of types 'e1 from an IO.t('a, 'e1) and converts it into a new IO.t('a, 'e1) value. This is much like flatMap/bind but works for the error channel of the IO.

let catchErrorMap: a r0 e1 e2. ('e1 => t('a'e2)) => ('r0 => 'a) => t('r0'e1) => t('a'e2);
let catchErrorApply: a r0 e1 e2. ('e1 => t('a'e2)) => t('r0 => 'a'e1) => t('r0'e1) => t('a'e2);
let catchErrorFlatMap: a r0 e1 e2. ('e1 => t('a'e2)) => ('r0 => t('a'e1)) => t('r0'e1) => t('a'e2);
let handleError: a e. ('e => 'a) => t('a'e) => t('a, Relude_Void.t);

Uses a function to convert an error value to a success value, which serves to "clear" the error in the IO, thereby making the error type Void.t.

let mapHandleError: a e b. ('a => 'b) => ('e => 'b) => t('a'e) => t('b, Relude_Void.t);

Maps the success channel and handles an error on the error channel to end up with an IO of a new type with a voided error channel

let bimap: a b e1 e2. ('a => 'b) => ('e1 => 'e2) => t('a'e1) => t('b'e2);

Applies functions on both the success and error channels of the IO.

let bitap: a e. ('a => unit) => ('e => unit) => t('a'e) => t('a'e);

Same as tap, but works on both the success and error channels simultaneously.

let alt: a e. t('a'e) => t('a'e) => t('a'e);

Returns a new IO that when run, will attempt the IO given as the first argument, and if it fails, will attempt the IO given as the second argument. The second IO is only run if the first fails.

The <|> operator version of alt can be accessed via the IO.WithError module functor, like this:

module IOE = IO.WithError({ type t = string; });

let a = ref(false);
let b = ref(false);

IOE.Infix.(
  IO.suspend(() => a := true)
  <|> IO.suspend(() => b := true) // this effect won't run in this case, because the previous IO succeeds
  |> IO.unsafeRunAsync(...)
);
let align: a b e. t('a'e) => t('b'e) => t(Relude_Ior_Type.t('a'b)'e);

Creates a new IO that will run the two input IO effects in parallel, and resolve if either or both succeed.

let alignWith: a b c e. (Relude_Ior_Type.t('a'b) => 'c) => t('a'e) => t('b'e) => t('c'e);

Creates a new IO that runs two effects in parallel, and if either or both succeed, convert the result into another type 'c

let orElse: a e. fallback:t('a'e) => t('a'e) => t('a'e);

Returns a new IO that when run, will attempt the IO given as the second, un-labeled argument, and if it fails, will attempt the IO given as the first argument with the label ~fallback.

This is intended to be used with the |> pipe operator, like this:

IO.suspend(() => a := true)
|> IO.orElse(~fallback=IO.suspend(() => b := true))
|> IO.unsafeRunAsync(...)
let tries: a. (unit => 'a) => t('a, exn);

Lifts a side-effect function that might throw an exception into a suspended IO.t('a, exn) value.

The exn type is OCaml's extensible error type.

let triesJS: a. (unit => 'a) => t('a, Js.Exn.t);

Lifts a side-effect function that might throw an JS exception into a suspended IO.t('a, Js.Exn.t) value.

If a normal Js.Exn.t is throw, it is captured as-is, but if the thrown object is not a Js.Exn.t it is unsafely coerced into a Js.Exn.t.

let flip: a e. t('a'e) => t('e'a);

Flips the values between the success and error channels.

let flipMap: a r0 e. ('r0 => 'a) => t('r0'e) => t('e'a);
let flipApply: a r0 e. t('r0 => 'a'e) => t('r0'e) => t('e'a);
let flipFlatMap: a r0 e. ('r0 => t('a'e)) => t('r0'e) => t('e'a);
let summonError: a e. t('a'e) => t(Pervasives.result('a'e), Relude_Void.t);

Summons an error of type 'e from the error channel into the success channel as a result('a, 'e). The error channel becomes Void.t because the error has been (re)moved.

let summonErrorMap: a r0 e. ('r0 => 'a) => t('r0'e) => t(Pervasives.result('a'e), Relude_Void.t);
let summonErrorApply: a r0 e. t('r0 => 'a'e) => t('r0'e) => t(Pervasives.result('a'e), Relude_Void.t);
let summonErrorFlatMap: a r0 e. ('r0 => t('a'e)) => t('r0'e) => t(Pervasives.result('a'e), Relude_Void.t);
let unsummonError: a e. t(Pervasives.result('a'e), Relude_Void.t) => t('a'e);

Unsummons an error from a success channel result('a, 'e) back into the error channel of the IO.

let unsummonErrorMap: r0 a e. ('r0 => Pervasives.result('a'e)) => t('r0, Relude_Void.t) => t('a'e);
let unsummonErrorApply: r0 a e. t('r0 => Pervasives.result('a'e), Relude_Void.t) => t('r0, Relude_Void.t) => t('a'e);
let unsummonErrorFlatMap: r0 a e. ('r0 => t(Pervasives.result('a'e), Relude_Void.t)) => t('r0, Relude_Void.t) => t('a'e);
let delay: e. int => t(unit, 'e);

Creates an async IO that waits for the given millisecond timeout before completing with a unit value.

let delayWithVoid: int => t(unit, Relude_Void.t);

Creates an async non-failing IO that waits for the given millisecond timeout before completing with a unit value.

let withDelayAfter: a e. int => t('a'e) => t('a'e);

Injects a delay in milliseconds after the given IO. The value or error from the previous IO is propagated after the delay.

When run, the given IO will be run first, then the delay will be run after the IO finishes.

IO.pure(4) |> IO.withDelayAfter(2000) |> ...
let withDelay: int => t('a'b) => t('a'b);

Alias for withDelayAfter

let withDelayBefore: a e. int => t('a'e) => t('a'e);

Injects a delay before the given IO.

When run, the delay will be executed first, then the given IO

let debounce: r a e. ?⁠immediate:bool => ?⁠intervalMs:int => ('r => t('a'e)) => 'r => t(option('a), 'e);

This will "debounce" an IO so that it will only allow the latest call within some interval to go through. All other calls will be cancelled.

Note: that the IO produced by this function is not referentially transparent, because the IO chain is manipulated at runtime via a mutable ref.

let ioLog = messageToLog => IO.pure() |> IO.map(() => Js.log(messageToLog));
let debouncedIoLog = IO.debounce(ioLog);

"This message will not get logged" |> debouncedIoLog |> IO.unsafeRunAsync(ignore);
"This message will also not get logged" |> debouncedIoLog |> IO.unsafeRunAsync(ignore);
"This message will get logged" |> debouncedIoLog |> IO.unsafeRunAsync(ignore);
let throttle: r a e. ?⁠intervalMs:int => ('r => t('a'e)) => 'r => t(option('a), 'e);

This will "throttle" an IO so that it will only allow subsequent calls to go through after some period of time has elapsed.

Note: that the IO produced by this function is not referentially transparent, because the IO chain is manipulated at runtime via a mutable ref.

let ioLog = messageToLog => IO.pure() |> IO.map(() => Js.log(messageToLog));
let throttledIoLog = IO.throttled(ioLog);

"This message will get logged" |> throttledIoLog |> IO.unsafeRunAsync(ignore);
"This message will not get logged" |> throttledIoLog |> IO.unsafeRunAsync(ignore);
"This message will also not get logged" |> throttledIoLog |> IO.unsafeRunAsync(ignore);
module Bifunctor: BsBastet.Interface.BIFUNCTOR with type Bifunctor.t('a, 'e) = t('a'e);
let bimap: ('a => 'b) => ('c => 'd) => t('a'c) => t('b'd);
include { ... };
let mapLeft: ('a => 'c) => Bifunctor.t('a'b) => Bifunctor.t('c'b);
let mapRight: ('b => 'd) => Bifunctor.t('a'b) => Bifunctor.t('a'd);
let mapError: ('a => 'b) => Bifunctor.t('c'a) => Bifunctor.t('c'b);
module WithError: (E: BsBastet.Interface.TYPE) => { ... };

Because this is a bifunctor, we need to use a module functor to lock in the error type, so we can implement many of the single-type parameter typeclasses.