File 2785-Support-bitstrings-as-literals-in-erl_syntax.patch of Package erlang

From 94c9898e8dfb1b71eac318375b5c1bae5021733d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?P=C3=A9ter=20G=C3=B6m=C3=B6ri?= <gomoripeti@gmail.com>
Date: Sun, 17 Jun 2018 12:32:40 +0200
Subject: [PATCH] Support bitstrings as literals in erl_syntax

Add support of non-whole-byte binaries to `abtract/1`, `concrete/1` and
`is_literal/1`. (They are literals in the beam file)
---
 lib/syntax_tools/src/erl_syntax.erl          | 41 ++++++++++++++++++++--------
 lib/syntax_tools/test/syntax_tools_SUITE.erl |  1 +
 2 files changed, 31 insertions(+), 11 deletions(-)

diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl
index 029f1e88ac..758aff32fd 100644
--- a/lib/syntax_tools/src/erl_syntax.erl
+++ b/lib/syntax_tools/src/erl_syntax.erl
@@ -7223,7 +7223,7 @@ macro_arguments(Node) ->
 %% @doc Returns the syntax tree corresponding to an Erlang term.
 %% `Term' must be a literal term, i.e., one that can be
 %% represented as a source code literal. Thus, it may not contain a
-%% process identifier, port, reference, binary or function value as a
+%% process identifier, port, reference or function value as a
 %% subterm. The function recognises printable strings, in order to get a
 %% compact and readable representation. Evaluation fails with reason
 %% `badarg' if `Term' is not a literal term.
@@ -7257,6 +7257,13 @@ abstract(T) when is_map(T) ->
 	      || {Key,Value} <- maps:to_list(T)]);
 abstract(T) when is_binary(T) ->
     binary([binary_field(integer(B)) || B <- binary_to_list(T)]);
+abstract(T) when is_bitstring(T) ->
+    S = bit_size(T),
+    ByteS = S div 8,
+    BitS = S rem 8,
+    <<Bin:ByteS/binary, I:BitS>> = T,
+    binary([binary_field(integer(B)) || B <- binary_to_list(Bin)]
+           ++ [binary_field(integer(I), integer(BitS), [])]);
 abstract(T) ->
     erlang:error({badarg, T}).
 
@@ -7332,15 +7339,20 @@ concrete(Node) ->
 		Node0 -> maps:merge(concrete(Node0),M0)
 	    end;
 	binary ->
-	    Fs = [revert_binary_field(
-		    binary_field(binary_field_body(F),
-				 case binary_field_size(F) of
-				     none -> none;
-				     S ->
-					 revert(S)
-				 end,
-				 binary_field_types(F)))
-		  || F <- binary_fields(Node)],
+            Fs = [begin
+                      B = binary_field_body(F),
+                      {Body, Size} =
+                          case type(B) of
+                              size_qualifier ->
+                                  {size_qualifier_body(B),
+                                   size_qualifier_argument(B)};
+                              _ ->
+                                  {B, none}
+                          end,
+                      revert_binary_field(
+                        binary_field(Body, Size, binary_field_types(F)))
+                  end
+                  || F <- binary_fields(Node)],
 	    {value, B, _} =
 		eval_bits:expr_grp(Fs, [],
 				   fun(F, _) ->
@@ -7413,7 +7425,14 @@ is_literal(T) ->
 
 is_literal_binary_field(F) ->
     case binary_field_types(F) of
-	[] -> is_literal(binary_field_body(F));
+	[] -> B = binary_field_body(F),
+              case type(B) of
+                  size_qualifier ->
+                      is_literal(size_qualifier_body(B)) andalso
+                          is_literal(size_qualifier_argument(B));
+                  _ ->
+                      is_literal(B)
+              end;
 	_  -> false
     end.
 
diff --git a/lib/syntax_tools/test/syntax_tools_SUITE.erl b/lib/syntax_tools/test/syntax_tools_SUITE.erl
index c8e6448d37..4cddf8f0c3 100644
--- a/lib/syntax_tools/test/syntax_tools_SUITE.erl
+++ b/lib/syntax_tools/test/syntax_tools_SUITE.erl
@@ -157,6 +157,7 @@ t_abstract_type(Config) when is_list(Config) ->
 		     {[$a,$b,$c],string},
 		     {"hello world",string},
 		     {<<1,2,3>>,binary},
+                     {<<1,2,3:4>>,binary},
 		     {#{a=>1,"b"=>2},map_expr},
 		     {#{#{i=>1}=>1,"b"=>#{v=>2}},map_expr},
 		     {{a,b,c},tuple}]),
-- 
2.16.4

openSUSE Build Service is sponsored by