File: control_test.erl

package info (click to toggle)
elixir-lang 1.18.3.dfsg-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 14,436 kB
  • sloc: erlang: 11,996; sh: 324; makefile: 277
file content (261 lines) | stat: -rw-r--r-- 9,681 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
-module(control_test).
-include_lib("eunit/include/eunit.hrl").

to_erl(String) ->
  Forms = elixir:'string_to_quoted!'(String, 1, 1, <<"nofile">>, []),
  {Expr, _, _, _} = elixir:quoted_to_erl(Forms, elixir:env_for_eval([])),
  Expr.

cond_line_test() ->
  {'case', 1, _,
    [{clause, 2, _, _, _},
     {clause, 3, _, _, _}]
  } = to_erl("cond do\n  1 -> :ok\n  2 -> :ok\nend").

float_match_test() ->
  {'case', _, _,
    [{clause, _, [{op, _, '+', {float, _, +0.0}}], [], [{atom, _, pos}]},
     {clause, _, [{op, _, '-', {float, _, +0.0}}], [], [{atom, _, neg}]}]
  } = to_erl("case X do\n  +0.0 -> :pos\n  -0.0 -> :neg\nend").

% Optimized

optimized_if_test() ->
  {'case', _, _,
    [{clause, _, [{atom, _, false}], [], [{atom, _, 'else'}]},
     {clause, _, [{atom, _, true}], [], [{atom, _, do}]}]
  } = to_erl("if is_list([]), do: :do, else: :else").

optimized_andand_test() ->
  {'case', _, _,
    [{clause, _,
      [{var, _, Var}],
      [[{op, _, 'orelse', _, _}]],
      [{var, _, Var}]},
    {clause, _, [{var, _, '_'}], [], [{atom, 1, done}]}]
  } = to_erl("is_list([]) && :done").

optimized_oror_test() ->
  {'case', _, _,
    [{clause, 1,
      [{var, 1, _}],
      [[{op, 1, 'orelse', _, _}]],
      [{atom, 1, done}]},
    {clause, 1, [{var, 1, Var}], [], [{var, 1, Var}]}]
  } = to_erl("is_list([]) || :done").

optimized_and_test() ->
  {'case',_, _,
   [{clause, _, [{atom, _, false}], [], [{atom, _, false}]},
    {clause, _, [{atom, _, true}], [], [{atom, _, done}]}]
  } = to_erl("is_list([]) and :done").

optimized_or_test() ->
  {'case', _, _,
    [{clause, _, [{atom, _, false}], [], [{atom, _, done}]},
     {clause, _, [{atom, _, true}], [], [{atom, _, true}]}]
  } = to_erl("is_list([]) or :done").

no_after_in_try_test() ->
  {'try', _, [_], [], [_], []} = to_erl("try do :foo.bar() catch _ -> :ok end").

optimized_inspect_interpolation_test() ->
    {bin, _,
     [{bin_element, _,
       {call, _, {remote, _,{atom, _, 'Elixir.Kernel'}, {atom, _, inspect}}, [_]},
       default, [binary]}]} = to_erl("\"#{inspect(1)}\"").

optimized_map_put_test() ->
  {map, _,
    [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}},
     {map_field_assoc, _, {atom, _, b}, {integer, _, 2}}]
  } = to_erl("Map.put(%{a: 1}, :b, 2)").

optimized_map_put_variable_test() ->
  {block, _,
    [_,
     {map, _, {var, _, _},
       [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}}]
     }]
  } = to_erl("x = %{}; Map.put(x, :a, 1)").

optimized_nested_map_put_variable_test() ->
  {block, _,
    [_,
     {map, _, {var, _, _},
       [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}},
        {map_field_assoc, _, {atom, _, b}, {integer, _, 2}}]
     }]
  } = to_erl("x = %{}; Map.put(Map.put(x, :a, 1), :b, 2)").

optimized_map_merge_test() ->
  {map, _,
    [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}},
     {map_field_assoc, _, {atom, _, b}, {integer, _, 2}},
     {map_field_assoc, _, {atom, _, c}, {integer, _, 3}}]
  } = to_erl("Map.merge(%{a: 1, b: 2}, %{c: 3})").

optimized_map_merge_variable_test() ->
  {block, _,
    [_,
     {map, _, {var, _, _},
       [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}}]
     }]
  } = to_erl("x = %{}; Map.merge(x, %{a: 1})").

optimized_map_update_and_merge_test() ->
  {block, _,
    [_,
     {map, _, {var, _, _},
       [{map_field_exact, _, {atom, _, a}, {integer, _, 2}},
        {map_field_assoc, _, {atom, _, b}, {integer, _, 3}}]
     }]
  } = to_erl("x = %{a: 1}; Map.merge(%{x | a: 2}, %{b: 3})"),
  {block, _,
    [_,
     {call, _, {remote, _, {atom, _, maps}, {atom, _, merge}},
       [{map, _,
          [{map_field_assoc, _, {atom, _, a}, {integer, _, 2}}]},
        {map, _, {var, _, _},
          [{map_field_exact, _, {atom, _, b}, {integer, _, 3}}]}]
     }]
  } = to_erl("x = %{a: 1}; Map.merge(%{a: 2}, %{x | b: 3})").

optimized_nested_map_merge_variable_test() ->
  {block, _,
    [_,
     {map, _, {var, _, _},
       [{map_field_assoc, _, {atom, _, a}, {integer, _, 1}},
        {map_field_assoc, _, {atom, _, b}, {integer, _, 2}}]
     }]
  } = to_erl("x = %{}; Map.merge(Map.merge(x, %{a: 1}), %{b: 2})").

optimized_map_set_new_test() ->
  {map, _,
    [
      {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.MapSet'}},
      {map_field_assoc, _,
        {atom, _, map},
        {map, _, [
          {map_field_assoc, _, {integer, _, 1}, {nil, _}},
          {map_field_assoc, _, {integer, _, 2}, {nil, _}},
          {map_field_assoc, _, {integer, _, 3}, {nil, _}}
        ]}
      }
    ]
  } = to_erl("MapSet.new([1, 2, 3])").

not_optimized_map_set_new_with_range_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.MapSet'}, {atom, _, new}}, [
      {map, _, [
        {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.Range'}},
        {map_field_assoc, _, {atom, _, first}, {integer, _, 1}},
        {map_field_assoc, _, {atom, _, last}, {integer, _, 3}},
        {map_field_assoc, _, {atom, _, step}, {integer, _, 1}}
      ]}
    ]
  } = to_erl("MapSet.new(1..3)").

map_set_new_with_failing_args_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.MapSet'}, {atom, _, new}}, [
      {atom, _, not_an_enumerable}
    ]
  } = to_erl("MapSet.new(:not_an_enumerable)").

optimized_date_shift_duration_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.Date'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {map, _, [
        {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.Duration'}},
        {map_field_assoc, _, {atom, _, day}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, hour}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, microsecond}, {tuple, _, [{integer, _, 0}, {integer, _, 0}]}},
        {map_field_assoc, _, {atom, _, minute}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, month}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, second}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, week}, {integer, _, 1}},
        {map_field_assoc, _, {atom, _, year}, {integer, _, 0}}
      ]}
    ]
  } = to_erl("Date.shift(:non_important, week: 1)").

not_optimized_date_shift_duration_unsupported_unit_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.Date'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {cons, _, {tuple, _, [{atom, _, hour}, {integer, _, 1}]}, {nil, _}}
    ]
  } = to_erl("Date.shift(:non_important, hour: 1)").

optimized_time_shift_duration_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.Time'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {map, _, [
        {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.Duration'}},
        {map_field_assoc, _, {atom, _, day}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, hour}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, microsecond}, {tuple, _, [{integer, _, 0}, {integer, _, 0}]}},
        {map_field_assoc, _, {atom, _, minute}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, month}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, second}, {integer, _, 2}},
        {map_field_assoc, _, {atom, _, week}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, year}, {integer, _, 0}}
      ]}
    ]
  } = to_erl("Time.shift(:non_important, second: 2)").

not_optimized_time_shift_duration_unsupported_unit_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.Time'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {cons, _, {tuple, _, [{atom, _, day}, {integer, _, 2}]}, {nil, _}}
    ]
  } = to_erl("Time.shift(:non_important, day: 2)").

optimized_date_time_shift_duration_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.DateTime'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {map, _, [
        {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.Duration'}},
        {map_field_assoc, _, {atom, _, day}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, hour}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, microsecond}, {tuple, _, [{integer, _, 0}, {integer, _, 0}]}},
        {map_field_assoc, _, {atom, _, minute}, {integer, _, 3}},
        {map_field_assoc, _, {atom, _, month}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, second}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, week}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, year}, {integer, _, 0}}
      ]}
    ]
  } = to_erl("DateTime.shift(:non_important, minute: 3)").

non_optimized_date_time_shift_duration_unknown_unit_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.DateTime'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {cons, _, {tuple, _, [{atom, _, unknown}, {integer, _, 3}]}, {nil, _}}
    ]
  } = to_erl("DateTime.shift(:non_important, unknown: 3)").

optimized_naive_date_time_shift_duration_test() ->
  {call, _,
    {remote, _, {atom, _, 'Elixir.NaiveDateTime'}, {atom, _, shift}}, [
      {atom, _, non_important},
      {map, _, [
        {map_field_assoc, _, {atom, _, '__struct__'}, {atom, _, 'Elixir.Duration'}},
        {map_field_assoc, _, {atom, _, day}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, hour}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, microsecond}, {tuple, _, [{integer, _, 0}, {integer, _, 0}]}},
        {map_field_assoc, _, {atom, _, minute}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, month}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, second}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, week}, {integer, _, 0}},
        {map_field_assoc, _, {atom, _, year}, {integer, _, 4}}
      ]}
    ]
  } = to_erl("NaiveDateTime.shift(:non_important, year: 4)").