11 Author: Isabell Huang <isabell(at)erlang(dot)org>
2- Status: Draft
2+ Status: Final/28.0 Implemented in OTP release 28
33 Type: Standards Track
44 Created: 21-Sep-2024
55 Erlang-Version: OTP-28.0
@@ -73,7 +73,7 @@ list of tuples. Variable bindings and pattern matching within a zip generator
7373works as expected, as ` Nm ` is supposed to bind to the same value in ` {Nm,P} `
7474and ` {Nm,S} ` . If the binding fails, then one element from each of the 3
7575generators is skipped. (If a strict generator is used, then the comprehension
76- fails with exception ` badmatch ` , as specified in EEP-70 .)
76+ fails with an exception , as specified in [ Error Behaviors ] ( #error-behaviors ) .)
7777
7878In summary, zip generators remove the user's need to call the zip function
7979within comprehensions and allows for any number of lists to be zipped at once.
@@ -138,6 +138,23 @@ filtered out from the resulting list.
138138
139139 [{X, Y} || X <- [a, b, c] && <<Y>> <= <<2, 4, 6>>, Y =/= 2].
140140
141+ The skipping behavior of individual generators within a zip generator is always
142+ respected. When strict generators are present in a zip generator, during every
143+ round of evaluation, all strict generators will be evaluated even if another
144+ relaxed generator already causes the result to be skipped.
145+
146+ For example, the following comprehension has a zip generator containing a
147+ strict generator and a relaxed generator.
148+
149+ [{X, Y} || {a, X} <:- L1 && {b, Y} <- L2]
150+
151+ It will ` badarg ` if pattern matching for ` {a, X} ` fails, for example, when
152+ ` L1 = [{a, 1}, {bad, 2}, {a, 3}] ` . It will simply skip 1 item from ` L1 ` and
153+ 1 item from ` L2 ` if pattern matching for ` {b, Y} ` fails, for example, when
154+ ` L2 = [{b, 1}, {bad, 2}, {b, 3}] ` . The attempt of matching ` {a, X} ` will
155+ be made every round, regardless of generators ordering and whether other
156+ pattern matchings succeed.
157+
141158Comparing to using helper functions, there is one advantage of using a zip
142159generator: The Erlang compiler does not generate any tuple when a zip
143160generator is translated into core Erlang. The generated code reflects the
@@ -170,7 +187,7 @@ all generators.
170187
171188For example, this comprehension will crash at runtime.
172189
173- [{X,Y} || X <- [1,2,3] && Y <- [1,2,3,4]].
190+ [{X,Y} || X <- [1,2,3] && Y <- [1,2,3,4]].
174191
175192The resulting error tuple is ` {bad_generators,{[],[4]}} ` . This is because
176193when the comprehension crashes, the first list in the zip generator has
@@ -183,6 +200,35 @@ different length comparing to others. The proposed error message aims to
183200gives the most helpful information without imposing extra burden on the
184201compiler or runtime.
185202
203+ Failed Strict Generator in a Zip Generator
204+ -----------------
205+
206+ When a zip generator crashes because at least one strict generators contained
207+ in it fails, the resulting error tuple is of the same format as when generators
208+ are of different lengths. Its first element is the atom ` bad_generators ` , and
209+ the second element is a tuple containing remaining data from all generators.
210+
211+ For example, this comprehension will crash at runtime, because ` bad ` cannot
212+ match the pattern ` {ok,A} ` .
213+
214+ [A + B || {ok,A} <:- [bad, {ok,1}] && B <- [2,3]].
215+
216+ The resulting error tuple is ` {bad_generators,{[bad, {ok,1}],[2,3]}} ` . Although
217+ strict generators alone fail with exception ` badmatch ` , as specified in
218+ [ EEP-70] [ 4 ] , it is not plausible to use the same exception in zip generators,
219+ due to difficulty in distinguishing between ` badmatch ` and ` bad_generators `
220+ errors.
221+
222+ In the following example, the comprehension will crash at runtime, either for
223+ the failed strict generator, or for two generators of different lengths.
224+
225+ [A + B || {ok,A} <:- [bad] && B <- []].
226+
227+ The emitted error message is ` {bad_generators,{[bad],[]}} ` . We do not
228+ distinguish between the two errors, and instead always output all remaining
229+ data in the generators. The user can examine the remaining data and see that
230+ the first generator fails matching, and the second generator is empty.
231+
186232Non-generator in a Zip Generator
187233-----------------
188234
@@ -212,8 +258,7 @@ this addition.
212258Reference Implementation
213259========================
214260
215- [ compiler: Add zip generators for comprehensions] [ 1 ] contains the implementation
216- for zip generators.
261+ [ PR-8926] [ 1 ] contains the implementation for zip generators.
217262
218263[ 1 ] : https://github.com/erlang/otp/pull/8926
219264[ 2 ] : https://downloads.haskell.org/~ghc/5.00/docs/set/parallel-list-comprehensions.html
0 commit comments