gleam/erlang/process

Types

Values returned when a timer is cancelled.

pub type Cancelled {
  TimerNotFound
  Cancelled(time_remaining: Int)
}

Constructors

  • TimerNotFound

    The timer could not be found. It likely has already triggered.

  • Cancelled(time_remaining: Int)

    The timer was found and cancelled before it triggered.

    The amount of remaining time before the timer was due to be triggered is returned in milliseconds.

A message received when a monitored process exits.

pub type Down {
  ProcessDown(monitor: Monitor, pid: Pid, reason: ExitReason)
  PortDown(monitor: Monitor, port: port.Port, reason: ExitReason)
}

Constructors

pub type ExitMessage {
  ExitMessage(pid: Pid, reason: ExitReason)
}

Constructors

pub type ExitReason {
  Normal
  Killed
  Abnormal(reason: dynamic.Dynamic)
}

Constructors

pub type Monitor

A name is an identity that a process can adopt, after which they will receive messages sent to that name. This has two main advantages:

  • Structuring OTP programs becomes easier as a name can be passed down the program from the top level, while without names subjects and pids would need to be passed up from the started process and then back down to the code that works with that process.
  • A new process can adopt the name of one that previously failed, allowing it to transparently take-over and handle messages that are sent to that name.

Names are globally unique as each process can have at most 1 name, and each name can be registered by at most 1 process. Create all the names your program needs at the start of your program and pass them down. Names are Erlang atoms internally, so never create them dynamically. Generating too many atoms will result in the atom table getting filled and causing the entire virtual machine to crash.

The most commonly used name functions are new_name, register, and named_subject.

pub type Name(message)

A Pid (or Process identifier) is a reference to an Erlang process. Each process has a Pid and it is one of the lowest level building blocks of inter-process communication in the Erlang and Gleam OTP frameworks.

pub type Pid

A type that enables a process to wait for messages from multiple Subjects at the same time, returning whichever message arrives first.

Used with the new_selector, selector_receive, and select* functions.

Examples

let int_subject = new_subject()
let string_subject = new_subject()
send(int_subject, 1)

let selector =
  new_selector()
  |> select(string_subject)
  |> select_map(int_subject, int.to_string)

select(selector, 10)
// -> Ok("1")
pub type Selector(payload)

A Subject is a value that processes can use to send and receive messages to and from each other in a well typed way.

Each subject is “owned” by the process that created it. Any process can use the send function to sent a message of the correct type to the process that owns the subject, and the owner can use the receive function or the Selector type to receive these messages.

The Subject type is similar to the “channel” types found in other languages and the “topic” concept found in some pub-sub systems.

Examples

let subject = new_subject()

// Send a message with the subject
send(subject, "Hello, Joe!")

// Receive the message
receive(subject, within: 10)
pub opaque type Subject(message)
pub type Timer

Values

pub fn call(
  subject: Subject(message),
  waiting timeout: Int,
  sending make_request: fn(Subject(reply)) -> message,
) -> reply

Send a message to a process and wait a given number of milliseconds for a reply.

Panics

This function will panic under the following circumstances:

  • The callee process exited prior to sending a reply.
  • The callee process did not send a reply within the permitted amount of time.
  • The subject is a named subject but no process is registered with that name.

Examples

pub type Message {
  // This message variant is to be used with `call`.
  // The `reply` field contains a subject that the reply message will be
  // sent over.
  SayHello(reply_to: Subject(String), name: String)
}

// Typically we make public functions that hide the details of a process'
// message-based API.
pub fn say_hello(subject: Subject(Message), name: String) -> String {
  // The `SayHello` message constructor is given _partially applied_ with
  // all the arguments except the reply subject, which will be supplied by
  // the `call` function itself before sending the message.
  process.call(subject, 100, SayHello(_, name))
}

// This is the message handling logic used by the process that owns the
// subject, and so receives the messages. In a real project it would be
// within a process or some higher level abstraction like an actor, but for
// this demonstration that has been omitted.
pub fn handle_message(message: Message) -> Nil {
  case message {
    SayHello(reply:, name:) -> {
      let data = "Hello, " <> name <> "!"
      // The reply subject is used to send the response back.
      // If the receiver process does not sent a reply in time then the
      // caller will crash.
      process.send(reply, data)
    }
  }
}

