File 2260-edoc-Fix-new-Maps-syntax.patch of Package erlang

From 5e7542d6f7cd1964839f6214915c7f9b7d7f8866 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Wed, 8 Jun 2016 12:14:21 +0200
Subject: [PATCH] edoc: Fix new Maps syntax

---
 lib/edoc/priv/edoc.dtd                  |  6 +++++-
 lib/edoc/src/edoc_layout.erl            | 24 +++++++++++++++++----
 lib/edoc/src/edoc_parser.yrl            | 17 ++++++++++++---
 lib/edoc/src/edoc_scanner.erl           |  2 ++
 lib/edoc/src/edoc_specs.erl             |  6 +++---
 lib/edoc/src/edoc_types.erl             |  4 ++--
 lib/edoc/src/edoc_types.hrl             |  2 +-
 lib/erl_docgen/src/docgen_otp_specs.erl | 38 +++++++++++++++++++++++----------
 8 files changed, 74 insertions(+), 25 deletions(-)

diff --git a/lib/edoc/priv/edoc.dtd b/lib/edoc/priv/edoc.dtd
index 4278a9e..89058f5 100644
--- a/lib/edoc/priv/edoc.dtd
+++ b/lib/edoc/priv/edoc.dtd
@@ -103,7 +103,7 @@
 <!ATTLIST type name CDATA #IMPLIED>
 
 <!ELEMENT union (typevar | atom | integer | float | nil | list | tuple |
-                 fun | record | abstype)+>
+                 fun | record | map | abstype)+>
 
 <!ELEMENT typevar EMPTY>
 <!ATTLIST typevar name CDATA #REQUIRED>
@@ -129,6 +129,10 @@
 
 <!ELEMENT field (atom, type)>
 
+<!ELEMENT map (map_field)*>
+
+<!ELEMENT map_field (type, type)>
+
 <!ELEMENT abstype (erlangName, type*)>
 <!ATTLIST abstype
   href CDATA #IMPLIED>
diff --git a/lib/edoc/src/edoc_layout.erl b/lib/edoc/src/edoc_layout.erl
index f723cd8..e86d090 100644
--- a/lib/edoc/src/edoc_layout.erl
+++ b/lib/edoc/src/edoc_layout.erl
@@ -898,8 +898,20 @@ t_map(Es) ->
     Fs = get_elem(map_field, Es),
     ["#{"] ++ seq(fun t_map_field/1, Fs, ["}"]).
 
