feat(one authn): merge simple authn and enhanced authn

This commit is contained in:
zhouzb 2021-07-14 16:53:52 +08:00
parent fe779925c5
commit 6a8e35ce3a
25 changed files with 742 additions and 976 deletions

View File

@ -18,27 +18,22 @@
-include("emqx.hrl"). -include("emqx.hrl").
-export([authenticate/1]). -export([ authenticate/1
, authorize/3
-export([ authorize/3
]). ]).
-type(result() :: #{auth_result := emqx_types:auth_result(),
anonymous := boolean()
}).
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
%% APIs %% APIs
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
-spec(authenticate(emqx_types:clientinfo()) -> {ok, result()} | {error, term()}). -spec(authenticate(emqx_types:clientinfo()) ->
authenticate(ClientInfo = #{zone := Zone}) -> ok | {ok, binary()} | {continue, map()} | {continue, binary(), map()} | {error, term()}).
AuthResult = default_auth_result(Zone), authenticate(Credential = #{zone := Zone}) ->
case emqx_zone:get_env(Zone, bypass_auth_plugins, false) of case emqx_zone:get_env(Zone, bypass_authentication, false) of
true -> true ->
return_auth_result(AuthResult); ok;
false -> false ->
return_auth_result(run_hooks('client.authenticate', [ClientInfo], AuthResult)) run_hooks('client.authenticate', [Credential], ok)
end. end.
%% @doc Check ACL %% @doc Check ACL
@ -65,18 +60,6 @@ do_authorize(ClientInfo, PubSub, Topic) ->
_Other -> deny _Other -> deny
end. end.
default_auth_result(Zone) ->
case emqx_zone:get_env(Zone, allow_anonymous, false) of
true -> #{auth_result => success, anonymous => true};
false -> #{auth_result => not_authorized, anonymous => false}
end.
-compile({inline, [run_hooks/3]}). -compile({inline, [run_hooks/3]}).
run_hooks(Name, Args, Acc) -> run_hooks(Name, Args, Acc) ->
ok = emqx_metrics:inc(Name), emqx_hooks:run_fold(Name, Args, Acc). ok = emqx_metrics:inc(Name), emqx_hooks:run_fold(Name, Args, Acc).
-compile({inline, [return_auth_result/1]}).
return_auth_result(Result = #{auth_result := success}) ->
{ok, Result};
return_auth_result(Result) ->
{error, maps:get(auth_result, Result, unknown_error)}.

View File

@ -98,7 +98,7 @@
-type(channel() :: #channel{}). -type(channel() :: #channel{}).
-type(conn_state() :: idle | connecting | connected | disconnected). -type(conn_state() :: idle | connecting | connected | reauthenticating | disconnected).
-type(reply() :: {outgoing, emqx_types:packet()} -type(reply() :: {outgoing, emqx_types:packet()}
| {outgoing, [emqx_types:packet()]} | {outgoing, [emqx_types:packet()]}
@ -272,7 +272,8 @@ take_ws_cookie(ClientInfo, ConnInfo) ->
| {ok, replies(), channel()} | {ok, replies(), channel()}
| {shutdown, Reason :: term(), channel()} | {shutdown, Reason :: term(), channel()}
| {shutdown, Reason :: term(), replies(), channel()}). | {shutdown, Reason :: term(), replies(), channel()}).
handle_in(?CONNECT_PACKET(), Channel = #channel{conn_state = connected}) -> handle_in(?CONNECT_PACKET(), Channel = #channel{conn_state = ConnState})
when ConnState =:= connected orelse ConnState =:= reauthenticating ->
handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel); handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel);
handle_in(?CONNECT_PACKET(ConnPkt), Channel) -> handle_in(?CONNECT_PACKET(ConnPkt), Channel) ->
@ -281,56 +282,64 @@ handle_in(?CONNECT_PACKET(ConnPkt), Channel) ->
fun check_connect/2, fun check_connect/2,
fun enrich_client/2, fun enrich_client/2,
fun set_log_meta/2, fun set_log_meta/2,
fun check_banned/2, fun check_banned/2
fun auth_connect/2
], ConnPkt, Channel#channel{conn_state = connecting}) of ], ConnPkt, Channel#channel{conn_state = connecting}) of
{ok, NConnPkt, NChannel = #channel{clientinfo = ClientInfo}} -> {ok, NConnPkt, NChannel = #channel{clientinfo = ClientInfo}} ->
NChannel1 = NChannel#channel{ NChannel1 = NChannel#channel{
will_msg = emqx_packet:will_msg(NConnPkt), will_msg = emqx_packet:will_msg(NConnPkt),
alias_maximum = init_alias_maximum(NConnPkt, ClientInfo) alias_maximum = init_alias_maximum(NConnPkt, ClientInfo)
}, },
case enhanced_auth(?CONNECT_PACKET(NConnPkt), NChannel1) of case authenticate(?CONNECT_PACKET(NConnPkt), NChannel1) of
{ok, Properties, NChannel2} -> {ok, Properties, NChannel2} ->
process_connect(Properties, ensure_connected(NChannel2)); process_connect(Properties, ensure_connected(NChannel2));
{continue, Properties, NChannel2} -> {continue, Properties, NChannel2} ->
handle_out(auth, {?RC_CONTINUE_AUTHENTICATION, Properties}, NChannel2); handle_out(auth, {?RC_CONTINUE_AUTHENTICATION, Properties}, NChannel2);
{error, ReasonCode, NChannel2} -> {error, ReasonCode} ->
handle_out(connack, ReasonCode, NChannel2) handle_out(connack, ReasonCode, NChannel1)
end; end;
{error, ReasonCode, NChannel} -> {error, ReasonCode, NChannel} ->
handle_out(connack, ReasonCode, NChannel) handle_out(connack, ReasonCode, NChannel)
end; end;
handle_in(Packet = ?AUTH_PACKET(?RC_CONTINUE_AUTHENTICATION, _Properties), handle_in(Packet = ?AUTH_PACKET(ReasonCode, _Properties),
Channel = #channel{conn_state = ConnState}) -> Channel = #channel{conn_state = ConnState}) ->
case enhanced_auth(Packet, Channel) of try
case {ReasonCode, ConnState} of
{?RC_CONTINUE_AUTHENTICATION, connecting} -> ok;
{?RC_CONTINUE_AUTHENTICATION, reauthenticating} -> ok;
{?RC_RE_AUTHENTICATE, connected} -> ok;
_ -> error(protocol_error)
end,
case authenticate(Packet, Channel) of
{ok, NProperties, NChannel} -> {ok, NProperties, NChannel} ->
case ConnState of case ConnState of
connecting -> connecting ->
process_connect(NProperties, ensure_connected(NChannel)); process_connect(NProperties, ensure_connected(NChannel));
connected -> _ ->
handle_out(auth, {?RC_SUCCESS, NProperties}, NChannel); handle_out(auth, {?RC_SUCCESS, NProperties}, NChannel#channel{conn_state = connected})
end;
{continue, NProperties, NChannel} ->
handle_out(auth, {?RC_CONTINUE_AUTHENTICATION, NProperties}, NChannel#channel{conn_state = reauthenticating});
{error, NReasonCode} ->
case ConnState of
connecting ->
handle_out(connack, NReasonCode, Channel);
_ ->
handle_out(disconnect, NReasonCode, Channel)
end
end
catch
_Class:_Reason ->
case ConnState of
connecting ->
handle_out(connack, ?RC_PROTOCOL_ERROR, Channel);
_ -> _ ->
handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel) handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel)
end; end
{continue, NProperties, NChannel} ->
handle_out(auth, {?RC_CONTINUE_AUTHENTICATION, NProperties}, NChannel);
{error, NReasonCode, NChannel} ->
handle_out(connack, NReasonCode, NChannel)
end; end;
handle_in(Packet = ?AUTH_PACKET(?RC_RE_AUTHENTICATE, _Properties), handle_in(?PACKET(_), Channel = #channel{conn_state = ConnState})
Channel = #channel{conn_state = connected}) -> when ConnState =/= connected andalso ConnState =/= reauthenticating ->
case enhanced_auth(Packet, Channel) of
{ok, NProperties, NChannel} ->
handle_out(auth, {?RC_SUCCESS, NProperties}, NChannel);
{continue, NProperties, NChannel} ->
handle_out(auth, {?RC_CONTINUE_AUTHENTICATION, NProperties}, NChannel);
{error, NReasonCode, NChannel} ->
handle_out(disconnect, NReasonCode, NChannel)
end;
handle_in(?PACKET(_), Channel = #channel{conn_state = ConnState}) when ConnState =/= connected ->
handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel); handle_out(disconnect, ?RC_PROTOCOL_ERROR, Channel);
handle_in(Packet = ?PUBLISH_PACKET(_QoS), Channel) -> handle_in(Packet = ?PUBLISH_PACKET(_QoS), Channel) ->
@ -469,9 +478,11 @@ handle_in({frame_error, frame_too_large}, Channel = #channel{conn_state = connec
handle_in({frame_error, Reason}, Channel = #channel{conn_state = connecting}) -> handle_in({frame_error, Reason}, Channel = #channel{conn_state = connecting}) ->
shutdown(Reason, ?CONNACK_PACKET(?RC_MALFORMED_PACKET), Channel); shutdown(Reason, ?CONNACK_PACKET(?RC_MALFORMED_PACKET), Channel);
handle_in({frame_error, frame_too_large}, Channel = #channel{conn_state = connected}) -> handle_in({frame_error, frame_too_large}, Channel = #channel{conn_state = ConnState})
when ConnState =:= connected orelse ConnState =:= reauthenticating ->
handle_out(disconnect, {?RC_PACKET_TOO_LARGE, frame_too_large}, Channel); handle_out(disconnect, {?RC_PACKET_TOO_LARGE, frame_too_large}, Channel);
handle_in({frame_error, Reason}, Channel = #channel{conn_state = connected}) -> handle_in({frame_error, Reason}, Channel = #channel{conn_state = ConnState})
when ConnState =:= connected orelse ConnState =:= reauthenticating ->
handle_out(disconnect, {?RC_MALFORMED_PACKET, Reason}, Channel); handle_out(disconnect, {?RC_MALFORMED_PACKET, Reason}, Channel);
handle_in({frame_error, Reason}, Channel = #channel{conn_state = disconnected}) -> handle_in({frame_error, Reason}, Channel = #channel{conn_state = disconnected}) ->
@ -967,8 +978,9 @@ handle_info({sock_closed, Reason}, Channel = #channel{conn_state = connecting})
shutdown(Reason, Channel); shutdown(Reason, Channel);
handle_info({sock_closed, Reason}, Channel = handle_info({sock_closed, Reason}, Channel =
#channel{conn_state = connected, #channel{conn_state = ConnState,
clientinfo = ClientInfo = #{zone := Zone}}) -> clientinfo = ClientInfo = #{zone := Zone}})
when ConnState =:= connected orelse ConnState =:= reauthenticating ->
emqx_zone:enable_flapping_detect(Zone) emqx_zone:enable_flapping_detect(Zone)
andalso emqx_flapping:detect(ClientInfo), andalso emqx_flapping:detect(ClientInfo),
Channel1 = ensure_disconnected(Reason, mabye_publish_will_msg(Channel)), Channel1 = ensure_disconnected(Reason, mabye_publish_will_msg(Channel)),
@ -1241,75 +1253,60 @@ check_banned(_ConnPkt, #channel{clientinfo = ClientInfo = #{zone := Zone}}) ->
end. end.
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
%% Auth Connect %% Authenticate
auth_connect(#mqtt_packet_connect{password = Password}, authenticate(?CONNECT_PACKET(
#mqtt_packet_connect{
proto_ver = ?MQTT_PROTO_V5,
properties = #{'Authentication-Method' := AuthMethod} = Properties}),
#channel{clientinfo = ClientInfo,
auth_cache = AuthCache} = Channel) ->
AuthData = emqx_mqtt_props:get('Authentication-Data', Properties, undefined),
do_authenticate(ClientInfo#{auth_method => AuthMethod,
auth_data => AuthData,
auth_cache => AuthCache}, Channel);
authenticate(?CONNECT_PACKET(#mqtt_packet_connect{password = Password}),
#channel{clientinfo = ClientInfo} = Channel) -> #channel{clientinfo = ClientInfo} = Channel) ->
#{clientid := ClientId, do_authenticate(ClientInfo#{password => Password}, Channel);
username := Username} = ClientInfo,
case emqx_access_control:authenticate(ClientInfo#{password => Password}) of authenticate(?AUTH_PACKET(_, #{'Authentication-Method' := AuthMethod} = Properties),
{ok, AuthResult} -> #channel{clientinfo = ClientInfo,
is_anonymous(AuthResult) andalso conninfo = #{conn_props := ConnProps},
emqx_metrics:inc('client.auth.anonymous'), auth_cache = AuthCache} = Channel) ->
NClientInfo = maps:merge(ClientInfo, AuthResult), case emqx_mqtt_props:get('Authentication-Method', ConnProps, undefined) of
{ok, Channel#channel{clientinfo = NClientInfo}}; AuthMethod ->
{error, Reason} -> AuthData = emqx_mqtt_props:get('Authentication-Data', Properties, undefined),
?LOG(warning, "Client ~s (Username: '~s') login failed for ~0p", do_authenticate(ClientInfo#{auth_method => AuthMethod,
[ClientId, Username, Reason]), auth_data => AuthData,
{error, emqx_reason_codes:connack_error(Reason)} auth_cache => AuthCache}, Channel);
_ ->
{error, ?RC_BAD_AUTHENTICATION_METHOD}
end. end.
is_anonymous(#{anonymous := true}) -> true; do_authenticate(#{auth_method := AuthMethod} = Credential, Channel) ->
is_anonymous(_AuthResult) -> false. Properties = #{'Authentication-Method' => AuthMethod},
case emqx_access_control:authenticate(Credential) of
%%-------------------------------------------------------------------- ok ->
%% Enhanced Authentication {ok, Properties, Channel#channel{auth_cache = #{}}};
{ok, AuthData} ->
enhanced_auth(?CONNECT_PACKET(#mqtt_packet_connect{ {ok, Properties#{'Authentication-Data' => AuthData},
proto_ver = Protover, Channel#channel{auth_cache = #{}}};
properties = Properties {continue, AuthCache} ->
}), Channel) -> {continue, Properties, Channel#channel{auth_cache = AuthCache}};
case Protover of {continue, AuthData, AuthCache} ->
?MQTT_PROTO_V5 -> {continue, Properties#{'Authentication-Data' => AuthData},
AuthMethod = emqx_mqtt_props:get('Authentication-Method', Properties, undefined), Channel#channel{auth_cache = AuthCache}};
AuthData = emqx_mqtt_props:get('Authentication-Data', Properties, undefined), {error, Reason} ->
do_enhanced_auth(AuthMethod, AuthData, Channel); {error, emqx_reason_codes:connack_error(Reason)}
_ ->
{ok, #{}, Channel}
end; end;
enhanced_auth(?AUTH_PACKET(_ReasonCode, Properties), Channel = #channel{conninfo = ConnInfo}) -> do_authenticate(Credential, Channel) ->
AuthMethod = emqx_mqtt_props:get('Authentication-Method', case emqx_access_control:authenticate(Credential) of
emqx_mqtt_props:get(conn_props, ConnInfo, #{}), ok ->
undefined
),
NAuthMethod = emqx_mqtt_props:get('Authentication-Method', Properties, undefined),
AuthData = emqx_mqtt_props:get('Authentication-Data', Properties, undefined),
case NAuthMethod =:= undefined orelse NAuthMethod =/= AuthMethod of
true ->
{error, emqx_reason_codes:connack_error(bad_authentication_method), Channel};
false ->
do_enhanced_auth(AuthMethod, AuthData, Channel)
end.
do_enhanced_auth(undefined, undefined, Channel) ->
{ok, #{}, Channel}; {ok, #{}, Channel};
do_enhanced_auth(undefined, _AuthData, Channel) -> {error, Reason} ->
{error, emqx_reason_codes:connack_error(not_authorized), Channel}; {error, emqx_reason_codes:connack_error(Reason)}
do_enhanced_auth(_AuthMethod, undefined, Channel) ->
{error, emqx_reason_codes:connack_error(not_authorized), Channel};
do_enhanced_auth(AuthMethod, AuthData, Channel = #channel{auth_cache = Cache}) ->
case run_hooks('client.enhanced_authenticate', [AuthMethod, AuthData], Cache) of
{ok, NAuthData, NCache} ->
NProperties = #{'Authentication-Method' => AuthMethod,
'Authentication-Data' => NAuthData},
{ok, NProperties, Channel#channel{auth_cache = NCache}};
{continue, NAuthData, NCache} ->
NProperties = #{'Authentication-Method' => AuthMethod,
'Authentication-Data' => NAuthData},
{continue, NProperties, Channel#channel{auth_cache = NCache}};
_ ->
{error, emqx_reason_codes:connack_error(not_authorized), Channel}
end. end.
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
@ -1703,7 +1700,8 @@ shutdown(Reason, Reply, Packet, Channel) ->
{shutdown, Reason, Reply, Packet, Channel}. {shutdown, Reason, Reply, Packet, Channel}.
disconnect_and_shutdown(Reason, Reply, Channel = ?IS_MQTT_V5 disconnect_and_shutdown(Reason, Reply, Channel = ?IS_MQTT_V5
= #channel{conn_state = connected}) -> = #channel{conn_state = ConnState})
when ConnState =:= connected orelse ConnState =:= reauthenticating ->
shutdown(Reason, Reply, ?DISCONNECT_PACKET(reason_code(Reason)), Channel); shutdown(Reason, Reply, ?DISCONNECT_PACKET(reason_code(Reason)), Channel);
disconnect_and_shutdown(Reason, Reply, Channel) -> disconnect_and_shutdown(Reason, Reply, Channel) ->

View File

@ -170,16 +170,11 @@ frame_error(frame_too_large) -> ?RC_PACKET_TOO_LARGE;
frame_error(_) -> ?RC_MALFORMED_PACKET. frame_error(_) -> ?RC_MALFORMED_PACKET.
connack_error(protocol_error) -> ?RC_PROTOCOL_ERROR; connack_error(protocol_error) -> ?RC_PROTOCOL_ERROR;
connack_error(client_identifier_not_valid) -> ?RC_CLIENT_IDENTIFIER_NOT_VALID;
connack_error(bad_username_or_password) -> ?RC_BAD_USER_NAME_OR_PASSWORD; connack_error(bad_username_or_password) -> ?RC_BAD_USER_NAME_OR_PASSWORD;
connack_error(bad_clientid_or_password) -> ?RC_BAD_USER_NAME_OR_PASSWORD;
connack_error(username_or_password_undefined) -> ?RC_BAD_USER_NAME_OR_PASSWORD;
connack_error(password_error) -> ?RC_BAD_USER_NAME_OR_PASSWORD;
connack_error(not_authorized) -> ?RC_NOT_AUTHORIZED; connack_error(not_authorized) -> ?RC_NOT_AUTHORIZED;
connack_error(server_unavailable) -> ?RC_SERVER_UNAVAILABLE; connack_error(server_unavailable) -> ?RC_SERVER_UNAVAILABLE;
connack_error(server_busy) -> ?RC_SERVER_BUSY; connack_error(server_busy) -> ?RC_SERVER_BUSY;
connack_error(banned) -> ?RC_BANNED; connack_error(banned) -> ?RC_BANNED;
connack_error(bad_authentication_method) -> ?RC_BAD_AUTHENTICATION_METHOD; connack_error(bad_authentication_method) -> ?RC_BAD_AUTHENTICATION_METHOD;
%% TODO: ??? connack_error(_) -> ?RC_UNSPECIFIED_ERROR.
connack_error(_) -> ?RC_NOT_AUTHORIZED.

View File

@ -1,26 +1,12 @@
emqx_authn: { emqx_authn: {
chains: [ authenticators: [
# {
# id: "chain1"
# type: simple
# authenticators: [
# { # {
# name: "authenticator1" # name: "authenticator1"
# type: built-in-database # mechanism: password-based
# config: { # config: {
# server_type: built-in-database
# user_id_type: clientid # user_id_type: clientid
# password_hash_algorithm: {
# name: sha256
# } # }
# } # }
# }
# ]
# }
]
bindings: [
# {
# chain_id: "chain1"
# listeners: ["mqtt-tcp", "mqtt-ssl"]
# }
] ]
} }

View File

@ -15,16 +15,15 @@
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
-define(APP, emqx_authn). -define(APP, emqx_authn).
-define(CHAIN, <<"mqtt">>).
-type chain_id() :: binary(). -type chain_id() :: binary().
-type authn_type() :: simple | enhanced.
-type authenticator_name() :: binary(). -type authenticator_name() :: binary().
-type authenticator_type() :: mnesia | jwt | mysql | postgresql. -type mechanism() :: 'password-based' | jwt | scram.
-type listener_id() :: binary().
-record(authenticator, -record(authenticator,
{ name :: authenticator_name() { name :: authenticator_name()
, type :: authenticator_type() , mechanism :: mechanism()
, provider :: module() , provider :: module()
, config :: map() , config :: map()
, state :: map() , state :: map()
@ -32,16 +31,10 @@
-record(chain, -record(chain,
{ id :: chain_id() { id :: chain_id()
, type :: authn_type()
, authenticators :: [{authenticator_name(), #authenticator{}}] , authenticators :: [{authenticator_name(), #authenticator{}}]
, created_at :: integer() , created_at :: integer()
}). }).
-record(binding,
{ bound :: {listener_id(), authn_type()}
, chain_id :: chain_id()
}).
-define(AUTH_SHARD, emqx_authn_shard). -define(AUTH_SHARD, emqx_authn_shard).
-define(CLUSTER_CALL(Module, Func, Args), ?CLUSTER_CALL(Module, Func, Args, ok)). -define(CLUSTER_CALL(Module, Func, Args), ?CLUSTER_CALL(Module, Func, Args, ok)).

View File

@ -22,16 +22,12 @@
, disable/0 , disable/0
]). ]).
-export([authenticate/1]). -export([authenticate/2]).
-export([ create_chain/1 -export([ create_chain/1
, delete_chain/1 , delete_chain/1
, lookup_chain/1 , lookup_chain/1
, list_chains/0 , list_chains/0
, bind/2
, unbind/2
, list_bindings/1
, list_bound_chains/1
, create_authenticator/2 , create_authenticator/2
, delete_authenticator/2 , delete_authenticator/2
, update_authenticator/3 , update_authenticator/3
@ -55,10 +51,8 @@
-boot_mnesia({mnesia, [boot]}). -boot_mnesia({mnesia, [boot]}).
-define(CHAIN_TAB, emqx_authn_chain). -define(CHAIN_TAB, emqx_authn_chain).
-define(BINDING_TAB, emqx_authn_binding).
-rlog_shard({?AUTH_SHARD, ?CHAIN_TAB}). -rlog_shard({?AUTH_SHARD, ?CHAIN_TAB}).
-rlog_shard({?AUTH_SHARD, ?BINDING_TAB}).
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
%% Mnesia bootstrap %% Mnesia bootstrap
@ -75,13 +69,6 @@ mnesia(boot) ->
{record_name, chain}, {record_name, chain},
{local_content, true}, {local_content, true},
{attributes, record_info(fields, chain)}, {attributes, record_info(fields, chain)},
{storage_properties, StoreProps}]),
%% Binding table
ok = ekka_mnesia:create_table(?BINDING_TAB, [
{ram_copies, [node()]},
{record_name, binding},
{local_content, true},
{attributes, record_info(fields, binding)},
{storage_properties, StoreProps}]). {storage_properties, StoreProps}]).
enable() -> enable() ->
@ -94,39 +81,35 @@ disable() ->
emqx:unhook('client.authenticate', {?MODULE, authenticate, []}), emqx:unhook('client.authenticate', {?MODULE, authenticate, []}),
ok. ok.
authenticate(#{listener_id := ListenerID} = ClientInfo) -> authenticate(Credential, _AuthResult) ->
case lookup_chain_by_listener(ListenerID, simple) of case mnesia:dirty_read(?CHAIN_TAB, ?CHAIN) of
{error, _} ->
{error, no_authenticators};
{ok, ChainID} ->
case mnesia:dirty_read(?CHAIN_TAB, ChainID) of
[#chain{authenticators = []}] ->
{error, no_authenticators};
[#chain{authenticators = Authenticators}] -> [#chain{authenticators = Authenticators}] ->
do_authenticate(Authenticators, ClientInfo); do_authenticate(Authenticators, Credential);
[] -> [] ->
{error, no_authenticators} {stop, {error, not_authorized}}
end
end. end.
do_authenticate([], _) -> do_authenticate([], _) ->
{error, user_not_found}; {stop, {error, not_authorized}};
do_authenticate([{_, #authenticator{provider = Provider, state = State}} | More], ClientInfo) -> do_authenticate([{_, #authenticator{provider = Provider, state = State}} | More], Credential) ->
case Provider:authenticate(ClientInfo, State) of case Provider:authenticate(Credential, State) of
ignore -> do_authenticate(More, ClientInfo); ignore ->
ok -> ok; do_authenticate(More, Credential);
{ok, NewClientInfo} -> {ok, NewClientInfo}; Result ->
{stop, Reason} -> {error, Reason} %% ok
%% {ok, AuthData}
%% {continue, AuthCache}
%% {continue, AuthData, AuthCache}
%% {error, Reason}
{stop, Result}
end. end.
create_chain(#{id := ID, create_chain(#{id := ID}) ->
type := Type}) ->
trans( trans(
fun() -> fun() ->
case mnesia:read(?CHAIN_TAB, ID, write) of case mnesia:read(?CHAIN_TAB, ID, write) of
[] -> [] ->
Chain = #chain{id = ID, Chain = #chain{id = ID,
type = Type,
authenticators = [], authenticators = [],
created_at = erlang:system_time(millisecond)}, created_at = erlang:system_time(millisecond)},
mnesia:write(?CHAIN_TAB, Chain, write), mnesia:write(?CHAIN_TAB, Chain, write),
@ -160,85 +143,20 @@ list_chains() ->
Chains = ets:tab2list(?CHAIN_TAB), Chains = ets:tab2list(?CHAIN_TAB),
{ok, [serialize_chain(Chain) || Chain <- Chains]}. {ok, [serialize_chain(Chain) || Chain <- Chains]}.
bind(ChainID, Listeners) ->
%% TODO: ensure listener id is valid
trans(
fun() ->
case mnesia:read(?CHAIN_TAB, ChainID, write) of
[] ->
{error, {not_found, {chain, ChainID}}};
[#chain{type = AuthNType}] ->
Result = lists:foldl(
fun(ListenerID, Acc) ->
case mnesia:read(?BINDING_TAB, {ListenerID, AuthNType}, write) of
[] ->
Binding = #binding{bound = {ListenerID, AuthNType}, chain_id = ChainID},
mnesia:write(?BINDING_TAB, Binding, write),
Acc;
_ ->
[ListenerID | Acc]
end
end, [], Listeners),
case Result of
[] -> ok;
Listeners0 -> {error, {already_bound, Listeners0}}
end
end
end).
unbind(ChainID, Listeners) ->
trans(
fun() ->
Result = lists:foldl(
fun(ListenerID, Acc) ->
MatchSpec = [{{binding, {ListenerID, '_'}, ChainID}, [], ['$_']}],
case mnesia:select(?BINDING_TAB, MatchSpec, write) of
[] ->
[ListenerID | Acc];
[#binding{bound = Bound}] ->
mnesia:delete(?BINDING_TAB, Bound, write),
Acc
end
end, [], Listeners),
case Result of
[] -> ok;
Listeners0 ->
{error, {not_found, Listeners0}}
end
end).
list_bindings(ChainID) ->
trans(
fun() ->
MatchSpec = [{{binding, {'$1', '_'}, ChainID}, [], ['$1']}],
Listeners = mnesia:select(?BINDING_TAB, MatchSpec),
{ok, #{chain_id => ChainID, listeners => Listeners}}
end).
list_bound_chains(ListenerID) ->
trans(
fun() ->
MatchSpec = [{{binding, {ListenerID, '_'}, '_'}, [], ['$_']}],
Bindings = mnesia:select(?BINDING_TAB, MatchSpec),
Chains = [{AuthNType, ChainID} || #binding{bound = {_, AuthNType},
chain_id = ChainID} <- Bindings],
{ok, maps:from_list(Chains)}
end).
create_authenticator(ChainID, #{name := Name, create_authenticator(ChainID, #{name := Name,
type := Type, mechanism := Mechanism,
config := Config}) -> config := Config}) ->
UpdateFun = UpdateFun =
fun(Chain = #chain{type = AuthNType, authenticators = Authenticators}) -> fun(Chain = #chain{authenticators = Authenticators}) ->
case lists:keymember(Name, 1, Authenticators) of case lists:keymember(Name, 1, Authenticators) of
true -> true ->
{error, {already_exists, {authenticator, Name}}}; {error, {already_exists, {authenticator, Name}}};
false -> false ->
Provider = authenticator_provider(AuthNType, Type), Provider = authenticator_provider(Mechanism, Config),
case Provider:create(ChainID, Name, Config) of case Provider:create(ChainID, Name, Config) of
{ok, State} -> {ok, State} ->
Authenticator = #authenticator{name = Name, Authenticator = #authenticator{name = Name,
type = Type, mechanism = Mechanism,
provider = Provider, provider = Provider,
config = Config, config = Config,
state = State}, state = State},
@ -367,12 +285,18 @@ list_users(ChainID, AuthenticatorName) ->
%% Internal functions %% Internal functions
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
authenticator_provider(simple, 'built-in-database') -> emqx_authn_mnesia; authenticator_provider('password-based', #{server_type := 'built-in-database'}) ->
authenticator_provider(simple, jwt) -> emqx_authn_jwt; emqx_authn_mnesia;
authenticator_provider(simple, mysql) -> emqx_authn_mysql; authenticator_provider('password-based', #{server_type := 'mysql'}) ->
authenticator_provider(simple, postgresql) -> emqx_authn_pgsql. emqx_authn_mysql;
authenticator_provider('password-based', #{server_type := 'pgsql'}) ->
% authenticator_provider(enhanced, 'enhanced-built-in-database') -> emqx_enhanced_authn_mnesia. emqx_authn_pgsql;
authenticator_provider('password-based', #{server_type := 'http-server'}) ->
emqx_authn_http;
authenticator_provider(jwt, _) ->
emqx_authn_jwt;
authenticator_provider(scram, #{server_type := 'built-in-database'}) ->
emqx_enhanced_authn_scram_mnesia.
do_delete_authenticator(#authenticator{provider = Provider, state = State}) -> do_delete_authenticator(#authenticator{provider = Provider, state = State}) ->
Provider:destroy(State). Provider:destroy(State).
@ -429,13 +353,13 @@ update_chain(ChainID, UpdateFun) ->
end end
end). end).
lookup_chain_by_listener(ListenerID, AuthNType) -> % lookup_chain_by_listener(ListenerID, AuthNType) ->
case mnesia:dirty_read(?BINDING_TAB, {ListenerID, AuthNType}) of % case mnesia:dirty_read(?BINDING_TAB, {ListenerID, AuthNType}) of
[] -> % [] ->
{error, not_found}; % {error, not_found};
[#binding{chain_id = ChainID}] -> % [#binding{chain_id = ChainID}] ->
{ok, ChainID} % {ok, ChainID}
end. % end.
call_authenticator(ChainID, AuthenticatorName, Func, Args) -> call_authenticator(ChainID, AuthenticatorName, Func, Args) ->
@ -457,11 +381,9 @@ call_authenticator(ChainID, AuthenticatorName, Func, Args) ->
end. end.
serialize_chain(#chain{id = ID, serialize_chain(#chain{id = ID,
type = Type,
authenticators = Authenticators, authenticators = Authenticators,
created_at = CreatedAt}) -> created_at = CreatedAt}) ->
#{id => ID, #{id => ID,
type => Type,
authenticators => serialize_authenticators(Authenticators), authenticators => serialize_authenticators(Authenticators),
created_at => CreatedAt}. created_at => CreatedAt}.
@ -474,10 +396,10 @@ serialize_authenticators(Authenticators) ->
[serialize_authenticator(Authenticator) || {_, Authenticator} <- Authenticators]. [serialize_authenticator(Authenticator) || {_, Authenticator} <- Authenticators].
serialize_authenticator(#authenticator{name = Name, serialize_authenticator(#authenticator{name = Name,
type = Type, mechanism = Mechanism,
config = Config}) -> config = Config}) ->
#{name => Name, #{name => Name,
type => Type, mechanism => Mechanism,
config => Config}. config => Config}.
trans(Fun) -> trans(Fun) ->

View File

@ -18,15 +18,7 @@
-include("emqx_authn.hrl"). -include("emqx_authn.hrl").
-export([ create_chain/2 -export([ create_authenticator/2
, delete_chain/2
, lookup_chain/2
, list_chains/2
, bind/2
, unbind/2
, list_bindings/2
, list_bound_chains/2
, create_authenticator/2
, delete_authenticator/2 , delete_authenticator/2
, update_authenticator/2 , update_authenticator/2
, lookup_authenticator/2 , lookup_authenticator/2
@ -40,135 +32,79 @@
, list_users/2 , list_users/2
]). ]).
-rest_api(#{name => create_chain,
method => 'POST',
path => "/authentication/chains",
func => create_chain,
descr => "Create a chain"
}).
-rest_api(#{name => delete_chain,
method => 'DELETE',
path => "/authentication/chains/:bin:id",
func => delete_chain,
descr => "Delete chain"
}).
-rest_api(#{name => lookup_chain,
method => 'GET',
path => "/authentication/chains/:bin:id",
func => lookup_chain,
descr => "Lookup chain"
}).
-rest_api(#{name => list_chains,
method => 'GET',
path => "/authentication/chains",
func => list_chains,
descr => "List all chains"
}).
-rest_api(#{name => bind,
method => 'POST',
path => "/authentication/chains/:bin:id/bindings/bulk",
func => bind,
descr => "Bind"
}).
-rest_api(#{name => unbind,
method => 'DELETE',
path => "/authentication/chains/:bin:id/bindings/bulk",
func => unbind,
descr => "Unbind"
}).
-rest_api(#{name => list_bindings,
method => 'GET',
path => "/authentication/chains/:bin:id/bindings",
func => list_bindings,
descr => "List bindings"
}).
-rest_api(#{name => list_bound_chains,
method => 'GET',
path => "/authentication/listeners/:bin:listener_id/bound_chains",
func => list_bound_chains,
descr => "List bound chains"
}).
-rest_api(#{name => create_authenticator, -rest_api(#{name => create_authenticator,
method => 'POST', method => 'POST',
path => "/authentication/chains/:bin:id/authenticators", path => "/authentication/authenticators",
func => create_authenticator, func => create_authenticator,
descr => "Create authenticator to chain" descr => "Create authenticator"
}). }).
-rest_api(#{name => delete_authenticator, -rest_api(#{name => delete_authenticator,
method => 'DELETE', method => 'DELETE',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name", path => "/authentication/authenticators/:bin:name",
func => delete_authenticator, func => delete_authenticator,
descr => "Delete authenticator from chain" descr => "Delete authenticator"
}). }).
-rest_api(#{name => update_authenticator, -rest_api(#{name => update_authenticator,
method => 'PUT', method => 'PUT',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name", path => "/authentication/authenticators/:bin:name",
func => update_authenticator, func => update_authenticator,
descr => "Update authenticator in chain" descr => "Update authenticator"
}). }).
-rest_api(#{name => lookup_authenticator, -rest_api(#{name => lookup_authenticator,
method => 'GET', method => 'GET',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name", path => "/authentication/authenticators/:bin:name",
func => lookup_authenticator, func => lookup_authenticator,
descr => "Lookup authenticator in chain" descr => "Lookup authenticator"
}). }).
-rest_api(#{name => list_authenticators, -rest_api(#{name => list_authenticators,
method => 'GET', method => 'GET',
path => "/authentication/chains/:bin:id/authenticators", path => "/authentication/authenticators",
func => list_authenticators, func => list_authenticators,
descr => "List authenticators in chain" descr => "List authenticators"
}). }).
-rest_api(#{name => move_authenticator, -rest_api(#{name => move_authenticator,
method => 'POST', method => 'POST',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/position", path => "/authentication/authenticators/:bin:name/position",
func => move_authenticator, func => move_authenticator,
descr => "Change the order of authenticators" descr => "Change the order of authenticators"
}). }).
-rest_api(#{name => import_users, -rest_api(#{name => import_users,
method => 'POST', method => 'POST',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/import-users", path => "/authentication/authenticators/:bin:name/import-users",
func => import_users, func => import_users,
descr => "Import users" descr => "Import users"
}). }).
-rest_api(#{name => add_user, -rest_api(#{name => add_user,
method => 'POST', method => 'POST',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/users", path => "/authentication/authenticators/:bin:name/users",
func => add_user, func => add_user,
descr => "Add user" descr => "Add user"
}). }).
-rest_api(#{name => delete_user, -rest_api(#{name => delete_user,
method => 'DELETE', method => 'DELETE',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/users/:bin:user_id", path => "/authentication/authenticators/:bin:name/users/:bin:user_id",
func => delete_user, func => delete_user,
descr => "Delete user" descr => "Delete user"
}). }).
-rest_api(#{name => update_user, -rest_api(#{name => update_user,
method => 'PUT', method => 'PUT',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/users/:bin:user_id", path => "/authentication/authenticators/:bin:name/users/:bin:user_id",
func => update_user, func => update_user,
descr => "Update user" descr => "Update user"
}). }).
-rest_api(#{name => lookup_user, -rest_api(#{name => lookup_user,
method => 'GET', method => 'GET',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/users/:bin:user_id", path => "/authentication/authenticators/:bin:name/users/:bin:user_id",
func => lookup_user, func => lookup_user,
descr => "Lookup user" descr => "Lookup user"
}). }).
@ -176,139 +112,33 @@
%% TODO: Support pagination %% TODO: Support pagination
-rest_api(#{name => list_users, -rest_api(#{name => list_users,
method => 'GET', method => 'GET',
path => "/authentication/chains/:bin:id/authenticators/:bin:authenticator_name/users", path => "/authentication/authenticators/:bin:name/users",
func => list_users, func => list_users,
descr => "List all users" descr => "List all users"
}). }).
create_chain(Binding, Params) ->
do_create_chain(uri_decode(Binding), maps:from_list(Params)).
do_create_chain(_Binding, Chain0) ->
Config = #{<<"authn">> => #{<<"chains">> => [Chain0#{<<"authenticators">> => []}],
<<"bindings">> => []}},
#{authn := #{chains := [Chain1]}}
= hocon_schema:check_plain(emqx_authn_schema, Config,
#{atom_key => true, nullable => true}),
case emqx_authn:create_chain(Chain1) of
{ok, Chain2} ->
return({ok, Chain2});
{error, Reason} ->
return(serialize_error(Reason))
end.
delete_chain(Binding, Params) ->
do_delete_chain(uri_decode(Binding), maps:from_list(Params)).
do_delete_chain(#{id := ChainID}, _Params) ->
case emqx_authn:delete_chain(ChainID) of
ok ->
return(ok);
{error, Reason} ->
return(serialize_error(Reason))
end.
lookup_chain(Binding, Params) ->
do_lookup_chain(uri_decode(Binding), maps:from_list(Params)).
do_lookup_chain(#{id := ChainID}, _Params) ->
case emqx_authn:lookup_chain(ChainID) of
{ok, Chain} ->
return({ok, Chain});
{error, Reason} ->
return(serialize_error(Reason))
end.
list_chains(Binding, Params) ->
do_list_chains(uri_decode(Binding), maps:from_list(Params)).
do_list_chains(_Binding, _Params) ->
{ok, Chains} = emqx_authn:list_chains(),
return({ok, Chains}).
bind(Binding, Params) ->
do_bind(uri_decode(Binding), lists_to_map(Params)).
do_bind(#{id := ChainID}, #{<<"listeners">> := Listeners}) ->
% Config = #{<<"authn">> => #{<<"chains">> => [],
% <<"bindings">> => [#{<<"chain">> := ChainID,
% <<"listeners">> := Listeners}]}},
% #{authn := #{bindings := [#{listeners := Listeners}]}}
% = hocon_schema:check_plain(emqx_authn_schema, Config,
% #{atom_key => true, nullable => true}),
case emqx_authn:bind(ChainID, Listeners) of
ok ->
return(ok);
{error, {alread_bound, Listeners}} ->
{ok, #{code => <<"ALREADY_EXISTS">>,
message => <<"ALREADY_BOUND">>,
detail => Listeners}};
{error, Reason} ->
return(serialize_error(Reason))
end;
do_bind(_, _) ->
return(serialize_error({missing_parameter, <<"listeners">>})).
unbind(Binding, Params) ->
do_unbind(uri_decode(Binding), lists_to_map(Params)).
do_unbind(#{id := ChainID}, #{<<"listeners">> := Listeners0}) ->
case emqx_authn:unbind(ChainID, Listeners0) of
ok ->
return(ok);
{error, {not_found, Listeners1}} ->
{ok, #{code => <<"NOT_FOUND">>,
detail => Listeners1}};
{error, Reason} ->
return(serialize_error(Reason))
end;
do_unbind(_, _) ->
return(serialize_error({missing_parameter, <<"listeners">>})).
list_bindings(Binding, Params) ->
do_list_bindings(uri_decode(Binding), lists_to_map(Params)).
do_list_bindings(#{id := ChainID}, _) ->
{ok, Binding} = emqx_authn:list_bindings(ChainID),
return({ok, Binding}).
list_bound_chains(Binding, Params) ->
do_list_bound_chains(uri_decode(Binding), lists_to_map(Params)).
do_list_bound_chains(#{listener_id := ListenerID}, _) ->
{ok, Chains} = emqx_authn:list_bound_chains(ListenerID),
return({ok, Chains}).
create_authenticator(Binding, Params) -> create_authenticator(Binding, Params) ->
do_create_authenticator(uri_decode(Binding), lists_to_map(Params)). do_create_authenticator(uri_decode(Binding), lists_to_map(Params)).
do_create_authenticator(#{id := ChainID}, Authenticator0) -> do_create_authenticator(_Binding, Authenticator0) ->
case emqx_authn:lookup_chain(ChainID) of Config = #{<<"emqx_authn">> => #{
{ok, #{type := Type}} -> <<"authenticators">> => [Authenticator0]
Chain = #{<<"id">> => ChainID, }},
<<"type">> => Type, #{emqx_authn := #{authenticators := [Authenticator1]}}
<<"authenticators">> => [Authenticator0]},
Config = #{<<"authn">> => #{<<"chains">> => [Chain],
<<"bindings">> => []}},
#{authn := #{chains := [#{authenticators := [Authenticator1]}]}}
= hocon_schema:check_plain(emqx_authn_schema, Config, = hocon_schema:check_plain(emqx_authn_schema, Config,
#{atom_key => true, nullable => true}), #{atom_key => true, nullable => true}),
case emqx_authn:create_authenticator(ChainID, Authenticator1) of case emqx_authn:create_authenticator(?CHAIN, Authenticator1) of
{ok, Authenticator2} -> {ok, Authenticator2} ->
return({ok, Authenticator2}); return({ok, Authenticator2});
{error, Reason} -> {error, Reason} ->
return(serialize_error(Reason)) return(serialize_error(Reason))
end;
{error, Reason} ->
return(serialize_error(Reason))
end. end.
delete_authenticator(Binding, Params) -> delete_authenticator(Binding, Params) ->
do_delete_authenticator(uri_decode(Binding), maps:from_list(Params)). do_delete_authenticator(uri_decode(Binding), maps:from_list(Params)).
do_delete_authenticator(#{id := ChainID, do_delete_authenticator(#{name := Name}, _Params) ->
authenticator_name := AuthenticatorName}, _Params) -> case emqx_authn:delete_authenticator(?CHAIN, Name) of
case emqx_authn:delete_authenticator(ChainID, AuthenticatorName) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
@ -320,31 +150,24 @@ update_authenticator(Binding, Params) ->
do_update_authenticator(uri_decode(Binding), lists_to_map(Params)). do_update_authenticator(uri_decode(Binding), lists_to_map(Params)).
%% TOOD: PUT method supports creation and update %% TOOD: PUT method supports creation and update
do_update_authenticator(#{id := ChainID, do_update_authenticator(#{name := Name}, NewConfig0) ->
authenticator_name := AuthenticatorName}, AuthenticatorConfig0) -> case emqx_authn:lookup_authenticator(?CHAIN, Name) of
case emqx_authn:lookup_chain(ChainID) of {ok, #{mechanism := Mechanism}} ->
{ok, #{type := ChainType}} -> Authenticator = #{<<"name">> => Name,
case emqx_authn:lookup_authenticator(ChainID, AuthenticatorName) of <<"mechanism">> => Mechanism,
{ok, #{type := Type}} -> <<"config">> => NewConfig0},
Authenticator = #{<<"name">> => AuthenticatorName, Config = #{<<"emqx_authn">> => #{
<<"type">> => Type, <<"authenticators">> => [Authenticator]
<<"config">> => AuthenticatorConfig0}, }},
Chain = #{<<"id">> => ChainID,
<<"type">> => ChainType,
<<"authenticators">> => [Authenticator]},
Config = #{<<"authn">> => #{<<"chains">> => [Chain],
<<"bindings">> => []}},
#{ #{
authn := #{ emqx_authn := #{
chains := [#{
authenticators := [#{ authenticators := [#{
config := AuthenticatorConfig1 config := NewConfig1
}]
}] }]
} }
} = hocon_schema:check_plain(emqx_authn_schema, Config, } = hocon_schema:check_plain(emqx_authn_schema, Config,
#{atom_key => true, nullable => true}), #{atom_key => true, nullable => true}),
case emqx_authn:update_authenticator(ChainID, AuthenticatorName, AuthenticatorConfig1) of case emqx_authn:update_authenticator(?CHAIN, Name, NewConfig1) of
{ok, NAuthenticator} -> {ok, NAuthenticator} ->
return({ok, NAuthenticator}); return({ok, NAuthenticator});
{error, Reason} -> {error, Reason} ->
@ -352,17 +175,13 @@ do_update_authenticator(#{id := ChainID,
end; end;
{error, Reason} -> {error, Reason} ->
return(serialize_error(Reason)) return(serialize_error(Reason))
end;
{error, Reason} ->
return(serialize_error(Reason))
end. end.
lookup_authenticator(Binding, Params) -> lookup_authenticator(Binding, Params) ->
do_lookup_authenticator(uri_decode(Binding), maps:from_list(Params)). do_lookup_authenticator(uri_decode(Binding), maps:from_list(Params)).
do_lookup_authenticator(#{id := ChainID, do_lookup_authenticator(#{name := Name}, _Params) ->
authenticator_name := AuthenticatorName}, _Params) -> case emqx_authn:lookup_authenticator(?CHAIN, Name) of
case emqx_authn:lookup_authenticator(ChainID, AuthenticatorName) of
{ok, Authenticator} -> {ok, Authenticator} ->
return({ok, Authenticator}); return({ok, Authenticator});
{error, Reason} -> {error, Reason} ->
@ -372,8 +191,8 @@ do_lookup_authenticator(#{id := ChainID,
list_authenticators(Binding, Params) -> list_authenticators(Binding, Params) ->
do_list_authenticators(uri_decode(Binding), maps:from_list(Params)). do_list_authenticators(uri_decode(Binding), maps:from_list(Params)).
do_list_authenticators(#{id := ChainID}, _Params) -> do_list_authenticators(_Binding, _Params) ->
case emqx_authn:list_authenticators(ChainID) of case emqx_authn:list_authenticators(?CHAIN) of
{ok, Authenticators} -> {ok, Authenticators} ->
return({ok, Authenticators}); return({ok, Authenticators});
{error, Reason} -> {error, Reason} ->
@ -383,25 +202,22 @@ do_list_authenticators(#{id := ChainID}, _Params) ->
move_authenticator(Binding, Params) -> move_authenticator(Binding, Params) ->
do_move_authenticator(uri_decode(Binding), maps:from_list(Params)). do_move_authenticator(uri_decode(Binding), maps:from_list(Params)).
do_move_authenticator(#{id := ChainID, do_move_authenticator(#{name := Name}, #{<<"position">> := <<"the front">>}) ->
authenticator_name := AuthenticatorName}, #{<<"position">> := <<"the front">>}) -> case emqx_authn:move_authenticator_to_the_front(?CHAIN, Name) of
case emqx_authn:move_authenticator_to_the_front(ChainID, AuthenticatorName) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
return(serialize_error(Reason)) return(serialize_error(Reason))
end; end;
do_move_authenticator(#{id := ChainID, do_move_authenticator(#{name := Name}, #{<<"position">> := <<"the end">>}) ->
authenticator_name := AuthenticatorName}, #{<<"position">> := <<"the end">>}) -> case emqx_authn:move_authenticator_to_the_end(?CHAIN, Name) of
case emqx_authn:move_authenticator_to_the_end(ChainID, AuthenticatorName) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
return(serialize_error(Reason)) return(serialize_error(Reason))
end; end;
do_move_authenticator(#{id := ChainID, do_move_authenticator(#{name := Name}, #{<<"position">> := N}) when is_number(N) ->
authenticator_name := AuthenticatorName}, #{<<"position">> := N}) when is_number(N) -> case emqx_authn:move_authenticator_to_the_nth(?CHAIN, Name, N) of
case emqx_authn:move_authenticator_to_the_nth(ChainID, AuthenticatorName, N) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
@ -413,9 +229,9 @@ do_move_authenticator(_Binding, _Params) ->
import_users(Binding, Params) -> import_users(Binding, Params) ->
do_import_users(uri_decode(Binding), maps:from_list(Params)). do_import_users(uri_decode(Binding), maps:from_list(Params)).
do_import_users(#{id := ChainID, authenticator_name := AuthenticatorName}, do_import_users(#{name := Name},
#{<<"filename">> := Filename}) -> #{<<"filename">> := Filename}) ->
case emqx_authn:import_users(ChainID, AuthenticatorName, Filename) of case emqx_authn:import_users(?CHAIN, Name, Filename) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
@ -428,9 +244,8 @@ do_import_users(_Binding, Params) ->
add_user(Binding, Params) -> add_user(Binding, Params) ->
do_add_user(uri_decode(Binding), maps:from_list(Params)). do_add_user(uri_decode(Binding), maps:from_list(Params)).
do_add_user(#{id := ChainID, do_add_user(#{name := Name}, UserInfo) ->
authenticator_name := AuthenticatorName}, UserInfo) -> case emqx_authn:add_user(?CHAIN, Name, UserInfo) of
case emqx_authn:add_user(ChainID, AuthenticatorName, UserInfo) of
{ok, User} -> {ok, User} ->
return({ok, User}); return({ok, User});
{error, Reason} -> {error, Reason} ->
@ -440,10 +255,9 @@ do_add_user(#{id := ChainID,
delete_user(Binding, Params) -> delete_user(Binding, Params) ->
do_delete_user(uri_decode(Binding), maps:from_list(Params)). do_delete_user(uri_decode(Binding), maps:from_list(Params)).
do_delete_user(#{id := ChainID, do_delete_user(#{name := Name,
authenticator_name := AuthenticatorName,
user_id := UserID}, _Params) -> user_id := UserID}, _Params) ->
case emqx_authn:delete_user(ChainID, AuthenticatorName, UserID) of case emqx_authn:delete_user(?CHAIN, Name, UserID) of
ok -> ok ->
return(ok); return(ok);
{error, Reason} -> {error, Reason} ->
@ -453,10 +267,9 @@ do_delete_user(#{id := ChainID,
update_user(Binding, Params) -> update_user(Binding, Params) ->
do_update_user(uri_decode(Binding), maps:from_list(Params)). do_update_user(uri_decode(Binding), maps:from_list(Params)).
do_update_user(#{id := ChainID, do_update_user(#{name := Name,
authenticator_name := AuthenticatorName,
user_id := UserID}, NewUserInfo) -> user_id := UserID}, NewUserInfo) ->
case emqx_authn:update_user(ChainID, AuthenticatorName, UserID, NewUserInfo) of case emqx_authn:update_user(?CHAIN, Name, UserID, NewUserInfo) of
{ok, User} -> {ok, User} ->
return({ok, User}); return({ok, User});
{error, Reason} -> {error, Reason} ->
@ -466,10 +279,9 @@ do_update_user(#{id := ChainID,
lookup_user(Binding, Params) -> lookup_user(Binding, Params) ->
do_lookup_user(uri_decode(Binding), maps:from_list(Params)). do_lookup_user(uri_decode(Binding), maps:from_list(Params)).
do_lookup_user(#{id := ChainID, do_lookup_user(#{name := Name,
authenticator_name := AuthenticatorName,
user_id := UserID}, _Params) -> user_id := UserID}, _Params) ->
case emqx_authn:lookup_user(ChainID, AuthenticatorName, UserID) of case emqx_authn:lookup_user(?CHAIN, Name, UserID) of
{ok, User} -> {ok, User} ->
return({ok, User}); return({ok, User});
{error, Reason} -> {error, Reason} ->
@ -479,9 +291,8 @@ do_lookup_user(#{id := ChainID,
list_users(Binding, Params) -> list_users(Binding, Params) ->
do_list_users(uri_decode(Binding), maps:from_list(Params)). do_list_users(uri_decode(Binding), maps:from_list(Params)).
do_list_users(#{id := ChainID, do_list_users(#{name := Name}, _Params) ->
authenticator_name := AuthenticatorName}, _Params) -> case emqx_authn:list_users(?CHAIN, Name) of
case emqx_authn:list_users(ChainID, AuthenticatorName) of
{ok, Users} -> {ok, Users} ->
return({ok, Users}); return({ok, Users});
{error, Reason} -> {error, Reason} ->
@ -526,11 +337,7 @@ serialize_error(_) ->
{error, <<"UNKNOWN_ERROR">>, <<"Unknown error">>}. {error, <<"UNKNOWN_ERROR">>, <<"Unknown error">>}.
serialize_type(authenticator) -> serialize_type(authenticator) ->
"Authenticator"; "Authenticator".
serialize_type(chain) ->
"Chain";
serialize_type(authenticator_type) ->
"Authenticator type".
get_missed_params(Actual, Expected) -> get_missed_params(Actual, Expected) ->
Keys = lists:foldl(fun(Key, Acc) -> Keys = lists:foldl(fun(Key, Acc) ->

View File

@ -38,40 +38,19 @@ stop(_State) ->
ok. ok.
initialize() -> initialize() ->
#{chains := Chains, #{authenticators := Authenticators} = emqx_config:get([emqx_authn], #{authenticators => []}),
bindings := Bindings} = emqx_config:get([authn], #{chains => [], bindings => []}), initialize(Authenticators).
initialize_chains(Chains),
initialize_bindings(Bindings).
initialize_chains([]) -> initialize(Authenticators) ->
{ok, _} = emqx_authn:create_chain(#{id => ?CHAIN}),
initialize_authenticators(Authenticators).
initialize_authenticators([]) ->
ok; ok;
initialize_chains([#{id := ChainID, initialize_authenticators([#{name := Name} = Authenticator | More]) ->
type := Type, case emqx_authn:create_authenticator(?CHAIN, Authenticator) of
authenticators := Authenticators} | More]) ->
case emqx_authn:create_chain(#{id => ChainID,
type => Type}) of
{ok, _} -> {ok, _} ->
initialize_authenticators(ChainID, Authenticators), initialize_authenticators(More);
initialize_chains(More);
{error, Reason} -> {error, Reason} ->
?LOG(error, "Failed to create chain '~s': ~p", [ChainID, Reason]) ?LOG(error, "Failed to create authenticator '~s': ~p", [Name, Reason])
end.
initialize_authenticators(_ChainID, []) ->
ok;
initialize_authenticators(ChainID, [#{name := Name} = Authenticator | More]) ->
case emqx_authn:create_authenticator(ChainID, Authenticator) of
{ok, _} ->
initialize_authenticators(ChainID, More);
{error, Reason} ->
?LOG(error, "Failed to create authenticator '~s' in chain '~s': ~p", [Name, ChainID, Reason])
end.
initialize_bindings([]) ->
ok;
initialize_bindings([#{chain_id := ChainID, listeners := Listeners} | More]) ->
case emqx_authn:bind(Listeners, ChainID) of
ok -> initialize_bindings(More);
{error, Reason} ->
?LOG(error, "Failed to bind: ~p", [Reason])
end. end.

View File

@ -21,94 +21,55 @@
-behaviour(hocon_schema). -behaviour(hocon_schema).
-export([structs/0, fields/1]). -export([ structs/0
, fields/1
]).
-reflect_type([ chain_id/0 -reflect_type([ authenticator_name/0
, authenticator_name/0
]). ]).
structs() -> ["emqx_authn"]. structs() -> ["emqx_authn"].
fields("emqx_authn") -> fields("emqx_authn") ->
[ {chains, fun chains/1} [ {authenticators, fun authenticators/1} ];
, {bindings, fun bindings/1}];
fields('simple-chain') -> fields('password-based') ->
[ {id, fun chain_id/1}
, {type, {enum, [simple]}}
, {authenticators, fun simple_authenticators/1}
];
% fields('enhanced-chain') ->
% [ {id, fun chain_id/1}
% , {type, {enum, [enhanced]}}
% , {authenticators, fun enhanced_authenticators/1}
% ];
fields(binding) ->
[ {chain_id, fun chain_id/1}
, {listeners, fun listeners/1}
];
fields('built-in-database') ->
[ {name, fun authenticator_name/1} [ {name, fun authenticator_name/1}
, {type, {enum, ['built-in-database']}} , {mechanism, {enum, ['password-based']}}
, {config, hoconsc:t(hoconsc:ref(emqx_authn_mnesia, config))} , {config, hoconsc:t(hoconsc:union(
[ hoconsc:ref(emqx_authn_mnesia, config)
, hoconsc:ref(emqx_authn_mysql, config)
, hoconsc:ref(emqx_authn_pgsql, config)
, hoconsc:ref(emqx_authn_http, get)
, hoconsc:ref(emqx_authn_http, post)
]))}
]; ];
% fields('enhanced-built-in-database') ->
% [ {name, fun authenticator_name/1}
% , {type, {enum, ['built-in-database']}}
% , {config, hoconsc:t(hoconsc:ref(emqx_enhanced_authn_mnesia, config))}
% ];
fields(jwt) -> fields(jwt) ->
[ {name, fun authenticator_name/1} [ {name, fun authenticator_name/1}
, {type, {enum, [jwt]}} , {mechanism, {enum, [jwt]}}
, {config, hoconsc:t(hoconsc:ref(emqx_authn_jwt, config))} , {config, hoconsc:t(hoconsc:union(
[ hoconsc:ref(emqx_authn_jwt, 'hmac-based')
, hoconsc:ref(emqx_authn_jwt, 'public-key')
, hoconsc:ref(emqx_authn_jwt, 'jwks')
]))}
]; ];
fields(mysql) -> fields(scram) ->
[ {name, fun authenticator_name/1} [ {name, fun authenticator_name/1}
, {type, {enum, [mysql]}} , {mechanism, {enum, [scram]}}
, {config, hoconsc:t(hoconsc:ref(emqx_authn_mysql, config))} , {config, hoconsc:t(hoconsc:union(
]; [ hoconsc:ref(emqx_enhanced_authn_scram_mnesia, config)
]))}
fields(pgsql) ->
[ {name, fun authenticator_name/1}
, {type, {enum, [postgresql]}}
, {config, hoconsc:t(hoconsc:ref(emqx_authn_pgsql, config))}
]. ].
chains(type) -> hoconsc:array({union, [hoconsc:ref(?MODULE, 'simple-chain')]}); authenticators(type) ->
chains(default) -> []; hoconsc:array({union, [ hoconsc:ref(?MODULE, 'password-based')
chains(_) -> undefined.
chain_id(type) -> chain_id();
chain_id(nullable) -> false;
chain_id(_) -> undefined.
simple_authenticators(type) ->
hoconsc:array({union, [ hoconsc:ref(?MODULE, 'built-in-database')
, hoconsc:ref(?MODULE, jwt) , hoconsc:ref(?MODULE, jwt)
, hoconsc:ref(?MODULE, mysql) , hoconsc:ref(?MODULE, scram)]});
, hoconsc:ref(?MODULE, pgsql)]}); authenticators(default) -> [];
simple_authenticators(default) -> []; authenticators(_) -> undefined.
simple_authenticators(_) -> undefined.
% enhanced_authenticators(type) ->
% hoconsc:array({union, [hoconsc:ref('enhanced-built-in-database')]});
% enhanced_authenticators(default) -> [];
% enhanced_authenticators(_) -> undefined.
authenticator_name(type) -> authenticator_name(); authenticator_name(type) -> authenticator_name();
authenticator_name(nullable) -> false; authenticator_name(nullable) -> false;
authenticator_name(_) -> undefined. authenticator_name(_) -> undefined.
bindings(type) -> hoconsc:array(hoconsc:ref(?MODULE, binding));
bindings(default) -> [];
bindings(_) -> undefined.
listeners(type) -> hoconsc:array(binary());
listeners(default) -> [];
listeners(_) -> undefined.

View File

@ -17,6 +17,7 @@
-module(emqx_authn_utils). -module(emqx_authn_utils).
-export([ replace_placeholder/2 -export([ replace_placeholder/2
, gen_salt/0
]). ]).
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
@ -41,6 +42,10 @@ replace_placeholder([<<"${cert-common-name}">> | More], #{cn := CommonName} = Da
replace_placeholder([_ | More], Data, Acc) -> replace_placeholder([_ | More], Data, Acc) ->
replace_placeholder(More, Data, [null | Acc]). replace_placeholder(More, Data, [null | Acc]).
gen_salt() ->
<<X:128/big-unsigned-integer>> = crypto:strong_rand_bytes(16),
iolist_to_binary(io_lib:format("~32.16.0b", [X])).
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
%% Internal functions %% Internal functions
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------

View File

@ -1,17 +0,0 @@
%%--------------------------------------------------------------------
%% Copyright (c) 2021 EMQ Technologies Co., Ltd. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%--------------------------------------------------------------------
-module(emqx_enhanced_authn_mnesia).

View File

@ -0,0 +1,240 @@
%%--------------------------------------------------------------------
%% Copyright (c) 2021 EMQ Technologies Co., Ltd. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%--------------------------------------------------------------------
-module(emqx_enhanced_authn_scram_mnesia).
-include("emqx_authn.hrl").
-include_lib("esasl/include/esasl_scram.hrl").
-include_lib("typerefl/include/types.hrl").
-behaviour(hocon_schema).
-export([ structs/0
, fields/1
]).
-export([ create/3
, update/4
, authenticate/2
, destroy/1
]).
-export([ add_user/2
, delete_user/2
, update_user/3
, lookup_user/2
, list_users/1
]).
-define(TAB, ?MODULE).
-export([mnesia/1]).
-boot_mnesia({mnesia, [boot]}).
-copy_mnesia({mnesia, [copy]}).
-rlog_shard({?AUTH_SHARD, ?TAB}).
%%------------------------------------------------------------------------------
%% Mnesia bootstrap
%%------------------------------------------------------------------------------
%% @doc Create or replicate tables.
-spec(mnesia(boot | copy) -> ok).
mnesia(boot) ->
ok = ekka_mnesia:create_table(?TAB, [
{disc_copies, [node()]},
{record_name, scram_user_credentail},
{attributes, record_info(fields, scram_user_credentail)},
{storage_properties, [{ets, [{read_concurrency, true}]}]}]);
mnesia(copy) ->
ok = ekka_mnesia:copy_table(?TAB, disc_copies).
%%------------------------------------------------------------------------------
%% Hocon Schema
%%------------------------------------------------------------------------------
structs() -> [config].
fields(config) ->
[ {server_type, fun server_type/1}
, {algorithm, fun algorithm/1}
, {iteration_count, fun iteration_count/1}
].
server_type(type) -> hoconsc:enum(['built-in-database']);
server_type(default) -> 'built-in-database';
server_type(_) -> undefined.
algorithm(type) -> hoconsc:enum([sha256, sha256]);
algorithm(default) -> sha256;
algorithm(_) -> undefined.
iteration_count(type) -> non_neg_integer();
iteration_count(default) -> 4096;
iteration_count(_) -> undefined.
%%------------------------------------------------------------------------------
%% APIs
%%------------------------------------------------------------------------------
create(ChainID, Authenticator, #{algorithm := Algorithm,
iteration_count := IterationCount}) ->
State = #{user_group => {ChainID, Authenticator},
algorithm => Algorithm,
iteration_count => IterationCount},
{ok, State}.
update(_ChainID, _Authenticator, _Config, _State) ->
{error, update_not_suppored}.
authenticate(#{auth_method := AuthMethod,
auth_data := AuthData,
auth_cache := AuthCache}, State) ->
case ensure_auth_method(AuthMethod, State) of
true ->
case AuthCache of
#{next_step := client_final} ->
check_client_final_message(AuthData, AuthCache, State);
_ ->
check_client_first_message(AuthData, AuthCache, State)
end;
false ->
ignore
end;
authenticate(_Credential, _State) ->
ignore.
destroy(#{user_group := UserGroup}) ->
trans(
fun() ->
MatchSpec = [{{scram_user_credentail, {UserGroup, '_'}, '_', '_', '_'}, [], ['$_']}],
ok = lists:foreach(fun(UserCredential) ->
mnesia:delete_object(?TAB, UserCredential, write)
end, mnesia:select(?TAB, MatchSpec, write))
end).
%% TODO: binary to atom
add_user(#{<<"user_id">> := UserID,
<<"password">> := Password}, #{user_group := UserGroup} = State) ->
trans(
fun() ->
case mnesia:read(?TAB, {UserGroup, UserID}, write) of
[] ->
add_user(UserID, Password, State),
{ok, #{user_id => UserID}};
[_] ->
{error, already_exist}
end
end).
delete_user(UserID, #{user_group := UserGroup}) ->
trans(
fun() ->
case mnesia:read(?TAB, {UserGroup, UserID}, write) of
[] ->
{error, not_found};
[_] ->
mnesia:delete(?TAB, {UserGroup, UserID}, write)
end
end).
update_user(UserID, #{<<"password">> := Password},
#{user_group := UserGroup} = State) ->
trans(
fun() ->
case mnesia:read(?TAB, {UserGroup, UserID}, write) of
[] ->
{error, not_found};
[_] ->
add_user(UserID, Password, State),
{ok, #{user_id => UserID}}
end
end).
lookup_user(UserID, #{user_group := UserGroup}) ->
case mnesia:dirty_read(?TAB, {UserGroup, UserID}) of
[#scram_user_credentail{user_id = {_, UserID}}] ->
{ok, #{user_id => UserID}};
[] ->
{error, not_found}
end.
%% TODO: Support Pagination
list_users(#{user_group := UserGroup}) ->
Users = [#{user_id => UserID} ||
#scram_user_credentail{user_id = {UserGroup0, UserID}} <- ets:tab2list(?TAB), UserGroup0 =:= UserGroup],
{ok, Users}.
%%------------------------------------------------------------------------------
%% Internal functions
%%------------------------------------------------------------------------------
ensure_auth_method('SCRAM-SHA-256', #{algorithm := sha256}) ->
true;
ensure_auth_method('SCRAM-SHA-512', #{algorithm := sha512}) ->
true;
ensure_auth_method(_, _) ->
false.
check_client_first_message(Bin, _Cache, #{iteration_count := IterationCount} = State) ->
LookupFun = fun(Username) ->
lookup_user2(Username, State)
end,
case esasl_scram:check_client_first_message(
Bin,
#{iteration_count => IterationCount,
lookup => LookupFun}
) of
{cotinue, ServerFirstMessage, Cache} ->
{cotinue, ServerFirstMessage, Cache};
{error, _Reason} ->
{error, not_authorized}
end.
check_client_final_message(Bin, Cache, #{algorithm := Alg}) ->
case esasl_scram:check_client_final_message(
Bin,
Cache#{algorithm => Alg}
) of
{ok, ServerFinalMessage} ->
{ok, ServerFinalMessage};
{error, _Reason} ->
{error, not_authorized}
end.
add_user(UserID, Password, State) ->
UserCredential = esasl_scram:generate_user_credential(UserID, Password, State),
mnesia:write(?TAB, UserCredential, write).
lookup_user2(UserID, #{user_group := UserGroup}) ->
case mnesia:dirty_read(?TAB, {UserGroup, UserID}) of
[#scram_user_credentail{} = UserCredential] ->
{ok, UserCredential};
[] ->
{error, not_found}
end.
%% TODO: Move to emqx_authn_utils.erl
trans(Fun) ->
trans(Fun, []).
trans(Fun, Args) ->
case ekka_mnesia:transaction(?AUTH_SHARD, Fun, Args) of
{atomic, Res} -> Res;
{aborted, Reason} -> {error, Reason}
end.

View File

@ -46,10 +46,9 @@
structs() -> [""]. structs() -> [""].
fields("") -> fields("") ->
[ {config, #{type => hoconsc:union( [ {config, {union, [ hoconsc:t(get)
[ hoconsc:ref(?MODULE, get) , hoconsc:t(post)
, hoconsc:ref(?MODULE, post) ]}}
])}}
]; ];
fields(get) -> fields(get) ->
@ -64,7 +63,8 @@ fields(post) ->
] ++ common_fields(). ] ++ common_fields().
common_fields() -> common_fields() ->
[ {url, fun url/1} [ {server_type, {enum, ['http-server']}}
, {url, fun url/1}
, {accept, fun accept/1} , {accept, fun accept/1}
, {headers, fun headers/1} , {headers, fun headers/1}
, {form_data, fun form_data/1} , {form_data, fun form_data/1}
@ -142,10 +142,12 @@ update(_ChainID, _AuthenticatorName, Config, #{resource_id := ResourceID} = Stat
{error, Reason} -> {error, Reason} {error, Reason} -> {error, Reason}
end. end.
authenticate(ClientInfo, #{resource_id := ResourceID, authenticate(#{auth_method := _}, _) ->
ignore;
authenticate(Credential, #{resource_id := ResourceID,
method := Method, method := Method,
request_timeout := RequestTimeout} = State) -> request_timeout := RequestTimeout} = State) ->
Request = generate_request(ClientInfo, State), Request = generate_request(Credential, State),
case emqx_resource:query(ResourceID, {Method, Request, RequestTimeout}) of case emqx_resource:query(ResourceID, {Method, Request, RequestTimeout}) of
{ok, 204, _Headers} -> ok; {ok, 204, _Headers} -> ok;
{ok, 200, Headers, Body} -> {ok, 200, Headers, Body} ->
@ -154,8 +156,8 @@ authenticate(ClientInfo, #{resource_id := ResourceID,
{ok, _NBody} -> {ok, _NBody} ->
%% TODO: Return by user property %% TODO: Return by user property
ok; ok;
{error, Reason} -> {error, _Reason} ->
{stop, Reason} ok
end; end;
{error, _Reason} -> {error, _Reason} ->
ignore ignore
@ -208,13 +210,13 @@ generate_base_url(#{scheme := Scheme,
port := Port}) -> port := Port}) ->
iolist_to_binary(io_lib:format("~p://~s:~p", [Scheme, Host, Port])). iolist_to_binary(io_lib:format("~p://~s:~p", [Scheme, Host, Port])).
generate_request(ClientInfo, #{method := Method, generate_request(Credential, #{method := Method,
path := Path, path := Path,
base_query := BaseQuery, base_query := BaseQuery,
content_type := ContentType, content_type := ContentType,
headers := Headers, headers := Headers,
form_data := FormData0}) -> form_data := FormData0}) ->
FormData = replace_placeholders(FormData0, ClientInfo), FormData = replace_placeholders(FormData0, Credential),
case Method of case Method of
get -> get ->
NPath = append_query(Path, BaseQuery ++ FormData), NPath = append_query(Path, BaseQuery ++ FormData),
@ -225,9 +227,9 @@ generate_request(ClientInfo, #{method := Method,
{NPath, Headers, Body} {NPath, Headers, Body}
end. end.
replace_placeholders(FormData0, ClientInfo) -> replace_placeholders(FormData0, Credential) ->
FormData = lists:map(fun({K, V0}) -> FormData = lists:map(fun({K, V0}) ->
case replace_placeholder(V0, ClientInfo) of case replace_placeholder(V0, Credential) of
undefined -> {K, undefined}; undefined -> {K, undefined};
V -> {K, bin(V)} V -> {K, bin(V)}
end end
@ -236,16 +238,16 @@ replace_placeholders(FormData0, ClientInfo) ->
V =/= undefined V =/= undefined
end, FormData). end, FormData).
replace_placeholder(<<"${mqtt-username}">>, ClientInfo) -> replace_placeholder(<<"${mqtt-username}">>, Credential) ->
maps:get(username, ClientInfo, undefined); maps:get(username, Credential, undefined);
replace_placeholder(<<"${mqtt-clientid}">>, ClientInfo) -> replace_placeholder(<<"${mqtt-clientid}">>, Credential) ->
maps:get(clientid, ClientInfo, undefined); maps:get(clientid, Credential, undefined);
replace_placeholder(<<"${ip-address}">>, ClientInfo) -> replace_placeholder(<<"${ip-address}">>, Credential) ->
maps:get(peerhost, ClientInfo, undefined); maps:get(peerhost, Credential, undefined);
replace_placeholder(<<"${cert-subject}">>, ClientInfo) -> replace_placeholder(<<"${cert-subject}">>, Credential) ->
maps:get(dn, ClientInfo, undefined); maps:get(dn, Credential, undefined);
replace_placeholder(<<"${cert-common-name}">>, ClientInfo) -> replace_placeholder(<<"${cert-common-name}">>, Credential) ->
maps:get(cn, ClientInfo, undefined); maps:get(cn, Credential, undefined);
replace_placeholder(Constant, _) -> replace_placeholder(Constant, _) ->
Constant. Constant.

View File

@ -132,10 +132,7 @@ handle_options(#{endpoint := Endpoint,
refresh_interval => limit_refresh_interval(RefreshInterval0), refresh_interval => limit_refresh_interval(RefreshInterval0),
ssl_opts => maps:to_list(SSLOpts), ssl_opts => maps:to_list(SSLOpts),
jwks => [], jwks => [],
request_id => undefined}; request_id => undefined}.
handle_options(#{enable_ssl := false} = Opts) ->
handle_options(Opts#{ssl_opts => #{}}).
refresh_jwks(#{endpoint := Endpoint, refresh_jwks(#{endpoint := Endpoint,
ssl_opts := SSLOpts} = State) -> ssl_opts := SSLOpts} = State) ->

View File

@ -35,21 +35,14 @@
%% Hocon Schema %% Hocon Schema
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
structs() -> [config]. structs() -> [""].
fields("") -> fields("") ->
[{config, {union, [ hoconsc:t('hmac-based') [ {config, {union, [ hoconsc:t('hmac-based')
, hoconsc:t('public-key') , hoconsc:t('public-key')
, hoconsc:t('jwks') , hoconsc:t('jwks')
, hoconsc:t('jwks-using-ssl') ]}}
]}}]; ];
fields(config) ->
[{union, [ hoconsc:t('hmac-based')
, hoconsc:t('public-key')
, hoconsc:t('jwks')
, hoconsc:t('jwks-using-ssl')
]}];
fields('hmac-based') -> fields('hmac-based') ->
[ {use_jwks, {enum, [false]}} [ {use_jwks, {enum, [false]}}
@ -67,35 +60,35 @@ fields('public-key') ->
]; ];
fields('jwks') -> fields('jwks') ->
[ {enable_ssl, {enum, [false]}} [ {use_jwks, {enum, [true]}}
] ++ jwks_fields(); , {endpoint, fun endpoint/1}
, {refresh_interval, fun refresh_interval/1}
, {verify_claims, fun verify_claims/1}
, {ssl, #{type => hoconsc:union(
[ hoconsc:ref(?MODULE, ssl_enable)
, hoconsc:ref(?MODULE, ssl_disable)
]),
default => #{<<"enable">> => false}}}
];
fields('jwks-using-ssl') -> fields(ssl_enable) ->
[ {enable_ssl, {enum, [true]}} [ {enable, #{type => true}}
, {ssl_opts, fun ssl_opts/1} , {cacertfile, fun cacertfile/1}
] ++ jwks_fields();
fields(ssl_opts) ->
[ {cacertfile, fun cacertfile/1}
, {certfile, fun certfile/1} , {certfile, fun certfile/1}
, {keyfile, fun keyfile/1} , {keyfile, fun keyfile/1}
, {verify, fun verify/1} , {verify, fun verify/1}
, {server_name_indication, fun server_name_indication/1} , {server_name_indication, fun server_name_indication/1}
]; ];
fields(ssl_disable) ->
[ {enable, #{type => false}} ];
fields(claim) -> fields(claim) ->
[ {"$name", fun expected_claim_value/1} ]. [ {"$name", fun expected_claim_value/1} ].
validations() -> validations() ->
[ {check_verify_claims, fun check_verify_claims/1} ]. [ {check_verify_claims, fun check_verify_claims/1} ].
jwks_fields() ->
[ {use_jwks, {enum, [true]}}
, {endpoint, fun endpoint/1}
, {refresh_interval, fun refresh_interval/1}
, {verify_claims, fun verify_claims/1}
].
secret(type) -> string(); secret(type) -> string();
secret(_) -> undefined. secret(_) -> undefined.
@ -109,9 +102,9 @@ certificate(_) -> undefined.
endpoint(type) -> string(); endpoint(type) -> string();
endpoint(_) -> undefined. endpoint(_) -> undefined.
ssl_opts(type) -> hoconsc:t(hoconsc:ref(ssl_opts)); % ssl_opts(type) -> hoconsc:t(hoconsc:ref(ssl_opts));
ssl_opts(default) -> []; % ssl_opts(default) -> [];
ssl_opts(_) -> undefined. % ssl_opts(_) -> undefined.
refresh_interval(type) -> integer(); refresh_interval(type) -> integer();
refresh_interval(default) -> 300; refresh_interval(default) -> 300;
@ -169,7 +162,9 @@ update(_ChainID, _AuthenticatorName, #{use_jwks := true} = Config, #{jwk := Conn
update(_ChainID, _AuthenticatorName, #{use_jwks := true} = Config, _) -> update(_ChainID, _AuthenticatorName, #{use_jwks := true} = Config, _) ->
create(Config). create(Config).
authenticate(ClientInfo = #{password := JWT}, #{jwk := JWK, authenticate(#{auth_method := _}, _) ->
ignore;
authenticate(Credential = #{password := JWT}, #{jwk := JWK,
verify_claims := VerifyClaims0}) -> verify_claims := VerifyClaims0}) ->
JWKs = case erlang:is_pid(JWK) of JWKs = case erlang:is_pid(JWK) of
false -> false ->
@ -178,11 +173,11 @@ authenticate(ClientInfo = #{password := JWT}, #{jwk := JWK,
{ok, JWKs0} = emqx_authn_jwks_connector:get_jwks(JWK), {ok, JWKs0} = emqx_authn_jwks_connector:get_jwks(JWK),
JWKs0 JWKs0
end, end,
VerifyClaims = replace_placeholder(VerifyClaims0, ClientInfo), VerifyClaims = replace_placeholder(VerifyClaims0, Credential),
case verify(JWT, JWKs, VerifyClaims) of case verify(JWT, JWKs, VerifyClaims) of
ok -> ok; ok -> ok;
{error, invalid_signature} -> ignore; {error, invalid_signature} -> ignore;
{error, {claims, _}} -> {stop, bad_password} {error, {claims, _}} -> {error, bad_username_or_password}
end. end.
destroy(#{jwk := Connector}) when is_pid(Connector) -> destroy(#{jwk := Connector}) when is_pid(Connector) ->
@ -222,8 +217,13 @@ create2(#{use_jwks := false,
verify_claims => VerifyClaims}}; verify_claims => VerifyClaims}};
create2(#{use_jwks := true, create2(#{use_jwks := true,
verify_claims := VerifyClaims} = Config) -> verify_claims := VerifyClaims,
case emqx_authn_jwks_connector:start_link(Config) of ssl := #{enable := Enable} = SSL} = Config) ->
SSLOpts = case Enable of
true -> maps:without(enable, SSL);
false -> #{}
end,
case emqx_authn_jwks_connector:start_link(Config#{ssl_opts => SSLOpts}) of
{ok, Connector} -> {ok, Connector} ->
{ok, #{jwk => Connector, {ok, #{jwk => Connector,
verify_claims => VerifyClaims}}; verify_claims => VerifyClaims}};

View File

@ -55,7 +55,7 @@
-boot_mnesia({mnesia, [boot]}). -boot_mnesia({mnesia, [boot]}).
-copy_mnesia({mnesia, [copy]}). -copy_mnesia({mnesia, [copy]}).
-define(TAB, mnesia_basic_auth). -define(TAB, ?MODULE).
-rlog_shard({?AUTH_SHARD, ?TAB}). -rlog_shard({?AUTH_SHARD, ?TAB}).
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
@ -81,7 +81,8 @@ mnesia(copy) ->
structs() -> [config]. structs() -> [config].
fields(config) -> fields(config) ->
[ {user_id_type, fun user_id_type/1} [ {server_type, {enum, ['built-in-database']}}
, {user_id_type, fun user_id_type/1}
, {password_hash_algorithm, fun password_hash_algorithm/1} , {password_hash_algorithm, fun password_hash_algorithm/1}
]; ];
@ -95,11 +96,11 @@ fields(other_algorithms) ->
]. ].
user_id_type(type) -> user_id_type(); user_id_type(type) -> user_id_type();
user_id_type(default) -> clientid; user_id_type(default) -> username;
user_id_type(_) -> undefined. user_id_type(_) -> undefined.
password_hash_algorithm(type) -> {union, [hoconsc:ref(bcrypt), hoconsc:ref(other_algorithms)]}; password_hash_algorithm(type) -> {union, [hoconsc:ref(bcrypt), hoconsc:ref(other_algorithms)]};
password_hash_algorithm(default) -> sha256; password_hash_algorithm(default) -> #{<<"name">> => sha256};
password_hash_algorithm(_) -> undefined. password_hash_algorithm(_) -> undefined.
salt_rounds(type) -> integer(); salt_rounds(type) -> integer();
@ -130,11 +131,13 @@ create(ChainID, AuthenticatorName, #{user_id_type := Type,
update(ChainID, AuthenticatorName, Config, _State) -> update(ChainID, AuthenticatorName, Config, _State) ->
create(ChainID, AuthenticatorName, Config). create(ChainID, AuthenticatorName, Config).
authenticate(ClientInfo = #{password := Password}, authenticate(#{auth_method := _}, _) ->
ignore;
authenticate(#{password := Password} = Credential,
#{user_group := UserGroup, #{user_group := UserGroup,
user_id_type := Type, user_id_type := Type,
password_hash_algorithm := Algorithm}) -> password_hash_algorithm := Algorithm}) ->
UserID = get_user_identity(ClientInfo, Type), UserID = get_user_identity(Credential, Type),
case mnesia:dirty_read(?TAB, {UserGroup, UserID}) of case mnesia:dirty_read(?TAB, {UserGroup, UserID}) of
[] -> [] ->
ignore; ignore;
@ -145,7 +148,7 @@ authenticate(ClientInfo = #{password := Password},
end, end,
case PasswordHash =:= hash(Algorithm, Password, Salt) of case PasswordHash =:= hash(Algorithm, Password, Salt) of
true -> ok; true -> ok;
false -> {stop, bad_password} false -> {error, bad_username_or_password}
end end
end. end.
@ -330,8 +333,7 @@ gen_salt(#{password_hash_algorithm := bcrypt,
{ok, Salt} = bcrypt:gen_salt(Rounds), {ok, Salt} = bcrypt:gen_salt(Rounds),
Salt; Salt;
gen_salt(_) -> gen_salt(_) ->
<<X:128/big-unsigned-integer>> = crypto:strong_rand_bytes(16), emqx_authn_utils:gen_salt().
iolist_to_binary(io_lib:format("~32.16.0b", [X])).
hash(bcrypt, Password, Salt) -> hash(bcrypt, Password, Salt) ->
{ok, Hash} = bcrypt:hashpw(Password, Salt), {ok, Hash} = bcrypt:hashpw(Password, Salt),
@ -343,10 +345,10 @@ insert_user(UserGroup, UserID, PasswordHash) ->
insert_user(UserGroup, UserID, PasswordHash, <<>>). insert_user(UserGroup, UserID, PasswordHash, <<>>).
insert_user(UserGroup, UserID, PasswordHash, Salt) -> insert_user(UserGroup, UserID, PasswordHash, Salt) ->
Credential = #user_info{user_id = {UserGroup, UserID}, UserInfo = #user_info{user_id = {UserGroup, UserID},
password_hash = PasswordHash, password_hash = PasswordHash,
salt = Salt}, salt = Salt},
mnesia:write(?TAB, Credential, write). mnesia:write(?TAB, UserInfo, write).
delete_user2(UserInfo) -> delete_user2(UserInfo) ->
mnesia:delete_object(?TAB, UserInfo, write). mnesia:delete_object(?TAB, UserInfo, write).

View File

@ -36,7 +36,8 @@
structs() -> [config]. structs() -> [config].
fields(config) -> fields(config) ->
[ {password_hash_algorithm, fun password_hash_algorithm/1} [ {server_type, {enum, [mysql]}}
, {password_hash_algorithm, fun password_hash_algorithm/1}
, {salt_position, {enum, [prefix, suffix]}} , {salt_position, {enum, [prefix, suffix]}}
, {query, fun query/1} , {query, fun query/1}
, {query_timeout, fun query_timeout/1} , {query_timeout, fun query_timeout/1}
@ -81,12 +82,14 @@ update(_ChainID, _AuthenticatorName, Config, #{resource_id := ResourceID} = Stat
{error, Reason} -> {error, Reason} {error, Reason} -> {error, Reason}
end. end.
authenticate(#{password := Password} = ClientInfo, authenticate(#{auth_method := _}, _) ->
ignore;
authenticate(#{password := Password} = Credential,
#{resource_id := ResourceID, #{resource_id := ResourceID,
placeholders := PlaceHolders, placeholders := PlaceHolders,
query := Query, query := Query,
query_timeout := Timeout} = State) -> query_timeout := Timeout} = State) ->
Params = emqx_authn_utils:replace_placeholder(PlaceHolders, ClientInfo), Params = emqx_authn_utils:replace_placeholder(PlaceHolders, Credential),
case emqx_resource:query(ResourceID, {sql, Query, Params, Timeout}) of case emqx_resource:query(ResourceID, {sql, Query, Params, Timeout}) of
{ok, _Columns, []} -> ignore; {ok, _Columns, []} -> ignore;
{ok, Columns, Rows} -> {ok, Columns, Rows} ->
@ -106,14 +109,14 @@ destroy(#{resource_id := ResourceID}) ->
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
check_password(undefined, _Algorithm, _Selected) -> check_password(undefined, _Algorithm, _Selected) ->
{stop, bad_password}; {error, bad_username_or_password};
check_password(Password, check_password(Password,
#{password_hash := Hash}, #{password_hash := Hash},
#{password_hash_algorithm := bcrypt}) -> #{password_hash_algorithm := bcrypt}) ->
{ok, Hash0} = bcrypt:hashpw(Password, Hash), {ok, Hash0} = bcrypt:hashpw(Password, Hash),
case list_to_binary(Hash0) =:= Hash of case list_to_binary(Hash0) =:= Hash of
true -> ok; true -> ok;
false -> {stop, bad_password} false -> {error, bad_username_or_password}
end; end;
check_password(Password, check_password(Password,
#{password_hash := Hash} = Selected, #{password_hash := Hash} = Selected,
@ -126,7 +129,7 @@ check_password(Password,
end, end,
case Hash0 =:= Hash of case Hash0 =:= Hash of
true -> ok; true -> ok;
false -> {stop, bad_password} false -> {error, bad_username_or_password}
end. end.
%% TODO: Support prepare %% TODO: Support prepare

View File

@ -36,7 +36,8 @@
structs() -> [config]. structs() -> [config].
fields(config) -> fields(config) ->
[ {password_hash_algorithm, fun password_hash_algorithm/1} [ {server_type, {enum, [pgsql]}}
, {password_hash_algorithm, fun password_hash_algorithm/1}
, {salt_position, {enum, [prefix, suffix]}} , {salt_position, {enum, [prefix, suffix]}}
, {query, fun query/1} , {query, fun query/1}
] ++ emqx_connector_schema_lib:relational_db_fields() ] ++ emqx_connector_schema_lib:relational_db_fields()
@ -75,11 +76,13 @@ update(_ChainID, _ServiceName, Config, #{resource_id := ResourceID} = State) ->
{error, Reason} -> {error, Reason} {error, Reason} -> {error, Reason}
end. end.
authenticate(#{password := Password} = ClientInfo, authenticate(#{auth_method := _}, _) ->
ignore;
authenticate(#{password := Password} = Credential,
#{resource_id := ResourceID, #{resource_id := ResourceID,
query := Query, query := Query,
placeholders := PlaceHolders} = State) -> placeholders := PlaceHolders} = State) ->
Params = emqx_authn_utils:replace_placeholder(PlaceHolders, ClientInfo), Params = emqx_authn_utils:replace_placeholder(PlaceHolders, Credential),
case emqx_resource:query(ResourceID, {sql, Query, Params}) of case emqx_resource:query(ResourceID, {sql, Query, Params}) of
{ok, _Columns, []} -> ignore; {ok, _Columns, []} -> ignore;
{ok, Columns, Rows} -> {ok, Columns, Rows} ->
@ -99,14 +102,14 @@ destroy(#{resource_id := ResourceID}) ->
%%------------------------------------------------------------------------------ %%------------------------------------------------------------------------------
check_password(undefined, _Algorithm, _Selected) -> check_password(undefined, _Algorithm, _Selected) ->
{stop, bad_password}; {error, bad_username_or_password};
check_password(Password, check_password(Password,
#{password_hash := Hash}, #{password_hash := Hash},
#{password_hash_algorithm := bcrypt}) -> #{password_hash_algorithm := bcrypt}) ->
{ok, Hash0} = bcrypt:hashpw(Password, Hash), {ok, Hash0} = bcrypt:hashpw(Password, Hash),
case list_to_binary(Hash0) =:= Hash of case list_to_binary(Hash0) =:= Hash of
true -> ok; true -> ok;
false -> {stop, bad_password} false -> {error, bad_username_or_password}
end; end;
check_password(Password, check_password(Password,
#{password_hash := Hash} = Selected, #{password_hash := Hash} = Selected,
@ -119,7 +122,7 @@ check_password(Password,
end, end,
case Hash0 =:= Hash of case Hash0 =:= Hash of
true -> ok; true -> ok;
false -> {stop, bad_password} false -> {error, bad_username_or_password}
end. end.
%% TODO: Support prepare %% TODO: Support prepare

View File

@ -22,6 +22,8 @@
-include_lib("common_test/include/ct.hrl"). -include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl"). -include_lib("eunit/include/eunit.hrl").
-include("emqx_authn.hrl").
-define(AUTH, emqx_authn). -define(AUTH, emqx_authn).
all() -> all() ->
@ -40,16 +42,17 @@ end_per_suite(_) ->
set_special_configs(emqx_authn) -> set_special_configs(emqx_authn) ->
application:set_env(emqx, plugins_etc_dir, application:set_env(emqx, plugins_etc_dir,
emqx_ct_helpers:deps_path(emqx_authn, "test")), emqx_ct_helpers:deps_path(emqx_authn, "test")),
Conf = #{<<"authn">> => #{<<"chains">> => [], <<"bindings">> => []}}, Conf = #{<<"emqx_authn">> => #{<<"authenticators">> => []}},
ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)), ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)),
ok; ok;
set_special_configs(_App) -> set_special_configs(_App) ->
ok. ok.
t_chain(_) -> t_chain(_) ->
?assertMatch({ok, #{id := ?CHAIN, authenticators := []}}, ?AUTH:lookup_chain(?CHAIN)),
ChainID = <<"mychain">>, ChainID = <<"mychain">>,
Chain = #{id => ChainID, Chain = #{id => ChainID},
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)), ?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
?assertEqual({error, {already_exists, {chain, ChainID}}}, ?AUTH:create_chain(Chain)), ?assertEqual({error, {already_exists, {chain, ChainID}}}, ?AUTH:create_chain(Chain)),
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:lookup_chain(ChainID)), ?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:lookup_chain(ChainID)),
@ -57,86 +60,37 @@ t_chain(_) ->
?assertMatch({error, {not_found, {chain, ChainID}}}, ?AUTH:lookup_chain(ChainID)), ?assertMatch({error, {not_found, {chain, ChainID}}}, ?AUTH:lookup_chain(ChainID)),
ok. ok.
t_binding(_) ->
Listener1 = <<"listener1">>,
Listener2 = <<"listener2">>,
ChainID = <<"mychain">>,
?assertEqual({error, {not_found, {chain, ChainID}}}, ?AUTH:bind(ChainID, [Listener1])),
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
?assertEqual(ok, ?AUTH:bind(ChainID, [Listener1])),
?assertEqual(ok, ?AUTH:bind(ChainID, [Listener2])),
?assertEqual({error, {already_bound, [Listener1]}}, ?AUTH:bind(ChainID, [Listener1])),
{ok, #{listeners := Listeners}} = ?AUTH:list_bindings(ChainID),
?assertEqual(2, length(Listeners)),
?assertMatch({ok, #{simple := ChainID}}, ?AUTH:list_bound_chains(Listener1)),
?assertEqual(ok, ?AUTH:unbind(ChainID, [Listener1])),
?assertEqual(ok, ?AUTH:unbind(ChainID, [Listener2])),
?assertEqual({error, {not_found, [Listener1]}}, ?AUTH:unbind(ChainID, [Listener1])),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok.
t_binding2(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
Listener1 = <<"listener1">>,
Listener2 = <<"listener2">>,
?assertEqual(ok, ?AUTH:bind(ChainID, [Listener1, Listener2])),
{ok, #{listeners := Listeners}} = ?AUTH:list_bindings(ChainID),
?assertEqual(2, length(Listeners)),
?assertEqual(ok, ?AUTH:unbind(ChainID, [Listener1, Listener2])),
?assertMatch({ok, #{listeners := []}}, ?AUTH:list_bindings(ChainID)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok.
t_authenticator(_) -> t_authenticator(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:lookup_chain(ChainID)),
AuthenticatorName1 = <<"myauthenticator1">>, AuthenticatorName1 = <<"myauthenticator1">>,
AuthenticatorConfig1 = #{name => AuthenticatorName1, AuthenticatorConfig1 = #{name => AuthenticatorName1,
type => 'built-in-database', mechanism => 'password-based',
config => #{ config => #{
server_type => 'built-in-database',
user_id_type => username, user_id_type => username,
password_hash_algorithm => #{ password_hash_algorithm => #{
name => sha256 name => sha256
}}}, }}},
?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig1)), ?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig1)),
?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:lookup_authenticator(ChainID, AuthenticatorName1)), ?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:lookup_authenticator(?CHAIN, AuthenticatorName1)),
?assertEqual({ok, [AuthenticatorConfig1]}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, [AuthenticatorConfig1]}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual({error, {already_exists, {authenticator, AuthenticatorName1}}}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig1)), ?assertEqual({error, {already_exists, {authenticator, AuthenticatorName1}}}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig1)),
AuthenticatorName2 = <<"myauthenticator2">>, AuthenticatorName2 = <<"myauthenticator2">>,
AuthenticatorConfig2 = AuthenticatorConfig1#{name => AuthenticatorName2}, AuthenticatorConfig2 = AuthenticatorConfig1#{name => AuthenticatorName2},
?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig2)), ?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig2)),
?assertMatch({ok, #{id := ChainID, authenticators := [AuthenticatorConfig1, AuthenticatorConfig2]}}, ?AUTH:lookup_chain(ChainID)), ?assertMatch({ok, #{id := ?CHAIN, authenticators := [AuthenticatorConfig1, AuthenticatorConfig2]}}, ?AUTH:lookup_chain(?CHAIN)),
?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:lookup_authenticator(ChainID, AuthenticatorName2)), ?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:lookup_authenticator(?CHAIN, AuthenticatorName2)),
?assertEqual({ok, [AuthenticatorConfig1, AuthenticatorConfig2]}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, [AuthenticatorConfig1, AuthenticatorConfig2]}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual(ok, ?AUTH:move_authenticator_to_the_front(ChainID, AuthenticatorName2)), ?assertEqual(ok, ?AUTH:move_authenticator_to_the_front(?CHAIN, AuthenticatorName2)),
?assertEqual({ok, [AuthenticatorConfig2, AuthenticatorConfig1]}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, [AuthenticatorConfig2, AuthenticatorConfig1]}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual(ok, ?AUTH:move_authenticator_to_the_end(ChainID, AuthenticatorName2)), ?assertEqual(ok, ?AUTH:move_authenticator_to_the_end(?CHAIN, AuthenticatorName2)),
?assertEqual({ok, [AuthenticatorConfig1, AuthenticatorConfig2]}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, [AuthenticatorConfig1, AuthenticatorConfig2]}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual(ok, ?AUTH:move_authenticator_to_the_nth(ChainID, AuthenticatorName2, 1)), ?assertEqual(ok, ?AUTH:move_authenticator_to_the_nth(?CHAIN, AuthenticatorName2, 1)),
?assertEqual({ok, [AuthenticatorConfig2, AuthenticatorConfig1]}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, [AuthenticatorConfig2, AuthenticatorConfig1]}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual({error, out_of_range}, ?AUTH:move_authenticator_to_the_nth(ChainID, AuthenticatorName2, 3)), ?assertEqual({error, out_of_range}, ?AUTH:move_authenticator_to_the_nth(?CHAIN, AuthenticatorName2, 3)),
?assertEqual({error, out_of_range}, ?AUTH:move_authenticator_to_the_nth(ChainID, AuthenticatorName2, 0)), ?assertEqual({error, out_of_range}, ?AUTH:move_authenticator_to_the_nth(?CHAIN, AuthenticatorName2, 0)),
?assertEqual(ok, ?AUTH:delete_authenticator(ChainID, AuthenticatorName1)), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName1)),
?assertEqual(ok, ?AUTH:delete_authenticator(ChainID, AuthenticatorName2)), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName2)),
?assertEqual({ok, []}, ?AUTH:list_authenticators(ChainID)), ?assertEqual({ok, []}, ?AUTH:list_authenticators(?CHAIN)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok. ok.

View File

@ -22,6 +22,8 @@
-include_lib("common_test/include/ct.hrl"). -include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl"). -include_lib("eunit/include/eunit.hrl").
-include("emqx_authn.hrl").
-define(AUTH, emqx_authn). -define(AUTH, emqx_authn).
all() -> all() ->
@ -39,18 +41,13 @@ end_per_suite(_) ->
set_special_configs(emqx_authn) -> set_special_configs(emqx_authn) ->
application:set_env(emqx, plugins_etc_dir, application:set_env(emqx, plugins_etc_dir,
emqx_ct_helpers:deps_path(emqx_authn, "test")), emqx_ct_helpers:deps_path(emqx_authn, "test")),
Conf = #{<<"authn">> => #{<<"chains">> => [], <<"bindings">> => []}}, Conf = #{<<"emqx_authn">> => #{<<"authenticators">> => []}},
ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)), ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)),
ok; ok;
set_special_configs(_App) -> set_special_configs(_App) ->
ok. ok.
t_jwt_authenticator(_) -> t_jwt_authenticator(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
AuthenticatorName = <<"myauthenticator">>, AuthenticatorName = <<"myauthenticator">>,
Config = #{use_jwks => false, Config = #{use_jwks => false,
algorithm => 'hmac-based', algorithm => 'hmac-based',
@ -58,84 +55,74 @@ t_jwt_authenticator(_) ->
secret_base64_encoded => false, secret_base64_encoded => false,
verify_claims => []}, verify_claims => []},
AuthenticatorConfig = #{name => AuthenticatorName, AuthenticatorConfig = #{name => AuthenticatorName,
type => jwt, mechanism => jwt,
config => Config}, config => Config},
?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig)), ?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig)),
ListenerID = <<"listener1">>,
?AUTH:bind(ChainID, [ListenerID]),
Payload = #{<<"username">> => <<"myuser">>}, Payload = #{<<"username">> => <<"myuser">>},
JWS = generate_jws('hmac-based', Payload, <<"abcdef">>), JWS = generate_jws('hmac-based', Payload, <<"abcdef">>),
ClientInfo = #{listener_id => ListenerID, ClientInfo = #{username => <<"myuser">>,
username => <<"myuser">>,
password => JWS}, password => JWS},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo, ok)),
BadJWS = generate_jws('hmac-based', Payload, <<"bad_secret">>), BadJWS = generate_jws('hmac-based', Payload, <<"bad_secret">>),
ClientInfo2 = ClientInfo#{password => BadJWS}, ClientInfo2 = ClientInfo#{password => BadJWS},
?assertEqual({error, user_not_found}, ?AUTH:authenticate(ClientInfo2)), ?assertEqual({stop, {error, not_authorized}}, ?AUTH:authenticate(ClientInfo2, ok)),
%% secret_base64_encoded %% secret_base64_encoded
Config2 = Config#{secret => base64:encode(<<"abcdef">>), Config2 = Config#{secret => base64:encode(<<"abcdef">>),
secret_base64_encoded => true}, secret_base64_encoded => true},
?assertMatch({ok, _}, ?AUTH:update_authenticator(ChainID, AuthenticatorName, Config2)), ?assertMatch({ok, _}, ?AUTH:update_authenticator(?CHAIN, AuthenticatorName, Config2)),
?assertEqual(ok, ?AUTH:authenticate(ClientInfo)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo, ok)),
Config3 = Config#{verify_claims => [{<<"username">>, <<"${mqtt-username}">>}]}, Config3 = Config#{verify_claims => [{<<"username">>, <<"${mqtt-username}">>}]},
?assertMatch({ok, _}, ?AUTH:update_authenticator(ChainID, AuthenticatorName, Config3)), ?assertMatch({ok, _}, ?AUTH:update_authenticator(?CHAIN, AuthenticatorName, Config3)),
?assertEqual(ok, ?AUTH:authenticate(ClientInfo)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo, ok)),
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo#{username => <<"otheruser">>})), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo#{username => <<"otheruser">>}, ok)),
%% Expiration %% Expiration
Payload3 = #{ <<"username">> => <<"myuser">> Payload3 = #{ <<"username">> => <<"myuser">>
, <<"exp">> => erlang:system_time(second) - 60}, , <<"exp">> => erlang:system_time(second) - 60},
JWS3 = generate_jws('hmac-based', Payload3, <<"abcdef">>), JWS3 = generate_jws('hmac-based', Payload3, <<"abcdef">>),
ClientInfo3 = ClientInfo#{password => JWS3}, ClientInfo3 = ClientInfo#{password => JWS3},
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo3)), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo3, ok)),
Payload4 = #{ <<"username">> => <<"myuser">> Payload4 = #{ <<"username">> => <<"myuser">>
, <<"exp">> => erlang:system_time(second) + 60}, , <<"exp">> => erlang:system_time(second) + 60},
JWS4 = generate_jws('hmac-based', Payload4, <<"abcdef">>), JWS4 = generate_jws('hmac-based', Payload4, <<"abcdef">>),
ClientInfo4 = ClientInfo#{password => JWS4}, ClientInfo4 = ClientInfo#{password => JWS4},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo4)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo4, ok)),
%% Issued At %% Issued At
Payload5 = #{ <<"username">> => <<"myuser">> Payload5 = #{ <<"username">> => <<"myuser">>
, <<"iat">> => erlang:system_time(second) - 60}, , <<"iat">> => erlang:system_time(second) - 60},
JWS5 = generate_jws('hmac-based', Payload5, <<"abcdef">>), JWS5 = generate_jws('hmac-based', Payload5, <<"abcdef">>),
ClientInfo5 = ClientInfo#{password => JWS5}, ClientInfo5 = ClientInfo#{password => JWS5},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo5)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo5, ok)),
Payload6 = #{ <<"username">> => <<"myuser">> Payload6 = #{ <<"username">> => <<"myuser">>
, <<"iat">> => erlang:system_time(second) + 60}, , <<"iat">> => erlang:system_time(second) + 60},
JWS6 = generate_jws('hmac-based', Payload6, <<"abcdef">>), JWS6 = generate_jws('hmac-based', Payload6, <<"abcdef">>),
ClientInfo6 = ClientInfo#{password => JWS6}, ClientInfo6 = ClientInfo#{password => JWS6},
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo6)), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo6, ok)),
%% Not Before %% Not Before
Payload7 = #{ <<"username">> => <<"myuser">> Payload7 = #{ <<"username">> => <<"myuser">>
, <<"nbf">> => erlang:system_time(second) - 60}, , <<"nbf">> => erlang:system_time(second) - 60},
JWS7 = generate_jws('hmac-based', Payload7, <<"abcdef">>), JWS7 = generate_jws('hmac-based', Payload7, <<"abcdef">>),
ClientInfo7 = ClientInfo#{password => JWS7}, ClientInfo7 = ClientInfo#{password => JWS7},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo7)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo7, ok)),
Payload8 = #{ <<"username">> => <<"myuser">> Payload8 = #{ <<"username">> => <<"myuser">>
, <<"nbf">> => erlang:system_time(second) + 60}, , <<"nbf">> => erlang:system_time(second) + 60},
JWS8 = generate_jws('hmac-based', Payload8, <<"abcdef">>), JWS8 = generate_jws('hmac-based', Payload8, <<"abcdef">>),
ClientInfo8 = ClientInfo#{password => JWS8}, ClientInfo8 = ClientInfo#{password => JWS8},
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo8)), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo8, ok)),
?AUTH:unbind([ListenerID], ChainID), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok. ok.
t_jwt_authenticator2(_) -> t_jwt_authenticator2(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
Dir = code:lib_dir(emqx_authn, test), Dir = code:lib_dir(emqx_authn, test),
PublicKey = list_to_binary(filename:join([Dir, "data/public_key.pem"])), PublicKey = list_to_binary(filename:join([Dir, "data/public_key.pem"])),
PrivateKey = list_to_binary(filename:join([Dir, "data/private_key.pem"])), PrivateKey = list_to_binary(filename:join([Dir, "data/private_key.pem"])),
@ -145,23 +132,18 @@ t_jwt_authenticator2(_) ->
certificate => PublicKey, certificate => PublicKey,
verify_claims => []}, verify_claims => []},
AuthenticatorConfig = #{name => AuthenticatorName, AuthenticatorConfig = #{name => AuthenticatorName,
type => jwt, mechanism => jwt,
config => Config}, config => Config},
?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig)), ?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig)),
ListenerID = <<"listener1">>,
?AUTH:bind(ChainID, [ListenerID]),
Payload = #{<<"username">> => <<"myuser">>}, Payload = #{<<"username">> => <<"myuser">>},
JWS = generate_jws('public-key', Payload, PrivateKey), JWS = generate_jws('public-key', Payload, PrivateKey),
ClientInfo = #{listener_id => ListenerID, ClientInfo = #{username => <<"myuser">>,
username => <<"myuser">>,
password => JWS}, password => JWS},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo, ok)),
?assertEqual({error, user_not_found}, ?AUTH:authenticate(ClientInfo#{password => <<"badpassword">>})), ?assertEqual({stop, {error, not_authorized}}, ?AUTH:authenticate(ClientInfo#{password => <<"badpassword">>}, ok)),
?AUTH:unbind([ListenerID], ChainID), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok. ok.
generate_jws('hmac-based', Payload, Secret) -> generate_jws('hmac-based', Payload, Secret) ->

View File

@ -22,6 +22,8 @@
-include_lib("common_test/include/ct.hrl"). -include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl"). -include_lib("eunit/include/eunit.hrl").
-include("emqx_authn.hrl").
-define(AUTH, emqx_authn). -define(AUTH, emqx_authn).
all() -> all() ->
@ -39,149 +41,125 @@ end_per_suite(_) ->
set_special_configs(emqx_authn) -> set_special_configs(emqx_authn) ->
application:set_env(emqx, plugins_etc_dir, application:set_env(emqx, plugins_etc_dir,
emqx_ct_helpers:deps_path(emqx_authn, "test")), emqx_ct_helpers:deps_path(emqx_authn, "test")),
Conf = #{<<"authn">> => #{<<"chains">> => [], <<"bindings">> => []}}, Conf = #{<<"emqx_authn">> => #{<<"authenticators">> => []}},
ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)), ok = file:write_file(filename:join(emqx:get_env(plugins_etc_dir), 'emqx_authn.conf'), jsx:encode(Conf)),
ok; ok;
set_special_configs(_App) -> set_special_configs(_App) ->
ok. ok.
t_mnesia_authenticator(_) -> t_mnesia_authenticator(_) ->
ChainID = <<"mychain">>, ct:pal("11111 ~p~n", [?AUTH:list_authenticators(<<"mqtt">>)]),
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
AuthenticatorName = <<"myauthenticator">>, AuthenticatorName = <<"myauthenticator">>,
AuthenticatorConfig = #{name => AuthenticatorName, AuthenticatorConfig = #{name => AuthenticatorName,
type => 'built-in-database', mechanism => 'password-based',
config => #{ config => #{
server_type => 'built-in-database',
user_id_type => username, user_id_type => username,
password_hash_algorithm => #{ password_hash_algorithm => #{
name => sha256 name => sha256
}}}, }}},
?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig)), ?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig)),
UserInfo = #{<<"user_id">> => <<"myuser">>, UserInfo = #{<<"user_id">> => <<"myuser">>,
<<"password">> => <<"mypass">>}, <<"password">> => <<"mypass">>},
?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:add_user(ChainID, AuthenticatorName, UserInfo)), ?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:add_user(?CHAIN, AuthenticatorName, UserInfo)),
?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser">>)), ?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser">>)),
ListenerID = <<"listener1">>, ClientInfo = #{username => <<"myuser">>,
?AUTH:bind(ChainID, [ListenerID]),
ClientInfo = #{listener_id => ListenerID,
username => <<"myuser">>,
password => <<"mypass">>}, password => <<"mypass">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo, ok)),
ClientInfo2 = ClientInfo#{username => <<"baduser">>}, ClientInfo2 = ClientInfo#{username => <<"baduser">>},
?assertEqual({error, user_not_found}, ?AUTH:authenticate(ClientInfo2)), ?assertEqual({stop, {error, not_authorized}}, ?AUTH:authenticate(ClientInfo2, ok)),
ClientInfo3 = ClientInfo#{password => <<"badpass">>}, ClientInfo3 = ClientInfo#{password => <<"badpass">>},
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo3)), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo3, ok)),
UserInfo2 = UserInfo#{<<"password">> => <<"mypass2">>}, UserInfo2 = UserInfo#{<<"password">> => <<"mypass2">>},
?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:update_user(ChainID, AuthenticatorName, <<"myuser">>, UserInfo2)), ?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:update_user(?CHAIN, AuthenticatorName, <<"myuser">>, UserInfo2)),
ClientInfo4 = ClientInfo#{password => <<"mypass2">>}, ClientInfo4 = ClientInfo#{password => <<"mypass2">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo4)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo4, ok)),
?assertEqual(ok, ?AUTH:delete_user(ChainID, AuthenticatorName, <<"myuser">>)), ?assertEqual(ok, ?AUTH:delete_user(?CHAIN, AuthenticatorName, <<"myuser">>)),
?assertEqual({error, not_found}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser">>)), ?assertEqual({error, not_found}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser">>)),
?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:add_user(ChainID, AuthenticatorName, UserInfo)), ?assertEqual({ok, #{user_id => <<"myuser">>}}, ?AUTH:add_user(?CHAIN, AuthenticatorName, UserInfo)),
?assertMatch({ok, #{user_id := <<"myuser">>}}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser">>)), ?assertMatch({ok, #{user_id := <<"myuser">>}}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser">>)),
?assertEqual(ok, ?AUTH:delete_authenticator(ChainID, AuthenticatorName)), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName)),
?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig)),
?assertMatch({error, not_found}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser">>)),
?AUTH:unbind([ListenerID], ChainID), ?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)), ?assertMatch({error, not_found}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser">>)),
?assertEqual([], ets:tab2list(mnesia_basic_auth)), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName)),
ok. ok.
t_import(_) -> t_import(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
AuthenticatorName = <<"myauthenticator">>, AuthenticatorName = <<"myauthenticator">>,
AuthenticatorConfig = #{name => AuthenticatorName, AuthenticatorConfig = #{name => AuthenticatorName,
type => 'built-in-database', mechanism => 'password-based',
config => #{ config => #{
server_type => 'built-in-database',
user_id_type => username, user_id_type => username,
password_hash_algorithm => #{ password_hash_algorithm => #{
name => sha256 name => sha256
}}}, }}},
?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig)), ?assertEqual({ok, AuthenticatorConfig}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig)),
Dir = code:lib_dir(emqx_authn, test), Dir = code:lib_dir(emqx_authn, test),
?assertEqual(ok, ?AUTH:import_users(ChainID, AuthenticatorName, filename:join([Dir, "data/user-credentials.json"]))), ?assertEqual(ok, ?AUTH:import_users(?CHAIN, AuthenticatorName, filename:join([Dir, "data/user-credentials.json"]))),
?assertEqual(ok, ?AUTH:import_users(ChainID, AuthenticatorName, filename:join([Dir, "data/user-credentials.csv"]))), ?assertEqual(ok, ?AUTH:import_users(?CHAIN, AuthenticatorName, filename:join([Dir, "data/user-credentials.csv"]))),
?assertMatch({ok, #{user_id := <<"myuser1">>}}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser1">>)), ?assertMatch({ok, #{user_id := <<"myuser1">>}}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser1">>)),
?assertMatch({ok, #{user_id := <<"myuser3">>}}, ?AUTH:lookup_user(ChainID, AuthenticatorName, <<"myuser3">>)), ?assertMatch({ok, #{user_id := <<"myuser3">>}}, ?AUTH:lookup_user(?CHAIN, AuthenticatorName, <<"myuser3">>)),
ListenerID = <<"listener1">>, ClientInfo1 = #{username => <<"myuser1">>,
?AUTH:bind(ChainID, [ListenerID]),
ClientInfo1 = #{listener_id => ListenerID,
username => <<"myuser1">>,
password => <<"mypassword1">>}, password => <<"mypassword1">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo1)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo1, ok)),
ClientInfo2 = ClientInfo1#{username => <<"myuser3">>, ClientInfo2 = ClientInfo1#{username => <<"myuser3">>,
password => <<"mypassword3">>}, password => <<"mypassword3">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo2)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo2, ok)),
?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName)),
?AUTH:unbind([ListenerID], ChainID),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)),
ok. ok.
t_multi_mnesia_authenticator(_) -> t_multi_mnesia_authenticator(_) ->
ChainID = <<"mychain">>,
Chain = #{id => ChainID,
type => simple},
?assertMatch({ok, #{id := ChainID, authenticators := []}}, ?AUTH:create_chain(Chain)),
AuthenticatorName1 = <<"myauthenticator1">>, AuthenticatorName1 = <<"myauthenticator1">>,
AuthenticatorConfig1 = #{name => AuthenticatorName1, AuthenticatorConfig1 = #{name => AuthenticatorName1,
type => 'built-in-database', mechanism => 'password-based',
config => #{ config => #{
server_type => 'built-in-database',
user_id_type => username, user_id_type => username,
password_hash_algorithm => #{ password_hash_algorithm => #{
name => sha256 name => sha256
}}}, }}},
AuthenticatorName2 = <<"myauthenticator2">>, AuthenticatorName2 = <<"myauthenticator2">>,
AuthenticatorConfig2 = #{name => AuthenticatorName2, AuthenticatorConfig2 = #{name => AuthenticatorName2,
type => 'built-in-database', mechanism => 'password-based',
config => #{ config => #{
server_type => 'built-in-database',
user_id_type => clientid, user_id_type => clientid,
password_hash_algorithm => #{ password_hash_algorithm => #{
name => sha256 name => sha256
}}}, }}},
?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig1)), ?assertEqual({ok, AuthenticatorConfig1}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig1)),
?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:create_authenticator(ChainID, AuthenticatorConfig2)), ?assertEqual({ok, AuthenticatorConfig2}, ?AUTH:create_authenticator(?CHAIN, AuthenticatorConfig2)),
?assertEqual({ok, #{user_id => <<"myuser">>}}, ?assertEqual({ok, #{user_id => <<"myuser">>}},
?AUTH:add_user(ChainID, AuthenticatorName1, ?AUTH:add_user(?CHAIN, AuthenticatorName1,
#{<<"user_id">> => <<"myuser">>, #{<<"user_id">> => <<"myuser">>,
<<"password">> => <<"mypass1">>})), <<"password">> => <<"mypass1">>})),
?assertEqual({ok, #{user_id => <<"myclient">>}}, ?assertEqual({ok, #{user_id => <<"myclient">>}},
?AUTH:add_user(ChainID, AuthenticatorName2, ?AUTH:add_user(?CHAIN, AuthenticatorName2,
#{<<"user_id">> => <<"myclient">>, #{<<"user_id">> => <<"myclient">>,
<<"password">> => <<"mypass2">>})), <<"password">> => <<"mypass2">>})),
ListenerID = <<"listener1">>, ClientInfo1 = #{username => <<"myuser">>,
?AUTH:bind(ChainID, [ListenerID]),
ClientInfo1 = #{listener_id => ListenerID,
username => <<"myuser">>,
clientid => <<"myclient">>, clientid => <<"myclient">>,
password => <<"mypass1">>}, password => <<"mypass1">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo1)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo1, ok)),
?assertEqual(ok, ?AUTH:move_authenticator_to_the_front(ChainID, AuthenticatorName2)), ?assertEqual(ok, ?AUTH:move_authenticator_to_the_front(?CHAIN, AuthenticatorName2)),
?assertEqual({error, bad_password}, ?AUTH:authenticate(ClientInfo1)), ?assertEqual({stop, {error, bad_username_or_password}}, ?AUTH:authenticate(ClientInfo1, ok)),
ClientInfo2 = ClientInfo1#{password => <<"mypass2">>}, ClientInfo2 = ClientInfo1#{password => <<"mypass2">>},
?assertEqual(ok, ?AUTH:authenticate(ClientInfo2)), ?assertEqual({stop, ok}, ?AUTH:authenticate(ClientInfo2, ok)),
?AUTH:unbind([ListenerID], ChainID), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName1)),
?assertEqual(ok, ?AUTH:delete_chain(ChainID)), ?assertEqual(ok, ?AUTH:delete_authenticator(?CHAIN, AuthenticatorName2)),
ok. ok.

