Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
Please login to access the resource
home:Ledest:erlang:23
erlang
1115-ftp-add-type-specs.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 1115-ftp-add-type-specs.patch of Package erlang
From bdc9ec4f244c6771999365c1fdfe5f1ff700bc58 Mon Sep 17 00:00:00 2001 From: Kiko Fernandez-Reyes <kiko@erlang.org> Date: Tue, 25 Oct 2022 14:13:20 +0200 Subject: [PATCH 3/3] ftp: add type specs --- lib/ftp/src/ftp.erl | 86 ++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 85 insertions(+), 1 deletion(-) diff --git a/lib/ftp/src/ftp.erl b/lib/ftp/src/ftp.erl index 9520580dc7..4d81c1b11d 100644 --- a/lib/ftp/src/ftp.erl +++ b/lib/ftp/src/ftp.erl @@ -1549,6 +1549,12 @@ start_link(Opts, GenServerOptions) -> %%% Help functions to handle_call and/or handle_ctrl_result %%-------------------------------------------------------------------------- %% User handling +-spec handle_user(User, Password, Account, State) -> Result when + User :: io:format(), + Password :: io:format(), + Account :: io:format(), + State :: #state{}, + Result :: {noreply, #state{}}. handle_user(User, Password, Acc, State0) -> _ = send_ctrl_message(State0, mk_cmd("USER ~s", [User])), State = activate_ctrl_connection(State0), @@ -1568,6 +1574,31 @@ handle_user_account(Acc, State0) -> %%-------------------------------------------------------------------------- %% handle_ctrl_result %%-------------------------------------------------------------------------- +-type ctrl_status_operation() :: efnamena + | elogin + | enofile + | epath + | error + | etnospc + | epnospc + | efnamena + | econn + | perm_neg_compl + | pos_compl + | pos_interm + | pos_interm_acct + | pos_prel + | tls_upgrade + | trans_neg_compl. + +-spec handle_ctrl_result(Operation, State) -> Result when + Operation :: {ctrl_status_operation(), list() | atom()}, + State :: #state{}, + Result :: {noreply, #state{}, integer()} + | {noreply, #state{}} + | {stop, normal | {error, Reason}, #state{}} + | {error, term()}, + Reason :: term(). handle_ctrl_result({pos_compl, _}, #state{csock = {tcp, _Socket}, tls_options = TLSOptions, timeout = Timeout, @@ -1961,6 +1992,13 @@ handle_ctrl_result(CtrlMsg, #state{caller = undefined} = State) -> %%-------------------------------------------------------------------------- %% Help functions to handle_ctrl_result %%-------------------------------------------------------------------------- + +-spec ctrl_result_response(Status, State, Error) -> Result when + Status :: ctrl_status_operation() | {ctrl_status_operation(), _}, + State :: #state{}, + Error :: {error, Reason}, + Reason :: term(), + Result :: {noreply, #state{}} | Error. ctrl_result_response(pos_compl, #state{client = From} = State, _) -> gen_server:reply(From, ok), {noreply, State#state{client = undefined, caller = undefined}}; @@ -1992,6 +2030,9 @@ ctrl_result_response(_, #state{client = From} = State, ErrorMsg) -> {noreply, State#state{client = undefined, caller = undefined}}. %%-------------------------------------------------------------------------- +-spec handle_caller(State) -> Result when + State :: #state{}, + Result :: {noreply, #state{}}. handle_caller(#state{caller = {dir, Dir, Len}} = State0) -> Cmd = case Len of short -> "NLST"; @@ -2045,6 +2086,13 @@ handle_caller(#state{caller = {transfer_data, {Cmd, Bin, RemoteFile}}} = %% Connect to FTP server at Host (default is TCP port 21) %% in order to establish a control connection. +-spec setup_ctrl_connection(Host, Port, Timeout, State) -> Result when + Host :: inet:socket_address() | inet:hostname(), + Port :: inet:port_number(), + Timeout :: timeout(), + State :: #state{}, + Reason :: timeout | inet:posix(), + Result :: {ok, State, integer()} | {error, Reason}. setup_ctrl_connection(Host, Port, Timeout, #state{sockopts_ctrl = SockOpts} = State0) -> MsTime = erlang:monotonic_time(), case connect(Host, Port, SockOpts, Timeout, State0) of @@ -2062,6 +2110,9 @@ setup_ctrl_connection(Host, Port, Timeout, #state{sockopts_ctrl = SockOpts} = St Error end. +-spec setup_data_connection(State) -> Result when + State :: #state{}, + Result :: {noreply, State}. setup_data_connection(#state{mode = active, caller = Caller, csock = CSock, @@ -2124,6 +2175,14 @@ setup_data_connection(#state{mode = passive, ipfamily = inet, State = activate_ctrl_connection(State0), {noreply, State#state{caller = {setup_data_connection, Caller}}}. +-spec connect(Host, Port, SockOpts, Timeout, State) -> Result when + Host :: inet:socket_address() | inet:hostname(), + Port :: inet:port_number(), + SockOpts :: [inet:inet_backend() | gen_tcp:connect_option()], + Timeout :: timeout(), + State :: #state{}, + Reason :: timeout | inet:posix(), + Result :: {ok, inet:address_family(), gen_tcp:socket()} | {error, Reason}. connect(Host, Port, SockOpts, Timeout, #state{ipfamily = inet = IpFam}) -> connect2(Host, Port, IpFam, SockOpts, Timeout); @@ -2157,6 +2216,14 @@ connect(Host, Port, SockOpts, Timeout, #state{ipfamily = inet6fb4}) -> end end. +-spec connect2(Host, Port, IpFam, SockOpts, Timeout) -> Result when + Host :: inet:socket_address() | inet:hostname(), + Port :: inet:port_number(), + SockOpts :: [inet:inet_backend() | gen_tcp:connect_option()], + Timeout :: timeout(), + IpFam :: inet:address_family(), + Reason :: timeout | inet:posix(), + Result :: {ok, inet:address_family(), gen_tcp:socket()} | {error, Reason}. connect2(Host, Port, IpFam, SockOpts, Timeout) -> Opts = [IpFam, binary, {packet, 0}, {active, false} | SockOpts], case gen_tcp:connect(Host, Port, Opts, Timeout) of @@ -2166,6 +2233,9 @@ connect2(Host, Port, IpFam, SockOpts, Timeout) -> Error end. +-spec accept_data_connection_tls_options(State) -> Result when + State :: #state{}, + Result :: [tuple()]. accept_data_connection_tls_options(#state{ csock = {ssl,Socket}, tls_options = TO0, tls_ctrl_session_reuse = true }) -> TO = lists:keydelete(reuse_sessions, 1, TO0), {ok, [{session_id,SSLSessionId},{session_data,SSLSessionData}]} = ssl:connection_information(Socket, [session_id, session_data]), @@ -2173,6 +2243,10 @@ accept_data_connection_tls_options(#state{ csock = {ssl,Socket}, tls_options = T accept_data_connection_tls_options(#state{ tls_options = TO }) -> TO. +-spec accept_data_connection(State) -> Result when + State :: #state{}, + Result :: {ok, #state{}} | {error, Reason}, + Reason :: term(). accept_data_connection(#state{mode = active, dtimeout = DTimeout, tls_options = TLSOptions0, @@ -2210,7 +2284,9 @@ accept_data_connection(#state{mode = passive, accept_data_connection(#state{mode = passive} = State) -> {ok,State}. - +-spec send_ctrl_message(State, Message) -> _ when + State :: #state{}, + Message :: [term() | Message]. send_ctrl_message(_S=#state{csock = Socket, verbose = Verbose}, Message) -> verbose(lists:flatten(Message),Verbose,send), ?DBG('<--ctrl ~p ---- ~s~p~n',[Socket,Message,_S]), @@ -2483,6 +2559,7 @@ start_options(Options) -> %% progress %% ftp_extension +-spec open_options([tuple()]) -> {ok, [tuple()]} | no_return(). open_options(Options) -> ValidateMode = fun(active) -> true; @@ -2559,6 +2636,8 @@ open_options(Options) -> {ftp_extension, ValidateFtpExtension, false, ?FTP_EXT_DEFAULT}], validate_options(Options, ValidOptions, []). +%% validates socket options and set defaults +-spec socket_options([tuple()]) -> {ok, tuple()} | no_return(). socket_options(Options) -> CtrlOpts = proplists:get_value(sock_ctrl, Options, []), DataActOpts = proplists:get_value(sock_data_act, Options, CtrlOpts), @@ -2585,6 +2664,11 @@ valid_socket_option({packet_size,_} ) -> false; valid_socket_option(_) -> true. +-spec validate_options(Options, ValidOptions, Acc) -> Result when + Options :: [tuple()], + ValidOptions :: [tuple()], + Acc :: [tuple()], + Result :: {ok, [tuple()]} | no_return(). validate_options([], [], Acc) -> {ok, lists:reverse(Acc)}; validate_options([], ValidOptions, Acc) -> -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor