Skip to content

Commit

Permalink
Replace "on the form" with "of the form"
Browse files Browse the repository at this point in the history
"On the form" is used when something is written on a paper or
electronic form, for example on a tax form.

To express that something has the shape or structure of something
else, the correct expression is "of the form" or "in the form".

Thanks to Richard O'Keefe for pointing this out. See
https://erlangforums.com/t/otp-28-0-rc1-released/4482/3.
  • Loading branch information
bjorng committed Feb 14, 2025
1 parent 53e6751 commit b33abad
Show file tree
Hide file tree
Showing 38 changed files with 47 additions and 47 deletions.
2 changes: 1 addition & 1 deletion erts/doc/guides/alt_dist.md
Original file line number Diff line number Diff line change
Expand Up @@ -213,7 +213,7 @@ The following functions are mandatory:
may not be the process registered as `net_kernel`) and is in this document
identified as `Kernel`. When a connection has been accepted by the acceptor
process, it needs to inform `Kernel` about the accepted connection. This is
done by passing a message on the form:
done by passing a message of the form:

```erlang
Kernel ! {accept, AcceptorPid, DistController, Family, Proto}
Expand Down
2 changes: 1 addition & 1 deletion erts/doc/references/epmd_cmd.md
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ This daemon acts as a name server on all hosts involved in distributed Erlang
computations. When an Erlang node starts, the node has a name and it obtains an
address from the host OS kernel. The name and address are sent to the `epmd`
daemon running on the local host. In a TCP/IP environment, the address consists
of the IP address and a port number. The node name is an atom on the form of
of the IP address and a port number. The node name is an atom of the form
`Name@Node`. The job of the `epmd` daemon is to keep track of which node name
listens on which address. Hence, `epmd` maps symbolic node names to machine
addresses.
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_driver.h
Original file line number Diff line number Diff line change
Expand Up @@ -503,7 +503,7 @@ EXTERN int null_func(void);

/* ErlDrvTerm is the type to use for casts when building
* terms that should be sent to connected process,
* for instance a tuple on the form {tcp, Port, [Tag|Binary]}
* for instance a tuple of the form {tcp, Port, [Tag|Binary]}
*
* ErlDrvTerm spec[] = {
* ERL_DRV_ATOM, driver_mk_atom("tcp"),
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_process.c
Original file line number Diff line number Diff line change
Expand Up @@ -11177,7 +11177,7 @@ dispatch_system_task(Process *c_p, erts_aint_t fail_state,
ERTS_BIF_PREP_RET(ret, am_ok);

/*
* Send message on the form: {Requester, Target, Operation}
* Send message of the form: {Requester, Target, Operation}
*/

ASSERT(is_immed(st->requester));
Expand Down
4 changes: 2 additions & 2 deletions erts/preloaded/src/erlang.erl
Original file line number Diff line number Diff line change
Expand Up @@ -10562,7 +10562,7 @@ Asynchronously send a spawn request. Returns a request identifier `ReqId`.
If the spawn operation succeeds, a new process is created on the node identified
by `Node`. When a spawn operation succeeds, the caller will by default be sent a
message on the form `{ReplyTag, ReqId, ok, Pid}` where `Pid` is the process
message of the form `{ReplyTag, ReqId, ok, Pid}` where `Pid` is the process
identifier of the newly created process. Such a message is referred to as a
_success message_ below in the text. `ReplyTag` is by default the atom
`spawn_reply` unless modified by the `{reply_tag, ReplyTag}` option. The new
Expand Down Expand Up @@ -11764,7 +11764,7 @@ equals `DHandle` used when setting this option. When the `get_size` option is:
- **`true`** - and there are distribution data available, a call to
`erlang:dist_ctrl_get_data(DHandle)` will return `Data` to pass over the
channel as well as the `Size` of `Data` in bytes. This is returned as a tuple
on the form `{Size, Data}`.
of the form `{Size, Data}`.
All options are set to default when a channel is closed.
Expand Down
2 changes: 1 addition & 1 deletion lib/common_test/doc/guides/run_test_chapter.md
Original file line number Diff line number Diff line change
Expand Up @@ -633,7 +633,7 @@ The step functionality can be used together with flag/option `suite` and `suite`
The most flexible way to specify what to test, is to use a test specification,
which is a sequence of Erlang terms. The terms are normally declared in one or
more text files (see `ct:run_test/1`), but can also be passed to `Common Test`
on the form of a list (see `ct:run_testspec/1`). There are two general types of
in the form of a list (see `ct:run_testspec/1`). There are two general types of
terms: configuration terms and test specification terms.

With configuration terms it is, for example, possible to do the following:
Expand Down
4 changes: 2 additions & 2 deletions lib/common_test/doc/guides/write_test_chapter.md
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ communication protocols such as RPC, SNMP, FTP, Telnet, and others.
## Test Suites

A test suite is an ordinary Erlang module that contains test cases. It is
recommended that the module has a name on the form `*_SUITE.erl`. Otherwise, the
recommended that the module has a name of the form `*_SUITE.erl`. Otherwise, the
directory and auto compilation function in `Common Test` cannot locate it (at
least not by default).

Expand Down Expand Up @@ -254,7 +254,7 @@ The following tags have special meaning:

A required variable can also be given a default value to be used if the
variable is not found in any configuration file. To specify a default value,
add a tuple on the form `{default_config,ConfigVariableName,Value}` to the
add a tuple of the form `{default_config,ConfigVariableName,Value}` to the
test case information list (the position in the list is irrelevant).

_Examples:_
Expand Down
2 changes: 1 addition & 1 deletion lib/common_test/test_server/ts_run.erl
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ ct_run_test(Dir, CommonTestArgs) ->
end.

%%
%% Deletes File from Files when File is on the form .../<SUITE>_data/<file>
%% Deletes File from Files when File is of the form .../<SUITE>_data/<file>
%% when all of <SUITE> has been skipped in Spec, i.e. there
%% exists a {skip, {<SUITE>, _}} tuple in Spec.
%%
Expand Down
2 changes: 1 addition & 1 deletion lib/compiler/src/cerl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1774,7 +1774,7 @@ A variable is identified by its name, given by the `Name` parameter.
If a name is given by a single atom, it should either be a "simple" atom which
does not need to be single-quoted in Erlang, or otherwise its print name should
correspond to a proper Erlang variable, that is, begin with an uppercase character
or an underscore. Names on the form `{A, N}` represent function name variables
or an underscore. Names of the form `{A, N}` represent function name variables
"`A/N`"; these are special variables which may be bound only in the function
definitions of a module or a `letrec`. They may not be bound in `let`
expressions and cannot occur in clause patterns. The atom `A` in a function name
Expand Down
2 changes: 1 addition & 1 deletion lib/compiler/src/cerl_trees.erl
Original file line number Diff line number Diff line change
Expand Up @@ -821,7 +821,7 @@ labeled.
The returned value is a tuple `{NewTree, Max}`, where `NewTree` is the labeled
tree and `Max` is 1 plus the largest label value used. All previous annotation
terms on the form `{label, X}` are deleted.
terms of the form `{label, X}` are deleted.
The values of L used in the tree is a dense range from `N` to `Max - 1`, where
`N =< Max =< N + size(Tree)`. Note that it is possible that no labels are used
Expand Down
2 changes: 1 addition & 1 deletion lib/compiler/src/compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -657,7 +657,7 @@ value are listed.
be deprecated.
- **`warn_deprecated_catch`** - Enables warnings for use of old style catch
expressions on the form `catch Expr` instead of the modern `try ... catch
expressions of the form `catch Expr` instead of the modern `try ... catch
... end`. You may enable this compiler option on the project level and
add `-compile(nowarn_deprecated_catch).` to individual files which still
contain old catches in order to prevent new uses from getting added.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@

