package lwt_react

  1. Overview
  2. Docs
include module type of React.E

Event combinators.

Consult their semantics.

Primitive and basics

type 'a t = 'a React.event

The type for events with occurrences of type 'a.

val never : 'a React.event

A never occuring event. For all t, [never]t = None.

val create : unit -> 'a React.event * (?step:React.step -> 'a -> unit)

create () is a primitive event e and a send function. The function send is such that:

  • send v generates an occurrence v of e at the time it is called and triggers an update step.
  • send ~step v generates an occurence v of e on the step step when step is executed.
  • send ~step v raises Invalid_argument if it was previously called with a step and this step has not executed yet or if the given step was already executed.

Warning. send must not be executed inside an update step.

val retain : 'a React.event -> (unit -> unit) -> [ `R of unit -> unit ]

retain e c keeps a reference to the closure c in e and returns the previously retained value. c will never be invoked.

Raises. Invalid_argument on E.never.

val stop : ?strong:bool -> 'a React.event -> unit

stop e stops e from occuring. It conceptually becomes never and cannot be restarted. Allows to disable effectful events.

The strong argument should only be used on platforms where weak arrays have a strong semantics (i.e. JavaScript). See details.

Note. If executed in an update step the event may still occur in the step.

val equal : 'a React.event -> 'a React.event -> bool

equal e e' is true iff e and e' are equal. If both events are different from never, physical equality is used.