View File

@ -260,25 +260,21 @@ handle_call({auth, ClientInfo0, Password},
Channel = #channel{conninfo = ConnInfo, Channel = #channel{conninfo = ConnInfo,
clientinfo = ClientInfo}) -> clientinfo = ClientInfo}) ->
ClientInfo1 = enrich_clientinfo(ClientInfo0, ClientInfo), ClientInfo1 = enrich_clientinfo(ClientInfo0, ClientInfo),
NConnInfo = enrich_conninfo(ClientInfo1, ConnInfo), ConnInfo1 = enrich_conninfo(ClientInfo1, ConnInfo),
Channel1 = Channel#channel{conninfo = NConnInfo, Channel1 = Channel#channel{conninfo = ConnInfo1,
clientinfo = ClientInfo1}, clientinfo = ClientInfo1},
#{clientid := ClientId, username := Username} = ClientInfo1, #{clientid := ClientId, username := Username} = ClientInfo1,
case emqx_access_control:authenticate(ClientInfo1#{password => Password}) of case emqx_access_control:authenticate(ClientInfo1#{password => Password}) of
{ok, AuthResult} -> ok ->
emqx_logger:set_metadata_clientid(ClientId), emqx_logger:set_metadata_clientid(ClientId),
is_anonymous(AuthResult) andalso case emqx_cm:open_session(true, ClientInfo1, ConnInfo1) of
emqx_metrics:inc('client.auth.anonymous'),
NClientInfo = maps:merge(ClientInfo1, AuthResult),
NChannel = Channel1#channel{clientinfo = NClientInfo},
case emqx_cm:open_session(true, NClientInfo, NConnInfo) of
{ok, _Session} -> {ok, _Session} ->
?LOG(debug, "Client ~s (Username: '~s') authorized successfully!", ?LOG(debug, "Client ~s (Username: '~s') authorized successfully!",
[ClientId, Username]), [ClientId, Username]),
{reply, ok, [{event, connected}], ensure_connected(NChannel)}; {reply, ok, [{event, connected}], ensure_connected(Channel1)};
{error, Reason} -> {error, Reason} ->
?LOG(warning, "Client ~s (Username: '~s') open session failed for ~0p", ?LOG(warning, "Client ~s (Username: '~s') open session failed for ~0p",
[ClientId, Username, Reason]), [ClientId, Username, Reason]),
@ -393,9 +389,6 @@ terminate(Reason, Channel) ->
Req = #{reason => stringfy(Reason)}, Req = #{reason => stringfy(Reason)},
try_dispatch(on_socket_closed, wrap(Req), Channel). try_dispatch(on_socket_closed, wrap(Req), Channel).
is_anonymous(#{anonymous := true}) -> true;
is_anonymous(_AuthResult) -> false.
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
%% Sub/UnSub %% Sub/UnSub
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------

View File

@ -33,7 +33,7 @@
%% Gateway ID %% Gateway ID
, type := gateway_type() , type := gateway_type()
%% Autenticator %% Autenticator
, auth := allow_anonymous | emqx_authentication:chain_id() , auth := emqx_authn:chain_id()
%% The ConnectionManager PID %% The ConnectionManager PID
, cm := pid() , cm := pid()
}. }.
@ -66,19 +66,19 @@
-spec authenticate(context(), emqx_types:clientinfo()) -spec authenticate(context(), emqx_types:clientinfo())
-> {ok, emqx_types:clientinfo()} -> {ok, emqx_types:clientinfo()}
| {error, any()}. | {error, any()}.
authenticate(_Ctx = #{auth := allow_anonymous}, ClientInfo) ->
{ok, ClientInfo#{anonymous => true}};
authenticate(_Ctx = #{auth := ChainId}, ClientInfo0) -> authenticate(_Ctx = #{auth := ChainId}, ClientInfo0) ->
ClientInfo = ClientInfo0#{ ClientInfo = ClientInfo0#{
zone => undefined, zone => undefined,
chain_id => ChainId chain_id => ChainId
}, },
case emqx_access_control:authenticate(ClientInfo) of case emqx_access_control:authenticate(ClientInfo) of
{ok, AuthResult} -> ok ->
{ok, mountpoint(maps:merge(ClientInfo, AuthResult))}; {ok, mountpoint(ClientInfo)};
{error, Reason} -> {error, Reason} ->
{error, Reason} {error, Reason}
end. end;
authenticate(_Ctx, ClientInfo) ->
{ok, ClientInfo}.
%% @doc Register the session to the cluster. %% @doc Register the session to the cluster.
%% %%

View File

@ -86,15 +86,14 @@ init(CoapPid, EndpointName, Peername = {_Peerhost, _Port}, RegInfo = #{<<"lt">>
ClientInfo = clientinfo(Lwm2mState), ClientInfo = clientinfo(Lwm2mState),
_ = run_hooks('client.connect', [conninfo(Lwm2mState)], undefined), _ = run_hooks('client.connect', [conninfo(Lwm2mState)], undefined),
case emqx_access_control:authenticate(ClientInfo) of case emqx_access_control:authenticate(ClientInfo) of
{ok, AuthResult} -> ok ->
_ = run_hooks('client.connack', [conninfo(Lwm2mState), success], undefined), _ = run_hooks('client.connack', [conninfo(Lwm2mState), success], undefined),
ClientInfo1 = maps:merge(ClientInfo, AuthResult),
Sockport = proplists:get_value(port, lwm2m_coap_responder:options(), 5683), Sockport = proplists:get_value(port, lwm2m_coap_responder:options(), 5683),
ClientInfo2 = maps:put(sockport, Sockport, ClientInfo1), ClientInfo1 = maps:put(sockport, Sockport, ClientInfo),
Lwm2mState1 = Lwm2mState#lwm2m_state{started_at = time_now(), Lwm2mState1 = Lwm2mState#lwm2m_state{started_at = time_now(),
mountpoint = maps:get(mountpoint, ClientInfo2)}, mountpoint = maps:get(mountpoint, ClientInfo1)},
run_hooks('client.connected', [ClientInfo2, conninfo(Lwm2mState1)]), run_hooks('client.connected', [ClientInfo1, conninfo(Lwm2mState1)]),
erlang:send(CoapPid, post_init), erlang:send(CoapPid, post_init),
erlang:send_after(2000, CoapPid, auto_observe), erlang:send_after(2000, CoapPid, auto_observe),

View File

@ -63,6 +63,7 @@
, {snabbkaffe, {git, "https://github.com/kafka4beam/snabbkaffe.git", {tag, "0.13.0"}}} , {snabbkaffe, {git, "https://github.com/kafka4beam/snabbkaffe.git", {tag, "0.13.0"}}}
, {hocon, {git, "https://github.com/emqx/hocon.git", {tag, "0.9.6"}}} , {hocon, {git, "https://github.com/emqx/hocon.git", {tag, "0.9.6"}}}
, {emqx_http_lib, {git, "https://github.com/emqx/emqx_http_lib.git", {tag, "0.2.1"}}} , {emqx_http_lib, {git, "https://github.com/emqx/emqx_http_lib.git", {tag, "0.2.1"}}}
, {esasl, {git, "https://github.com/emqx/esasl", {branch, "refactor/sasl"}}}
]}. ]}.
{xref_ignores, {xref_ignores,