@@ -1805,13 +1805,12 @@ defmodule Module.Types.Descr do
18051805 #
18061806 # A negation only matters when the negated list type is a supertype of the
18071807 # corresponding positive list type; in that case we subtract the negated
1808- # variant from the positive one.
1808+ # variant from the positive one. This is done in list_bdd_to_pos_dnf/1.
18091809 { list_type , last_type } =
18101810 list_bdd_to_pos_dnf ( bdd )
18111811 |> Enum . reduce ( { list_type , last_type_no_list } , fn
1812- { head , tail } , { acc_head , acc_tail } ->
1813- tail = list_tail_unfold ( tail )
1814- { union ( head , acc_head ) , union ( tail , acc_tail ) }
1812+ { list , last , _negs } , { acc_list , acc_last } ->
1813+ { union ( list , acc_list ) , union ( last , acc_last ) }
18151814 end )
18161815
18171816 list_new ( list_type , last_type )
@@ -1839,40 +1838,50 @@ defmodule Module.Types.Descr do
18391838 end
18401839 end
18411840
1842- # Takes all the lines from the root to the leaves finishing with a 1,
1843- # and compile into tuples of positive and negative nodes. Positive nodes are
1844- # those followed by a left path, negative nodes are those followed by a right path.
1845- defp list_bdd_to_dnf ( bdd ) do
1846- bdd_to_dnf ( bdd )
1847- |> Enum . reduce ( [ ] , fn { pos_list , neg_list } , acc ->
1848- case non_empty_list_literals_intersection ( pos_list ) do
1849- :empty ->
1850- acc
1851-
1852- { list , last } ->
1853- if list_line_empty? ( list , last , neg_list ) ,
1854- do: acc ,
1855- else: [ { { list , last } , neg_list } | acc ]
1856- end
1857- end )
1858- end
1859-
18601841 # Takes all the lines from the root to the leaves finishing with a 1,
18611842 # and compile into tuples of positive and negative nodes. Keep only the non-empty positives,
18621843 # and include the impact of negations on the last type.
18631844 # To see if a negation changes the last type or the list type, we just need to check
18641845 # if the negative list type is a supertype of the positive list type. In that case,
18651846 # we can remove the negative last type from the positive one.
1847+
18661848 # (If this subtracted type was empty, the whole type would be empty)
18671849 defp list_bdd_to_pos_dnf ( bdd ) do
18681850 bdd_to_dnf ( bdd )
1869- |> Enum . reduce ( [ ] , fn { pos_list , neg_list } , acc ->
1851+ |> Enum . reduce ( [ ] , fn { pos_list , negs } , acc ->
18701852 case non_empty_list_literals_intersection ( pos_list ) do
18711853 :empty ->
18721854 acc
18731855
18741856 { list , last } ->
1875- if list_line_empty? ( list , last , neg_list ) , do: acc , else: [ { list , last } | acc ]
1857+ if empty? ( list ) or empty? ( last ) do
1858+ acc
1859+ else
1860+ Enum . reduce_while ( negs , { list_tail_unfold ( last ) , [ ] } , fn { neg_type , neg_last } ,
1861+ { acc_last , acc_negs } ->
1862+ if subtype? ( list , neg_type ) do
1863+ difference = difference ( acc_last , neg_last )
1864+ if empty? ( difference ) , do: { :halt , nil } , else: { :cont , { difference , acc_negs } }
1865+ else
1866+ { :cont , { acc_last , [ { neg_type , neg_last } | acc_negs ] } }
1867+ end
1868+ end )
1869+ |> case do
1870+ { :halt , nil } -> acc
1871+ { last , negs } -> [ { list , last , Enum . reverse ( negs ) } | acc ]
1872+ end
1873+ end
1874+ end
1875+ end )
1876+ end
1877+
1878+ # Compute the head of a list (faster because we discard computations on the last type).
1879+ defp list_bdd_to_hd ( bdd ) do
1880+ bdd_to_dnf ( bdd )
1881+ |> Enum . reduce ( none ( ) , fn { pos_list , neg_list } , acc ->
1882+ case non_empty_list_literals_intersection ( pos_list ) do
1883+ :empty -> acc
1884+ { list , last } -> if list_line_empty? ( list , last , neg_list ) , do: acc , else: union ( acc , list )
18761885 end
18771886 end )
18781887 end
@@ -1895,6 +1904,47 @@ defmodule Module.Types.Descr do
18951904 defp list_top? ( bdd_leaf ( :term , :term ) ) , do: true
18961905 defp list_top? ( _ ) , do: false
18971906
1907+ @ doc """
1908+ Checks if a list type is a proper list (terminated by empty list).
1909+ """
1910+ def list_proper? ( :term ) , do: false
1911+
1912+ def list_proper? ( % { } = descr ) do
1913+ case :maps . take ( :dynamic , descr ) do
1914+ :error ->
1915+ list_proper_static? ( descr )
1916+
1917+ { dynamic , static } ->
1918+ list_proper_static? ( static ) and ( list_proper_static? ( dynamic ) or empty? ( dynamic ) )
1919+ end
1920+ end
1921+
1922+ defp list_proper_static? ( :term ) , do: false
1923+
1924+ defp list_proper_static? ( % { } = descr ) do
1925+ # A list is proper if it's either the empty list alone, or all non-empty
1926+ # list types have tails that are subtypes of empty list
1927+ case descr do
1928+ % { bitmap: bitmap , list: bdd } ->
1929+ ( bitmap &&& @ bit_empty_list ) != 0 and empty? ( Map . drop ( descr , [ :list , :bitmap ] ) ) and
1930+ list_bdd_proper? ( bdd )
1931+
1932+ % { bitmap: bitmap } ->
1933+ ( bitmap &&& @ bit_empty_list ) != 0 and empty? ( Map . delete ( descr , :bitmap ) )
1934+
1935+ % { list: bdd } ->
1936+ empty? ( Map . delete ( descr , :list ) ) and list_bdd_proper? ( bdd )
1937+
1938+ % { } ->
1939+ false
1940+ end
1941+ end
1942+
1943+ defp list_bdd_proper? ( bdd ) do
1944+ list_bdd_to_pos_dnf ( bdd )
1945+ |> Enum . all? ( fn { _list , last , _negs } -> subtype? ( last , @ empty_list ) end )
1946+ end
1947+
18981948 defp list_intersection ( bdd_leaf ( list1 , last1 ) , bdd_leaf ( list2 , last2 ) ) do
18991949 try do
19001950 list = non_empty_intersection! ( list1 , list2 )
@@ -1924,10 +1974,16 @@ defmodule Module.Types.Descr do
19241974 # The result may be larger than the initial bdd1, which is maintained in the accumulator.
19251975 defp list_difference ( bdd_leaf ( list1 , last1 ) = bdd1 , bdd_leaf ( list2 , last2 ) = bdd2 ) do
19261976 cond do
1927- disjoint? ( list1 , list2 ) or disjoint? ( last1 , last2 ) -> bdd_leaf ( list1 , last1 )
1928- subtype? ( list1 , list2 ) and subtype? ( last1 , last2 ) -> :bdd_bot
1929- equal? ( list1 , list2 ) -> bdd_leaf ( list1 , difference ( last1 , last2 ) )
1930- true -> bdd_difference ( bdd1 , bdd2 )
1977+ disjoint? ( list1 , list2 ) or disjoint? ( last1 , last2 ) ->
1978+ bdd_leaf ( list1 , last1 )
1979+
1980+ subtype? ( list1 , list2 ) ->
1981+ if subtype? ( last1 , last2 ) ,
1982+ do: :bdd_bot ,
1983+ else: bdd_leaf ( list1 , difference ( last1 , last2 ) )
1984+
1985+ true ->
1986+ bdd_difference ( bdd1 , bdd2 )
19311987 end
19321988 end
19331989
@@ -1999,22 +2055,20 @@ defmodule Module.Types.Descr do
19992055
20002056 defp list_hd_static ( :term ) , do: :term
20012057
2002- defp list_hd_static ( % { list: bdd } ) do
2003- list_bdd_to_pos_dnf ( bdd )
2004- |> Enum . reduce ( none ( ) , fn { list , _ } , acc ->
2005- union ( list , acc )
2006- end )
2007- end
2058+ defp list_hd_static ( % { list: bdd } ) , do: list_bdd_to_hd ( bdd )
20082059
20092060 defp list_hd_static ( % { } ) , do: none ( )
20102061
20112062 @ doc """
2012- Returns the tail of a list.
2063+ Computes the type of the tail of a non-empty list type .
20132064
2014- Errors on a possibly empty list.
2015- On a non empty list of integers, it returns a (possibly empty) list of integers.
2016- On a non empty list of integers, with an atom tail element, it returns either an atom,
2017- or a (possibly empty) list of integers with an atom tail element.
2065+ Returns `{dynamic?, type}` on success, where `dynamic?` indicates whether
2066+ the result contains a dynamic component. Returns `:badnonemptylist` if the
2067+ input type is not guaranteed to be a non-empty list.
2068+
2069+ For a `non_empty_list(t)`, the tail type is `list(t)` (possibly empty).
2070+ For an improper list `non_empty_list(t, s)`, the tail type is
2071+ `list(t, s) or s` (either the rest of the list or the terminator).
20182072 """
20192073 def list_tl ( :term ) , do: :badnonemptylist
20202074
@@ -2052,7 +2106,9 @@ defmodule Module.Types.Descr do
20522106 % { list: bdd }
20532107 end
20542108
2055- list_bdd_to_pos_dnf ( bdd ) |> Enum . reduce ( initial , fn { _ , tail } , acc -> union ( tail , acc ) end )
2109+ list_bdd_to_pos_dnf ( bdd )
2110+ |> Enum . reduce ( none ( ) , fn { _list , last , _negs } , acc -> union ( acc , last ) end )
2111+ |> union ( initial )
20562112 end
20572113
20582114 defp list_tl_static ( % { } ) , do: none ( )
@@ -2076,6 +2132,10 @@ defmodule Module.Types.Descr do
20762132 name = if empty? , do: :list , else: :non_empty_list
20772133 { name , [ to_quoted ( list_type , opts ) ] , empty? }
20782134
2135+ subtype? ( @ not_non_empty_list , last_type ) ->
2136+ args = [ to_quoted ( list_type , opts ) , { :term , [ ] , [ ] } ]
2137+ { :non_empty_list , args , list_rendered? }
2138+
20792139 true ->
20802140 args = [ to_quoted ( list_type , opts ) , to_quoted ( last_type , opts ) ]
20812141 { :non_empty_list , args , list_rendered? }
@@ -2115,27 +2175,19 @@ defmodule Module.Types.Descr do
21152175 end
21162176
21172177 # Eliminate empty lists from the union, and redundant types (that are subtypes of others,
2118- # or that can be merged with others).
2178+ # or that can be merged with others). List_bdd_to_pos_dnf already takes into account the
2179+ # impact of negations on the last type.
21192180 defp list_normalize ( bdd ) do
2120- list_bdd_to_dnf ( bdd )
2121- |> Enum . reduce ( [ ] , fn { { list , last } , negs } , acc ->
2122- # First, try to eliminate the negations from the existing type .
2123- { list , last , negs } =
2181+ list_bdd_to_pos_dnf ( bdd )
2182+ |> Enum . reduce ( [ ] , fn { list , last , negs } , acc ->
2183+ # Prune negations from those with empty intersections .
2184+ negs =
21242185 Enum . uniq ( negs )
2125- |> Enum . reduce ( { list , last , [ ] } , fn { nlist , nlast } , { acc_list , acc_last , acc_negs } ->
2126- last = list_tail_unfold ( last )
2127- new_list = intersection ( list , nlist )
2128- new_last = intersection ( last , nlast )
2129-
2130- cond do
2131- # No intersection between the list and the negative
2132- empty? ( new_list ) or empty? ( new_last ) -> { acc_list , acc_last , acc_negs }
2133- subtype? ( list , nlist ) -> { acc_list , difference ( acc_last , nlast ) , acc_negs }
2134- true -> { acc_list , acc_last , [ { nlist , nlast } | acc_negs ] }
2135- end
2186+ |> Enum . filter ( fn { nlist , nlast } ->
2187+ not empty? ( intersection ( list , nlist ) ) and not empty? ( intersection ( last , nlast ) )
21362188 end )
21372189
2138- add_to_list_normalize ( acc , list , last , negs |> Enum . reverse ( ) )
2190+ add_to_list_normalize ( acc , list , last , negs )
21392191 end )
21402192 end
21412193
0 commit comments