%% Expand function definition forms of parameterized module. We assume
%% all record definitions, imports, queries, etc., have been expanded
%% away. Any calls on the form 'foo(...)' must be calls to local
%% away. Any calls of the form 'foo(...)' must be calls to local
%% functions. Auto-generated functions (module_info,...) have not yet
%% been added to the function definitions, but are listed in 'defined'
%% and 'exports'. The 'new/N' function is neither added to the
Expand Down
2 changes: 1 addition & 1 deletion lib/edoc/doc/guides/chapter.md
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ documentation for other tools like `m:shell_docs`.
## Introduction

EDoc lets you write the documentation of an Erlang program as comments in the
source code itself, using _tags_ on the form "`@Name ...`". A source file does
source code itself, using _tags_ of the form "`@Name ...`". A source file does
not have to contain tags for EDoc to generate its documentation, but without
tags the result will only contain the basic available information that can be
extracted from the module.
Expand Down
2 changes: 1 addition & 1 deletion lib/eunit/src/eunit_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -368,7 +368,7 @@ context_error(Type, Class, Trace, Term) ->
throw({context_error, Type, {Class, Term, get_stacktrace(Trace)}}).

%% This generates single setup/cleanup functions from a list of tuples
%% on the form {Tag, Setup, Cleanup}, where the setup function always
%% of the form {Tag, Setup, Cleanup}, where the setup function always
%% backs out correctly from partial completion.

