Skip to content

Commit 0602b06

Browse files
committed
Don't use protocol name aliases for socket option names
1 parent 5ce7212 commit 0602b06

File tree

3 files changed

+26
-46
lines changed

3 files changed

+26
-46
lines changed

Diff for: erts/emulator/nifs/common/prim_socket_nif.c

+1-2
Original file line numberDiff line numberDiff line change
@@ -5088,8 +5088,7 @@ ERL_NIF_TERM esock_supports_options(ErlNifEnv* env)
50885088
}
50895089
levels =
50905090
MKC(env,
5091-
MKT2(env,
5092-
esock_encode_level(env, levelP->level), options),
5091+
MKT3(env, *levelP->nameP, MKI(env, levelP->level), options),
50935092
levels);
50945093
}
50955094

Diff for: erts/preloaded/ebin/prim_socket.beam

-96 Bytes
Binary file not shown.

Diff for: erts/preloaded/src/prim_socket.erl

+25-44
Original file line numberDiff line numberDiff line change
@@ -164,15 +164,14 @@ on_load(Extra) when is_map(Extra) ->
164164
init().
165165

166166
init() ->
167-
PT =
168-
put_supports_table(protocols,
169-
fun (Protocols) -> protocols_table(Protocols) end),
170-
_ = put_supports_table(options,
171-
fun (Options) -> options_table(Options, PT) end),
172-
_ = put_supports_table(ioctl_requests,
173-
fun (Requests) -> Requests end),
174-
_ = put_supports_table(ioctl_flags, fun (Flags) -> Flags end),
175-
_ = put_supports_table(msg_flags, fun (Flags) -> Flags end),
167+
put_supports_table(protocols,
168+
fun (Protocols) -> protocols_table(Protocols) end),
169+
put_supports_table(options,
170+
fun (Options) -> options_table(Options) end),
171+
put_supports_table(ioctl_requests,
172+
fun (Requests) -> Requests end),
173+
put_supports_table(ioctl_flags, fun (Flags) -> Flags end),
174+
put_supports_table(msg_flags, fun (Flags) -> Flags end),
176175
ok.
177176

178177
put_supports_table(Tag, MkTable) ->
@@ -184,8 +183,7 @@ put_supports_table(Tag, MkTable) ->
184183
error : notsup ->
185184
#{}
186185
end,
187-
p_put(Tag, Table),
188-
Table.
186+
p_put(Tag, Table).
189187

190188
%% Like maps:from_list/1 the last duplicate key wins,
191189
%% except if both values are lists; append the second to the first.
@@ -219,41 +217,24 @@ protocols_table(Protocols, [], _Num) ->
219217
protocols_table(Protocols).
220218

221219
%% ->
222-
%% [{{socket,Opt}, {socket,OptNum}} |
223-
%% {{Level, Opt}, {LevelNum, OptNum}} for all Levels (protocol aliases)]
224-
options_table([], _PT) ->
220+
%% [{{socket,Opt}, {socket,OptNum} | undefined} |
221+
%% {{Level, Opt}, {LevelNum, OptNum} | undefined}]
222+
options_table([]) ->
225223
[];
226-
options_table([{socket, LevelOpts} | Options], PT) ->
227-
options_table(Options, PT, socket, LevelOpts, [socket]);
228-
options_table([{LevelNum, LevelOpts} | Options], PT) ->
229-
Levels = maps:get(LevelNum, PT),
230-
options_table(Options, PT, LevelNum, LevelOpts, Levels).
224+
options_table([{socket = Level, _LevelNum, LevelOpts} | Options]) ->
225+
options_table(Options, Level, Level, LevelOpts);
226+
options_table([{Level, LevelNum, LevelOpts} | Options]) ->
227+
options_table(Options, Level, LevelNum, LevelOpts).
231228
%%
232-
options_table(Options, PT, _Level, [], _Levels) ->
233-
options_table(Options, PT);
234-
options_table(Options, PT, Level, [LevelOpt | LevelOpts], Levels) ->
235-
LevelOptNum =
236-
case LevelOpt of
237-
{Opt, OptNum} ->
238-
{Level,OptNum};
239-
Opt when is_atom(Opt) ->
240-
undefined
241-
end,
242-
options_table(
243-
Options, PT, Level, LevelOpts, Levels,
244-
Opt, LevelOptNum, Levels).
245-
%%
246-
options_table(
247-
Options, PT, Level, LevelOpts, Levels,
248-
_Opt, _LevelOptNum, []) ->
249-
options_table(Options, PT, Level, LevelOpts, Levels);
250-
options_table(
251-
Options, PT, Level, LevelOpts, Levels,
252-
Opt, LevelOptNum, [L | Ls]) ->
253-
[{{L,Opt}, LevelOptNum} |
254-
options_table(
255-
Options, PT, Level, LevelOpts, Levels,
256-
Opt, LevelOptNum, Ls)].
229+
options_table(Options, _Level, _LevelNum, []) ->
230+
options_table(Options);
231+
options_table(Options, Level, LevelNum, [LevelOpt | LevelOpts]) ->
232+
[case LevelOpt of
233+
{Opt, OptNum} ->
234+
{{Level, Opt}, {LevelNum,OptNum}};
235+
Opt when is_atom(Opt) ->
236+
{{Level, Opt}, undefined}
237+
end | options_table(Options, Level, LevelNum, LevelOpts)].
257238

258239
%% ===========================================================================
259240
%% API for 'socket'

0 commit comments

Comments
 (0)