@@ -35,17 +35,12 @@ defmodule Module.Types.Descr do
35
35
@ map_top [ { :open , % { } , [ ] } ]
36
36
@ map_empty [ { :closed , % { } , [ ] } ]
37
37
38
- # Guard helpers
39
-
40
- @ term % { bitmap: @ bit_top , atom: @ atom_top , map: @ map_top }
41
- @ none % { }
42
- @ dynamic % { dynamic: @ term }
43
-
44
38
# Type definitions
45
39
46
- def dynamic ( ) , do: @ dynamic
47
- def term ( ) , do: @ term
48
- def none ( ) , do: @ none
40
+ def dynamic ( ) , do: % { dynamic: :term }
41
+ def none ( ) , do: % { }
42
+ def term ( ) , do: :term
43
+ defp unfolded_term , do: % { bitmap: @ bit_top , atom: @ atom_top , map: @ map_top }
49
44
50
45
def atom ( as ) , do: % { atom: atom_new ( as ) }
51
46
def atom ( ) , do: % { atom: @ atom_top }
@@ -84,14 +79,17 @@ defmodule Module.Types.Descr do
84
79
@ term_or_optional % { bitmap: @ bit_top ||| @ bit_optional , atom: @ atom_top , map: @ map_top }
85
80
86
81
def not_set ( ) , do: @ not_set
87
- def if_set ( type ) , do: Map . update ( type , :bitmap , @ bit_optional , & ( & 1 ||| @ bit_optional ) )
88
82
defp term_or_optional ( ) , do: @ term_or_optional
89
83
84
+ def if_set ( :term ) , do: @ term_or_optional
85
+ def if_set ( type ) , do: Map . update ( type , :bitmap , @ bit_optional , & ( & 1 ||| @ bit_optional ) )
86
+
90
87
## Set operations
91
88
92
- def term_type? ( @ term ) , do: true
93
- def term_type? ( descr ) , do: subtype_static ( @ term , Map . delete ( descr , :dynamic ) )
89
+ def term_type? ( : term) , do: true
90
+ def term_type? ( descr ) , do: subtype_static ( unfolded_term ( ) , Map . delete ( descr , :dynamic ) )
94
91
92
+ def gradual? ( :term ) , do: false
95
93
def gradual? ( descr ) , do: is_map_key ( descr , :dynamic )
96
94
97
95
@ doc """
@@ -102,13 +100,14 @@ defmodule Module.Types.Descr do
102
100
def dynamic ( descr ) do
103
101
case descr do
104
102
% { dynamic: dynamic } -> % { dynamic: dynamic }
105
- % { } -> % { dynamic: descr }
103
+ _ -> % { dynamic: descr }
106
104
end
107
105
end
108
106
109
107
@ doc """
110
108
Computes the union of two descrs.
111
109
"""
110
+ # TODO!!!
112
111
def union ( % { } = left , % { } = right ) do
113
112
is_gradual_left = gradual? ( left )
114
113
is_gradual_right = gradual? ( right )
@@ -136,6 +135,7 @@ defmodule Module.Types.Descr do
136
135
@ doc """
137
136
Computes the intersection of two descrs.
138
137
"""
138
+ # TODO!!!
139
139
def intersection ( % { } = left , % { } = right ) do
140
140
is_gradual_left = gradual? ( left )
141
141
is_gradual_right = gradual? ( right )
@@ -164,21 +164,23 @@ defmodule Module.Types.Descr do
164
164
@ doc """
165
165
Computes the difference between two types.
166
166
"""
167
+ # TODO!!!
167
168
def difference ( left = % { } , right = % { } ) do
168
169
if gradual? ( left ) or gradual? ( right ) do
169
170
{ left_dynamic , left_static } = Map . pop ( left , :dynamic , left )
170
171
{ right_dynamic , right_static } = Map . pop ( right , :dynamic , right )
171
172
dynamic_part = difference_static ( left_dynamic , right_static )
172
173
173
174
if empty? ( dynamic_part ) ,
174
- do: @ none ,
175
+ do: none ( ) ,
175
176
else: Map . put ( difference_static ( left_static , right_dynamic ) , :dynamic , dynamic_part )
176
177
else
177
178
difference_static ( left , right )
178
179
end
179
180
end
180
181
181
182
# For static types, the difference is component-wise.
183
+ # TODO!!!
182
184
defp difference_static ( left , right ) do
183
185
iterator_difference ( :maps . next ( :maps . iterator ( right ) ) , left )
184
186
end
@@ -193,7 +195,8 @@ defmodule Module.Types.Descr do
193
195
@ doc """
194
196
Compute the negation of a type.
195
197
"""
196
- def negation ( % { } = descr ) , do: difference ( term ( ) , descr )
198
+ def negation ( :term ) , do: none ( )
199
+ def negation ( % { } = descr ) , do: difference ( unfolded_term ( ) , descr )
197
200
198
201
@ doc """
199
202
Check if a type is empty.
@@ -203,18 +206,20 @@ defmodule Module.Types.Descr do
203
206
(bitmap, atom) are checked first for speed since, if they are present,
204
207
the type is non-empty as we normalize then during construction.
205
208
"""
209
+ def empty? ( :term ) , do: false
210
+
206
211
def empty? ( % { } = descr ) do
207
212
descr = Map . get ( descr , :dynamic , descr )
208
213
209
- descr == @ none or
214
+ descr == none ( ) or
210
215
( not Map . has_key? ( descr , :bitmap ) and not Map . has_key? ( descr , :atom ) and
211
216
( not Map . has_key? ( descr , :map ) or map_empty? ( descr . map ) ) )
212
217
end
213
218
214
219
@ doc """
215
220
Converts a descr to its quoted representation.
216
221
"""
217
- def to_quoted ( % { } = descr ) do
222
+ def to_quoted ( descr ) do
218
223
if term_type? ( descr ) do
219
224
{ :term , [ ] , [ ] }
220
225
else
@@ -260,6 +265,7 @@ defmodule Module.Types.Descr do
260
265
Because of the dynamic/static invariant in the `descr`, subtyping can be
261
266
simplified in several cases according to which type is gradual or not.
262
267
"""
268
+ # TODO!!!
263
269
def subtype? ( % { } = left , % { } = right ) do
264
270
is_grad_left = gradual? ( left )
265
271
is_grad_right = gradual? ( right )
@@ -278,6 +284,7 @@ defmodule Module.Types.Descr do
278
284
end
279
285
end
280
286
287
+ defp subtype_static ( same , same ) , do: true
281
288
defp subtype_static ( left , right ) , do: empty? ( difference_static ( left , right ) )
282
289
283
290
@ doc """
@@ -305,6 +312,7 @@ defmodule Module.Types.Descr do
305
312
include `dynamic()`, `integer()`, but also `dynamic() and (integer() or atom())`.
306
313
Incompatible subtypes include `integer() or list()`, `dynamic() and atom()`.
307
314
"""
315
+ # TODO!!!
308
316
def compatible? ( input_type , expected_type ) do
309
317
{ input_dynamic , input_static } = Map . pop ( input_type , :dynamic , input_type )
310
318
expected_dynamic = Map . get ( expected_type , :dynamic , expected_type )
@@ -323,35 +331,35 @@ defmodule Module.Types.Descr do
323
331
"""
324
332
def fun_type? ( % { dynamic: % { bitmap: bitmap } } ) when ( bitmap &&& @ bit_fun ) != 0 , do: true
325
333
def fun_type? ( % { bitmap: bitmap } ) when ( bitmap &&& @ bit_fun ) != 0 , do: true
326
- def fun_type? ( % { } ) , do: false
334
+ def fun_type? ( _ ) , do: false
327
335
328
336
@ doc """
329
337
Optimized version of `not empty?(intersection(binary(), type))`.
330
338
"""
331
339
def binary_type? ( % { dynamic: % { bitmap: bitmap } } ) when ( bitmap &&& @ bit_binary ) != 0 , do: true
332
340
def binary_type? ( % { bitmap: bitmap } ) when ( bitmap &&& @ bit_binary ) != 0 , do: true
333
- def binary_type? ( % { } ) , do: false
341
+ def binary_type? ( _ ) , do: false
334
342
335
343
@ doc """
336
344
Optimized version of `not empty?(intersection(integer(), type))`.
337
345
"""
338
346
def integer_type? ( % { dynamic: % { bitmap: bitmap } } ) when ( bitmap &&& @ bit_integer ) != 0 , do: true
339
347
def integer_type? ( % { bitmap: bitmap } ) when ( bitmap &&& @ bit_integer ) != 0 , do: true
340
- def integer_type? ( % { } ) , do: false
348
+ def integer_type? ( _ ) , do: false
341
349
342
350
@ doc """
343
351
Optimized version of `not empty?(intersection(float(), type))`.
344
352
"""
345
353
def float_type? ( % { dynamic: % { bitmap: bitmap } } ) when ( bitmap &&& @ bit_float ) != 0 , do: true
346
354
def float_type? ( % { bitmap: bitmap } ) when ( bitmap &&& @ bit_float ) != 0 , do: true
347
- def float_type? ( % { } ) , do: false
355
+ def float_type? ( _ ) , do: false
348
356
349
357
@ doc """
350
358
Optimized version of `not empty?(intersection(integer() or float(), type))`.
351
359
"""
352
360
def number_type? ( % { dynamic: % { bitmap: bitmap } } ) when ( bitmap &&& @ bit_number ) != 0 , do: true
353
361
def number_type? ( % { bitmap: bitmap } ) when ( bitmap &&& @ bit_number ) != 0 , do: true
354
- def number_type? ( % { } ) , do: false
362
+ def number_type? ( _ ) , do: false
355
363
356
364
defp bitmap_union ( v1 , v2 ) , do: v1 ||| v2
357
365
defp bitmap_intersection ( v1 , v2 ) , do: v1 &&& v2
@@ -400,16 +408,19 @@ defmodule Module.Types.Descr do
400
408
"""
401
409
def atom_type? ( % { dynamic: % { atom: _ } } ) , do: true
402
410
def atom_type? ( % { atom: _ } ) , do: true
403
- def atom_type? ( % { } ) , do: false
411
+ def atom_type? ( _ ) , do: false
404
412
405
413
@ doc """
406
414
Optimized version of `not empty?(intersection(atom([atom]), type))`.
407
415
"""
416
+ def atom_type? ( :term , _atom ) , do: false
417
+
408
418
def atom_type? ( % { } = descr , atom ) do
409
419
{ static_or_dynamic , static } = Map . pop ( descr , :dynamic , descr )
410
420
411
421
atom_only? ( static ) and
412
422
case static_or_dynamic do
423
+ :term -> true
413
424
% { atom: { :union , set } } -> :sets . is_element ( atom , set )
414
425
% { atom: { :negation , set } } -> not :sets . is_element ( atom , set )
415
426
% { } -> false
@@ -423,11 +434,14 @@ defmodule Module.Types.Descr do
423
434
`:error` otherwise. Notice `known_set` may be empty in infinite
424
435
cases, due to negations.
425
436
"""
437
+ def atom_fetch ( :term ) , do: :error
438
+
426
439
def atom_fetch ( % { } = descr ) do
427
440
{ static_or_dynamic , static } = Map . pop ( descr , :dynamic , descr )
428
441
429
442
if atom_only? ( static ) do
430
443
case static_or_dynamic do
444
+ :term -> { :infinite , [ ] }
431
445
% { atom: { :union , set } } -> { :finite , :sets . to_list ( set ) }
432
446
% { atom: { :negation , _ } } -> { :infinite , [ ] }
433
447
% { } -> :error
@@ -554,19 +568,22 @@ defmodule Module.Types.Descr do
554
568
# `:dynamic` field is not_set, or it contains a type equal to the static component
555
569
# (that is, there are no extra dynamic values).
556
570
571
+ # TODO!!!
557
572
defp dynamic_intersection ( left , right ) do
558
573
inter = symmetrical_intersection ( left , right , & intersection / 3 )
559
574
if empty? ( inter ) , do: 0 , else: inter
560
575
end
561
576
577
+ # TODO!!!
562
578
defp dynamic_difference ( left , right ) do
563
579
diff = difference_static ( left , right )
564
580
if empty? ( diff ) , do: 0 , else: diff
565
581
end
566
582
583
+ # TODO!!!
567
584
defp dynamic_union ( left , right ) , do: symmetrical_merge ( left , right , & union / 3 )
568
585
569
- defp dynamic_to_quoted ( % { } = descr ) do
586
+ defp dynamic_to_quoted ( descr ) do
570
587
cond do
571
588
term_type? ( descr ) -> [ { :dynamic , [ ] , [ ] } ]
572
589
single = indivisible_bitmap ( descr ) -> [ single ]
@@ -642,6 +659,8 @@ defmodule Module.Types.Descr do
642
659
In static mode, we likely want to raise if `map.field`
643
660
(or pattern matching?) is called on an optional key.
644
661
"""
662
+ def map_fetch ( :term , _key ) , do: :badmap
663
+
645
664
def map_fetch ( % { } = descr , key ) do
646
665
case :maps . take ( :dynamic , descr ) do
647
666
:error ->
@@ -657,7 +676,7 @@ defmodule Module.Types.Descr do
657
676
:badmap
658
677
end
659
678
660
- { % { map: { :open , fields , [ ] } } , static } when fields == % { } and static == @ none ->
679
+ { :term , _static } ->
661
680
{ true , dynamic ( ) }
662
681
663
682
{ dynamic , static } ->
0 commit comments