File 2113-Add-comment-versions-of-assert-macros.patch of Package erlang

From d2be06f9c113812a1ffd56e0fdc25c28cdbf0abf Mon Sep 17 00:00:00 2001
From: Richard Carlsson <richardc@klarna.com>
Date: Sat, 29 Oct 2016 17:24:25 +0200
Subject: [PATCH] Add comment-versions of assert macros

For all assert macros in assert.hrl, add corresponding versions with an
additional last Comment argument, assumed to be chardata. If an
exception occurs, it will contain an entry {comment, Comment}, which a
reporting tool may pretty-print for better readability.
---
 lib/stdlib/doc/src/assert_hrl.xml |  33 +++++--
 lib/stdlib/include/assert.hrl     | 176 +++++++++++++++++++++++++++++++++++++-
 2 files changed, 201 insertions(+), 8 deletions(-)

diff --git a/lib/stdlib/doc/src/assert_hrl.xml b/lib/stdlib/doc/src/assert_hrl.xml
index e2dfc2a..a29f6d6 100644
--- a/lib/stdlib/doc/src/assert_hrl.xml
+++ b/lib/stdlib/doc/src/assert_hrl.xml
@@ -28,7 +28,7 @@
     <date></date>
     <rev></rev>
   </header>
-  <file>assert.hrl.xml</file>
+  <file>assert.hrl</file>
   <filesummary>Assert macros.</filesummary>
   <description>
     <p>The include file <c>assert.hrl</c> provides macros for inserting
@@ -49,25 +49,33 @@
       entries in the <c>Info</c> list are optional; do not rely programmatically
       on any of them being present.</p>
 
+    <p>Each assert macro has a corresponding version with an extra argument,
+      for adding comments to assertions. These can for example be printed as
+      part of error reports, to clarify the meaning of the check that
+      failed. For example, <c>?assertEqual(0, fib(0), "Fibonacci is defined
+      for zero")</c>. The comment text can be any character data (string,
+      UTF8-binary, or deep list of such data), and will be included in the
+      error term as <c>{comment, Text}</c>.</p>
+
     <p>If the macro <c>NOASSERT</c> is defined when <c>assert.hrl</c> is read
       by the compiler, the macros are defined as equivalent to the atom
-      <c>ok</c>. The test is not performed and there is no cost at runtime.</p>
+      <c>ok</c>. The test will not be performed and there is no cost at runtime.</p>
 
     <p>For example, using <c>erlc</c> to compile your modules, the following
-      disable all assertions:</p>
+      disables all assertions:</p>
 
     <code type="none">
 erlc -DNOASSERT=true *.erl</code>
 
-    <p>The value of <c>NOASSERT</c> does not matter, only the fact that it is
-      defined.</p>
+    <p>(The value of <c>NOASSERT</c> does not matter, only the fact that it is
+      defined.)</p>
 
     <p>A few other macros also have effect on the enabling or disabling of
       assertions:</p>
 
     <list type="bulleted">
-      <item><p>If <c>NODEBUG</c> is defined, it implies <c>NOASSERT</c>, unless
-        <c>DEBUG</c> is also defined, which is assumed to take precedence.</p>
+      <item><p>If <c>NODEBUG</c> is defined, it implies <c>NOASSERT</c> (unless
+        <c>DEBUG</c> is also defined, which overrides <c>NODEBUG</c>).</p>
       </item>
       <item><p>If <c>ASSERT</c> is defined, it overrides <c>NOASSERT</c>, that
         is, the assertions remain enabled.</p></item>
@@ -84,16 +92,19 @@ erlc -DNOASSERT=true *.erl</code>
     <title>Macros</title>
     <taglist>
       <tag><c>assert(BoolExpr)</c></tag>
+      <tag><c>assert(BoolExpr, Comment)</c></tag>
       <item>
         <p>Tests that <c>BoolExpr</c> completes normally returning
           <c>true</c>.</p>
       </item>
       <tag><c>assertNot(BoolExpr)</c></tag>
+      <tag><c>assertNot(BoolExpr, Comment)</c></tag>
       <item>
         <p>Tests that <c>BoolExpr</c> completes normally returning
           <c>false</c>.</p>
       </item>
       <tag><c>assertMatch(GuardedPattern, Expr)</c></tag>
+      <tag><c>assertMatch(GuardedPattern, Expr, Comment)</c></tag>
       <item>
         <p>Tests that <c>Expr</c> completes normally yielding a value that
           matches <c>GuardedPattern</c>, for example:</p>
@@ -104,6 +115,7 @@ erlc -DNOASSERT=true *.erl</code>
 ?assertMatch({bork, X} when X > 0, f())</code>
       </item>
       <tag><c>assertNotMatch(GuardedPattern, Expr)</c></tag>
+      <tag><c>assertNotMatch(GuardedPattern, Expr, Comment)</c></tag>
       <item>
         <p>Tests that <c>Expr</c> completes normally yielding a value that does
           not match <c>GuardedPattern</c>.</p>
@@ -111,16 +123,19 @@ erlc -DNOASSERT=true *.erl</code>
           <c>when</c> part.</p>
       </item>
       <tag><c>assertEqual(ExpectedValue, Expr)</c></tag>
+      <tag><c>assertEqual(ExpectedValue, Expr, Comment)</c></tag>
       <item>
          <p>Tests that <c>Expr</c> completes normally yielding a value that is
            exactly equal to <c>ExpectedValue</c>.</p>
       </item>
       <tag><c>assertNotEqual(ExpectedValue, Expr)</c></tag>
+      <tag><c>assertNotEqual(ExpectedValue, Expr, Comment)</c></tag>
       <item>
         <p>Tests that <c>Expr</c> completes normally yielding a value that is
           not exactly equal to <c>ExpectedValue</c>.</p>
       </item>
       <tag><c>assertException(Class, Term, Expr)</c></tag>
+      <tag><c>assertException(Class, Term, Expr, Comment)</c></tag>
       <item>
         <p>Tests that <c>Expr</c> completes abnormally with an exception of type
           <c>Class</c> and with the associated <c>Term</c>. The assertion fails
@@ -130,6 +145,7 @@ erlc -DNOASSERT=true *.erl</code>
           patterns, as in <c>assertMatch</c>.</p>
       </item>
       <tag><c>assertNotException(Class, Term, Expr)</c></tag>
+      <tag><c>assertNotException(Class, Term, Expr, Comment)</c></tag>
       <item>
         <p>Tests that <c>Expr</c> does not evaluate abnormally with an
           exception of type <c>Class</c> and with the associated <c>Term</c>.
@@ -139,14 +155,17 @@ erlc -DNOASSERT=true *.erl</code>
           be guarded patterns.</p>
       </item>
       <tag><c>assertError(Term, Expr)</c></tag>
+      <tag><c>assertError(Term, Expr, Comment)</c></tag>
       <item>
         <p>Equivalent to <c>assertException(error, Term, Expr)</c></p>
       </item>
       <tag><c>assertExit(Term, Expr)</c></tag>
+      <tag><c>assertExit(Term, Expr, Comment)</c></tag>
       <item>
         <p>Equivalent to <c>assertException(exit, Term, Expr)</c></p>
       </item>
       <tag><c>assertThrow(Term, Expr)</c></tag>
+      <tag><c>assertThrow(Term, Expr, Comment)</c></tag>
       <item>
         <p>Equivalent to <c>assertException(throw, Term, Expr)</c></p>
       </item>
diff --git a/lib/stdlib/include/assert.hrl b/lib/stdlib/include/assert.hrl
index 9e5d4eb..5a75255 100644
--- a/lib/stdlib/include/assert.hrl
+++ b/lib/stdlib/include/assert.hrl
@@ -56,7 +56,8 @@
 %% It is not possible to nest assert macros.
 
 -ifdef(NOASSERT).
--define(assert(BoolExpr),ok).
+-define(assert(BoolExpr), ok).
+-define(assert(BoolExpr, Comment), ok).
 -else.
 %% The assert macro is written the way it is so as not to cause warnings
 %% for clauses that cannot match, even if the expression is a constant or
@@ -79,11 +80,31 @@
             end
           end)())
         end).
+-define(assert(BoolExpr, Comment),
+        begin
+        ((fun () ->
+            __T = is_process_alive(self()),  % cheap source of truth
+            case (BoolExpr) of
+                __T -> ok;
+                __V -> erlang:error({assert,
+                                     [{module, ?MODULE},
+                                      {line, ?LINE},
+                                      {comment, (Comment)},
+                                      {expression, (??BoolExpr)},
+                                      {expected, true},
+                                      case not __T of
+                                          __V -> {value, false};
+                                          _ -> {not_boolean, __V}
+                                      end]})
+            end
+          end)())
+        end).
 -endif.
 
 %% This is the inverse case of assert, for convenience.
 -ifdef(NOASSERT).
 -define(assertNot(BoolExpr),ok).
+-define(assertNot(BoolExpr, Comment), ok).
 -else.
 -define(assertNot(BoolExpr),
         begin
@@ -103,12 +124,32 @@
             end
           end)())
         end).
+-define(assertNot(BoolExpr, Comment),
+        begin
+        ((fun () ->
+            __F = not is_process_alive(self()),
+            case (BoolExpr) of
+                __F -> ok;
+                __V -> erlang:error({assert,
+                                     [{module, ?MODULE},
+                                      {line, ?LINE},
+                                      {comment, (Comment)},
+                                      {expression, (??BoolExpr)},
+                                      {expected, false},
+                                      case not __F of
+                                          __V -> {value, true};
+                                          _ -> {not_boolean, __V}
+                                      end]})
+            end
+          end)())
+        end).
 -endif.
 
 %% This is mostly a convenience which gives more detailed reports.
 %% Note: Guard is a guarded pattern, and can not be used for value.
 -ifdef(NOASSERT).
 -define(assertMatch(Guard, Expr), ok).
+-define(assertMatch(Guard, Expr, Comment), ok).
 -else.
 -define(assertMatch(Guard, Expr),
         begin
@@ -124,11 +165,27 @@
             end
           end)())
         end).
+-define(assertMatch(Guard, Expr, Comment),
+        begin
+        ((fun () ->
+            case (Expr) of
+                Guard -> ok;
+                __V -> erlang:error({assertMatch,
+                                     [{module, ?MODULE},
+                                      {line, ?LINE},
+                                      {comment, (Comment)},
+                                      {expression, (??Expr)},
+                                      {pattern, (??Guard)},
+                                      {value, __V}]})
+            end
+          end)())
+        end).
 -endif.
 
 %% This is the inverse case of assertMatch, for convenience.
 -ifdef(NOASSERT).
 -define(assertNotMatch(Guard, Expr), ok).
+-define(assertNotMatch(Guard, Expr, Comment), ok).
 -else.
 -define(assertNotMatch(Guard, Expr),
         begin
@@ -145,12 +202,29 @@
             end
           end)())
         end).
+-define(assertNotMatch(Guard, Expr, Comment),
+        begin
+        ((fun () ->
+            __V = (Expr),
+            case __V of
+                Guard -> erlang:error({assertNotMatch,
+                                       [{module, ?MODULE},
+                                        {line, ?LINE},
+                                        {comment, (Comment)},
+                                        {expression, (??Expr)},
+                                        {pattern, (??Guard)},
+                                        {value, __V}]});
+                _ -> ok
+            end
+          end)())
+        end).
 -endif.
 
 %% This is a convenience macro which gives more detailed reports when
 %% the expected LHS value is not a pattern, but a computed value
 -ifdef(NOASSERT).
 -define(assertEqual(Expect, Expr), ok).
+-define(assertEqual(Expect, Expr, Comment), ok).
 -else.
 -define(assertEqual(Expect, Expr),
         begin
@@ -167,11 +241,28 @@
             end
           end)())
         end).
+-define(assertEqual(Expect, Expr, Comment),
+        begin
+        ((fun () ->
+            __X = (Expect),
+            case (Expr) of
+                __X -> ok;
+                __V -> erlang:error({assertEqual,
+                                     [{module, ?MODULE},
+                                      {line, ?LINE},
+                                      {comment, (Comment)},
+                                      {expression, (??Expr)},
+                                      {expected, __X},
+                                      {value, __V}]})
+            end
+          end)())
+        end).
 -endif.
 
 %% This is the inverse case of assertEqual, for convenience.
 -ifdef(NOASSERT).
 -define(assertNotEqual(Unexpected, Expr), ok).
+-define(assertNotEqual(Unexpected, Expr, Comment), ok).
 -else.
 -define(assertNotEqual(Unexpected, Expr),
         begin
@@ -187,12 +278,28 @@
             end
           end)())
         end).
+-define(assertNotEqual(Unexpected, Expr, Comment),
+        begin
+        ((fun () ->
+            __X = (Unexpected),
+            case (Expr) of
+                __X -> erlang:error({assertNotEqual,
+                                     [{module, ?MODULE},
+                                      {line, ?LINE},
+                                      {comment, (Comment)},
+                                      {expression, (??Expr)},
+                                      {value, __X}]});
+                _ -> ok
+            end
+          end)())
+        end).
 -endif.
 
 %% Note: Class and Term are patterns, and can not be used for value.
 %% Term can be a guarded pattern, but Class cannot.
 -ifdef(NOASSERT).
 -define(assertException(Class, Term, Expr), ok).
+-define(assertException(Class, Term, Expr, Comment), ok).
 -else.
 -define(assertException(Class, Term, Expr),
         begin
@@ -222,17 +329,54 @@
             end
           end)())
         end).
+-define(assertException(Class, Term, Expr, Comment),
+        begin
+        ((fun () ->
+            try (Expr) of
+                __V -> erlang:error({assertException,
+                                      [{module, ?MODULE},
+                                       {line, ?LINE},
+                                       {comment, (Comment)},
+                                       {expression, (??Expr)},
+                                       {pattern,
+                                        "{ "++(??Class)++" , "++(??Term)
+                                        ++" , [...] }"},
+                                       {unexpected_success, __V}]})
+            catch
+                Class:Term -> ok;
+                __C:__T ->
+                    erlang:error({assertException,
+                                  [{module, ?MODULE},
+                                   {line, ?LINE},
+                                   {comment, (Comment)},
+                                   {expression, (??Expr)},
+                                   {pattern,
+                                    "{ "++(??Class)++" , "++(??Term)
+                                    ++" , [...] }"},
+                                   {unexpected_exception,
+                                    {__C, __T,
+                                     erlang:get_stacktrace()}}]})
+            end
+          end)())
+        end).
 -endif.
 
 -define(assertError(Term, Expr), ?assertException(error, Term, Expr)).
+-define(assertError(Term, Expr, Comment),
+        ?assertException(error, Term, Expr, Comment)).
 -define(assertExit(Term, Expr), ?assertException(exit, Term, Expr)).
+-define(assertExit(Term, Expr, Comment),
+        ?assertException(exit, Term, Expr, Comment)).
 -define(assertThrow(Term, Expr), ?assertException(throw, Term, Expr)).
+-define(assertThrow(Term, Expr, Comment),
+        ?assertException(throw, Term, Expr, Comment)).
 
 %% This is the inverse case of assertException, for convenience.
 %% Note: Class and Term are patterns, and can not be used for value.
 %% Both Class and Term can be guarded patterns.
 -ifdef(NOASSERT).
 -define(assertNotException(Class, Term, Expr), ok).
+-define(assertNotException(Class, Term, Expr, Comment), ok).
 -else.
 -define(assertNotException(Class, Term, Expr),
         begin
@@ -263,6 +407,36 @@
             end
           end)())
         end).
+-define(assertNotException(Class, Term, Expr, Comment),
+        begin
+        ((fun () ->
+            try (Expr) of
+                _ -> ok
+            catch
+                __C:__T ->
+                    case __C of
+                        Class ->
+                            case __T of
+                                Term ->
+                                    erlang:error({assertNotException,
+                                                  [{module, ?MODULE},
+                                                   {line, ?LINE},
+                                                   {comment, (Comment)},
+                                                   {expression, (??Expr)},
+                                                   {pattern,
+                                                    "{ "++(??Class)++" , "
+                                                    ++(??Term)++" , [...] }"},
+                                                   {unexpected_exception,
+                                                    {__C, __T,
+                                                     erlang:get_stacktrace()
+                                                    }}]});
+                                _ -> ok
+                            end;
+                        _ -> ok
+                    end
+            end
+          end)())
+        end).
 -endif.
 
 -endif. % ASSERT_HRL
-- 
2.10.2

openSUSE Build Service is sponsored by