// Here is what it looks like using the functional API to call the process.
pub fn run(subject: Subject(Message)) {
  say_hello(subject, "Lucy")
  // -> "Hello, Lucy!"
  say_hello(subject, "Nubi")
  // -> "Hello, Nubi!"
}
pub fn call_forever(
  subject: Subject(message),
  make_request: fn(Subject(reply)) -> message,
) -> reply

Send a message to a process and wait for a reply.

Panics

This function will panic under the following circumstances:

  • The callee process exited prior to sending a reply.
  • The subject is a named subject but no process is registered with that name.
pub fn cancel_timer(timer: Timer) -> Cancelled

Cancel a given timer, causing it not to trigger if it has not done already.

pub fn demonitor_process(monitor monitor: Monitor) -> Nil

Remove the monitor for a process so that when the monitor process exits a Down message is not sent to the monitoring process.

If the message has already been sent it is removed from the monitoring process’ mailbox.

pub fn deselect(
  selector: Selector(payload),
  for subject: Subject(message),
) -> Selector(payload)

Remove a new Subject from the Selector so that its messages will not be selected from the receiver process inbox.

pub fn deselect_specific_monitor(
  selector: Selector(payload),
  monitor: Monitor,
) -> Selector(payload)

Remove a Monitor from a Selector prevoiusly added by select_specific_monitor. If the Monitor is not in the Selector it will be returned unchanged.

pub fn flush_messages() -> Nil

Discard all messages in the current process’ mailbox.

Warning: This function may cause other processes to crash if they sent a message to the current process and are waiting for a response, so use with caution.

This function may be useful in tests.

pub fn is_alive(a: Pid) -> Bool

Check to see whether the process for a given Pid is alive.

See the Erlang documentation for more information.

pub fn kill(pid: Pid) -> Nil

Send an untrappable kill exit signal to the target process.

See the documentation for the Erlang erlang:exit function for more information.

pub fn link(pid pid: Pid) -> Bool

Creates a link between the calling process and another process.

When a process crashes any linked processes will also crash. This is useful to ensure that groups of processes that depend on each other all either succeed or fail together.

Returns True if the link was created successfully, returns False if the process was not alive and as such could not be linked.

pub fn map_selector(a: Selector(a), b: fn(a) -> b) -> Selector(b)

Add a transformation function to a selector. When a message is received using this selector the transformation function is applied to the message.

This function can be used to change the type of messages received and may be useful when combined with the merge_selector function.

pub fn merge_selector(
  a: Selector(a),
  b: Selector(a),
) -> Selector(a)

Merge one selector into another, producing a selector that contains the message handlers of both.

If a subject is handled by both selectors the handler function of the second selector is used.

pub fn monitor(pid: Pid) -> Monitor

Start monitoring a process so that when the monitored process exits a message is sent to the monitoring process.

The message is only sent once, when the target process exits. If the process was not alive when this function is called the message will never be received.

The down message can be received with a selector and the select_monitors function.

The process can be demonitored with the demonitor_process function.

pub fn named(name: Name(a)) -> Result(Pid, Nil)

Look up a process by registered name, returning the pid if it exists.

pub fn named_subject(name: Name(message)) -> Subject(message)

Create a subject for a name, which can be used to send and receive messages.

All subjects created for the same name behave identically and can be used interchangably.

pub fn new_name(prefix prefix: String) -> Name(message)

Generate a new name that a process can register itself with using the register function, and other processes can send messages to using named_subject.

The string argument is a prefix for the Erlang name. A unique suffix is added to the prefix to make the name, removing the possibility of name collisions.

Safe use

Use this function to create all the names your program needs when it starts. Never call this function dynamically such as within a loop or within a process within a supervision tree.

Each time this function is called a new atom will be generated. Generating too many atoms will result in the atom table getting filled and causing the entire virtual machine to crash.

pub fn new_selector() -> Selector(payload)

