File 0190-erts-Fix-doxygen-formatting.patch of Package erlang
From f64e5a13080e97f92dcc9034d63f2c60e0ed3c4b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 15 Oct 2019 12:00:20 +0200
Subject: [PATCH] erts: Fix doxygen formatting
doxygen only looks for tags in comments that start with `/**` or
`///`, tags inside plain comments are ignored.
---
erts/emulator/beam/erl_db_catree.c | 8 ++++----
erts/emulator/beam/erl_db_tree.c | 8 ++++----
erts/emulator/beam/erl_db_util.h | 6 +++---
erts/emulator/beam/erl_lock_count.h | 11 ++++++-----
erts/emulator/beam/erl_lock_flags.h | 4 ++--
erts/emulator/nifs/common/prim_file_nif.h | 12 ++++++------
erts/emulator/nifs/win32/win_prim_file.c | 6 +++---
erts/emulator/sys/common/erl_osenv.h | 18 +++++++++---------
8 files changed, 37 insertions(+), 36 deletions(-)
diff --git a/erts/emulator/beam/erl_db_catree.c b/erts/emulator/beam/erl_db_catree.c
index 176966edb5..d6e2f2c581 100644
--- a/erts/emulator/beam/erl_db_catree.c
+++ b/erts/emulator/beam/erl_db_catree.c
@@ -1367,7 +1367,7 @@ static void split_catree(DbTableCATree *tb,
}
}
-/* @brief Free the entire catree and its sub-trees.
+/** @brief Free the entire catree and its sub-trees.
*
* @param reds Reductions to spend.
* @return Reductions left. Negative value if not done.
@@ -1464,7 +1464,7 @@ static SWord db_free_table_continue_catree(DbTable *tbl, SWord reds)
return reds;
}
-/* @brief Free all objects of a base node, but keep the base node.
+/** @brief Free all objects of a base node, but keep the base node.
*
* @param reds Reductions to spend.
* @return Reductions left. Negative value if not done.
@@ -1776,7 +1776,7 @@ TreeDbTerm** catree_find_prev_root(CATreeRootIterator *iter, Eterm* keyp)
return catree_find_nextprev_root(iter, 0, keyp);
}
-/* @brief Find root of tree where object with smallest key of all larger than
+/** @brief Find root of tree where object with smallest key of all larger than
* partially bound key may reside. Can be used as a starting point for
* a reverse iteration with pb_key.
*
@@ -1829,7 +1829,7 @@ TreeDbTerm** catree_find_next_from_pb_key_root(Eterm pb_key,
}
}
-/* @brief Find root of tree where object with largest key of all smaller than
+/** @brief Find root of tree where object with largest key of all smaller than
* partially bound key may reside. Can be used as a starting point for
* a forward iteration with pb_key.
*
diff --git a/erts/emulator/beam/erl_db_tree.c b/erts/emulator/beam/erl_db_tree.c
index 67eb511681..9f50733892 100644
--- a/erts/emulator/beam/erl_db_tree.c
+++ b/erts/emulator/beam/erl_db_tree.c
@@ -3031,8 +3031,8 @@ found_prev:
}
-/* @brief Find object with smallest key of all larger than partially bound key.
- * Can be used as a starting point for a reverse iteration with pb_key.
+/** @brief Find object with smallest key of all larger than partially bound
+ * key. Can be used as a starting point for a reverse iteration with pb_key.
*
* @param pb_key The partially bound key. Example {42, '$1'}
* @param *rootpp Will return pointer to root pointer of tree with found object.
@@ -3081,8 +3081,8 @@ static TreeDbTerm *find_next_from_pb_key(DbTable *tbl, TreeDbTerm*** rootpp,
}
}
-/* @brief Find object with largest key of all smaller than partially bound key.
- * Can be used as a starting point for a forward iteration with pb_key.
+/** @brief Find object with largest key of all smaller than partially bound
+ * key. Can be used as a starting point for a forward iteration with pb_key.
*
* @param pb_key The partially bound key. Example {42, '$1'}
* @param *rootpp Will return pointer to root pointer of found object.
diff --git a/erts/emulator/beam/erl_db_util.h b/erts/emulator/beam/erl_db_util.h
index 4a87956c99..870d9e3a43 100644
--- a/erts/emulator/beam/erl_db_util.h
+++ b/erts/emulator/beam/erl_db_util.h
@@ -543,9 +543,9 @@ ERTS_GLB_INLINE Eterm erts_db_make_match_prog_ref(Process *p, Binary *mp, Eterm
ERTS_GLB_INLINE Binary *erts_db_get_match_prog_binary(Eterm term);
ERTS_GLB_INLINE Binary *erts_db_get_match_prog_binary_unchecked(Eterm term);
-/* @brief Ensure off-heap header is word aligned, make a temporary copy if not.
- * Needed when inspecting ETS off-heap lists that may contain unaligned
- * ProcBins if table is 'compressed'.
+/** @brief Ensure off-heap header is word aligned, make a temporary copy if
+ * not. Needed when inspecting ETS off-heap lists that may contain unaligned
+ * ProcBins if table is 'compressed'.
*/
struct erts_tmp_aligned_offheap
{
diff --git a/erts/emulator/beam/erl_lock_count.h b/erts/emulator/beam/erl_lock_count.h
index 0d47b16e0b..c061e7894d 100644
--- a/erts/emulator/beam/erl_lock_count.h
+++ b/erts/emulator/beam/erl_lock_count.h
@@ -78,7 +78,7 @@ typedef struct {
} erts_lcnt_time_t;
typedef struct {
- /* @brief log2 array of nano seconds occurences */
+ /** @brief log2 array of nano seconds occurences */
Uint32 ns[ERTS_LCNT_HISTOGRAM_SLOT_SIZE];
} erts_lcnt_hist_t;
@@ -271,7 +271,7 @@ int erts_lcnt_check_ref_installed(erts_lcnt_ref_t *ref);
erts_lcnt_lock_info_carrier_t *erts_lcnt_create_lock_info_carrier(int count);
-/* @brief Initializes the lock info at the given index.
+/** @brief Initializes the lock info at the given index.
* @param id An immediate erlang term with whatever extra data you want to
* identify this lock with.
* @param flags The flags the lock itself was initialized with. Keep in mind
@@ -300,9 +300,10 @@ void erts_lcnt_pre_thr_init(void);
void erts_lcnt_post_thr_init(void);
void erts_lcnt_late_init(void);
-/* @brief Called after everything in the system has been initialized, including
- * the schedulers. This is mainly a backwards compatibility shim for matching
- * the old lcnt behavior where all lock counting was enabled by default. */
+/** @brief Called after everything in the system has been initialized,
+ * including the schedulers. This is mainly a backwards compatibility shim for
+ * matching the old lcnt behavior where all lock counting was enabled by
+ * default. */
void erts_lcnt_post_startup(void);
void erts_lcnt_thread_setup(void);
diff --git a/erts/emulator/beam/erl_lock_flags.h b/erts/emulator/beam/erl_lock_flags.h
index 2db133b598..9d2216eaf6 100644
--- a/erts/emulator/beam/erl_lock_flags.h
+++ b/erts/emulator/beam/erl_lock_flags.h
@@ -71,10 +71,10 @@
typedef unsigned short erts_lock_flags_t;
typedef unsigned short erts_lock_options_t;
-/* @brief Gets the type name of the lock, honoring the RW flag if supplied. */
+/** @brief Gets the type name of the lock, honoring the RW flag if supplied. */
const char *erts_lock_flags_get_type_name(erts_lock_flags_t flags);
-/* @brief Gets a short-form description of the given lock options. (rw/r/w) */
+/** @brief Gets a short-form description of the given lock options. (rw/r/w) */
const char *erts_lock_options_get_short_desc(erts_lock_options_t options);
#endif /* ERTS_LOCK_FLAGS_H__ */
diff --git a/erts/emulator/nifs/common/prim_file_nif.h b/erts/emulator/nifs/common/prim_file_nif.h
index 28c1ea9d00..1cf5d52192 100644
--- a/erts/emulator/nifs/common/prim_file_nif.h
+++ b/erts/emulator/nifs/common/prim_file_nif.h
@@ -112,7 +112,7 @@ typedef struct {
typedef ErlNifBinary efile_path_t;
-/* @brief Translates the given "raw name" into the format expected by the APIs
+/** @brief Translates the given "raw name" into the format expected by the APIs
* used by the underlying implementation. The result is transient and does not
* need to be released.
*
@@ -123,30 +123,30 @@ typedef ErlNifBinary efile_path_t;
* prim_file:internal_native2name for compatibility reasons. */
posix_errno_t efile_marshal_path(ErlNifEnv *env, ERL_NIF_TERM path, efile_path_t *result);
-/* @brief Returns the underlying handle as an implementation-defined term.
+/** @brief Returns the underlying handle as an implementation-defined term.
*
* This is an internal function intended to support tests and tricky
* operations like sendfile(2). */
ERL_NIF_TERM efile_get_handle(ErlNifEnv *env, efile_data_t *d);
-/* @brief Read until EOF or the given iovec has been filled.
+/** @brief Read until EOF or the given iovec has been filled.
*
* @return -1 on failure, or the number of bytes read on success. The return
* value will be 0 if no bytes could be read before EOF or the end of the
* iovec. */
Sint64 efile_readv(efile_data_t *d, SysIOVec *iov, int iovlen);
-/* @brief Write the entirety of the given iovec.
+/** @brief Write the entirety of the given iovec.
*
* @return -1 on failure, or the number of bytes written on success. "Partial"
* failures will be reported with -1 and not the number of bytes we managed to
* write to disk before the failure. */
Sint64 efile_writev(efile_data_t *d, SysIOVec *iov, int iovlen);
-/* @brief As \c efile_readv, but starting from a file offset. */
+/** @brief As \c efile_readv, but starting from a file offset. */
Sint64 efile_preadv(efile_data_t *d, Sint64 offset, SysIOVec *iov, int iovlen);
-/* @brief As \c efile_writev, but starting from a file offset. */
+/** @brief As \c efile_writev, but starting from a file offset. */
Sint64 efile_pwritev(efile_data_t *d, Sint64 offset, SysIOVec *iov, int iovlen);
int efile_seek(efile_data_t *d, enum efile_seek_t seek, Sint64 offset, Sint64 *new_position);
diff --git a/erts/emulator/nifs/win32/win_prim_file.c b/erts/emulator/nifs/win32/win_prim_file.c
index 839ac3ea6e..fca7385809 100644
--- a/erts/emulator/nifs/win32/win_prim_file.c
+++ b/erts/emulator/nifs/win32/win_prim_file.c
@@ -269,7 +269,7 @@ static int handle_has_file_attributes(HANDLE handle, DWORD mask) {
return enif_realloc_binary(path, length * sizeof(WCHAR));
}
-/* @brief Checks whether all the given attributes are set on the object at the
+/** @brief Checks whether all the given attributes are set on the object at the
* given path. Note that it assumes false on errors. */
static int has_file_attributes(const efile_path_t *path, DWORD mask) {
DWORD attributes = GetFileAttributesW((WCHAR*)path->data);
@@ -313,7 +313,7 @@ static int get_drive_number(const efile_path_t *path) {
return -1;
}
-/* @brief Checks whether two *paths* are on the same mount point; they don't
+/** @brief Checks whether two *paths* are on the same mount point; they don't
* have to refer to existing or accessible files/directories. */
static int has_same_mount_point(const efile_path_t *path_a, const efile_path_t *path_b) {
WCHAR *mount_a, *mount_b;
diff --git a/erts/emulator/sys/common/erl_osenv.h b/erts/emulator/sys/common/erl_osenv.h
index f2e96a6af7..d0902e0ba1 100644
--- a/erts/emulator/sys/common/erl_osenv.h
+++ b/erts/emulator/sys/common/erl_osenv.h
@@ -47,7 +47,7 @@ struct __erts_osenv_data_t {
void erts_osenv_init(erts_osenv_t *env);
void erts_osenv_clear(erts_osenv_t *env);
-/* @brief Merges \c with into \c env
+/** @brief Merges \c with into \c env
*
* @param overwrite Whether to overwrite existing entries or keep them as they
* are. */
@@ -55,25 +55,25 @@ void erts_osenv_merge(erts_osenv_t *env, const erts_osenv_t *with, int overwrite
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
-/* @brief Copies env[key] into \c value
+/** @brief Copies env[key] into \c value
*
* @return 1 on success, 0 if the key couldn't be found, and -1 if the input
* was invalid. */
int erts_osenv_get_term(const erts_osenv_t *env, struct process *process,
Eterm key, Eterm *value);
-/* @brief Copies \c value into \c env[key]
+/** @brief Copies \c value into \c env[key]
*
* @return 1 on success, -1 if the input was invalid. */
int erts_osenv_put_term(erts_osenv_t *env, Eterm key, Eterm value);
-/* @brief Removes \c env[key]
+/** @brief Removes \c env[key]
*
* @return 1 on success, 0 if the key couldn't be found, and -1 if the input
* was invalid. */
int erts_osenv_unset_term(erts_osenv_t *env, Eterm key);
-/* @brief Copies env[key] into \c value
+/** @brief Copies env[key] into \c value
*
* @param value [in,out] The buffer to copy the value into, may be NULL if you
* only wish to query presence.
@@ -83,13 +83,13 @@ int erts_osenv_unset_term(erts_osenv_t *env, Eterm key);
int erts_osenv_get_native(const erts_osenv_t *env, const erts_osenv_data_t *key,
erts_osenv_data_t *value);
-/* @brief Copies \c value into \c env[key]
+/** @brief Copies \c value into \c env[key]
*
* @return 1 on success, -1 on failure. */
int erts_osenv_put_native(erts_osenv_t *env, const erts_osenv_data_t *key,
const erts_osenv_data_t *value);
-/* @brief Removes \c key from the env.
+/** @brief Removes \c key from the env.
*
* @return 1 on success, 0 if the key couldn't be found. */
int erts_osenv_unset_native(erts_osenv_t *env, const erts_osenv_data_t *key);
@@ -103,8 +103,8 @@ typedef void (*erts_osenv_foreach_native_cb_t)(void *state,
const erts_osenv_data_t *key,
const erts_osenv_data_t *value);
-/* @brief Walks through all environment variables, calling \c callback for each
- * one. It's unsafe to modify \c env within the callback. */
+/** @brief Walks through all environment variables, calling \c callback for
+ * each one. It's unsafe to modify \c env within the callback. */
void erts_osenv_foreach_term(const erts_osenv_t *env, struct process *process,
void *state, erts_osenv_foreach_term_cb_t callback);
--
2.16.4