File 2031-system-Add-descriptions-about-zip-generators-to-docu.patch of Package erlang

From a31310e56425579ed50388ec68d771f4d8dfe3dc Mon Sep 17 00:00:00 2001
From: lucioleKi <isabell@erlang.org>
Date: Fri, 29 Nov 2024 15:36:58 +0100
Subject: [PATCH] system: Add descriptions about zip generators to
 documentation

Also add a section for comparing and contrasting strict and relaxed
generators.
---
 .../list_comprehensions.md                    | 114 +++++++++++++++---
 system/doc/reference_manual/expressions.md    |  77 +++++++++---
 2 files changed, 152 insertions(+), 39 deletions(-)

diff --git a/system/doc/programming_examples/list_comprehensions.md b/system/doc/programming_examples/list_comprehensions.md
index 5bfa45acbe..c8c6a07a24 100644
--- a/system/doc/programming_examples/list_comprehensions.md
+++ b/system/doc/programming_examples/list_comprehensions.md
@@ -24,32 +24,45 @@ limitations under the License.
 This section starts with a simple example, showing a generator and a filter:
 
 ```erlang
-> [X || X <- [1,2,a,3,4,b,5,6], X > 3].
+> [X || X <:- [1,2,a,3,4,b,5,6], X > 3].
 [a,4,b,5,6]
 ```
 
 This is read as follows: The list of X such that X is taken from the list
 `[1,2,a,...]` and X is greater than 3.
 
-The notation `X <- [1,2,a,...]` is a generator and the expression `X > 3` is a
+The notation `X <:- [1,2,a,...]` is a generator and the expression `X > 3` is a
 filter.
 
 An additional filter, [`is_integer(X)`](`is_integer/1`), can be added to
 restrict the result to integers:
 
 ```erlang
-> [X || X <- [1,2,a,3,4,b,5,6], is_integer(X), X > 3].
+> [X || X <:- [1,2,a,3,4,b,5,6], is_integer(X), X > 3].
 [4,5,6]
 ```
 
-Generators can be combined. For example, the Cartesian product of two lists can
-be written as follows:
+Generators can be combined in two ways. For example, the Cartesian product of
+two lists can be written as follows:
 
 ```erlang
-> [{X, Y} || X <- [1,2,3], Y <- [a,b]].
+> [{X, Y} || X <:- [1,2,3], Y <:- [a,b]].
 [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}]
 ```
 
