File 0335-stdlib-Correct-the-linter-s-check-of-map-guard-expre.patch of Package erlang

From 52c10eb847dfbe04b9e51e5631d254aed06bddb7 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 24 Apr 2018 15:52:34 +0200
Subject: [PATCH 1/2] stdlib: Correct the linter's check of map guard
 expressions

The check is used by evaluating modules such as erl_eval.

An example: "if map_size(#{}) =:= 0 -> ok end.".
---
 lib/stdlib/src/erl_lint.erl        | 14 +++++++++-
 lib/stdlib/test/erl_eval_SUITE.erl | 56 ++++++++++++++++++++++++++++++++++++--
 2 files changed, 66 insertions(+), 4 deletions(-)

diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 79dc6ce180..e9ac2fcdff 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2095,6 +2095,10 @@ is_gexpr({cons,_L,H,T}, Info) -> is_gexpr_list([H,T], Info);
 is_gexpr({tuple,_L,Es}, RDs) -> is_gexpr_list(Es, RDs);
 %%is_gexpr({struct,_L,_Tag,Es}, RDs) ->
 %%    is_gexpr_list(Es, RDs);
+is_gexpr({map,_L,Es}, Info) ->
+    is_map_fields(Es, Info);
+is_gexpr({map,_L,Src,Es}, Info) ->
+    is_gexpr(Src, Info) andalso is_map_fields(Es, Info);
 is_gexpr({record_index,_L,_Name,Field}, RDs) ->
     is_gexpr(Field, RDs);
 is_gexpr({record_field,_L,Rec,_Name,Field}, RDs) ->
@@ -2137,6 +2141,14 @@ is_gexpr_op(Op, A) ->
 
 is_gexpr_list(Es, RDs) -> all(fun (E) -> is_gexpr(E, RDs) end, Es).
 
+is_map_fields([{Tag,_,K,V}|Fs], Info) when Tag =:= map_field_assoc;
+                                           Tag =:= map_field_exact ->
+    is_gexpr(K, Info) andalso
+    is_gexpr(V, Info) andalso
+    is_map_fields(Fs, Info);
+is_map_fields([], _Info) -> true;
+is_map_fields(_T, _Info) -> false.
+
 is_gexpr_fields(Fs, L, Name, RDs) ->
     IFs = case dict:find(Name, RDs) of
               {ok,{_Line,Fields}} -> Fs ++ init_fields(Fs, L, Fields);
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index 8eb85cab8e..f4019d477b 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %% 
-%% Copyright Ericsson AB 1998-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2018. 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.
@@ -47,7 +47,8 @@
 	 eval_expr_5/1,
 	 zero_width/1,
          eep37/1,
-         eep43/1]).
+         eep43/1,
+         otp_15035/1]).
 
 %%
 %% Define to run outside of test server
@@ -87,7 +88,7 @@ all() ->
      otp_6539, otp_6543, otp_6787, otp_6977, otp_7550,
      otp_8133, otp_10622, otp_13228,
      funs, try_catch, eval_expr_5, zero_width,
-     eep37, eep43].
+     eep37, eep43, otp_15035].
 
 groups() -> 
     [].
@@ -1606,6 +1607,55 @@ eep43(Config) when is_list(Config) ->
     error_check("(#{})#{nonexisting:=value}.", {badkey,nonexisting}),
     ok.
 
+otp_15035(Config) when is_list(Config) ->
+    check(fun() ->
+                  fun() when #{} ->
+                          a;
+                     () when #{a => b} ->
+                          b;
+                     () when #{a => b} =:= #{a => b} ->
+                          c
+                  end()
+          end,
+          "fun() when #{} ->
+                   a;
+              () when #{a => b} ->
+                   b;
+              () when #{a => b} =:= #{a => b} ->
+                   c
+           end().",
+          c),
+    check(fun() ->
+                  F = fun(M) when M#{} ->
+                              a;
+                         (M) when M#{a => b} ->
+                              b;
+                         (M) when M#{a := b} ->
+                              c;
+                         (M) when M#{a := b} =:= M#{a := b} ->
+                              d;
+                         (M) when M#{a => b} =:= M#{a => b} ->
+                              e
+                      end,
+                  {F(#{}), F(#{a => b})}
+          end,
+          "fun() ->
+                  F = fun(M) when M#{} ->
+                              a;
+                         (M) when M#{a => b} ->
+                              b;
+                         (M) when M#{a := b} ->
+                              c;
+                         (M) when M#{a := b} =:= M#{a := b} ->
+                              d;
+                         (M) when M#{a => b} =:= M#{a => b} ->
+                              e
+                      end,
+                  {F(#{}), F(#{a => b})}
+          end().",
+          {e, d}),
+    ok.
+
 %% Check the string in different contexts: as is; in fun; from compiled code.
 check(F, String, Result) ->
     check1(F, String, Result),
-- 
2.16.3

openSUSE Build Service is sponsored by