Create a new Selector which can be used to receive messages on multiple Subjects at once.

pub fn new_subject() -> Subject(message)

Create a new Subject owned by the current process.

pub fn receive(
  from subject: Subject(message),
  within timeout: Int,
) -> Result(message, Nil)

Receive a message that has been sent to current process using the Subject.

If there is not an existing message for the Subject in the process’ mailbox or one does not arrive within the permitted timeout then the Error(Nil) is returned.

Only the process that is owner of the Subject can receive a message using it. If a process that does not own the Subject attempts to receive with it then it will not receive a message.

To wait for messages from multiple Subjects at the same time see the Selector type.

The within parameter specifies the timeout duration in milliseconds.

Panics

This function will panic if a process tries to receive with a non-named subject that it does not own.

pub fn receive_forever(from subject: Subject(message)) -> message

Receive a message that has been sent to current process using the Subject.

Same as receive but waits forever and returns the message as is.

pub fn register(
  pid: Pid,
  name: Name(message),
) -> Result(Nil, Nil)

Register a process under a given name, allowing it to be looked up using the named function.

This function will return an error under the following conditions:

  • The process for the pid no longer exists.
  • The name has already been registered.
  • The process already has a name.
pub fn select(
  selector: Selector(payload),
  for subject: Subject(payload),
) -> Selector(payload)

See deselect to remove a subject from a selector.

pub fn select_map(
  selector: Selector(payload),
  for subject: Subject(message),
  mapping transform: fn(message) -> payload,
) -> Selector(payload)

Add a new Subject to the Selector so that its messages can be selected from the receiver process inbox.

The mapping function provided with the Subject can be used to convert the type of messages received using this Subject. This is useful for when you wish to add multiple Subjects to a Selector when they have differing message types. If you do not wish to transform the incoming messages in any way then the identity function can be given.

See deselect to remove a subject from a selector.

pub fn select_monitors(
  selector: Selector(payload),
  mapping: fn(Down) -> payload,
) -> Selector(payload)

Select for any messages sent for any monitors set up by the select process.

If you want to select for a specific message then use select_specific_monitor, but this function is preferred if you need to select for multiple monitors.

pub fn select_other(
  selector: Selector(payload),
  mapping handler: fn(dynamic.Dynamic) -> payload,
) -> Selector(payload)

Add a catch-all handler to a selector that will be used when no other handler in a selector is suitable for a given message.

This may be useful for when you want to ensure that any message in the inbox is handled, or when you need to handle messages from other BEAM languages which do not use subjects or record format messages.

pub fn select_record(
  selector: Selector(payload),
  tag tag: tag,
  fields arity: Int,
  mapping transform: fn(dynamic.Dynamic) -> payload,
) -> Selector(payload)

Add a handler to a selector for tuple messages with a given tag in the first position followed by a given number of fields.

Typically you want to use the select function with a Subject instead, but this function may be useful if you need to receive messages sent from other BEAM languages that do not use the Subject type.

This will not select messages sent via a subject even if the message has the same tag in the first position. This is because when a message is sent via a subject a new tag is used that is unique and specific to that subject.

pub fn select_specific_monitor(
  selector: Selector(payload),
  monitor: Monitor,
  mapping: fn(Down) -> payload,
) -> Selector(payload)

Select for a message sent for a given monitor.

Each monitor handler added to a selector has a select performance cost, so prefer select_monitors if you are select for multiple monitors.

The handler can be removed from the selector later using deselect_specific_monitor.

pub fn select_trapped_exits(
  selector: Selector(a),
  handler: fn(ExitMessage) -> a,
) -> Selector(a)

Add a handler for trapped exit messages. In order for these messages to be sent to the process when a linked process exits the process must call the trap_exit beforehand.

pub fn selector_receive(
  from from: Selector(payload),
  within within: Int,
) -> Result(payload, Nil)

Receive a message that has been sent to current process using any of the Subjects that have been added to the Selector with the select* functions.

If there is not an existing message for the Selector in the process’ mailbox or one does not arrive within the permitted timeout then the Error(Nil) is returned.

