Skip to content

Commit

Permalink
Document and test node functions
Browse files Browse the repository at this point in the history
  • Loading branch information
lpil committed Aug 30, 2023
1 parent 63e5b5c commit 20c1156
Show file tree
Hide file tree
Showing 4 changed files with 65 additions and 12 deletions.
8 changes: 8 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,13 @@
# Changelog

## v0.22.0 - Unreleased

- The `gleam/erlang/process` module gains the `register`, `unregister`, and
`named` functions.
- The `gleam/erlang/node` module has been created with the `Node` and
`ConnectError` types, and the `self`, `visible`, `connect`, `send`, and
`to_atom` functions.

## v0.21.0 - 2023-08-25

- The `gleam/erlang` module gains the `priv_directory` function.
Expand Down
39 changes: 29 additions & 10 deletions src/gleam/erlang/node.gleam
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,23 @@ pub type Node

type DoNotLeak

// TODO: test
// TODO: document
/// Return the current node.
///
@external(erlang, "erlang", "node")
pub fn self() -> Node

// TODO: test
// TODO: document
/// Return a list of all visible nodes in the cluster, not including the current
/// node.
///
/// The current node can be included by calling `self()` and prepending the
/// result.
///
/// ```gleam
/// let all_nodes = [node.self(), ..node.visible()]
/// ```
///
@external(erlang, "erlang", "nodes")
pub fn list() -> List(Node)
pub fn visible() -> List(Node)

pub type ConnectError {
/// Was unable to connect to the node.
Expand All @@ -22,13 +30,24 @@ pub type ConnectError {
LocalNodeIsNotAlive
}

// TODO: test
// TODO: document
// TODO: test unknown node
// TODO: test successfully connecting
/// Establish a connection to a node, so the nodes can send messages to each
/// other and any other connected nodes.
///
/// Returns `Error(FailedToConnect)` if the node is not reachable.
///
/// Returns `Error(LocalNodeIsNotAlive)` if the local node is not alive, meaning
/// it is not running in distributed mode.
///
@external(erlang, "gleam_erlang_ffi", "connect_node")
pub fn connect(node: Atom) -> Result(Node, ConnectError)

// TODO: test
// TODO: document
/// Send a message to a named process on a given node.
///
/// These messages are untyped, like regular Erlang messages.
///
pub fn send(node: Node, name: Atom, message: message) -> Nil {
raw_send(#(name, node), message)
Nil
Expand All @@ -37,7 +56,7 @@ pub fn send(node: Node, name: Atom, message: message) -> Nil {
@external(erlang, "erlang", "send")
fn raw_send(receiver: #(Atom, Node), message: message) -> DoNotLeak

// TODO: test
// TODO: document
/// Convert a node to the atom of its name.
///
@external(erlang, "gleam_erlang_ffi", "identity")
pub fn to_atom(node: Node) -> Atom
7 changes: 5 additions & 2 deletions src/gleam_erlang_ffi.erl
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
insert_selector_handler/3, select/1, select/2, trap_exits/1, map_selector/2,
merge_selector/2, flush_messages/0, file_info/1, link_info/1,
priv_directory/1, connect_node/1, register_process/2, unregister_process/1,
process_named/1
process_named/1, identity/1
]).

-define(is_posix_error(Error),
Expand Down Expand Up @@ -234,7 +234,7 @@ connect_node(Node) ->
case net_kernel:connect_node(Node) of
true -> {ok, Node};
false -> {error, failed_to_connect};
ignored -> {error, local_node_is_not_online}
ignored -> {error, local_node_is_not_alive}
end.

register_process(Pid, Name) ->
Expand All @@ -258,3 +258,6 @@ process_named(Name) ->
Pid when is_pid(Pid) -> {ok, Pid};
_ -> {error, nil}
end.

identity(X) ->
X.
23 changes: 23 additions & 0 deletions test/gleam/erlang/node_tests.gleam
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
import gleam/erlang/node
import gleam/erlang/atom

// TODO: Improve these tests by spawning a peer node.

pub fn self_test() {
let a = node.self()
let b = node.self()
let assert True = a == b
}

pub fn visible_test() {
let assert [] = node.visible()
}

pub fn connect_not_alive_test() {
let name = atom.create_from_string("not_found@localhost")
let assert Error(node.LocalNodeIsNotAlive) = node.connect(name)
}

pub fn to_atom_test() {
let assert "nonode@nohost" = atom.to_string(node.to_atom(node.self()))
}

0 comments on commit 20c1156

Please sign in to comment.