multi_setup(List) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/doc/guides/logger_chapter.md
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,7 @@ The handlers are called in sequence, and the order is not defined.
## Logger API

The API for logging consists of a set of [macros](`m:logger#module-macros`), and a set
of functions on the form `logger:Level/1,2,3`, which are all shortcuts for
of functions of the form `logger:Level/1,2,3`, which are all shortcuts for
[`logger:log(Level,Arg1[,Arg2[,Arg3]])`](`logger:log/2`).

The macros are defined in `logger.hrl`, which is included in a module with the
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/src/inet.erl
Original file line number Diff line number Diff line change
Expand Up @@ -377,7 +377,7 @@ Add the following directive to the module:
-doc """
A general network address.
A general network address format on the form `{Family, Destination}`
A general network address format of the form `{Family, Destination}`
where `Family` is an atom such as `local` and the format of `Destination`
depends on `Family`. `Destination` is a complete address (for example
an IP address with port number).
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/src/logger_formatter.erl
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ following keys can be set as configuration parameters:
An empty string is interpreted as local time. The values `"Z"`, `"z"` or `0`
are interpreted as Universal Coordinated Time (UTC).
Strings, other than `"Z"`, `"z"`, or `""`, must be on the form `±[hh]:[mm]`,
Strings, other than `"Z"`, `"z"`, or `""`, must be of the form `±[hh]:[mm]`,
for example `"-02:00"` or `"+00:00"`.
Integers must be in microseconds, meaning that the offset `7200000000` is
Expand Down
6 changes: 3 additions & 3 deletions lib/kernel/src/rpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -593,8 +593,8 @@ rpc_check(X) -> X.


%% This is a real handy function to be used when interacting with
%% a server called Name at node Node, It is assumed that the server
%% Receives messages on the form {From, Request} and replies on the
%% a server called Name at node Node. It is assumed that the server
%% receives messages of the form {From, Request} and replies are of the
%% form From ! {ReplyWrapper, Node, Reply}.
%% This function makes such a server call and ensures that that
%% The entire call is packed into an atomic transaction which
Expand Down Expand Up @@ -905,7 +905,7 @@ rpcmulticallify([_N|Ns], [{Class, Reason}|Rlts], Ok, Err) ->
%% that failed during the timespan of the call.
%% This function assumes that if we send a request to a server
%% called Name, the server will reply with a reply
%% on the form {Name, Node, Reply}, otherwise this function will
%% of the form {Name, Node, Reply}, otherwise this function will
%% hang forever.
%% It also assumes that the server receives messages on the form
%% {From, Msg} and then replies as From ! {Name, node(), Reply}.
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/src/socket.erl
Original file line number Diff line number Diff line change
Expand Up @@ -952,7 +952,7 @@ internal use only.
-doc """
Socket option.

Socket options on the form `{Level, Opt}` where the OS protocol `Level` =
Socket options of the form `{Level, Opt}` where the OS protocol `Level` =
`t:level/0` and `Opt` is a socket option on that protocol level.

The OS name for an options is, except where otherwise noted, the `Opt` atom, in
Expand Down
2 changes: 1 addition & 1 deletion lib/mnesia/src/mnesia_index.erl
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ merge([], _, _, Ack) ->

