@@ -1795,13 +1795,12 @@ defmodule Module.Types.Descr do
17951795 #
17961796 # A negation only matters when the negated list type is a supertype of the
17971797 # corresponding positive list type; in that case we subtract the negated
1798- # variant from the positive one.
1798+ # variant from the positive one. This is done in list_bdd_to_pos_dnf/1.
17991799 { list_type , last_type } =
18001800 list_bdd_to_pos_dnf ( bdd )
18011801 |> Enum . reduce ( { list_type , last_type_no_list } , fn
1802- { head , tail } , { acc_head , acc_tail } ->
1803- tail = list_tail_unfold ( tail )
1804- { union ( head , acc_head ) , union ( tail , acc_tail ) }
1802+ { list , last , _negs } , { acc_list , acc_last } ->
1803+ { union ( list , acc_list ) , union ( last , acc_last ) }
18051804 end )
18061805
18071806 list_new ( list_type , last_type )
@@ -1829,40 +1828,34 @@ defmodule Module.Types.Descr do
18291828 end
18301829 end
18311830
1832- # Takes all the lines from the root to the leaves finishing with a 1,
1833- # and compile into tuples of positive and negative nodes. Positive nodes are
1834- # those followed by a left path, negative nodes are those followed by a right path.
1835- defp list_bdd_to_dnf ( bdd ) do
1836- bdd_to_dnf ( bdd )
1837- |> Enum . reduce ( [ ] , fn { pos_list , neg_list } , acc ->
1838- case non_empty_list_literals_intersection ( pos_list ) do
1839- :empty ->
1840- acc
1841-
1842- { list , last } ->
1843- if list_line_empty? ( list , last , neg_list ) ,
1844- do: acc ,
1845- else: [ { { list , last } , neg_list } | acc ]
1846- end
1847- end )
1848- end
1849-
18501831 # Takes all the lines from the root to the leaves finishing with a 1,
18511832 # and compile into tuples of positive and negative nodes. Keep only the non-empty positives,
18521833 # and include the impact of negations on the last type.
18531834 # To see if a negation changes the last type or the list type, we just need to check
18541835 # if the negative list type is a supertype of the positive list type. In that case,
18551836 # we can remove the negative last type from the positive one.
1837+
18561838 # (If this subtracted type was empty, the whole type would be empty)
18571839 defp list_bdd_to_pos_dnf ( bdd ) do
18581840 bdd_to_dnf ( bdd )
1859- |> Enum . reduce ( [ ] , fn { pos_list , neg_list } , acc ->
1841+ |> Enum . reduce ( [ ] , fn { pos_list , negs } , acc ->
18601842 case non_empty_list_literals_intersection ( pos_list ) do
18611843 :empty ->
18621844 acc
18631845
18641846 { list , last } ->
1865- if list_line_empty? ( list , last , neg_list ) , do: acc , else: [ { list , last } | acc ]
1847+ Enum . reduce_while ( negs , { last , [ ] } , fn { neg_type , neg_last } , { acc_last , acc_negs } ->
1848+ if subtype? ( list , neg_type ) do
1849+ difference = difference ( acc_last , neg_last )
1850+ if empty? ( difference ) , do: { :halt , nil } , else: { :cont , { difference , acc_negs } }
1851+ else
1852+ { :cont , { acc_last , [ { neg_type , neg_last } | acc_negs ] } }
1853+ end
1854+ end )
1855+ |> case do
1856+ nil -> acc
1857+ { last , negs } -> [ { list , last , Enum . reverse ( negs ) } | acc ]
1858+ end
18661859 end
18671860 end )
18681861 end
@@ -1885,6 +1878,38 @@ defmodule Module.Types.Descr do
18851878 defp list_top? ( bdd_leaf ( :term , :term ) ) , do: true
18861879 defp list_top? ( _ ) , do: false
18871880
1881+ @ doc """
1882+ Checks if a list type is a proper list (terminated by empty list).
1883+ """
1884+ def list_proper? ( :term ) , do: false
1885+ def list_proper? ( % { } = descr ) , do: Map . get ( descr , :dynamic , descr ) |> list_proper_static? ( )
1886+
1887+ defp list_proper_static? ( :term ) , do: false
1888+
1889+ defp list_proper_static? ( % { } = descr ) do
1890+ # A list is proper if it's either the empty list alone, or all non-empty
1891+ # list types have tails that are subtypes of empty list
1892+ case descr do
1893+ % { bitmap: bitmap , list: bdd } ->
1894+ ( bitmap &&& @ bit_empty_list ) != 0 and empty? ( Map . drop ( descr , [ :list , :bitmap ] ) ) and
1895+ list_bdd_proper? ( bdd )
1896+
1897+ % { bitmap: bitmap } ->
1898+ ( bitmap &&& @ bit_empty_list ) != 0 and empty? ( Map . delete ( descr , :bitmap ) )
1899+
1900+ % { list: bdd } ->
1901+ empty? ( Map . delete ( descr , :list ) ) and list_bdd_proper? ( bdd )
1902+
1903+ % { } ->
1904+ empty? ( descr )
1905+ end
1906+ end
1907+
1908+ defp list_bdd_proper? ( bdd ) do
1909+ list_bdd_to_pos_dnf ( bdd )
1910+ |> Enum . all? ( fn { _list , last , _negs } -> subtype? ( last , @ empty_list ) end )
1911+ end
1912+
18881913 defp list_intersection ( bdd_leaf ( list1 , last1 ) , bdd_leaf ( list2 , last2 ) ) do
18891914 try do
18901915 list = non_empty_intersection! ( list1 , list2 )
@@ -1914,10 +1939,16 @@ defmodule Module.Types.Descr do
19141939 # The result may be larger than the initial bdd1, which is maintained in the accumulator.
19151940 defp list_difference ( bdd_leaf ( list1 , last1 ) = bdd1 , bdd_leaf ( list2 , last2 ) = bdd2 ) do
19161941 cond do
1917- disjoint? ( list1 , list2 ) or disjoint? ( last1 , last2 ) -> bdd_leaf ( list1 , last1 )
1918- subtype? ( list1 , list2 ) and subtype? ( last1 , last2 ) -> :bdd_bot
1919- equal? ( list1 , list2 ) -> bdd_leaf ( list1 , difference ( last1 , last2 ) )
1920- true -> bdd_difference ( bdd1 , bdd2 )
1942+ disjoint? ( list1 , list2 ) or disjoint? ( last1 , last2 ) ->
1943+ bdd_leaf ( list1 , last1 )
1944+
1945+ subtype? ( list1 , list2 ) ->
1946+ if subtype? ( last1 , last2 ) ,
1947+ do: :bdd_bot ,
1948+ else: bdd_leaf ( list1 , difference ( last1 , last2 ) )
1949+
1950+ true ->
1951+ bdd_difference ( bdd1 , bdd2 )
19211952 end
19221953 end
19231954
@@ -1991,20 +2022,17 @@ defmodule Module.Types.Descr do
19912022
19922023 defp list_hd_static ( % { list: bdd } ) do
19932024 list_bdd_to_pos_dnf ( bdd )
1994- |> Enum . reduce ( none ( ) , fn { list , _ } , acc ->
1995- union ( list , acc )
1996- end )
2025+ |> Enum . reduce ( none ( ) , fn { list , _last , _negs } , acc -> union ( acc , list ) end )
19972026 end
19982027
19992028 defp list_hd_static ( % { } ) , do: none ( )
20002029
20012030 @ doc """
2002- Returns the tail of a list.
2031+ Returns the tail of a list.
20032032
2004- Errors on a possibly empty list.
2005- On a non empty list of integers, it returns a (possibly empty) list of integers.
2006- On a non empty list of integers, with an atom tail element, it returns either an atom,
2007- or a (possibly empty) list of integers with an atom tail element.
2033+ For a `non_empty_list(t)`, the tail type is `list(t)`.
2034+ For an improper list `non_empty_list(t, s)`, the tail type is
2035+ `list(t, s) or s` (either the rest of the list or the terminator)
20082036 """
20092037 def list_tl ( :term ) , do: :badnonemptylist
20102038
@@ -2042,7 +2070,8 @@ defmodule Module.Types.Descr do
20422070 % { list: bdd }
20432071 end
20442072
2045- list_bdd_to_pos_dnf ( bdd ) |> Enum . reduce ( initial , fn { _ , tail } , acc -> union ( tail , acc ) end )
2073+ list_bdd_to_pos_dnf ( bdd )
2074+ |> Enum . reduce ( initial , fn { _list , last , _negs } , acc -> union ( acc , last ) end )
20462075 end
20472076
20482077 defp list_tl_static ( % { } ) , do: none ( )
@@ -2054,12 +2083,19 @@ defmodule Module.Types.Descr do
20542083 dnf
20552084 |> Enum . reduce ( { [ ] , false } , fn { list_type , last_type , negs } , { acc , list_rendered? } ->
20562085 { name , arguments , list_rendered? } =
2057- if subtype? ( last_type , @ empty_list ) do
2058- name = if empty? , do: :list , else: :non_empty_list
2059- { name , [ to_quoted ( list_type , opts ) ] , empty? }
2060- else
2061- args = [ to_quoted ( list_type , opts ) , to_quoted ( last_type , opts ) ]
2062- { :non_empty_list , args , list_rendered? }
2086+ cond do
2087+ subtype? ( last_type , @ empty_list ) ->
2088+ name = if empty? , do: :list , else: :non_empty_list
2089+ { name , [ to_quoted ( list_type , opts ) ] , empty? }
2090+
2091+ # Sugar: print the last type as term() if it only misses non empty lists.
2092+ subtype? ( @ not_non_empty_list , last_type ) ->
2093+ args = [ to_quoted ( list_type , opts ) , { :term , [ ] , [ ] } ]
2094+ { :non_empty_list , args , list_rendered? }
2095+
2096+ true ->
2097+ args = [ to_quoted ( list_type , opts ) , to_quoted ( last_type , opts ) ]
2098+ { :non_empty_list , args , list_rendered? }
20632099 end
20642100
20652101 acc =
@@ -2096,27 +2132,19 @@ defmodule Module.Types.Descr do
20962132 end
20972133
20982134 # Eliminate empty lists from the union, and redundant types (that are subtypes of others,
2099- # or that can be merged with others).
2135+ # or that can be merged with others). List_bdd_to_pos_dnf already takes into account the
2136+ # impact of negations on the last type.
21002137 defp list_normalize ( bdd ) do
2101- list_bdd_to_dnf ( bdd )
2102- |> Enum . reduce ( [ ] , fn { { list , last } , negs } , acc ->
2103- # First, try to eliminate the negations from the existing type .
2104- { list , last , negs } =
2138+ list_bdd_to_pos_dnf ( bdd )
2139+ |> Enum . reduce ( [ ] , fn { list , last , negs } , acc ->
2140+ # Prune negations from those with empty intersections .
2141+ negs =
21052142 Enum . uniq ( negs )
2106- |> Enum . reduce ( { list , last , [ ] } , fn { nlist , nlast } , { acc_list , acc_last , acc_negs } ->
2107- last = list_tail_unfold ( last )
2108- new_list = intersection ( list , nlist )
2109- new_last = intersection ( last , nlast )
2110-
2111- cond do
2112- # No intersection between the list and the negative
2113- empty? ( new_list ) or empty? ( new_last ) -> { acc_list , acc_last , acc_negs }
2114- subtype? ( list , nlist ) -> { acc_list , difference ( acc_last , nlast ) , acc_negs }
2115- true -> { acc_list , acc_last , [ { nlist , nlast } | acc_negs ] }
2116- end
2143+ |> Enum . filter ( fn { nlist , nlast } ->
2144+ not empty? ( intersection ( list , nlist ) ) and not empty? ( intersection ( last , nlast ) )
21172145 end )
21182146
2119- add_to_list_normalize ( acc , list , last , negs |> Enum . reverse ( ) )
2147+ add_to_list_normalize ( acc , list , last , negs )
21202148 end )
21212149 end
21222150
0 commit comments