File 7601-tftp-add-function-specifications-for-open-APIs.patch of Package erlang

From 06fb7139e8c7e37ff7fa0c4c4757fabaf4cd7068 Mon Sep 17 00:00:00 2001
From: Jianhui Wu <jianhui@erlang.org>
Date: Fri, 15 Mar 2024 11:56:13 +0100
Subject: [PATCH] tftp: add function specifications for open APIs

 with auto-generated doc parts.
---
 lib/tftp/src/tftp.erl        | 37 +++++++++++++++++++++++++++++++-----
 lib/tftp/src/tftp_engine.erl | 20 +++++++++++++++++++
 2 files changed, 52 insertions(+), 5 deletions(-)

diff --git a/lib/tftp/src/tftp.erl b/lib/tftp/src/tftp.erl
index 7fb2f94186..3596d8db26 100644
--- a/lib/tftp/src/tftp.erl
+++ b/lib/tftp/src/tftp.erl
@@ -234,28 +234,30 @@
 
 -type access() :: read | write.
 
--type options() :: [{Key :: string(), Value :: string()}].
+-type option() :: {Key :: string(), Value :: string()}.
 
 -type error_code() :: undef | enoent | eacces | enospc |
 		      badop | eexist | baduser | badopt |
 		      integer().
 
+-export_type([option/0]).
+
 -callback prepare(Peer :: peer(),
 		  Access :: access(),
 		  Filename :: file:name(),
 		  Mode :: string(),
-		  SuggestedOptions :: options(),
+		  SuggestedOptions :: [option()],
 		  InitialState :: [] | [{root_dir, string()}]) ->
-    {ok, AcceptedOptions :: options(), NewState :: term()} |
+    {ok, AcceptedOptions :: [option()], NewState :: term()} |
     {error, {Code :: error_code(), string()}}.
 
 -callback open(Peer :: peer(),
 	       Access :: access(),
 	       Filename :: file:name(),
 	       Mode :: string(),
-	       SuggestedOptions :: options(),
+	       SuggestedOptions :: [option()],
 	       State :: [] | [{root_dir, string()}] | term()) ->
-    {ok, AcceptedOptions :: options(), NewState :: term()} |
+    {ok, AcceptedOptions :: [option()], NewState :: term()} |
     {error, {Code :: error_code(), string()}}.
 
 -callback read(State :: term()) -> {more, binary(), NewState :: term()} |
@@ -293,6 +295,14 @@
 %% LastCallbackState.
 %%-------------------------------------------------------------------
 
+-spec read_file(RemoteFilename, LocalFilename, Options) ->
+        {ok, LastCallbackState} | {error, Reason} when
+    RemoteFilename    :: file:filename(),
+    LocalFilename     :: file:filename_all(),
+    Options           :: [option()],
+    LastCallbackState :: term(),
+    Reason            :: term().
+
 read_file(RemoteFilename, LocalFilename, Options) ->
     tftp_engine:client_start(read, RemoteFilename, LocalFilename, Options).
     
@@ -319,6 +329,14 @@ read_file(RemoteFilename, LocalFilename,
 %% of transferred bytes will be returned as LastCallbackState.
 %%-------------------------------------------------------------------
 
+-spec write_file(RemoteFilename, LocalFilename, Options) ->
+        {ok, LastCallbackState} | {error, Reason} when
+    RemoteFilename    :: file:filename(),
+    LocalFilename     :: file:filename_all(),
+    Options           :: [option()],
+    LastCallbackState :: term(),
+    Reason            :: term().
+
 write_file(RemoteFilename, LocalFilename, Options) ->
     tftp_engine:client_start(write, RemoteFilename, LocalFilename, Options).
 
@@ -335,6 +353,11 @@ write_file(RemoteFilename, LocalFilename
 %% of the (virtual) file.
 %%-------------------------------------------------------------------
 
+-spec start(Options) -> {ok, Pid} | {error, Reason} when
+    Options :: [option()],
+    Pid     :: pid(),
+    Reason  :: term().
+
 start(Options) ->
     tftp_engine:daemon_start(Options).
 
diff --git a/lib/tftp/src/tftp_engine.erl b/lib/tftp/src/tftp_engine.erl
index 68ada7ff14..495fbd3565 100644
--- a/lib/tftp/src/tftp_engine.erl
+++ b/lib/tftp/src/tftp_engine.erl
@@ -74,6 +74,14 @@
 %%% Info
 %%%-------------------------------------------------------------------
 
+-spec info(Procs) -> [{Pid, Result}] when
+    Procs   :: daemons | servers,
+    Pid     :: pid(),
+    Result  :: term();
+          (Pid) -> Result when
+    Pid     :: pid(),
+    Result  :: term().
+
 info(daemons) ->
     Daemons = supervisor:which_children(tftp_sup),
     [{Pid, info(Pid)} || {_, Pid, _, _} <- Daemons];
@@ -83,6 +91,18 @@ info(servers) ->
 info(ToPid) when is_pid(ToPid) ->
     call(info, ToPid, timer:seconds(10)).
 
+-spec change_config(Procs, Options) -> [{Pid, Result}] when
+    Procs   :: daemons | servers,
+    Options :: [tftp:option()],
+    Pid     :: pid(),
+    Result  :: ok | {error, Reason},
+    Reason  :: term();
+                   (Pid, Options) -> Result when
+    Pid     :: pid(),
+    Options :: [tftp:option()],
+    Result  :: ok | {error, Reason},
+    Reason  :: term().
+
 change_config(daemons, Options) ->
     Daemons = supervisor:which_children(tftp_sup),
     [{Pid, change_config(Pid, Options)} || {_, Pid, _, _} <- Daemons];
-- 
2.35.3

openSUSE Build Service is sponsored by