summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLinus Nordberg <linus@sunet.se>2020-02-11 13:14:28 +0100
committerLinus Nordberg <linus@sunet.se>2020-02-11 13:14:28 +0100
commit37277c3ba0119f50af8ffff014ce13b93f225557 (patch)
tree44ab83cdaa4d80e7598d32323201a5e57239a539
parent9f50fa4e8d7d82605116e07ea376da7ebedb8a57 (diff)
Some more documentation and cosmetic changes
-rw-r--r--p11p-daemon/src/p11p_client.erl94
-rw-r--r--p11p-daemon/src/p11p_rpc.erl12
-rw-r--r--p11p-daemon/src/p11p_server.erl126
3 files changed, 133 insertions, 99 deletions
diff --git a/p11p-daemon/src/p11p_client.erl b/p11p-daemon/src/p11p_client.erl
index 87c2949..d6c73ac 100644
--- a/p11p-daemon/src/p11p_client.erl
+++ b/p11p-daemon/src/p11p_client.erl
@@ -1,20 +1,31 @@
%%% Copyright (c) 2019, Sunet.
%%% See LICENSE for licensing information.
-%% A client spawns an Erlang port running a proxy app, i.e. the
-%% 'remote' program from p11-kit.
-
-%% Receive p11 requests from p11p_server, forward them to the proxy app,
-%% wait for a reply. If a reply is received within a timeout period,
-%% proxy the reply to the requesting p11p_server. If the request
-%% times out, inform the manager (our parent).
+%% Spawn an Erlang port running a proxy app. We use the 'remote'
+%% program from p11-kit as the proxy app.
+
+%% Receive PKCS#11 requests from a p11p_server, forward them to the
+%% proxy app, wait for a reply. If a reply is received within a
+%% timeout period, proxy the reply to the requesting p11p_server. If
+%% the request times out, inform the manager (our parent) and exit.
+
+%% Track a subset of the PKCS#11 state in order to handle token
+%% restarts. We start in state 'started'. While in 'started', we allow
+%% only a few "opening" calls (Initialize, OpenSession and Login)
+%% through to the token. Corresponding "closing" calls (Finalize,
+%% CloseSession and Logout) are sent an immediate OK response without
+%% forwarding them to the token. Any other call is rejected by
+%% responding with an error. This should make well behaving P11
+%% applications be able to deal with us switching the token under
+%% their feet.
-module(p11p_client).
-behaviour(gen_server).
%% API.
-export([start_link/6]).
--export([request/2, stop/2]).
+-export([request/2, % Request from p11p-server.
+ stop/2]). % Manager stopping us.
-include("p11p_rpc.hrl").
@@ -23,7 +34,12 @@
code_change/3]).
%% Records and types.
--type token_state() :: started | initialized | session | loggedin | opact | finalized.
+-type token_state() :: started |
+ initialized |
+ session |
+ loggedin |
+ opact |
+ finalized.
-record(state, {
token :: string(), % Token name.
@@ -40,8 +56,8 @@
}).
%% API.
--spec start_link(atom(), string(), pid(), string(), list(), non_neg_integer()) ->
- {ok, pid()} | {error, term()}.
+-spec start_link(atom(), string(), pid(), string(), list(),
+ non_neg_integer()) -> {ok, pid()} | {error, term()}.
start_link(ServName, TokName, Server, ModPath, ModEnv, Timeout) ->
lager:info("~p: starting p11p_client for ~s", [self(), TokName]),
gen_server:start_link({local, ServName}, ?MODULE,
@@ -51,12 +67,13 @@ start_link(ServName, TokName, Server, ModPath, ModEnv, Timeout) ->
request(Client, Request) ->
gen_server:call(Client, {request, Request}).
-%% Use stop/1 instead of gen_server:stop/1 if you're uncertain whether
-%% we (Pid) are alive or not. An example of when that can happen is
-%% when the manager receives a server_event about a lost p11 app. If
-%% the server process terminated on request from us because we timed
-%% out on an rpc call, chances are that we have already terminated by
-%% the time the manager acts on the information about the lost app.
+%% You should invoke stop/1 instead of gen_server:stop/1 if you're
+%% uncertain whether we (Pid) are alive or not. An example of when
+%% that can happen is when the manager receives a server_event about a
+%% lost P11 app -- if the server process terminated on request from us
+%% because we timed out on an RPC call, chances are that we have
+%% already terminated by the time the manager acts on the information
+%% about the lost app.
stop(Pid, Reason) ->
gen_server:cast(Pid, {stop, Reason}).
@@ -72,13 +89,16 @@ init([TokName, Server, ModPath, ModEnv, Timeout]) ->
true = is_port(Port),
lager:debug("~p: ~s: new proxy app port: ~p", [self(), ProxyAppBinPath, Port]),
lager:debug("~p: ~s: module: ~s, env: ~p", [self(), ProxyAppBinPath, ModPath, ModEnv]),
- {ok, #state{port = Port, token = TokName, replyto = Server, timeout = Timeout}}.
+ {ok, #state{port = Port,
+ token = TokName,
+ replyto = Server,
+ timeout = Timeout}}.
handle_call({request, Request},
{FromPid, _Tag},
- S = #state{port = Port, send_count = Sent}) ->
+ State = #state{port = Port, send_count = Sent}) ->
case
- case S#state.p11state of
+ case State#state.p11state of
started ->
case p11p_rpc:req_id(Request) of
?P11_RPC_CALL_C_Logout -> ack;
@@ -96,9 +116,9 @@ handle_call({request, Request},
end
of
ack ->
- {reply, ack, S};
+ {reply, ack, State};
nack ->
- {reply, nack, S};
+ {reply, nack, State};
pass ->
lager:debug("~p: sending request from ~p to prxoy app ~p", [self(), FromPid, Port]),
D = p11p_rpc:serialise(Request),
@@ -110,9 +130,9 @@ handle_call({request, Request},
{reply,
{ok, size(Buf)},
- S#state{replyto = FromPid,
- timer = start_timer(S#state.timeout, Port),
- send_count = Sent + 1}}
+ State#state{replyto = FromPid,
+ timer = start_timer(State#state.timeout, Port),
+ send_count = Sent + 1}}
end;
handle_call(Call, _From, State) ->
@@ -126,12 +146,13 @@ handle_cast(Cast, State) ->
lager:debug("~p: unhandled cast: ~p~n", [self(), Cast]),
{noreply, State}.
-%% Receiving the very first response from proxy app since it was started.
+%% Receiving the very first octets from proxy app since it was started.
handle_info({Port, {data, Data}}, State)
when Port == State#state.port, State#state.response == undefined ->
case hd(Data) of % First octet is RPC protocol version.
?RPC_VERSION ->
- {noreply, response_in(State, p11p_rpc:new(), tl(Data))};
+ NewState = response_in(State, p11p_rpc:new(), tl(Data)),
+ {noreply, NewState};
BadVersion ->
lager:info("~p: ~p: invalid RPC version: ~p", [self(), Port,
BadVersion]),
@@ -139,17 +160,18 @@ handle_info({Port, {data, Data}}, State)
end;
%% Receiving more data from proxy app.
-handle_info({Port, {data, Data}}, #state{response = Msg} = State)
+handle_info({Port, {data, Data}}, State)
when Port == State#state.port ->
- {noreply, response_in(State, Msg, Data)};
+ NewState = response_in(State, State#state.response, Data),
+ {noreply, NewState};
%% Proxy app timed out.
-handle_info({timeout, Timer, Port}, S = #state{token = Tok})
- when Port == S#state.port, Timer == S#state.timer ->
- lager:info("~p: rpc request for ~s timed out, exiting", [self(), Tok]),
- p11p_manager:client_event(timeout, Tok),
- State = S#state{timer = undefined},
- {stop, normal, State};
+handle_info({timeout, Timer, Port}, State)
+ when Port == State#state.port, Timer == State#state.timer ->
+ lager:info("~p: rpc request for ~s timed out, exiting", [self(), State#state.token]),
+ p11p_manager:client_event(timeout, State#state.token),
+ NewState = State#state{timer = undefined},
+ {stop, normal, NewState};
handle_info(Info, State) ->
lager:debug("~p: Unhandled info: ~p~n", [self(), Info]),
@@ -176,7 +198,7 @@ do_send(Port, Buf) ->
end,
{ok, size(Buf)}.
-response_in(#state{replyto = Pid, timer = Timer, recv_count = Recv} = S,
+response_in(S = #state{replyto = Pid, timer = Timer, recv_count = Recv},
MsgIn, DataIn) ->
case p11p_rpc:parse(MsgIn, list_to_binary(DataIn)) of
{needmore, Msg} ->
diff --git a/p11p-daemon/src/p11p_rpc.erl b/p11p-daemon/src/p11p_rpc.erl
index 0e52bc5..b04cbbf 100644
--- a/p11p-daemon/src/p11p_rpc.erl
+++ b/p11p-daemon/src/p11p_rpc.erl
@@ -6,10 +6,11 @@
-module(p11p_rpc).
-export([
+ call_code/1,
dump/1,
- error/2,
+ msg_error/2,
+ msg_ok/1,
new/0, new/1,
- ok/1,
parse/2,
req_id/1,
serialise/1
@@ -17,6 +18,9 @@
-include("p11p_rpc.hrl").
+call_code(Msg) ->
+ Msg#p11rpc_msg.call_code.
+
dump(Msg = #p11rpc_msg{data = Data}) ->
{ReqId, Data2} = parse_req_id(Data),
{ArgsDesc, Data3} = parse_args_desc(Data2),
@@ -29,7 +33,7 @@ dump(Msg = #p11rpc_msg{data = Data}) ->
Data3
]).
-error(CallCode, ErrorCode) ->
+msg_error(CallCode, ErrorCode) ->
DataBuf = serialise_error(ErrorCode),
#p11rpc_msg{
state = done,
@@ -38,7 +42,7 @@ error(CallCode, ErrorCode) ->
data_len = size(DataBuf),
data = DataBuf}.
-ok(CallCode) ->
+msg_ok(CallCode) ->
#p11rpc_msg{
state = done,
call_code = CallCode,
diff --git a/p11p-daemon/src/p11p_server.erl b/p11p-daemon/src/p11p_server.erl
index 7b05da7..c27d825 100644
--- a/p11p-daemon/src/p11p_server.erl
+++ b/p11p-daemon/src/p11p_server.erl
@@ -1,8 +1,14 @@
%%% Copyright (c) 2019, Sunet.
%%% See LICENSE for licensing information.
-%% Create an AF_UNIX socket and accept connections. On connect, spawn
-%% another p11p_server process.
+%% Create an AF_UNIX socket and accept connections from a P11 app. On
+%% connect, spawn another p11p_server process.
+
+%% Recevie PKCS#11 requests on the socket and forward them to a
+%% p11p-client.
+
+%% Receive responses from our p11p-client and forward them to the P11
+%% app.
-module(p11p_server).
-behaviour(gen_server).
@@ -11,7 +17,8 @@
%% API.
-export([start_link/1]).
--export([reply/2, token_gone/2]).
+-export([reply/2, % Replies from p11p-client.
+ token_gone/2]). % p11p-client disappeared.
%% Genserver callbacks.
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2,
@@ -19,13 +26,13 @@
%% Records and types.
-record(state, {
- tokname :: string(),
- client :: pid() | undefined,
- socket :: gen_tcp:socket(),
- req_in :: p11rpc_msg() | undefined,
- req_out :: p11rpc_msg() | undefined,
- recv_count = 0 :: non_neg_integer(), % received from app
- send_count = 0 :: non_neg_integer() % sent to token
+ tokname :: string(), % Virtual token being served.
+ socket :: gen_tcp:socket(), % AF_UNIX socket.
+ client :: pid() | undefined, % Our p11p-client.
+ req_in :: p11rpc_msg() | undefined, % Request received from P11 app.
+ req_out :: p11rpc_msg() | undefined, % Request sent to p11p-client.
+ recv_count = 0 :: non_neg_integer(), % Counting requests from P11 app.
+ send_count = 0 :: non_neg_integer() % Conting requests to p11p-client.
}).
%% API.
@@ -46,15 +53,17 @@ token_gone(Pid, Hangup) ->
%% Genserver callbacks.
init([Token, Socket]) ->
lager:debug("~p: p11p_server starting for ~s", [self(), Token]),
- process_flag(trap_exit, true), % Need terminate/2.
- gen_server:cast(self(), accept), % Invoke accept, returning a socket in state.
+ process_flag(trap_exit, true), % Call terminate/2 on exit.
+ %% Invoking gen_tcp:accept(), updating state with a new socket.
+ gen_server:cast(self(), accept),
{ok, #state{tokname = Token, socket = Socket}}.
-%% FIXME: make this a cast
+%% FIXME: make this a cast?
handle_call({respond, Resp}, _, State = #state{send_count = Sent}) ->
- N = send_response(State#state.socket, p11p_rpc:serialise(Resp), Sent),
- {reply, {ok, N}, State#state{req_out = undefined,
- send_count = Sent + 1}};
+ {reply,
+ {ok, send_response(State#state.socket, p11p_rpc:serialise(Resp), Sent)},
+ State#state{req_out = undefined,
+ send_count = Sent + 1}};
handle_call(Call, _, S) ->
lager:debug("~p: Unhandled call: ~p~n", [self(), Call]),
@@ -62,13 +71,13 @@ handle_call(Call, _, S) ->
%% Wait for new connection.
handle_cast(accept, State = #state{tokname = TokName, socket = ListenSocket}) ->
- %% Blocking until client connects or timeout fires.
+ %% Blocking until P11 app connects or the timeout fires.
%% Without a timeout our supervisor cannot terminate us.
%% On timeout, just invoke ourselves again.
case gen_tcp:accept(ListenSocket, 900) of
{ok, Sock} ->
lager:debug("~p: ~p: new connection accepted", [self(), Sock]),
- %% Start a new acceptor and return with new socket in state.
+ %% Start a new acceptor and return with the new socket in state.
p11p_server_sup:start_server([TokName, ListenSocket]),
{noreply, State#state{socket = Sock}};
{error, timeout} ->
@@ -79,65 +88,65 @@ handle_cast(accept, State = #state{tokname = TokName, socket = ListenSocket}) ->
{stop, normal, State}
end;
-
handle_cast({token_gone, Hangup}, State = #state{send_count = Sent}) ->
- Resp = p11p_rpc:error(State#state.req_out#p11rpc_msg.call_code,
- ?CKR_DEVICE_ERROR),
+ Resp = p11p_rpc:msg_error(p11p_rpc:call_code(State#state.req_out),
+ ?CKR_DEVICE_ERROR),
{ok, _} = send_response(State#state.socket, p11p_rpc:serialise(Resp), Sent),
NewState = State#state{req_out = undefined,
send_count = Sent + 1},
case Hangup of
true ->
- lager:info("~p: Token reported gone, no more retries, closing.", [self()]),
+ lager:info("~p: Token reported gone, no more retries, closing.",
+ [self()]),
{stop, normal, NewState}; %FIXME: no need to update state, i think
false ->
- lager:info("~p: Token reported gone, retrying with new token.", [self()]),
- {noreply,
- NewState#state{client =
- p11p_manager:client_for_token(State#state.tokname)}}
+ lager:info("~p: Token reported gone, retrying with new token.",
+ [self()]),
+ NewClient = p11p_manager:client_for_token(State#state.tokname),
+ {noreply, NewState#state{client = NewClient}}
end;
handle_cast(Cast, State) ->
lager:debug("~p: Unhandled cast: ~p~n", [self(), Cast]),
{noreply, State}.
-%% First packet from P11 client.
-handle_info({tcp, Port, DataIn}, #state{tokname = TokName} = S)
- when S#state.client == undefined ->
+%% First chunk from P11 app.
+handle_info({tcp, Port, DataIn}, State)
+ when State#state.client == undefined ->
lager:debug("~p: received ~B octets from client on socket ~p, from new client", [self(), size(DataIn), Port]),
<<RPCVersion:8, Data/binary>> = DataIn,
case RPCVersion of
?RPC_VERSION ->
- {noreply,
- p11_app_data(
- S#state{client = p11p_manager:client_for_token(TokName)},
- p11p_rpc:new(),
- Data)};
+ NewClient = p11p_manager:client_for_token(State#state.tokname),
+ NewState = request_in(State#state{client = NewClient},
+ p11p_rpc:new(), Data),
+ {noreply, NewState};
BadVersion ->
lager:info("~p: ~p: invalid RPC version: ~p", [self(), Port,
BadVersion]),
- {stop, bad_proto, S}
+ {stop, bad_proto, State}
end;
-%% Subsequent packages from P11 client.
-handle_info({tcp, Port, DataIn}, #state{req_in = Msg} = S) ->
+%% Subsequent packages from P11 app.
+handle_info({tcp, Port, DataIn}, State) ->
+ Msg = State#state.req_in,
lager:debug("~p: received ~B octets from client on socket ~p, with ~B octets already in buffer", [self(), size(DataIn), Port, size(Msg#p11rpc_msg.buffer)]),
- {noreply, p11_app_data(S, Msg, DataIn)};
+ NewState = request_in(State, State#state.req_in, DataIn),
+ {noreply, NewState};
-handle_info({tcp_closed, Port}, S) ->
+handle_info({tcp_closed, Port}, State) ->
lager:debug("~p: socket ~p closed", [self(), Port]),
- {stop, normal, S};
+ {stop, normal, State};
-handle_info(Info, S) ->
+handle_info(Info, State) ->
lager:debug("~p: Unhandled info: ~p~n", [self(), Info]),
- {noreply, S}.
+ {noreply, State}.
terminate(Reason, #state{socket = Sock, tokname = TokName}) ->
ok = gen_tcp:close(Sock),
- %% FIXME: tell manager, so that the client can be stopped. we
- %% don't want to risk that another app (socket client) uses it
-
+ %% Let manager know, so that the client can be stopped. We don't
+ %% want to risk that another P11 app uses it.
p11p_manager:server_event(server_gone, TokName),
lager:debug("~p: terminated with reason ~p", [self(), Reason]),
@@ -147,17 +156,16 @@ code_change(_OldVersion, State, _Extra) ->
{ok, State}.
%% Private functions.
-p11_app_data(#state{client = Client, recv_count = Recv} = S, MsgIn,
- DataIn) ->
+request_in(S, MsgIn, DataIn) ->
case p11p_rpc:parse(MsgIn, DataIn) of
{needmore, Msg} ->
S#state{req_in = Msg};
{done, Msg} ->
lager:debug("~p: -> ~s", [self(), p11p_rpc:dump(Msg)]),
- case p11p_client:request(Client, Msg) of
+ case p11p_client:request(S#state.client, Msg) of
ack ->
lager:debug("~p: acking request", [self()]),
- Resp = p11p_rpc:ok(Msg#p11rpc_msg.call_code),
+ Resp = p11p_rpc:msg_ok(p11p_rpc:call_code(Msg)),
{ok, _} = send_response(S#state.socket,
p11p_rpc:serialise(Resp),
S#state.send_count),
@@ -165,8 +173,8 @@ p11_app_data(#state{client = Client, recv_count = Recv} = S, MsgIn,
send_count = S#state.send_count + 1};
nack ->
lager:debug("~p: nacking request", [self()]),
- Resp = p11p_rpc:error(Msg#p11rpc_msg.call_code,
- ?CKR_DEVICE_ERROR),
+ Resp = p11p_rpc:msg_error(p11p_rpc:call_code(Msg),
+ ?CKR_DEVICE_ERROR),
{ok, _} = send_response(S#state.socket,
p11p_rpc:serialise(Resp),
S#state.send_count),
@@ -175,15 +183,15 @@ p11_app_data(#state{client = Client, recv_count = Recv} = S, MsgIn,
{ok, _BytesSent} ->
S#state{req_out = Msg,
req_in = p11p_rpc:new(Msg#p11rpc_msg.buffer),
- recv_count = Recv + 1}
+ recv_count = S#state.recv_count + 1}
end
end.
send_response(Sock, Inbuf, Sent) ->
- Buf = case Sent of
- 0 -> <<?RPC_VERSION:8, Inbuf/binary>>;
- _ -> Inbuf
- end,
- lager:debug("~p: sending ~B octets as response", [self(), size(Inbuf)]),
- ok = gen_tcp:send(Sock, Buf),
- {ok, size(Inbuf)}.
+ Outbuf = case Sent of
+ 0 -> <<?RPC_VERSION:8, Inbuf/binary>>;
+ _ -> Inbuf
+ end,
+ lager:debug("~p: sending ~B octets as response", [self(), size(Outbuf)]),
+ ok = gen_tcp:send(Sock, Outbuf),
+ {ok, size(Outbuf)}.