Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
0928-Fix-typos-repeated-words-doc-ci-skip.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0928-Fix-typos-repeated-words-doc-ci-skip.patch of Package erlang
From d9a29bfd6747ab4a67b4426775fe6f2ac1e35ac8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Marc-Andr=C3=A9=20Lafortune?= <github@marc-andre.ca> Date: Sat, 5 Feb 2022 14:19:12 -0500 Subject: [PATCH] Fix typos (repeated words) [doc] [ci skip] --- erts/emulator/beam/beam_common.c | 6 +++--- erts/emulator/beam/bif.c | 4 ++-- erts/emulator/beam/emu/emu_load.c | 2 +- erts/emulator/beam/erl_arith.c | 2 +- erts/emulator/beam/erl_bif_port.c | 2 +- erts/emulator/beam/erl_map.c | 2 +- erts/emulator/beam/erl_md5.c | 2 +- erts/emulator/beam/erl_proc_sig_queue.c | 2 +- erts/emulator/beam/erl_thr_queue.c | 2 +- erts/emulator/beam/erl_trace.c | 4 ++-- erts/emulator/drivers/common/inet_drv.c | 2 +- erts/emulator/pcre/pcre_compile.c | 6 +++--- erts/emulator/pcre/pcre_exec.c | 8 ++++---- erts/emulator/pcre/pcre_maketables.c | 2 +- erts/emulator/pcre/pcre_valid_utf8.c | 4 ++-- erts/emulator/sys/unix/sys_signal_stack.c | 2 +- erts/emulator/sys/win32/erl_win32_sys_ddll.c | 2 +- erts/emulator/sys/win32/sys.c | 4 ++-- erts/emulator/zlib/inftrees.c | 2 +- erts/epmd/src/epmd_srv.c | 2 +- erts/lib_src/common/ethr_mutex.c | 2 +- lib/erl_interface/src/connect/ei_connect.c | 2 +- lib/erl_interface/src/decode/decode_fun.c | 2 +- lib/erl_interface/src/misc/eimd5.c | 2 +- lib/erl_interface/src/prog/erl_call.c | 2 +- 25 files changed, 36 insertions(+), 36 deletions(-) diff --git a/erts/emulator/beam/beam_emu.c b/erts/emulator/beam/beam_emu.c index 75a74e6fcf..13b5a51f90 100644 --- a/erts/emulator/beam/beam_emu.c +++ b/erts/emulator/beam/beam_emu.c @@ -841,7 +841,7 @@ gather_stacktrace(Process* p, struct StackTrace* s, int depth) * * There is an issue with line number information. Line number * information is associated with the address *before* an operation - * that may fail or be stored stored on the stack. But continuation + * that may fail or be stored on the stack. But continuation * pointers point after its call instruction, not before. To avoid * finding the wrong line number, we'll need to adjust them so that * they point at the beginning of the call instruction or inside the @@ -1113,7 +1113,7 @@ static Eterm *get_freason_ptr_from_exc(Eterm exc) { if (exc == NIL) { /* - * Is is not exactly clear when exc can be NIL. Probably only + * It is not exactly clear when exc can be NIL. Probably only * when the exception has been generated from native code. * Return a pointer to an Eterm that can be safely written and * ignored. @@ -2179,7 +2179,7 @@ erts_gc_update_map_assoc(Process* p, Eterm* reg, Uint live, old_keys++, old_vals++, num_old--; } else { /* Replace or insert new */ GET_TERM(new_p[1], *hp++); - if (c > 0) { /* If new new key */ + if (c > 0) { /* If new key */ *kp++ = new_key; } else { /* If replacement */ *kp++ = key; diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c index e81b4c3c1e..b9b3a93ee3 100644 --- a/erts/emulator/beam/bif.c +++ b/erts/emulator/beam/bif.c @@ -1314,7 +1314,7 @@ BIF_RETTYPE error_3(BIF_ALIST_3) /**********************************************************************/ /* * This is like exactly like error/1. The only difference is - * that Dialyzer thinks that it it will return an arbitrary term. + * that Dialyzer thinks that it will return an arbitrary term. * It is useful in stub functions for NIFs. */ @@ -1327,7 +1327,7 @@ BIF_RETTYPE nif_error_1(BIF_ALIST_1) /**********************************************************************/ /* * This is like exactly like error/2. The only difference is - * that Dialyzer thinks that it it will return an arbitrary term. + * that Dialyzer thinks that it will return an arbitrary term. * It is useful in stub functions for NIFs. */ diff --git a/erts/emulator/beam/erl_arith.c b/erts/emulator/beam/erl_arith.c index 5d475ed061..fbb0fd5227 100644 --- a/erts/emulator/beam/erl_arith.c +++ b/erts/emulator/beam/erl_arith.c @@ -710,7 +710,7 @@ erts_mixed_times(Process* p, Eterm arg1, Eterm arg2) return res; } else { /* - * The result is a a big number. + * The result is a big number. * Allocate a heap fragment and copy the result. * Be careful to allocate exactly what we need * to not leave any holes. diff --git a/erts/emulator/beam/erl_bif_port.c b/erts/emulator/beam/erl_bif_port.c index 6e9bcdff17..2ede2c966c 100644 --- a/erts/emulator/beam/erl_bif_port.c +++ b/erts/emulator/beam/erl_bif_port.c @@ -1124,7 +1124,7 @@ open_port(Process* p, Eterm name, Eterm settings, int *err_typep, int *err_nump) goto do_return; } -/* Merges the the global environment and the given {Key, Value} list into env, +/* Merges the global environment and the given {Key, Value} list into env, * unsetting all keys whose value is either 'false' or NIL. The behavior on * NIL is undocumented and perhaps surprising, but the previous implementation * worked in this manner. */ diff --git a/erts/emulator/beam/erl_map.c b/erts/emulator/beam/erl_map.c index d9b56e08c5..25e6f43aef 100644 --- a/erts/emulator/beam/erl_map.c +++ b/erts/emulator/beam/erl_map.c @@ -3401,7 +3401,7 @@ static Eterm hashmap_bld_tuple_uint(Uint **hpp, Uint *szp, Uint n, Uint nums[]) * continues down the 0:th slot until it finds a leaf. * * Once the leaf has been found, the return value is created - * by traversing the tree using the the stack that was built + * by traversing the tree using the stack that was built * when searching for the first leaf to return. * * The index can become a bignum, which complicates the code diff --git a/erts/emulator/beam/erl_md5.c b/erts/emulator/beam/erl_md5.c index 8d0352a367..f4b6301b5c 100644 --- a/erts/emulator/beam/erl_md5.c +++ b/erts/emulator/beam/erl_md5.c @@ -172,7 +172,7 @@ void MD5Update (context, input, inputLen) } /* - * MD5 finalization. Ends an MD5 message-digest operation, writing the + * MD5 finalization. Ends an MD5 message-digest operation, writing the message digest and zeroizing the context. */ void MD5Final (digest, context) diff --git a/erts/emulator/beam/erl_proc_sig_queue.c b/erts/emulator/beam/erl_proc_sig_queue.c index dfc8026df0..ea14d7024a 100644 --- a/erts/emulator/beam/erl_proc_sig_queue.c +++ b/erts/emulator/beam/erl_proc_sig_queue.c @@ -3684,7 +3684,7 @@ convert_to_down_message(Process *c_p, if (mdp->origin.flags & (ERTS_ML_FLG_SPAWN_ABANDONED | ERTS_ML_FLG_SPAWN_NO_EMSG)) { /* - * Operation has been been abandoned or + * Operation has been abandoned or * error message has been disabled... */ erts_monitor_release(*omon); diff --git a/erts/emulator/beam/erl_thr_queue.c b/erts/emulator/beam/erl_thr_queue.c index aab7c199d2..37c99a0419 100644 --- a/erts/emulator/beam/erl_thr_queue.c +++ b/erts/emulator/beam/erl_thr_queue.c @@ -52,7 +52,7 @@ * deallocation. Memory allocation can be moved to another more suitable * thread using erts_thr_q_prepare_enqueue() together with * erts_thr_q_enqueue_prepared() instead of using erts_thr_q_enqueue(). - * Memory deallocation can can be moved to another more suitable thread by + * Memory deallocation can be moved to another more suitable thread by * disabling auto_finalize_dequeue when initializing the queue and then use * erts_thr_q_get_finalize_dequeue_data() together * erts_thr_q_finalize_dequeue() after dequeuing or cleaning. diff --git a/erts/emulator/beam/erl_trace.c b/erts/emulator/beam/erl_trace.c index bb2e34a81b..25a7474cdf 100644 --- a/erts/emulator/beam/erl_trace.c +++ b/erts/emulator/beam/erl_trace.c @@ -1122,7 +1122,7 @@ erts_call_trace(Process* p, ErtsCodeInfo *info, Binary *match_spec, * use process flags */ tracee_flags = &ERTS_TRACE_FLAGS(p); - /* Is is not ideal at all to call this check twice, + /* It is not ideal at all to call this check twice, it should be optimized so that only one call is made. */ if (!is_tracer_enabled(p, ERTS_PROC_LOCK_MAIN, &p->common, &tnif, TRACE_FUN_ENABLED, am_trace_status) @@ -1246,7 +1246,7 @@ erts_call_trace(Process* p, ErtsCodeInfo *info, Binary *match_spec, ASSERT(!ERTS_TRACER_IS_NIL(*tracer)); /* - * Build the the {M,F,A} tuple in the local heap. + * Build the {M,F,A} tuple in the local heap. * (A is arguments or arity.) */ diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c index 04a1f70bf4..118c588780 100644 --- a/erts/emulator/drivers/common/inet_drv.c +++ b/erts/emulator/drivers/common/inet_drv.c @@ -10661,7 +10661,7 @@ static int tcp_inet_multi_timeout(ErlDrvData e, ErlDrvTermData caller) ** output on a socket only ! ** a reply code will be sent to connected (caller later) ** {inet_reply, S, Status} -** NOTE! normal sockets use the the tcp_inet_commandv +** NOTE! normal sockets use the tcp_inet_commandv ** but distribution still uses the tcp_inet_command!! */ diff --git a/erts/emulator/pcre/pcre_compile.c b/erts/emulator/pcre/pcre_compile.c index 80b966869a..94a7222e4d 100644 --- a/erts/emulator/pcre/pcre_compile.c +++ b/erts/emulator/pcre/pcre_compile.c @@ -4834,7 +4834,7 @@ for (;; ptr++) If the class contains characters outside the 0-255 range, a different opcode is compiled. It may optionally have a bit map for characters < 256, - but those above are are explicitly listed afterwards. A flag byte tells + but those above are explicitly listed afterwards. A flag byte tells whether the bitmap is present, and whether this is a negated class or not. In JavaScript compatibility mode, an isolated ']' causes an error. In @@ -5855,7 +5855,7 @@ for (;; ptr++) /* If previous was a character type match (\d or similar), abolish it and create a suitable repeat item. The code is shared with single-character repeats by setting op_type to add a suitable offset into repeat_type. Note - the the Unicode property types will be present only when SUPPORT_UCP is + the Unicode property types will be present only when SUPPORT_UCP is defined, but we don't wrap the little bits of code here because it just makes it horribly messy. */ @@ -7070,7 +7070,7 @@ for (;; ptr++) /* Optimize (?!) to (*FAIL) unless it is quantified - which is a weird thing to do, but Perl allows all assertions to be quantified, and when they contain capturing parentheses there may be a potential use for - this feature. Not that that applies to a quantified (?!) but we allow + this feature. Not that applies to a quantified (?!) but we allow it for uniformity. */ /* ------------------------------------------------------------ */ diff --git a/erts/emulator/pcre/pcre_exec.c b/erts/emulator/pcre/pcre_exec.c index e4da43e99f..bf7a9044ee 100644 --- a/erts/emulator/pcre/pcre_exec.c +++ b/erts/emulator/pcre/pcre_exec.c @@ -301,7 +301,7 @@ been known for decades.) So.... There is a fudge, triggered by defining NO_RECURSE, which avoids recursive calls by keeping local variables that need to be preserved in blocks of memory -obtained from malloc() instead instead of on the stack. Macros are used to +obtained from malloc() instead of on the stack. Macros are used to achieve this so that the actual code doesn't look very different to what it always used to. @@ -626,7 +626,7 @@ frame->Xoffset_top = offset_top; frame->Xeptrb = eptrb; frame->Xrdepth = rdepth; -/* This is where control jumps back to to effect "recursion" */ +/* This is where control jumps back to effect "recursion" */ HEAP_RECURSE: @@ -3213,7 +3213,7 @@ for (;;) /* Match an extended character class. In the 8-bit library, this opcode is - encountered only when UTF-8 mode mode is supported. In the 16-bit and + encountered only when UTF-8 mode is supported. In the 16-bit and 32-bit libraries, codepoints greater than 255 may be encountered even when UTF is not supported. */ @@ -7371,7 +7371,7 @@ for(;;) break; } - /* If req_char is set, we know that that character must appear in the + /* If req_char is set, we know that character must appear in the subject for the match to succeed. If the first character is set, req_char must be later in the subject; otherwise the test starts at the match point. This optimization can save a huge amount of backtracking in patterns with diff --git a/erts/emulator/pcre/pcre_maketables.c b/erts/emulator/pcre/pcre_maketables.c index 89204d1152..7877a577e9 100644 --- a/erts/emulator/pcre/pcre_maketables.c +++ b/erts/emulator/pcre/pcre_maketables.c @@ -108,7 +108,7 @@ exclusive ones - in some locales things may be different. Note that the table for "space" includes everything "isspace" gives, including VT in the default locale. This makes it work for the POSIX class [:space:]. -From release 8.34 is is also correct for Perl space, because Perl added VT at +From release 8.34 is also correct for Perl space, because Perl added VT at release 5.18. Note also that it is possible for a character to be alnum or alpha without diff --git a/erts/emulator/pcre/pcre_valid_utf8.c b/erts/emulator/pcre/pcre_valid_utf8.c index 1dc1f9ba0c..95a60c3fdb 100644 --- a/erts/emulator/pcre/pcre_valid_utf8.c +++ b/erts/emulator/pcre/pcre_valid_utf8.c @@ -219,7 +219,7 @@ for (p = string; length-- > 0; p++) switch (ab) { /* 2-byte character. No further bytes to check for 0x80. Check first byte - for for xx00 000x (overlong sequence). */ + for xx00 000x (overlong sequence). */ case 1: if ((c & 0x3e) == 0) { @@ -251,7 +251,7 @@ for (p = string; length-- > 0; p++) break; /* 4-byte character. Check 3rd and 4th bytes for 0x80. Then check first 2 - bytes for for 1111 0000, xx00 xxxx (overlong sequence), then check for a + bytes for 1111 0000, xx00 xxxx (overlong sequence), then check for a character greater than 0x0010ffff (f4 8f bf bf) */ case 3: diff --git a/erts/emulator/hipe/hipe_x86_signal.c b/erts/emulator/hipe/hipe_x86_signal.c index f4731a5034..772041d74d 100644 --- a/erts/emulator/hipe/hipe_x86_signal.c +++ b/erts/emulator/hipe/hipe_x86_signal.c @@ -97,7 +97,7 @@ * Assumes Mac OS X >= 10.3 (dlsym operations not available in 10.2 and * earlier). * - * The code below assumes that is is part of the main image (earlier + * The code below assumes that is part of the main image (earlier * in the load order than libSystem and certainly before any dylib * that might use sigaction) -- a standard RTLD_NEXT caveat. * diff --git a/erts/emulator/sys/win32/erl_win32_sys_ddll.c b/erts/emulator/sys/win32/erl_win32_sys_ddll.c index 7fe1f5cc78..01bc74a12a 100644 --- a/erts/emulator/sys/win32/erl_win32_sys_ddll.c +++ b/erts/emulator/sys/win32/erl_win32_sys_ddll.c @@ -91,7 +91,7 @@ int erts_sys_ddll_open(const char *full_name, void **handle, ErtsSysDdllError* e /* LOAD_WITH_ALTERED_SEARCH_PATH adds the specified DLL's directory to the * dependency search path. This also removes the directory we started in, - * but we've explicitly added that in in erl_sys_ddll_init. */ + * but we've explicitly added that in erl_sys_ddll_init. */ if ((hinstance = LoadLibraryExW(wcp, NULL, LOAD_WITH_ALTERED_SEARCH_PATH)) == NULL) { code = ERL_DE_DYNAMIC_ERROR_OFFSET - GetLastError(); if (err != NULL) { diff --git a/erts/emulator/sys/win32/sys.c b/erts/emulator/sys/win32/sys.c index b006908f09..63eb35a7c4 100644 --- a/erts/emulator/sys/win32/sys.c +++ b/erts/emulator/sys/win32/sys.c @@ -708,7 +708,7 @@ release_driver_data(DriverData* dp) requests issued by another thread and that we can't use CancelIoEx as that's only available in Vista etc. R14: Avoid scheduler deadlock by only wait for 10ms, and then spawn - a thread that will keep waiting in in order to close handles. */ + a thread that will keep waiting in order to close handles. */ HANDLE handles[2]; int i = 0; int timeout = 10; @@ -1526,7 +1526,7 @@ create_child_process wchar_t *wd, /* Working dir for the child */ unsigned st, /* Flags for spawn, tells us how to interpret origcmd */ wchar_t **argv, /* Argument vector if given. */ - int *errno_return /* Place to put an errno in in case of failure */ + int *errno_return /* Place to put an errno in case of failure */ ) { PROCESS_INFORMATION piProcInfo = {0}; diff --git a/erts/emulator/zlib/inftrees.c b/erts/emulator/zlib/inftrees.c index 2ea08fc13e..80e27a489e 100644 --- a/erts/emulator/zlib/inftrees.c +++ b/erts/emulator/zlib/inftrees.c @@ -87,7 +87,7 @@ unsigned short FAR *work; This routine assumes, but does not check, that all of the entries in lens[] are in the range 0..MAXBITS. The caller must assure this. - 1..MAXBITS is interpreted as that code length. zero means that that + 1..MAXBITS is interpreted as that code length. zero means that symbol does not occur in this code. The codes are sorted by computing a count of codes for each length, diff --git a/erts/epmd/src/epmd_srv.c b/erts/epmd/src/epmd_srv.c index 96d9d088b7..c414e156fb 100644 --- a/erts/epmd/src/epmd_srv.c +++ b/erts/epmd/src/epmd_srv.c @@ -543,7 +543,7 @@ void run(EpmdVars *g) /* * The accept() succeeded, and we have at least one file * descriptor still free, which means that another accept() - * could succeed. Go do do another select(), in case there + * could succeed. Go do another select(), in case there * are more incoming connections waiting to be accepted. */ goto select_again; diff --git a/erts/lib_src/common/ethr_mutex.c b/erts/lib_src/common/ethr_mutex.c index 2bb5f76b78..b3fe4a310a 100644 --- a/erts/lib_src/common/ethr_mutex.c +++ b/erts/lib_src/common/ethr_mutex.c @@ -884,7 +884,7 @@ enqueue_mtx(ethr_mutex *mtx, ethr_ts_event *tse_start, ethr_ts_event *tse_end) * is not currently locked by current thread, we almost certainly have a * hard to debug race condition. There might however be some (strange) * use for it. POSIX also allow a call to `pthread_cond_signal' or - * `pthread_cond_broadcast' even though the the associated mutex isn't + * `pthread_cond_broadcast' even though the associated mutex isn't * locked by the caller. Therefore, we also allow this kind of strange * usage, but optimize for the case where the mutex is locked by the * calling thread. diff --git a/lib/erl_interface/src/connect/ei_connect.c b/lib/erl_interface/src/connect/ei_connect.c index eac23c40c7..5abab56bb5 100644 --- a/lib/erl_interface/src/connect/ei_connect.c +++ b/lib/erl_interface/src/connect/ei_connect.c @@ -1139,7 +1139,7 @@ struct hostent *dyn_gethostbyname_r(const char *name, #endif } -/* Finds the the IP address for hostname and saves that IP address at +/* Finds the IP address for hostname and saves that IP address at the location that ip_wb points to. Returns a negative error code if the IP address cannot be found for the hostname. */ static int ip_address_from_hostname(char* hostname, diff --git a/lib/erl_interface/src/decode/decode_fun.c b/lib/erl_interface/src/decode/decode_fun.c index 3622ebbe02..cad8ba9bfb 100644 --- a/lib/erl_interface/src/decode/decode_fun.c +++ b/lib/erl_interface/src/decode/decode_fun.c @@ -120,7 +120,7 @@ int ei_decode_fun(const char *buf, int *index, erlang_fun *p) /* then the old_uniq */ if (ei_decode_long(s, &ix, p_uniq) < 0) return -1; - /* the the pid */ + /* the pid */ if (ei_decode_pid(s, &ix, p_pid) < 0) return -1; /* finally the free vars */ diff --git a/lib/erl_interface/src/misc/eimd5.c b/lib/erl_interface/src/misc/eimd5.c index 426b96d962..3d7dd960e7 100644 --- a/lib/erl_interface/src/misc/eimd5.c +++ b/lib/erl_interface/src/misc/eimd5.c @@ -161,7 +161,7 @@ void ei_MD5Update (MD5_CTX *context, unsigned char *input, } /* - * MD5 finalization. Ends an MD5 message-digest operation, writing the + * MD5 finalization. Ends an MD5 message-digest operation, writing the message digest and zeroizing the context. */ void ei_MD5Final (unsigned char digest[16], MD5_CTX *context) -- 2.34.1
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