@@ -2,7 +2,6 @@ Code.require_file("../../test_helper.exs", __DIR__)
22
33defmodule Module.Types.PatternTest do
44 use ExUnit.Case , async: true
5- import Module.Types.Infer , only: [ new_var: 2 ]
65
76 alias Module.Types
87 alias Module.Types.Pattern
@@ -16,12 +15,12 @@ defmodule Module.Types.PatternTest do
1615 end
1716 end
1817
19- defmacrop quoted_guard ( vars , guards ) do
18+ defmacrop quoted_head ( patterns , guards \\ [ ] ) do
2019 quote do
21- { vars , guards } = unquote ( Macro . escape ( expand_head ( vars , guards ) ) )
22- context = Enum . reduce ( vars , new_context ( ) , & ( new_var ( & 1 , & 2 ) |> elem ( 1 ) ) )
20+ { patterns , guards } = unquote ( Macro . escape ( expand_head ( patterns , guards ) ) )
2321
24- Pattern . of_guard ( guards , new_stack ( ) , context )
22+ Pattern . of_head ( patterns , guards , new_stack ( ) , new_context ( ) )
23+ |> lift_result ( )
2524 end
2625 end
2726
@@ -43,13 +42,7 @@ defmodule Module.Types.PatternTest do
4342 end
4443
4544 defp new_context ( ) do
46- Types . context (
47- "pattern_test.ex" ,
48- TypesTest ,
49- { :test , 0 } ,
50- [ ] ,
51- Module.ParallelChecker . test_cache ( )
52- )
45+ Types . context ( "types_test.ex" , TypesTest , { :test , 0 } , [ ] , Module.ParallelChecker . test_cache ( ) )
5346 end
5447
5548 defp new_stack ( ) do
@@ -59,6 +52,10 @@ defmodule Module.Types.PatternTest do
5952 }
6053 end
6154
55+ defp lift_result ( { :ok , types , context } ) when is_list ( types ) do
56+ { :ok , Types . lift_types ( types , context ) }
57+ end
58+
6259 defp lift_result ( { :ok , type , context } ) do
6360 { :ok , Types . lift_type ( type , context ) }
6461 end
@@ -67,7 +64,7 @@ defmodule Module.Types.PatternTest do
6764 { :error , { type , reason } }
6865 end
6966
70- defmodule :"Elixir.Module.Types.InferTest .Struct" do
67+ defmodule :"Elixir.Module.Types.PatternTest .Struct" do
7168 defstruct foo: :atom , bar: 123 , baz: % { }
7269 end
7370
@@ -136,18 +133,18 @@ defmodule Module.Types.PatternTest do
136133 end
137134
138135 test "struct" do
139- assert quoted_pattern ( % :"Elixir.Module.Types.InferTest .Struct" { } ) ==
136+ assert quoted_pattern ( % :"Elixir.Module.Types.PatternTest .Struct" { } ) ==
140137 { :ok ,
141138 { :map ,
142139 [
143- { :required , { :atom , :__struct__ } , { :atom , Module.Types.InferTest .Struct } }
140+ { :required , { :atom , :__struct__ } , { :atom , Module.Types.PatternTest .Struct } }
144141 ] } }
145142
146- assert quoted_pattern ( % :"Elixir.Module.Types.InferTest .Struct" { foo: 123 , bar: :atom } ) ==
143+ assert quoted_pattern ( % :"Elixir.Module.Types.PatternTest .Struct" { foo: 123 , bar: :atom } ) ==
147144 { :ok ,
148145 { :map ,
149146 [
150- { :required , { :atom , :__struct__ } , { :atom , Module.Types.InferTest .Struct } } ,
147+ { :required , { :atom , :__struct__ } , { :atom , Module.Types.PatternTest .Struct } } ,
151148 { :required , { :atom , :foo } , :integer } ,
152149 { :required , { :atom , :bar } , { :atom , :atom } }
153150 ] } }
@@ -221,83 +218,7 @@ defmodule Module.Types.PatternTest do
221218 end
222219 end
223220
224- describe "guards" do
225- test "of_guard/2" do
226- assert { :ok , :boolean , context } = quoted_guard ( [ x ] , is_tuple ( x ) )
227- assert Types . lift_type ( { :var , 0 } , context ) == :tuple
228-
229- assert { :ok , :dynamic , context } = quoted_guard ( [ x ] , elem ( x , 0 ) )
230- assert Types . lift_type ( { :var , 0 } , context ) == :tuple
231-
232- assert { :ok , { :atom , true } , _context } = quoted_guard ( [ ] , true )
233- assert { :ok , { :atom , false } , _context } = quoted_guard ( [ ] , false )
234- assert { :ok , { :atom , :fail } , _context } = quoted_guard ( [ ] , :fail )
235- assert { :ok , :boolean , _context } = quoted_guard ( [ ] , is_atom ( true or :fail ) )
236-
237- assert { :error , { :unable_unify , { :tuple , :boolean , _ } , _ } } =
238- quoted_guard ( [ x ] , is_tuple ( x ) and is_boolean ( x ) )
239- end
240- end
241- end
242-
243- defmodule Module.Types.TempTypesTest do
244- use ExUnit.Case , async: true
245- import Bitwise , warn: false
246-
247- alias Module.Types
248- alias Module.Types.Pattern
249-
250- defmacrop quoted_head ( patterns , guards \\ [ true ] ) do
251- quote do
252- { patterns , guards } = unquote ( Macro . escape ( expand_head ( patterns , guards ) ) )
253-
254- Pattern . of_head (
255- patterns ,
256- guards ,
257- new_stack ( ) ,
258- new_context ( )
259- )
260- |> lift_result ( )
261- end
262- end
263-
264- defp expand_head ( patterns , guards ) do
265- fun =
266- quote do
267- fn unquote ( patterns ) when unquote ( guards ) -> :ok end
268- end
269-
270- fun =
271- Macro . prewalk ( fun , fn
272- { var , meta , nil } -> { var , meta , __MODULE__ }
273- other -> other
274- end )
275-
276- { ast , _env } = :elixir_expand . expand ( fun , __ENV__ )
277- { :fn , _ , [ { :-> , _ , [ [ { :when , _ , [ patterns , guards ] } ] , _ ] } ] } = ast
278- { patterns , guards }
279- end
280-
281- defp new_context ( ) do
282- Types . context ( "types_test.ex" , TypesTest , { :test , 0 } , [ ] , Module.ParallelChecker . test_cache ( ) )
283- end
284-
285- defp new_stack ( ) do
286- % {
287- Types . stack ( )
288- | last_expr: { :foo , [ ] , nil }
289- }
290- end
291-
292- defp lift_result ( { :ok , types , context } ) when is_list ( types ) do
293- { :ok , Types . lift_types ( types , context ) }
294- end
295-
296- defp lift_result ( { :error , { type , reason , _context } } ) do
297- { :error , { type , reason } }
298- end
299-
300- describe "of_head/4" do
221+ describe "heads" do
301222 test "variable" do
302223 assert quoted_head ( [ a ] ) == { :ok , [ { :var , 0 } ] }
303224 assert quoted_head ( [ a , b ] ) == { :ok , [ { :var , 0 } , { :var , 1 } ] }
0 commit comments