val trace : ?iff:bool React.signal -> ('a -> unit) -> 'a React.event -> 'a React.event

trace iff tr e is e except tr is invoked with e's occurence when iff is true (defaults to S.const true). For all t where [e]t = Some v and [iff]t = true, tr is invoked with v.

Transforming and filtering

val once : 'a React.event -> 'a React.event

once e is e with only its next occurence.

  • [once e]t = Some v if [e]t = Some v and [e]<t = None.
  • [once e]t = None otherwise.
val drop_once : 'a React.event -> 'a React.event

drop_once e is e without its next occurrence.

  • [drop_once e]t = Some v if [e]t = Some v and [e]<t = Some _.
  • [drop_once e]t = None otherwise.
val app : ('a -> 'b) React.event -> 'a React.event -> 'b React.event

app ef e occurs when both ef and e occur simultaneously. The value is ef's occurence applied to e's one.

  • [app ef e]t = Some v' if [ef]t = Some f and [e]t = Some v and f v = v'.
  • [app ef e]t = None otherwise.
val map : ('a -> 'b) -> 'a React.event -> 'b React.event

map f e applies f to e's occurrences.

  • [map f e]t = Some (f v) if [e]t = Some v.
  • [map f e]t = None otherwise.
val stamp : 'b React.event -> 'a -> 'a React.event

stamp e v is map (fun _ -> v) e.

val filter : ('a -> bool) -> 'a React.event -> 'a React.event

filter p e are e's occurrences that satisfy p.

  • [filter p e]t = Some v if [e]t = Some v and p v = true
  • [filter p e]t = None otherwise.
val fmap : ('a -> 'b option) -> 'a React.event -> 'b React.event

fmap fm e are e's occurrences filtered and mapped by fm.

  • [fmap fm e]t = Some v if fm [e]t = Some v
  • [fmap fm e]t = None otherwise.
val diff : ('a -> 'a -> 'b) -> 'a React.event -> 'b React.event

diff f e occurs whenever e occurs except on the next occurence. Occurences are f v v' where v is e's current occurrence and v' the previous one.

  • [diff f e]t = Some r if [e]t = Some v, [e]<t = Some v' and f v v' = r.
  • [diff f e]t = None otherwise.
val changes : ?eq:('a -> 'a -> bool) -> 'a React.event -> 'a React.event

changes eq e is e's occurrences with occurences equal to the previous one dropped. Equality is tested with eq (defaults to structural equality).

  • [changes eq e]t = Some v if [e]t = Some v and either [e]<t = None or [e]<t = Some v' and eq v v' = false.
  • [changes eq e]t = None otherwise.
val on : bool React.signal -> 'a React.event -> 'a React.event

on c e is the occurrences of e when c is true.

  • [on c e]t = Some v if [c]t = true and [e]t = Some v.
  • [on c e]t = None otherwise.
val when_ : bool React.signal -> 'a React.event -> 'a React.event
  • deprecated

    Use on.

val dismiss : 'b React.event -> 'a React.event -> 'a React.event

dismiss c e is the occurences of e except the ones when c occurs.

  • [dimiss c e]t = Some v if [c]t = None and [e]t = Some v.
  • [dimiss c e]t = None otherwise.
val until : 'a React.event -> 'b React.event -> 'b React.event

until c e is e's occurences until c occurs.

  • [until c e]t = Some v if [e]t = Some v and [c]<=t = None
  • [until c e]t = None otherwise.

Accumulating

val accum : ('a -> 'a) React.event -> 'a -> 'a React.event

accum ef i accumulates a value, starting with i, using e's functional occurrences.

  • [accum ef i]t = Some (f i) if [ef]t = Some f and [ef]<t = None.
  • [accum ef i]t = Some (f acc) if [ef]t = Some f and [accum ef i]<t = Some acc.
  • [accum ef i] = None otherwise.
val fold : ('a -> 'b -> 'a) -> 'a -> 'b React.event -> 'a React.event

fold f i e accumulates e's occurrences with f starting with i.

  • [fold f i e]t = Some (f i v) if [e]t = Some v and [e]<t = None.
  • [fold f i e]t = Some (f acc v) if [e]t = Some v and [fold f i e]<t = Some acc.
  • [fold f i e]t = None otherwise.

Combining

val select : 'a React.event list -> 'a React.event

select el is the occurrences of every event in el. If more than one event occurs simultaneously the leftmost is taken and the others are lost.

  • [select el]t = [List.find (fun e -> [e]t <> None) el]t.
  • [select el]t = None otherwise.
val merge : ('a -> 'b -> 'a) -> 'a -> 'b React.event list -> 'a React.event

merge f a el merges the simultaneous occurrences of every event in el using f and the accumulator a.

[merge f a el]t = List.fold_left f a (List.filter (fun o -> o <> None) (List.map []t el)).

val switch : 'a React.event -> 'a React.event React.event -> 'a React.event

switch e ee is e's occurrences until there is an occurrence e' on ee, the occurrences of e' are then used until there is a new occurrence on ee, etc..

  • [switch e ee]t = [e]t if [ee]<=t = None.
  • [switch e ee]t = [e']t if [ee]<=t = Some e'.
val fix : ('a React.event -> 'a React.event * 'b) -> 'b

fix ef allows to refer to the value an event had an infinitesimal amount of time before.

In fix ef, ef is called with an event e that represents the event returned by ef delayed by an infinitesimal amount of time. If e', r = ef e then r is returned by fix and e is such that :

  • [e]t = None if t = 0
  • [e]t = [e']t-dt otherwise

Raises. Invalid_argument if e' is directly a delayed event (i.e. an event given to a fixing function).

Lifting

Lifting combinators. For a given n the semantics is:

  • [ln f e1 ... en]t = Some (f v1 ... vn) if for all i : [ei]t = Some vi.
  • [ln f e1 ... en]t = None otherwise.
val l1 : ('a -> 'b) -> 'a React.event -> 'b React.event
val l2 : ('a -> 'b -> 'c) -> 'a React.event -> 'b React.event -> 'c React.event
val l3 : ('a -> 'b -> 'c -> 'd) -> 'a React.event -> 'b React.event -> 'c React.event -> 'd React.event
val l4 : ('a -> 'b -> 'c -> 'd -> 'e) -> 'a React.event -> 'b React.event -> 'c React.event -> 'd React.event -> 'e React.event
val l5 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f) -> 'a React.event -> 'b React.event -> 'c React.event -> 'd React.event -> 'e React.event -> 'f React.event
val l6 : ('a -> 'b -> 'c -> 'd -> 'e -> 'f -> 'g) -> 'a React.event -> 'b React.event -> 'c React.event -> 'd React.event -> 'e React.event -> 'f React.event -> 'g React.event

Stdlib support

module Option : sig ... end

Events with option occurences.

Lwt-specific utilities

val with_finaliser : (unit -> unit) -> 'a event -> 'a event

with_finaliser f e returns an event e' which behave as e, except that f is called when e' is garbage collected.

val next : 'a event -> 'a Lwt.t

next e returns the next occurrence of e.

Avoid trying to create an “asynchronous loop” by calling next e again in a callback attached to the promise returned by next e:

  • The callback is called within the React update step, so calling next e within it will return a promise that is fulfilled with the same value as the current occurrence.
  • If you instead arrange for the React update step to end (for example, by calling Lwt.pause () within the callback), multiple React update steps may occur before the callback calls next e again, so some occurrences can be effectively “lost.”

To robustly asynchronously process occurrences of e in a loop, use to_stream e, and repeatedly call Lwt_stream.next on the resulting stream.

val limit : (unit -> unit Lwt.t) -> 'a event -> 'a event

limit f e limits the rate of e with f.

For example, to limit the rate of an event to 1 per second you can use: limit (fun () -> Lwt_unix.sleep 1.0) event.

val from : (unit -> 'a Lwt.t) -> 'a event

from f creates an event which occurs each time f () returns a value. If f raises an exception, the event is just stopped.

val to_stream : 'a event -> 'a Lwt_stream.t

Creates a stream holding all values occurring on the given event

val of_stream : 'a Lwt_stream.t -> 'a event

of_stream stream creates an event which occurs each time a value is available on the stream.

If updating the event causes an exception at any point during the update step, the exception is passed to !Lwt.async_exception_hook, which terminates the process by default.

val delay : 'a event Lwt.t -> 'a event

delay promise is an event which does not occur until promise resolves. Then it behaves as the event returned by promise.

val keep : 'a event -> unit

keep e keeps a reference to e so it will never be garbage collected.

Threaded versions of React transformation functions

The following functions behave as their React counterpart, except that they take functions that may yield.

As usual the _s suffix is used when calls are serialized, and the _p suffix is used when they are not.

Note that *_p functions may not preserve event order.

val app_s : ('a -> 'b Lwt.t) event -> 'a event -> 'b event
val app_p : ('a -> 'b Lwt.t) event -> 'a event -> 'b event
val map_s : ('a -> 'b Lwt.t) -> 'a event -> 'b event
val map_p : ('a -> 'b Lwt.t) -> 'a event -> 'b event
val filter_s : ('a -> bool Lwt.t) -> 'a event -> 'a event
val filter_p : ('a -> bool Lwt.t) -> 'a event -> 'a event
val fmap_s : ('a -> 'b option Lwt.t) -> 'a event -> 'b event
val fmap_p : ('a -> 'b option Lwt.t) -> 'a event -> 'b event
val diff_s : ('a -> 'a -> 'b Lwt.t) -> 'a event -> 'b event
val accum_s : ('a -> 'a Lwt.t) event -> 'a -> 'a event
val fold_s : ('a -> 'b -> 'a Lwt.t) -> 'a -> 'b event -> 'a event
val merge_s : ('a -> 'b -> 'a Lwt.t) -> 'a -> 'b event list -> 'a event
val run_s : 'a Lwt.t event -> 'a event
val run_p : 'a Lwt.t event -> 'a event