Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Dec 12, 2024
2 parents e9545fd + c9491a9 commit a12eb10
Show file tree
Hide file tree
Showing 682 changed files with 1,039 additions and 4,166 deletions.
2 changes: 2 additions & 0 deletions lib/stdlib/src/shell_docs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -614,6 +614,8 @@ extract_type_specs(Module) ->
-spec find_path(Mod :: module()) -> non_existing | file:filename_all().
find_path(Module) ->
maybe
%% This is set to non_existing by tests to generate docs without any specs
undefined ?= get({?MODULE, nospecs}),
preloaded ?= code:which(Module),
PreloadedPath = filename:join(code:lib_dir(erts),"ebin"),
filename:join(PreloadedPath, atom_to_list(Module) ++ ".beam")
Expand Down
1 change: 1 addition & 0 deletions lib/stdlib/test/shell_docs_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -470,6 +470,7 @@ render_all(Dir) ->
end).

render_module(Mod, #docs_v1{ docs = Docs } = D) ->
put({shell_docs, nospecs}, non_existing),
Opts = #{ ansi => true, columns => 80, encoding => unicode },
case application:get_application(Mod) of
{ok, App} ->
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/erlang.docs_v1

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/file.docs_v1

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@

-spec advise(IoDevice, Offset, Length, Advise) -> ok | {error, Reason}
 when
 IoDevice :: io_device(),
 Offset :: integer(),
 Length :: integer(),
 Advise :: posix_file_advise(),
 Reason :: posix() | badarg.
  advise(IoDevice, Offset, Length, Advise)

Since:
OTP R14B
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@

-spec allocate(File, Offset, Length) -> ok | {error, posix()}
 when
 File :: io_device(),
 Offset :: non_neg_integer(),
 Length :: non_neg_integer().
  allocate(File, Offset, Length)

Since:
OTP R16B
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@

-spec altname(Name :: name_all()) -> any().
  altname(Name)

The documentation for altname/1 is hidden. This probably means
that it is internal and not to be used by other applications.
Original file line number Diff line number Diff line change
@@ -1,8 +1,4 @@

-spec change_group(Filename, Gid) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Gid :: integer(),
 Reason :: posix() | badarg.
  change_group(Filename, Gid)

Changes group of a file. See write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@

-spec change_mode(Filename, Mode) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Mode :: integer(),
 Reason :: posix() | badarg.
  change_mode(Filename, Mode)

Since:
OTP R14B
Expand Down
Original file line number Diff line number Diff line change
@@ -1,8 +1,4 @@

-spec change_owner(Filename, Uid) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Uid :: integer(),
 Reason :: posix() | badarg.
  change_owner(Filename, Uid)

Changes owner of a file. See write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@

-spec change_owner(Filename, Uid, Gid) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Uid :: integer(),
 Gid :: integer(),
 Reason :: posix() | badarg.
  change_owner(Filename, Uid, Gid)

Changes owner and group of a file. See write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,17 +1,8 @@

-spec change_owner(Filename, Uid) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Uid :: integer(),
 Reason :: posix() | badarg.
  change_owner(Filename, Uid)

Changes owner of a file. See write_file_info/2.

-spec change_owner(Filename, Uid, Gid) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Uid :: integer(),
 Gid :: integer(),
 Reason :: posix() | badarg.
  change_owner(Filename, Uid, Gid)

Changes owner and group of a file. See write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@

-spec change_time(Filename, Mtime) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Mtime :: date_time(),
 Reason :: posix() | badarg.
  change_time(Filename, Mtime)

Changes the modification and access times of a file. See 
write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,10 +1,5 @@

-spec change_time(Filename, Atime, Mtime) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Atime :: date_time(),
 Mtime :: date_time(),
 Reason :: posix() | badarg.
  change_time(Filename, Atime, Mtime)

Changes the modification and last access times of a file. See 
write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,19 +1,10 @@

-spec change_time(Filename, Mtime) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Mtime :: date_time(),
 Reason :: posix() | badarg.
  change_time(Filename, Mtime)

Changes the modification and access times of a file. See 
write_file_info/2.

-spec change_time(Filename, Atime, Mtime) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Atime :: date_time(),
 Mtime :: date_time(),
 Reason :: posix() | badarg.
  change_time(Filename, Atime, Mtime)

Changes the modification and last access times of a file. See 
write_file_info/2.
Original file line number Diff line number Diff line change
@@ -1,8 +1,5 @@

-spec close(IoDevice) -> ok | {error, Reason}
 when
 IoDevice :: io_device(),
 Reason :: posix() | badarg | terminated.
  close(IoDevice)

Closes the file referenced by IoDevice. It mostly returns ok,
except for some severe errors such as out of memory.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,5 @@

-spec consult(Filename) -> {ok, Terms} | {error, Reason}
 when
 Filename :: name_all(),
 Terms :: [term()],
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()}.
  consult(Filename)

Reads Erlang terms, separated by ., from Filename. Returns one
of the following:
Expand Down
Original file line number Diff line number Diff line change
@@ -1,15 +1,5 @@