-t_map_field(#xmlElement{content = [K,V]}) ->
-    t_utype_elem(K) ++ [" => "] ++ t_utype_elem(V).
+t_map_field(#xmlElement{content = [K,V]}=E) ->
+    KElem = t_utype_elem(K),
+    VElem = t_utype_elem(V),
+    AT = get_attrval(assoc_type, E),
+    IsAny = fun(["any","()"]) -> true; (_) -> false end,
+    case AT =:= "assoc" andalso IsAny(KElem) andalso IsAny(VElem) of
+        true -> "...";
+        false ->
+            AS = case AT of
+                     "assoc" -> " => ";
+                     "exact" -> " := "
+                 end,
+            KElem ++ [AS] ++ VElem
+    end.
 
 t_record(E, Es) ->
     Name = ["#"] ++ t_type(get_elem(atom, Es)),
@@ -1133,8 +1145,12 @@ ot_tuple(Es) ->
 ot_map(Es) ->
     {type,0,map,[ot_map_field(E) || E <- get_elem(map_field,Es)]}.
 
-ot_map_field(#xmlElement{content=[K,V]}) ->
-    {type,0,map_field_assoc,ot_utype_elem(K), ot_utype_elem(V)}.
+ot_map_field(#xmlElement{content=[K,V]}=E) ->
+    A = case get_attrval(assoc_type, E) of
+            "assoc" -> map_field_assoc;
+            "exact" -> map_field_exact
+        end,
+    {type,0,A,[ot_utype_elem(K), ot_utype_elem(V)]}.
 
 ot_fun(Es) ->
     Range = ot_utype(get_elem(type, Es)),
diff --git a/lib/edoc/src/edoc_parser.yrl b/lib/edoc/src/edoc_parser.yrl
index 835e7cc..983e2f8 100644
--- a/lib/edoc/src/edoc_parser.yrl
+++ b/lib/edoc/src/edoc_parser.yrl
@@ -36,8 +36,8 @@ Terminals
 atom float integer var an_var string start_spec start_typedef start_throws
 start_ref
 
-'(' ')' ',' '.' '=>' '->' '{' '}' '[' ']' '|' '+' ':' '::' '=' '/' '//' '*'
-'#' 'where' '<<' '>>' '..' '...'.
+'(' ')' ',' '.' '=>' ':=' '->' '{' '}' '[' ']' '|' '+' ':' '::' '=' '/' '//'
+'*' '#' 'where' '<<' '>>' '..' '...'.
 
 Rootsymbol start.
 
@@ -76,7 +76,15 @@ utype_map_fields -> '$empty' : [].
 utype_map_fields -> utype_map_field : ['$1'].
 utype_map_fields -> utype_map_fields ',' utype_map_field : ['$3' | '$1'].
 
-utype_map_field -> utype '=>' utype : #t_map_field{ k_type = '$1', v_type = '$3'}.
+utype_map_field -> utype '=>' utype : #t_map_field{assoc_type = assoc,
+                                                   k_type = '$1',
+                                                   v_type = '$3'}.
+utype_map_field -> utype ':=' utype : #t_map_field{assoc_type = exact,
+                                                   k_type = '$1',
+                                                   v_type = '$3'}.
+utype_map_field -> '...' : #t_map_field{assoc_type = assoc,
+                                        k_type = any(),
+                                        v_type = any()}.
 
 utype_tuple -> '{' utypes '}' : lists:reverse('$2').
 
@@ -346,6 +354,9 @@ all_vars([#t_var{} | As]) ->
 all_vars(As) ->
     As =:= [].
 
+any() ->
+    #t_type{name = #t_name{name = any}, args = []}.
+
 %% ---------------------------------------------------------------------
 
 %% @doc EDoc type specification parsing. Parses the content of
diff --git a/lib/edoc/src/edoc_scanner.erl b/lib/edoc/src/edoc_scanner.erl
index 36423d6..f1d5e1d 100644
--- a/lib/edoc/src/edoc_scanner.erl
+++ b/lib/edoc/src/edoc_scanner.erl
@@ -146,6 +146,8 @@ scan1([$>,$>|Cs], Toks, Pos) ->
     scan1(Cs, [{'>>',Pos}|Toks], Pos);
 scan1([$-,$>|Cs], Toks, Pos) ->
     scan1(Cs, [{'->',Pos}|Toks], Pos);
+scan1([$:,$=|Cs], Toks, Pos) ->
+    scan1(Cs, [{':=',Pos}|Toks], Pos);
 scan1([$:,$:|Cs], Toks, Pos) ->
     scan1(Cs, [{'::',Pos}|Toks], Pos);
 scan1([$/,$/|Cs], Toks, Pos) ->
diff --git a/lib/edoc/src/edoc_specs.erl b/lib/edoc/src/edoc_specs.erl
index faee8ad..c15dfd3 100644
--- a/lib/edoc/src/edoc_specs.erl
+++ b/lib/edoc/src/edoc_specs.erl
@@ -369,11 +369,11 @@ d2e({type,_,map,any}, _Prec) ->
 d2e({type,_,map,Es}, _Prec) ->
     #t_map{types = d2e(Es) };
 d2e({type,_,map_field_assoc,[K,V]}, Prec) ->
-    T = #t_map_field{k_type = d2e(K), v_type=d2e(V) },
+    T = #t_map_field{assoc_type = assoc, k_type = d2e(K), v_type=d2e(V) },
     {P,_R} = erl_parse:type_preop_prec('#'),
     maybe_paren(P, Prec, T);
-d2e({type,_,map_field_exact,K,V}, Prec) ->
-    T = #t_map_field{k_type = d2e(K), v_type=d2e(V) },
+d2e({type,_,map_field_exact,[K,V]}, Prec) ->
+    T = #t_map_field{assoc_type = exact, k_type = d2e(K), v_type=d2e(V) },
     {P,_R} = erl_parse:type_preop_prec('#'),
     maybe_paren(P, Prec, T);
 d2e({type,_,tuple,Ts0}, _Prec) ->
diff --git a/lib/edoc/src/edoc_types.erl b/lib/edoc/src/edoc_types.erl
index 65fba61..5bb68e7 100644
--- a/lib/edoc/src/edoc_types.erl
+++ b/lib/edoc/src/edoc_types.erl
@@ -89,8 +89,8 @@ to_xml(#t_fun{args = As, range = T}, Env) ->
 	     wrap_utype(T, Env)]};
 to_xml(#t_map{ types = Ts}, Env) ->
     {map, map(fun to_xml/2, Ts, Env)};
-to_xml(#t_map_field{ k_type=K, v_type=V}, Env) ->
-    {map_field, [wrap_utype(K,Env), wrap_utype(V, Env)]};
+to_xml(#t_map_field{assoc_type = AT, k_type=K, v_type=V}, Env) ->
+    {map_field, [{assoc_type, AT}], [wrap_utype(K,Env), wrap_utype(V, Env)]};
 to_xml(#t_tuple{types = Ts}, Env) ->
     {tuple, map(fun wrap_utype/2, Ts, Env)};
 to_xml(#t_list{type = T}, Env) ->
diff --git a/lib/edoc/src/edoc_types.hrl b/lib/edoc/src/edoc_types.hrl
index 7fec10d..3e5e914 100644
--- a/lib/edoc/src/edoc_types.hrl
+++ b/lib/edoc/src/edoc_types.hrl
@@ -157,5 +157,5 @@
 -record(t_paren, {a=[], type}).		% parentheses
 
 -record(t_map, {a=[], types=[]}).
--record(t_map_field, {a=[], k_type, v_type}).
+-record(t_map_field, {a=[], assoc_type, k_type, v_type}).
 
diff --git a/lib/erl_docgen/src/docgen_otp_specs.erl b/lib/erl_docgen/src/docgen_otp_specs.erl
index e154323..5bc3be7 100644
--- a/lib/erl_docgen/src/docgen_otp_specs.erl
+++ b/lib/erl_docgen/src/docgen_otp_specs.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2015. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -389,10 +389,10 @@ t_type([#xmlElement{name = list, content = Es}]) ->
     t_list(Es);
 t_type([#xmlElement{name = nonempty_list, content = Es}]) ->
     t_nonempty_list(Es);
-t_type([#xmlElement{name = tuple, content = Es}]) ->
-    t_tuple(Es);
 t_type([#xmlElement{name = map, content = Es}]) ->
     t_map(Es);
+t_type([#xmlElement{name = tuple, content = Es}]) ->
+    t_tuple(Es);
 t_type([#xmlElement{name = 'fun', content = Es}]) ->
     ["fun("] ++ t_fun(Es) ++ [")"];
 t_type([E = #xmlElement{name = record, content = Es}]) ->
@@ -435,16 +435,28 @@ t_nonempty_list(Es) ->
 t_tuple(Es) ->
     ["{"] ++ seq(fun t_utype_elem/1, Es, ["}"]).
 
+t_fun(Es) ->
+    ["("] ++ seq(fun t_utype_elem/1, get_content(argtypes, Es),
+		 [") -> "] ++ t_utype(get_elem(type, Es))).
+
 t_map(Es) ->
     Fs = get_elem(map_field, Es),
     ["#{"] ++ seq(fun t_map_field/1, Fs, ["}"]).
 
-t_map_field(#xmlElement{content = [K,V]}) ->
-    [t_utype_elem(K) ++ " => " ++ t_utype_elem(V)].
-
-t_fun(Es) ->
-    ["("] ++ seq(fun t_utype_elem/1, get_content(argtypes, Es),
-		 [") -> "] ++ t_utype(get_elem(type, Es))).
+t_map_field(#xmlElement{content = [K,V]}=E) ->
+    KElem = t_utype_elem(K),
+    VElem = t_utype_elem(V),
+    AT = get_attrval(assoc_type, E),
+    IsAny = fun(["any","()"]) -> true; (_) -> false end,
+    case AT =:= "assoc" andalso IsAny(KElem) andalso IsAny(VElem) of
+        true -> "...";
+        false ->
+            AS = case AT of
+                     "assoc" -> " => ";
+                     "exact" -> " := "
+                 end,
+            KElem ++ [AS] ++ VElem
+    end.
 
 t_record(E, Es) ->
     Name = ["#"] ++ t_type(get_elem(atom, Es)),
@@ -618,8 +630,12 @@ ot_tuple(Es) ->
 ot_map(Es) ->
     {type,0,map,[ot_map_field(E) || E <- get_elem(map_field,Es)]}.
 
-ot_map_field(#xmlElement{content=[K,V]}) ->
-    {type,0,map_field_assoc,[ot_utype_elem(K),ot_utype_elem(V)]}.
+ot_map_field(#xmlElement{content=[K,V]}=E) ->
+    A = case get_attrval(assoc_type, E) of
+            "assoc" -> map_field_assoc;
+            "exact" -> map_field_exact
+        end,
+    {type,0,A,[ot_utype_elem(K), ot_utype_elem(V)]}.
 
 ot_fun(Es) ->
     Range = ot_utype(get_elem(type, Es)),
-- 
2.1.4

openSUSE Build Service is sponsored by