Skip to content

Commit a66a465

Browse files
committed
ssh: polish docs around types
1 parent 6bf99d6 commit a66a465

File tree

2 files changed

+24
-19
lines changed

2 files changed

+24
-19
lines changed

lib/ssh/src/ssh.erl

Lines changed: 15 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,8 @@ The directory could be changed with the option
135135
[{type,<<"Client Options">>},
136136
{type,<<"Daemon Options">>},
137137
{type,<<"Common Options">>},
138-
{type,<<"Other data types">>}]}).
138+
{type,<<"Deprecated Types">>},
139+
{type,<<"Other Data Types">>}]}).
139140

140141
-include("ssh.hrl").
141142
-include("ssh_connect.hrl").
@@ -174,8 +175,11 @@ The directory could be changed with the option
174175

175176
%%% "Deprecated" types export:
176177
-export_type([ssh_daemon_ref/0, ssh_connection_ref/0, ssh_channel_id/0]).
178+
-doc(#{title => <<"Deprecated Types">>}).
177179
-opaque ssh_daemon_ref() :: daemon_ref().
180+
-doc(#{title => <<"Deprecated Types">>}).
178181
-opaque ssh_connection_ref() :: connection_ref().
182+
-doc(#{title => <<"Deprecated Types">>}).
179183
-opaque ssh_channel_id() :: channel_id().
180184

181185

@@ -208,15 +212,15 @@ Opaque data type representing a daemon.
208212

209213
Returned by the functions [`daemon/1,2,3`](`daemon/1`).
210214
""".
211-
-doc(#{title => <<"Other data types">>}).
215+
-doc(#{title => <<"Other Data Types">>}).
212216
-opaque daemon_ref() :: pid() .
213217
-doc """
214218
Opaque data type representing a channel inside a connection.
215219

216220
Returned by the functions
217221
[ssh_connection:session_channel/2,4](`ssh_connection:session_channel/2`).
218222
""".
219-
-doc(#{title => <<"Other data types">>}).
223+
-doc(#{title => <<"Other Data Types">>}).
220224
-opaque channel_id() :: non_neg_integer().
221225
-doc """
222226
Opaque data type representing a connection between a client and a server
@@ -225,7 +229,7 @@ Opaque data type representing a connection between a client and a server
225229
Returned by the functions [`connect/2,3,4`](`connect/3`) and
226230
[`ssh_sftp:start_channel/2,3`](`ssh_sftp:start_channel/2`).
227231
""".
228-
-doc(#{title => <<"Other data types">>}).
232+
-doc(#{title => <<"Other Data Types">>}).
229233
-type connection_ref() :: pid(). % should be -opaque, but that gives problems
230234

231235
%%--------------------------------------------------------------------
@@ -427,13 +431,13 @@ close(ConnectionRef) ->
427431
%%--------------------------------------------------------------------
428432
%% Description: Retrieves information about a connection.
429433
%%---------------------------------------------------------------------
430-
-doc(#{title => <<"Other data types">>}).
434+
-doc(#{title => <<"Other Data Types">>}).
431435
-type version() :: {protocol_version(), software_version()}.
432-
-doc(#{title => <<"Other data types">>}).
436+
-doc(#{title => <<"Other Data Types">>}).
433437
-type protocol_version() :: {Major::pos_integer(), Minor::non_neg_integer()}.
434-
-doc(#{title => <<"Other data types">>}).
438+
-doc(#{title => <<"Other Data Types">>}).
435439
-type software_version() :: string().
436-
-doc(#{title => <<"Other data types">>}).
440+
-doc(#{title => <<"Other Data Types">>}).
437441
-type conn_info_algs() :: [{kex, kex_alg()}
438442
| {hkey, pubkey_alg()}
439443
| {encrypt, cipher_alg()}
@@ -451,10 +455,10 @@ Return values from the `connection_info/1` and `connection_info/2` functions.
451455
In the `option` info tuple are only the options included that differs from the
452456
default values.
453457
""".
454-
-doc(#{title => <<"Other data types">>}).
458+
-doc(#{title => <<"Other Data Types">>}).
455459
-type conn_info_channels() :: [proplists:proplist()].
456460

457-
-doc(#{title => <<"Other data types">>}).
461+
-doc(#{title => <<"Other Data Types">>}).
458462
-type connection_info_tuple() ::
459463
{client_version, version()}
460464
| {server_version, version()}
@@ -691,7 +695,7 @@ Return values from the `daemon_info/1` and `daemon_info/2` functions.
691695
In the `option` info tuple are only the options included that differs from the
692696
default values.
693697
""".
694-
-doc(#{title => <<"Other data types">>}).
698+
-doc(#{title => <<"Other Data Types">>}).
695699
-type daemon_info_tuple() ::
696700
{port, inet:port_number()}
697701
| {ip, inet:ip_address()}

lib/ssh/src/ssh.hrl

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -122,16 +122,17 @@
122122

123123

124124
%% Types
125+
-doc(#{title => <<"Other Data Types">>}).
125126
-type role() :: client | server .
126127

127-
-doc(#{title => <<"Other data types">>}).
128+
-doc(#{title => <<"Other Data Types">>}).
128129
-type host() :: string() | inet:ip_address() | loopback .
129130
-doc """
130131
The socket is supposed to be result of a [gen_tcp:connect](`gen_tcp:connect/3`)
131132
or a [gen_tcp:accept](`gen_tcp:accept/1`). The socket must be in passive mode
132133
(that is, opened with the option `{active,false})`.
133134
""".
134-
-doc(#{title => <<"Other data types">>}).
135+
-doc(#{title => <<"Other Data Types">>}).
135136
-type open_socket() :: gen_tcp:socket().
136137

137138
-doc """
@@ -514,7 +515,7 @@ protocol).
514515
Opaque types that define experimental options that are not to be used in
515516
products.
516517
""".
517-
-doc(#{title => <<"Other data types">>}).
518+
-doc(#{title => <<"Other Data Types">>}).
518519
-type opaque_common_options() ::
519520
{transport, {atom(),atom(),atom()} }
520521
| {vsn, {non_neg_integer(),non_neg_integer()} }
@@ -547,7 +548,7 @@ risk.
547548
| gen_tcp:connect_option()
548549
| ?COMMON_OPTION .
549550

550-
-doc(#{title => <<"Other data types">>}).
551+
-doc(#{title => <<"Other Data Types">>}).
551552
-type opaque_client_options() ::
552553
{keyboard_interact_fun, fun((Name::iodata(),
553554
Instruction::iodata(),
@@ -1149,17 +1150,17 @@ in the User's Guide chapter.
11491150
{failfun, fun((User::string(), PeerAddress::inet:ip_address(), Reason::term()) -> _)}
11501151
| {connectfun, fun((User::string(), PeerAddress::inet:ip_address(), Method::string()) ->_)} .
11511152

1152-
-doc(#{title => <<"Other data types">>}).
1153+
-doc(#{title => <<"Other Data Types">>}).
11531154
-type opaque_daemon_options() ::
11541155
{infofun, fun()}
11551156
| opaque_common_options().
11561157

1157-
-doc(#{title => <<"Other data types">>}).
1158+
-doc(#{title => <<"Other Data Types">>}).
11581159
-type ip_port() :: {inet:ip_address(), inet:port_number()} .
11591160

1160-
-doc(#{title => <<"Other data types">>}).
1161+
-doc(#{title => <<"Other Data Types">>}).
11611162
-type mod_args() :: {Module::atom(), Args::list()} .
1162-
-doc(#{title => <<"Other data types">>}).
1163+
-doc(#{title => <<"Other Data Types">>}).
11631164
-type mod_fun_args() :: {Module::atom(), Function::atom(), Args::list()} .
11641165

11651166

0 commit comments

Comments
 (0)