-spec copy(Source, Destination, ByteCount) ->
 {ok, BytesCopied} | {error, Reason}
 when
 Source :: io_device() | Filename | {Filename, Modes},
 Destination ::
 io_device() | Filename | {Filename, Modes},
 Filename :: name_all(),
 Modes :: [mode()],
 ByteCount :: non_neg_integer() | infinity,
 BytesCopied :: non_neg_integer(),
 Reason :: posix() | badarg | terminated.
  copy(Source, Destination, ByteCount)

Copies ByteCount bytes from Source to Destination. Source
and Destination refer to either filenames or IO devices from,
Expand Down
22 changes: 2 additions & 20 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_file_copy_func.txt
Original file line number Diff line number Diff line change
@@ -1,27 +1,9 @@

-spec copy(Source, Destination) -> {ok, BytesCopied} | {error, Reason}
 when
 Source :: io_device() | Filename | {Filename, Modes},
 Destination ::
 io_device() | Filename | {Filename, Modes},
 Filename :: name_all(),
 Modes :: [mode()],
 BytesCopied :: non_neg_integer(),
 Reason :: posix() | badarg | terminated.
  copy(Source, Destination)

There is no documentation for copy(Source, Destination, infinity)

-spec copy(Source, Destination, ByteCount) ->
 {ok, BytesCopied} | {error, Reason}
 when
 Source :: io_device() | Filename | {Filename, Modes},
 Destination ::
 io_device() | Filename | {Filename, Modes},
 Filename :: name_all(),
 Modes :: [mode()],
 ByteCount :: non_neg_integer() | infinity,
 BytesCopied :: non_neg_integer(),
 Reason :: posix() | badarg | terminated.
  copy(Source, Destination, ByteCount)

Copies ByteCount bytes from Source to Destination. Source
and Destination refer to either filenames or IO devices from,
Expand Down
Original file line number Diff line number Diff line change
@@ -1,8 +1,5 @@

-spec datasync(IoDevice) -> ok | {error, Reason}
 when
 IoDevice :: io_device(),
 Reason :: posix() | badarg | terminated.
  datasync(IoDevice)

Since:
OTP R14B
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@

-type date_time() :: calendar:datetime().
  date_time()

Must denote a valid date and time.
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@

-spec del_dir(Dir) -> ok | {error, Reason}
 when Dir :: name_all(), Reason :: posix() | badarg.
  del_dir(Dir)

Tries to delete directory Dir. The directory must be empty
before it can be deleted. Returns ok if successful.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@

-spec del_dir_r(File) -> ok | {error, Reason}
 when File :: name_all(), Reason :: posix() | badarg.
  del_dir_r(File)

Since:
OTP 23.0
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@

-spec delete(Filename, Opts) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Opts :: [delete_option()],
 Reason :: posix() | badarg.
  delete(Filename, Opts)

Since:
OTP 24.0
Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,9 @@

-spec delete(Filename) -> ok | {error, Reason}
 when Filename :: name_all(), Reason :: posix() | badarg.
  delete(Filename)

There is no documentation for delete(Filename, [])

-spec delete(Filename, Opts) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Opts :: [delete_option()],
 Reason :: posix() | badarg.
  delete(Filename, Opts)

Since:
OTP 24.0
Expand Down
Original file line number Diff line number Diff line change
@@ -1,13 +1,5 @@

-spec eval(Filename) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()}.
  eval(Filename)

Reads and evaluates Erlang expressions, separated by . (or ,,
a sequence of expressions is also an expression) from Filename.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,5 @@

-spec eval(Filename, Bindings) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Bindings :: erl_eval:binding_struct(),
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()}.
  eval(Filename, Bindings)

The same as eval/1, but the variable bindings Bindings are
used in the evaluation. For information about the variable
Expand Down
21 changes: 2 additions & 19 deletions lib/stdlib/test/shell_docs_SUITE_data/kernel_file_eval_func.txt
Original file line number Diff line number Diff line change
@@ -1,13 +1,5 @@

-spec eval(Filename) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()}.
  eval(Filename)

Reads and evaluates Erlang expressions, separated by . (or ,,
a sequence of expressions is also an expression) from Filename.
Expand All @@ -30,16 +22,7 @@
The encoding of Filename can be set by a comment, as described
in epp.

-spec eval(Filename, Bindings) -> ok | {error, Reason}
 when
 Filename :: name_all(),
 Bindings :: erl_eval:binding_struct(),
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()}.
  eval(Filename, Bindings)

The same as eval/1, but the variable bindings Bindings are
used in the evaluation. For information about the variable
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@

-type fd() :: file_descriptor().
  fd()

A file descriptor representing a file opened in raw mode.
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@

-type file_descriptor() :: #file_descriptor{}.
  file_descriptor()

The documentation for file_descriptor/0 is hidden. This probably
means that it is internal and not to be used by other
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@

-type filename() :: string().
  filename()

A file name as returned from file API functions.

Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@

-type filename_all() :: string() | (RawFilename :: binary()).
  filename_all()

A file name as returned from file API functions.

Expand Down
Original file line number Diff line number Diff line change
@@ -1,13 +1,5 @@

-spec format_error(Reason) -> Chars
 when
 Reason ::
 posix() |
 badarg | terminated | system_limit |
 {Line :: integer(),
 Mod :: module(),
 Term :: term()},
 Chars :: string().
  format_error(Reason)

Given the error reason returned by any function in this module,
returns a descriptive string of the error in English.
Loading

0 comments on commit a12eb10

Please sign in to comment.