Only the process that is owner of the Subjects can receive a message using them. If a process that does not own the a Subject attempts to receive with it then it will not receive a message.

To wait forever for the next message rather than for a limited amount of time see the selector_receive_forever function.

The within parameter specifies the timeout duration in milliseconds.

pub fn selector_receive_forever(
  from from: Selector(payload),
) -> payload

Similar to the select function but will wait forever for a message to arrive rather than timing out after a specified amount of time.

pub fn self() -> Pid

Get the Pid for the current process.

pub fn send(subject: Subject(message), message: message) -> Nil

Send a message to a process using a Subject. The message must be of the type that the Subject accepts.

This function does not wait for the Subject owner process to call the receive function, instead it returns once the message has been placed in the process’ mailbox.

Named Subjects

If this function is called on a named subject for which a process has not been registered, it will simply drop the message as there’s no mailbox to send it to.

Panics

This function will panic when sending to a named subject if no process is currently registed under that name.

Ordering

If process P1 sends two messages to process P2 it is guaranteed that process P1 will receive the messages in the order they were sent.

If you wish to receive the messages in a different order you can send them on two different subjects and the receiver function can call the receive function for each subject in the desired order, or you can write some Erlang code to perform a selective receive.

Examples

let subject = new_subject()
send(subject, "Hello, Joe!")
pub fn send_abnormal_exit(pid: Pid, reason: anything) -> Nil

Sends an exit signal to a process, indicating that the process is to shut down due to an abnormal reason such as a failure.

See the Erlang documentation for more information.

pub fn send_after(
  subject: Subject(msg),
  delay: Int,
  message: msg,
) -> Timer

Send a message over a channel after a specified number of milliseconds.

pub fn send_exit(to pid: Pid) -> Nil

Sends an exit signal to a process, indicating that the process is to shut down.

See the Erlang documentation for more information.

pub fn sleep(a: Int) -> Nil

Suspends the process calling this function for the specified number of milliseconds.

pub fn sleep_forever() -> Nil

Suspends the process forever! This may be useful for suspending the main process in a Gleam program when it has no more work to do but we want other processes to continue to work.

pub fn spawn(running: fn() -> anything) -> Pid

Create a new Erlang process that runs concurrently to the creator. In other languages this might be called a fibre, a green thread, or a coroutine.

The child process is linked to the creator process. When a process terminates an exit signal is sent to all other processes that are linked to it, causing the process to either terminate or have to handle the signal. If you want an unlinked process use the spawn_unlinked function.

More can be read about processes and links in the Erlang documentation.

This function starts processes via the Erlang proc_lib module, and as such they benefit from the functionality described in the proc_lib documentation.

pub fn spawn_unlinked(a: fn() -> anything) -> Pid

Create a new Erlang process that runs concurrently to the creator. In other languages this might be called a fibre, a green thread, or a coroutine.

Typically you want to create a linked process using the spawn function, but creating an unlinked process may be occasionally useful.

More can be read about processes and links in the Erlang documentation.

This function starts processes via the Erlang proc_lib module, and as such they benefit from the functionality described in the proc_lib documentation.

pub fn subject_owner(
  subject: Subject(message),
) -> Result(Pid, Nil)

Get the owner process for a subject, which is the process that will receive any messages sent using the subject.

If the subject was created from a name and no process is currently registered with that name then this function will return an error.

pub fn trap_exits(a: Bool) -> Nil

Set whether the current process is to trap exit signals or not.

When not trapping exits if a linked process crashes the exit signal propagates to the process which will also crash. This is the normal behaviour before this function is called.

When trapping exits (after this function is called) if a linked process crashes an exit message is sent to the process instead. These messages can be handled with the select_trapped_exits function.

pub fn unlink(pid: Pid) -> Nil

Removes any existing link between the caller process and the target process.

pub fn unregister(name: Name(message)) -> Result(Nil, Nil)

Un-register a process name, after which the process can no longer be looked up by that name, and both the name and the process can be re-used in other registrations.

It is possible to un-register process that are not from your application, including those from Erlang/OTP itself. This is not recommended and will likely result in undesirable behaviour and crashes.

Search Document