realkeys(Tab, Pos, IxKey) ->
Index = get_index_table(Tab, Pos),
db_get(Index, IxKey). % a list on the form [{IxKey, RealKey1} , ....
db_get(Index, IxKey). % a list of the form [{IxKey, RealKey1} , ....

dirty_select(Tab, Spec, Pos) when is_integer(Pos) ->
%% Assume that we are on the node where the replica is
Expand Down
2 changes: 1 addition & 1 deletion lib/snmp/src/agent/snmpa_agent.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2810,7 +2810,7 @@ v2err_to_v1err(_Error) -> genErr.
%% transforms a (hopefully correct) return value ((perhaps) from a
%% mib-function) to a typed and guaranteed correct return value.
%% An incorrect return value is transformed to {error, genErr}.
%% A correct return value is on the form:
%% A correct return value is of the form:
%% {error, <error-msg>} | {value, <variable-type>, <value>}
%%-----------------------------------------------------------------
make_value_a_correct_value({value, Val}, Asn1, Mfa)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ following functions:
The semantics of them and their exact signatures are explained below.
Legacy notification delivery information receiver modules used a target argument
on the form `{IpAddr, PortNumber}` instead of `{Domain, Addr}`, and if the SNMP
of the form `{IpAddr, PortNumber}` instead of `{Domain, Addr}`, and if the SNMP
Agent is run without changing the configuration to use transport domains the
notification delivery information receiver will still get the old arguments and
work as before.
Expand Down
2 changes: 1 addition & 1 deletion lib/snmp/test/snmp_test_mgr_misc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@


%%----------------------------------------------------------------------
%% The InHandler process will receive messages on the form {snmp_pdu, Pdu}.
%% The InHandler process will receive messages of the form {snmp_pdu, Pdu}.
%%----------------------------------------------------------------------

start_link_packet(
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/erl_eval.erl
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ called for such calls. The argument can have the following formats:
```

`Anno` is the [`erl_anno:anno()`](`t:erl_anno:anno/0`) of the node, `FuncSpec`
is the name of the function on the form `{Module,Function}` or a fun, and
is the name of the function of the form `{Module,Function}` or a fun, and
`Arguments` is a list of the _evaluated_ arguments. The function handler
returns the value of the function. To signal an error, the function handler
calls [`exit/1`](`exit/1`) with a suitable exit value.
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/gen_event.erl
Original file line number Diff line number Diff line change
Expand Up @@ -940,7 +940,7 @@ or returns an unexpected value `Term`, this function returns
`{error, {'EXIT', Reason}}` or `{error, Term}`, respectively.

When this call fails it [exits](`erlang:exit/1`) the calling process.
The exit term is on the form `{Reason, Location}` where
The exit term is of the form `{Reason, Location}` where
`Location = {gen_event, call, ArgList}`. See `gen_server:call/3`
that has a description of relevant values for the `Reason`
in the exit term.
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/gen_fsm.erl
Original file line number Diff line number Diff line change
Expand Up @@ -746,7 +746,7 @@ of the `gen_fsm` process.

The function is to return `Status`, a term that change the details
of the current state and status of the `gen_fsm` process.
There are no restrictions on the form `Status` can take,
There are no restrictions of the form `Status` can take,
but for the [`sys:get_status/1,2`](`sys:get_status/1`) case
(when `Opt` is `normal`), the recommended form for the `Status` value
is `[{data, [{"StateData", Term}]}]`, where `Term` provides
Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/src/gen_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -571,7 +571,7 @@ of the `gen_server` process..

The function is to return `Status`, a term that changes the details
of the current state and status of the `gen_server` process.
There are no restrictions on the form `Status` can take,
There are no restrictions of the form `Status` can take,
but for the `sys:get_status/1,2` case (when `Opt` is `normal`),
the recommended form for the `Status` value is
`[{data, [{"State", Term}]}]`, where `Term` provides relevant details
Expand Down Expand Up @@ -1177,7 +1177,7 @@ process with an exit term containing `Reason = timeout` as described below.
> with the reply, it may arrive to the process message queue
> any time later. The calling process must therefore after
> catching a time-out exit be prepared to receive garbage message(s)
> on the form `{reference(), _}` and deal with them appropriately
> of the form `{reference(), _}` and deal with them appropriately
> (discard them) so they do not clog the process message queue,
> or gets mistaken for other messages.
>
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1851,7 +1851,7 @@ that returns a term describing the current status of the `gen_statem`.

The function is to return `Status`, a term that contains
the appropriate details of the current state and status
of the `gen_statem`. There are no restrictions on the form `Status`
of the `gen_statem`. There are no restrictions of the form `Status`
can take, but for the [`sys:get_status/1,2`](`sys:get_status/1`) case
(when `Opt` is `normal`), the recommended form for the `Status` value
is `[{data, [{"State", Term}]}]`, where `Term` provides relevant details
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/qlc_pt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2284,7 +2284,7 @@ bindings_subset(F1, F2, Imp) ->
deref_var(V, F1, Imp) =:= deref_var(V, F2, Imp)
end, Vars).

%% Recognizes all QLCs on the form [T || P <- LE, F] such that
%% Recognizes all QLCs of the form [T || P <- LE, F] such that
%% ets:fun2ms(fun(P) when F -> T end) is a match spec. This is OK with
%% the guard semantics implemented in filter/_ below. If one chooses
%% not to have guard semantics, affected filters will have to be
Expand Down
8 changes: 4 additions & 4 deletions lib/stdlib/src/rand.erl
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ relying on them will produce the same pseudo random sequences as before.
> less than 0.5 had got smaller intervals decreasing as the generated value
> approached 0.0 although still uniformly distributed for sufficiently large
> subranges. The new algorithms produces uniformly distributed floats
> on the form `N * 2.0^(-53)` hence they are equally spaced.
> of the form `N * 2.0^(-53)` hence they are equally spaced.

[](){: #generator-state }
#### Generator State
Expand Down Expand Up @@ -391,7 +391,7 @@ the generator's range:
(IEEE 745 Double, that has got a 53-bit mantissa) in the range
`0..1`, that is `0.0 =< V < 1.0` is to generate a 53-bit number `X`
and then use `V = X * (1.0/((1 bsl 53)))` as your value.
This will create a value on the form N*2^-53 with equal probability
This will create a value of the form N*2^-53 with equal probability
for every possible N for the range.
""".
-moduledoc(#{since => "OTP 18.0",
Expand Down Expand Up @@ -794,7 +794,7 @@ From the specified `State`, generates a random number `X ::` `t:float/0`,
uniformly distributed in the value range `0.0 =< X < 1.0`.
Returns the number `X` and the updated `NewState`.

The generated numbers are on the form `N * 2.0^(-53)`, that is;
The generated numbers are of the form `N * 2.0^(-53)`, that is;
equally spaced in the interval.

> #### Warning {: .warning }
Expand All @@ -820,7 +820,7 @@ uniform_s(State = {#{uniform:=Uniform}, _}) ->
Uniform(State);
uniform_s({#{bits:=Bits, next:=Next} = AlgHandler, R0}) ->
{V, R1} = Next(R0),
%% Produce floats on the form N * 2^(-53)
%% Produce floats of the form N * 2^(-53)
{(V bsr (Bits - 53)) * ?TWO_POW_MINUS53, {AlgHandler, R1}};
uniform_s({#{max:=Max, next:=Next} = AlgHandler, R0}) ->
{V, R1} = Next(R0),
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/src/sys.erl
Original file line number Diff line number Diff line change
Expand Up @@ -745,7 +745,7 @@ remove(Name, FuncOrFuncId, Timeout) ->
send_system_msg(Name, {debug, {remove, FuncOrFuncId}}, Timeout).

%%-----------------------------------------------------------------
%% All system messages sent are on the form {system, From, Msg}
%% All system messages sent are of the form {system, From, Msg}
%% The receiving side should send Msg to handle_system_msg/5.
%%-----------------------------------------------------------------
send_system_msg(Name, Request) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/test/ets_tough_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -787,7 +787,7 @@ table_lookup(Table, Key) ->
%%% table_lookup_batch(Tables, Class, Cond) -> KeyList
%%%
%%% Extract the keys from a table or a table group.
%%% If a condition is supplied, it is on the form {Mod, Fun, ExtraArgs}
%%% If a condition is supplied, it is of the form {Mod, Fun, ExtraArgs}
%%% and returns {true,Key} or false when called using
%%% apply(Mod, Fun, [Instance|ExtraArgs]).
%%% Instance is, for historic reasons, {{Class, Key}, Value} when the function
Expand Down
4 changes: 2 additions & 2 deletions lib/syntax_tools/src/erl_syntax.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2512,7 +2512,7 @@ is_list_skeleton(Node) ->
-doc """
Returns `true` if `Node` represents a proper list, and `false` otherwise.

A proper list is a list skeleton either on the form "`[]`" or "`[E1,
A proper list is a list skeleton either of the form "`[]`" or "`[E1,
..., En]`", or "`[... | Tail]`" where recursively `Tail` also
represents a proper list.

Expand Down Expand Up @@ -3476,7 +3476,7 @@ module_qualifier_body(Node) ->


%% Don't use the name 'function' for this record, to avoid confusion with
%% the tuples on the form {function,Name,Arity} used by erl_parse.
%% the tuples of the form {function,Name,Arity} used by erl_parse.
%%
%% (There's no real point in precomputing and storing the arity,
%% and passing it as a constructor argument makes it possible to
Expand Down
2 changes: 1 addition & 1 deletion lib/syntax_tools/src/prettypr.erl
Original file line number Diff line number Diff line change
Expand Up @@ -622,7 +622,7 @@ flatrev([], As, []) ->
%% selects the "best" layout of a document, returning a simplified
%% representation that can be given directly to `layout', unless the
%% returned value is `empty', signaling that no layout could be
%% produced. In addition, documents on the form `#union{d1 = D1, d2 =
%% produced. In addition, documents of the form `#union{d1 = D1, d2 =
%% D2}' and `#fit{d = D}' are used internally.
%%
%% Note: It is vital for this algorithm to maintain the invariant on
Expand Down
Loading

0 comments on commit b33abad

Please sign in to comment.