+Alternatively, two lists can be zipped together using a zip generator as
+follows:
+
+```erlang
+> [{X, Y} || X <:- [1,2,3] && Y <:- [a,b,c]].
+[{1,a},{2,b},{3,c}]
+```
+
+> #### Change {: .info }
+>
+> Strict generators are used by default in the examples. More details and
+> comparisons can be found in [Strict and Relaxed Generators](#strict-and-relaxed-generators).
+
 ## Quick Sort
 
 The well-known quick sort routine can be written as follows:
@@ -58,15 +71,15 @@ The well-known quick sort routine can be written as follows:
 sort([]) -> [];
 sort([_] = L) -> L;
 sort([Pivot|T]) ->
-    sort([ X || X <- T, X < Pivot]) ++
+    sort([ X || X <:- T, X < Pivot]) ++
     [Pivot] ++
-    sort([ X || X <- T, X >= Pivot]).
+    sort([ X || X <:- T, X >= Pivot]).
 ```
 
-The expression `[X || X <- T, X < Pivot]` is the list of all elements in `T`
+The expression `[X || X <:- T, X < Pivot]` is the list of all elements in `T`
 that are less than `Pivot`.
 
-`[X || X <- T, X >= Pivot]` is the list of all elements in `T` that are greater
+`[X || X <:- T, X >= Pivot]` is the list of all elements in `T` that are greater
 than or equal to `Pivot`.
 
 With the algorithm above, a list is sorted as follows:
@@ -100,7 +113,7 @@ The following example generates all permutations of the elements in a list:
 
 ```erlang
 perms([]) -> [[]];
-perms(L)  -> [[H|T] || H <- L, T <- perms(L--[H])].
+perms(L)  -> [[H|T] || H <:- L, T <:- perms(L--[H])].
 ```
 
 This takes `H` from `L` in all possible ways. The result is the set of all lists
@@ -124,9 +137,9 @@ The function `pyth(N)` generates a list of all integers `{A,B,C}` such that
 ```erlang
 pyth(N) ->
     [ {A,B,C} ||
-        A <- lists:seq(1,N),
-        B <- lists:seq(1,N),
-        C <- lists:seq(1,N),
+        A <:- lists:seq(1,N),
+        B <:- lists:seq(1,N),
+        C <:- lists:seq(1,N),
         A+B+C =< N,
         A*A+B*B == C*C
     ].
@@ -159,9 +172,9 @@ The following code reduces the search space and is more efficient:
 ```erlang
 pyth1(N) ->
    [{A,B,C} ||
-       A <- lists:seq(1,N-2),
-       B <- lists:seq(A+1,N-1),
-       C <- lists:seq(B+1,N),
+       A <:- lists:seq(1,N-2),
+       B <:- lists:seq(A+1,N-1),
+       C <:- lists:seq(B+1,N),
        A+B+C =< N,
        A*A+B*B == C*C ].
 ```
@@ -172,9 +185,10 @@ As an example, list comprehensions can be used to simplify some of the functions
 in `lists.erl`:
 
 ```erlang
-append(L)   ->  [X || L1 <- L, X <- L1].
-map(Fun, L) -> [Fun(X) || X <- L].
-filter(Pred, L) -> [X || X <- L, Pred(X)].
+append(L)   ->  [X || L1 <:- L, X <:- L1].
+map(Fun, L) -> [Fun(X) || X <:- L].
+filter(Pred, L) -> [X || X <:- L, Pred(X)].
+zip(L1, L2) -> [{X,Y} || X <:- L1 && Y <:- L2].
 ```
 
 ## Variable Bindings in List Comprehensions
@@ -186,6 +200,7 @@ The scope rules for variables that occur in list comprehensions are as follows:
 - Any variables that are defined before the list comprehension, and that are
   used in filters, have the values they had before the list comprehension.
 - Variables cannot be exported from a list comprehension.
+- Within a zip generator, binding of all variables happen at the same time.
 
 As an example of these rules, suppose you want to write the function `select`,
 which selects certain elements from a list of tuples. Suppose you write
@@ -254,3 +269,62 @@ f(...) ->
     [ Expression || PatternInvolving Y1  <- Expr, Y == Y1, ...]
     ...
 ```
+
+## Strict and Relaxed Generators
+
+Strict and relaxed generators have different behaviors when the right-hand
+side expression does not match the left-hand side pattern. A relaxed generator
+ignores that term and continues on. A strict generator fails with an exception.
+
+Their difference can be shown in the following example. The generator
+expects a two-tuple pattern. If a relaxed generator is used, `b` will be
+silently skipped. If a strict generator is used, an exception will be raised
+when the pattern matching fails with `b`.
+
+```
+{_,_} <-  [{ok, a}, b]
+{_,_} <:- [{ok, a}, b]
+```
+
+Semantically, strict or relaxed generators convey different intentions from
+the programmer. Strict generators are used when unexpected elements in the
+input data should not be tolerated. Any element not conforming to specific
+patterns should immediately crash the comprehension, because the program may
+not be prepared to handle it.
+
+For example, the following comprehension is rewritten from one in the Erlang
+linter. It extracts arities from all defined functions. All elements in the
+list `DefinedFuns` are two-tuples, containing name and arity for functions.
+If any of them differs from this pattern, it means that something has added
+an invalid item into the list of defined functions. It is better for the linter
+to crash in the comprehension than skipping the invalid item and continue
+running. Using a strict generator here is correct, because the linter should
+not hide the presence of an internal inconsistency.
+
+```
+[Arity || {_FunName, Arity} <:- DefinedFuns]
+```
+
+In contrast, relaxed generators are used when unexpected elements in the input
+data should be _filtered out_. The programmer is aware that some elements
+may not conform to specific patterns. Those elements can be safely excluded
+from the comprehension result.
+
+For example, the following comprehension is from a compiler module that
+transforms normal Erlang code to Core Erlang. It finds all defined functions
+from an abstract form, and output them in two-tuples, each containing name and
+arity of a function. Not all forms are function declarations. All the forms
+that are not function declarations should be ignored by this comprehensions.
+Using a relaxed generator here is correct, because the programmer intends to
+exclude all elements with other patterns.
+
+```
+[{Name,Arity} || {function,_,Name,Arity,_} <- Forms]
+```
+
+Strict and relaxed generators don't always have distinct use cases. When the
+left-hand side pattern of a generator is a fresh variable, pattern matching
+cannot fail. Using either strict or relaxed generators leads to the same
+behavior. While the preference and use cases might be individual, it is
+recommended to use strict generators when either can be used. Using strict
+generators by default aligns with Erlang's "Let it crash" philosophy.
\ No newline at end of file
diff --git a/system/doc/reference_manual/expressions.md b/system/doc/reference_manual/expressions.md
index 214c513409..f9932981ba 100644
--- a/system/doc/reference_manual/expressions.md
+++ b/system/doc/reference_manual/expressions.md
@@ -1991,16 +1991,17 @@ is either a **generator** or a **filter**.
 >
 > Map comprehensions and map generators were introduced in Erlang/OTP 26.
 
-There are three kinds of generators, each with a relaxed and a strict
-variant.
+There are four kinds of generators. Three of them have a relaxed and a strict
+variant. The fourth kind of generator, zip generator, is composed by two or
+more non-zip generators.
 
 > #### Change {: .info }
 >
-> Strict generators were introduced in Erlang/OTP 28.
+> Strict generators and zip generators were introduced in Erlang/OTP 28.
+> Using strict generators is a better practice when either strict or relaxed
+> generators work. More details are in
+> [Programming Examples.](`e:system:list_comprehensions.md`)
 
-Relaxed generators ignore terms in the right-hand side expression that
-do not match the left-hand side pattern. Strict generators on the other
-hand fail with exception `badmatch`.
 
 A _list generator_ has the following syntax for relaxed:
 
@@ -2045,6 +2046,15 @@ KeyPattern := ValuePattern <:- MapExpression
 where `MapExpr` is an expression that evaluates to a map, or a map iterator
 obtained by calling `maps:iterator/1` or `maps:iterator/2`.
 
+A _zip generator_ has the following syntax:
+
+```
+Generator_1 && ... && Generator_n
+```
+
+where every `Generator_i` is a non-zip generator. Generators within a zip
+generator are treated as one generator and evaluated in parallel.
+
 A _filter_ is an expression that evaluates to `true` or `false`.
 
 The variables in the generator patterns shadow previously bound variables,
@@ -2076,49 +2086,49 @@ occurrence is stored in the map.
 Multiplying each element in a list by two:
 
 ```
-1> [X*2 || X <- [1,2,3]].
+1> [X*2 || X <:- [1,2,3]].
 [2,4,6]
 ```
 
 Multiplying each byte in a binary by two, returning a list:
 
 ```
-1> [X*2 || <<X>> <= <<1,2,3>>].
+1> [X*2 || <<X>> <:= <<1,2,3>>].
 [2,4,6]
 ```
 
 Multiplying each byte in a binary by two:
 
 ```
-1> << <<(X*2)>> || <<X>> <= <<1,2,3>> >>.
+1> << <<(X*2)>> || <<X>> <:= <<1,2,3>> >>.
 <<2,4,6>>
 ```
 
 Multiplying each element in a list by two, returning a binary:
 
 ```
-1> << <<(X*2)>> || X <- [1,2,3] >>.
+1> << <<(X*2)>> || X <:- [1,2,3] >>.
 <<2,4,6>>
 ```
 
 Creating a mapping from an integer to its square:
 
 ```
-1> #{X => X*X || X <- [1,2,3]}.
+1> #{X => X*X || X <:- [1,2,3]}.
 #{1 => 1,2 => 4,3 => 9}
 ```
 
 Multiplying the value of each element in a map by two:
 
 ```
-1> #{K => 2*V || K := V <- #{a => 1,b => 2,c => 3}}.
+1> #{K => 2*V || K := V <:- #{a => 1,b => 2,c => 3}}.
 #{a => 2,b => 4,c => 6}
 ```
 
 Filtering a list, keeping odd numbers:
 
 ```
-1> [X || X <- [1,2,3,4,5], X rem 2 =:= 1].
+1> [X || X <:- [1,2,3,4,5], X rem 2 =:= 1].
 [1,3,5]
 ```
 
@@ -2129,13 +2139,42 @@ Filtering a list, keeping only elements that match:
 [{a,b},{1,2}]
 ```
 
+Filtering a list, crashing when the element is not a 2-tuple:
+
+```
+1> [X || {_,_}=X <:- [{a,b}, [a], {x,y,z}, {1,2}]].
+** exception error: no match of right hand side value [a]
+```
+
 Combining elements from two list generators:
 
 ```
-1> [{P,Q} || P <- [a,b,c], Q <- [1,2]].
+1> [{P,Q} || P <:- [a,b,c], Q <:- [1,2]].
 [{a,1},{a,2},{b,1},{b,2},{c,1},{c,2}]
 ```
 
+Combining elements from two list generators, using a zip generator:
+
+```
+1> [{P,Q} || P <:- [a,b,c] && Q <:- [1,2,3]].
+[{a,1},{b,2},{c,3}]
+```
+
+Combining elements from two list generators using a zip generator, filtering
+out odd numbers:
+
+```
+1> [{P,Q} || P <:- [a,b,c] && Q <:- [1,2,3], Q rem 2 =:= 0].
+[{a,1},{b,2},{c,3}]
+```
+
+Filtering out non-matching elements from two lists.
+
+```
+1> [X || X <- [1,2,3,5] && X <- [1,4,3,6]].
+[1,3]
+```
+
 More examples are provided in
 [Programming Examples.](`e:system:list_comprehensions.md`)
 
@@ -2169,9 +2208,9 @@ depends on the expression:
 ```
 1> List = [1,2,a,b,c,3,4].
 [1,2,a,b,c,3,4]
-2> [E || E <- List, E rem 2].
+2> [E || E <:- List, E rem 2].
 []
-3> [E || E <- List, E rem 2 =:= 0].
+3> [E || E <:- List, E rem 2 =:= 0].
 [2,4]
 ```
 
@@ -2182,15 +2221,15 @@ depends on the expression:
 [1,2,a,b,c,3,4]
 2> FaultyIsEven = fun(E) -> E rem 2 end.
 #Fun<erl_eval.42.17316486>
-3> [E || E <- List, FaultyIsEven(E)].
+3> [E || E <:- List, FaultyIsEven(E)].
 ** exception error: bad filter 1
 4> IsEven = fun(E) -> E rem 2 =:= 0 end.
 #Fun<erl_eval.42.17316486>
-5> [E || E <- List, IsEven(E)].
+5> [E || E <:- List, IsEven(E)].
 ** exception error: an error occurred when evaluating an arithmetic expression
      in operator  rem/2
         called as a rem 2
-6> [E || E <- List, is_integer(E), IsEven(E)].
+6> [E || E <:- List, is_integer(E), IsEven(E)].
 [2,4]
 ```
 
-- 
2.43.0

openSUSE Build Service is sponsored by