public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [patch, fortran] Handling of .and. and .or. expressions
@ 2018-06-12 18:00 Thomas Koenig
  2018-06-13  8:43 ` Toon Moene
                   ` (3 more replies)
  0 siblings, 4 replies; 92+ messages in thread
From: Thomas Koenig @ 2018-06-12 18:00 UTC (permalink / raw)
  To: fortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 1808 bytes --]

Hello world,

the attached patch introduces the following changes:

If a logical .and. or .or. expression contains a reference to a function
which is impure and which also does not behave like a pure function
(i.e. does not have the implicit_pure attribute set), it emits a
warning with -Wsurprising that the function might not be evaluated.
(-Wsurprising is enabled by -Wall).

It special cases the idiom  if (associated(m) .and. m%t) which
people appear to use.

And, if there is an expression like   func() .and. flag , it
reverses the test as an optimization. The middle end should be
capable of doing this, but apparently it doesn't, so the front
end might as well do this.

What it does not do is one part of PR 57160, i.e. warn against
if (a /= 0 .and. 1/a > 5) which people who are used to C might
also like to write.

There is already quite some discussion in the PRs, especially 85599,
where not all people were of the same opinion. Let us see where the
discussion here leads us.

Regression-tested (which found one bug in the testsuite).

OK for trunk?

Regards

	Thomas

2018-06-11  Thomas Koenig  <tkoenig@gcc.gnu.org>

         PR fortran/57160
         PR fortran/85599
         * dump-parse-tree (show_attr): Add handling of implicit_pure.
         * resolve.c (impure_function_callback): New function.
         (resolve_operator): Call it vial gfc_expr_walker. Special-case
         if (associated(m) .and. m%t).  If an .and. or .or. expression
         has a function or a non-function, exchange the operands.

2018-06-11  Thomas Koenig  <tkoenig@gcc.gnu.org>

         PR fortran/57160
         PR fortran/85599
         * gfortran.dg/logical_evaluation_1.f90: New test.
         * gfortran.dg/alloc_comp_default_init_2.f90: Fix code which
         implicitly depends on short-circuiting.

[-- Attachment #2: p4.diff --]
[-- Type: text/x-patch, Size: 4584 bytes --]

Index: fortran/dump-parse-tree.c
===================================================================
--- fortran/dump-parse-tree.c	(Revision 261388)
+++ fortran/dump-parse-tree.c	(Arbeitskopie)
@@ -716,6 +716,8 @@ show_attr (symbol_attribute *attr, const char * mo
     fputs (" ELEMENTAL", dumpfile);
   if (attr->pure)
     fputs (" PURE", dumpfile);
+  if (attr->implicit_pure)
+    fputs (" IMPLICIT_PURE", dumpfile);
   if (attr->recursive)
     fputs (" RECURSIVE", dumpfile);
 
Index: fortran/resolve.c
===================================================================
--- fortran/resolve.c	(Revision 261388)
+++ fortran/resolve.c	(Arbeitskopie)
@@ -3807,7 +3807,43 @@ lookup_uop_fuzzy (const char *op, gfc_symtree *uop
   return gfc_closest_fuzzy_match (op, candidates);
 }
 
+/* Callback finding an impure function as an operand to an .and. or
+   .or.  expression.  Remember the last function warned about to
+   avoid double warnings when recursing.  */
 
+static int
+impure_function_callback (gfc_expr **e, int *walk_subtrees ATTRIBUTE_UNUSED,
+			  void *data)
+{
+  gfc_expr *f = *e;
+  const char *name;
+  static gfc_expr *last = NULL;
+  bool *found = (bool *) data;
+
+  if (f->expr_type == EXPR_FUNCTION)
+    {
+      *found = 1;
+      if (f != last && !pure_function (f, &name))
+	{
+	  /* This could still be a function without side effects, i.e.
+	     implicit pure.  Do not warn for that case.  */
+	  if (f->symtree == NULL || f->symtree->n.sym == NULL
+	      || !gfc_implicit_pure (f->symtree->n.sym))
+	    {
+	      if (name)
+		gfc_warning (OPT_Wsurprising, "Impure function %qs at %L "
+			     "might not be evaluated", name, &f->where);
+	      else
+		gfc_warning (OPT_Wsurprising, "Impure function at %L "
+			     "might not be evaluated", &f->where);
+	    }
+	}
+      last = f;
+    }
+
+  return 0;
+}
+
 /* Resolve an operator expression node.  This can involve replacing the
    operation with a user defined function call.  */
 
@@ -3910,6 +3946,8 @@ resolve_operator (gfc_expr *e)
     case INTRINSIC_NEQV:
       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
 	{
+	  bool dont_move = false;
+
 	  e->ts.type = BT_LOGICAL;
 	  e->ts.kind = gfc_kind_max (op1, op2);
 	  if (op1->ts.kind < e->ts.kind)
@@ -3916,6 +3954,53 @@ resolve_operator (gfc_expr *e)
 	    gfc_convert_type (op1, &e->ts, 2);
 	  else if (op2->ts.kind < e->ts.kind)
 	    gfc_convert_type (op2, &e->ts, 2);
+
+	  if (e->value.op.op == INTRINSIC_AND || e->value.op.op == INTRINSIC_OR)
+	    {
+	      bool op1_f, op2_f;
+
+	      op1_f = false;
+	      op2_f = false;
+	      gfc_expr_walker (&op1, impure_function_callback, &op1_f);
+	      gfc_expr_walker (&op2, impure_function_callback, &op2_f);
+
+	      /* Some people code which depends on the short-circuiting that
+		 Fortran does not provide, such as
+
+		 if (associated(m) .and. m%t) then
+
+		 So, warn about this idiom. However, avoid breaking
+		 it on purpose.  */
+
+	      if (op1->expr_type == EXPR_FUNCTION && op1->value.function.isym
+		  && op1->value.function.isym->id == GFC_ISYM_ASSOCIATED)
+		{
+		  gfc_expr *e = op1->value.function.actual->expr;
+		  gfc_expr *en = op1->value.function.actual->next->expr;
+		  if (en == NULL && gfc_check_dependency (e, op2, true))
+		    {
+		      gfc_warning (OPT_Wsurprising, "%qs function call at %L does "
+				   "not guard expression at %L", "ASSOCIATED",
+				   &op1->where, &op2->where);
+		      dont_move = true;
+		    }
+		}
+
+	      /* A bit of optimization: Transfer if (f(x) .and. flag)
+		 into if (flag .and. f(x)), to save evaluation of a
+		 function.  The middle end should be capable of doing
+		 this with a TRUTH_AND_EXPR, but it currently does not do
+		 so. See PR 85599.  */
+
+	      if (!dont_move && op1_f && !op2_f)
+		{
+		  e->value.op.op1 = op2;
+		  e->value.op.op2 = op1;
+		  op1 = e->value.op.op1;
+		  op2 = e->value.op.op2;
+		}
+	    }
+
 	  break;
 	}
 
Index: testsuite/gfortran.dg/alloc_comp_default_init_2.f90
===================================================================
--- testsuite/gfortran.dg/alloc_comp_default_init_2.f90	(Revision 261388)
+++ testsuite/gfortran.dg/alloc_comp_default_init_2.f90	(Arbeitskopie)
@@ -11,7 +11,8 @@ program testprog
   integer, save :: callnb = 0
   type(t_type) :: this
   allocate ( this % chars ( 4))
-  if (.not.recursivefunc (this) .or. (callnb .ne. 10)) STOP 1
+  if (.not.recursivefunc (this)) STOP 1 
+  if (callnb .ne. 10) STOP 2
 contains
   recursive function recursivefunc ( this ) result ( match )
     type(t_type), intent(in) :: this

[-- Attachment #3: logical_evaluation_1.f90 --]
[-- Type: text/x-fortran, Size: 1206 bytes --]

! { dg-do compile }
! { dg-additional-options "-Wsurprising -fdump-tree-original" }
! PR 85599 - check warning that impure function calls might be removed,
! and that logical expressions involving .and. and .or. will be
! reordered. 

MODULE M1
 TYPE T1
   LOGICAL :: T=.TRUE.
 END TYPE T1
CONTAINS
 SUBROUTINE S1(m)
   TYPE(T1), POINTER :: m
   IF (ASSOCIATED(m) .AND. m%T) THEN ! { dg-warning "does not guard expression" }
    WRITE(6,*) "X"
   ENDIF
 END SUBROUTINE
END MODULE

module x
  logical :: flag = .true.
  integer :: count = 0
contains
  pure function f()
    logical :: f
    f = .true.
  end function f

  function g()
    logical :: g
    g = .false.
  end function g

  real function h()
     h = 1.2
     count = count + 1
  end function h
end module x

program main
  use x
  print *, g() .and. f() ! No warning, because g() follows all the rules of a pure function
  print *, f() .and. flag
  print *, h() > 1.0 .and. flag ! { dg-warning "might not be evaluated" }
  print *, h() < 1.0 .or. flag ! { dg-warning "might not be evaluated" }

end program main
! { dg-final { scan-tree-dump-times "flag &&" 2 "original" } }
! { dg-final { scan-tree-dump-times "flag \\|\\|" 1 "original" } }

^ permalink raw reply	[flat|nested] 92+ messages in thread
* Re: [patch, fortran] Handling of .and. and .or. expressions
@ 2018-06-13 13:55 Dominique d'Humières
  2018-06-13 20:42 ` Thomas Koenig
  0 siblings, 1 reply; 92+ messages in thread
From: Dominique d'Humières @ 2018-06-13 13:55 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: gfortran

Hi Thomas,

As I said in one of the PRs, I don’t like the warnings triggering with -Wall.

Also I don’t understand what is special with ASSOCIATED, as shown by the following code

MODULE M1
 TYPE T1
   LOGICAL :: T=.FALSE.
 END TYPE T1
CONTAINS
 SUBROUTINE S1(m)
   TYPE(T1), allocatable :: m
   IF (ALLOCATED(m) .AND. m%T) THEN
    WRITE(6,*) "X"
   ENDIF
 END SUBROUTINE
END MODULE

USE M1
 TYPE(T1), allocatable :: m
 CALL S1(m)
 allocate(m)
 CALL S1(m)
 m%t = .true.
 CALL S1(m)
 deallocate(m)
END

In addition I don’t understand the associated warning: in short-circuit evaluation ASSOCIATED(m) (or ALLOCATED(m)) does protect m%T to be accessed.

Cheers,

Dominique

^ permalink raw reply	[flat|nested] 92+ messages in thread
* Re: [patch, fortran] Handling of .and. and .or. expressions
@ 2018-06-16 19:21 graham stott via fortran
  2018-06-16 19:43 ` Steve Kargl
  0 siblings, 1 reply; 92+ messages in thread
From: graham stott via fortran @ 2018-06-16 19:21 UTC (permalink / raw)
  To: Steve Kargl, Janus Weil
  Cc: Janne Blomqvist, Thomas Koenig, fortran, gcc-patches

if i read this correctly it appears that IMPURE/PURE are not the normal pure attribute used by gcc but some entirely diff attribute specific to FORTANso people are taking about different things

-------- Original message --------
From: Steve Kargl <sgk@troutmask.apl.washington.edu> 
Date: 16/06/2018  17:38  (GMT+00:00) 
To: Janus Weil <janus@gcc.gnu.org> 
Cc: Janne Blomqvist <blomqvist.janne@gmail.com>, Thomas Koenig <tkoenig@netcologne.de>, fortran@gcc.gnu.org, gcc-patches <gcc-patches@gcc.gnu.org> 
Subject: Re: [patch, fortran] Handling of .and. and .or. expressions 

On Sat, Jun 16, 2018 at 01:09:36PM +0200, Janus Weil wrote:
> 
> 
> Am 15. Juni 2018 20:38:17 MESZ schrieb Steve Kargl <sgk@troutmask.apl.washington.edu>:
> >> But at least for pure functions, this optimization looks Ok.
> >> 
> >
> >Why is everyone fixated on PURE vs IMPURE functions?
> 
> Simply because it makes a difference in this context!

It does not!  A function marked as PURE by a programmer
must meet certain requirement of the Fortran standard.
An unmarked function or a function marked as IMPURE can
still meet those same requirements.  Marking something as 
IMPURE has only a single requirement in the standard.

   An impure elemental procedure processes array arguments
   in array element order.

That's it.  Marking a function as IMPURE does not mean 
the function has side effects.  It does not mean that
a function must be evaluated for each reference.  Are
you advocating that gfortran must evaluate ping() 
twice for

  impure real function ping()
  end function ping
  
  x = ping() + 0 * ping()
  end

-- 
Steve

^ permalink raw reply	[flat|nested] 92+ messages in thread

end of thread, other threads:[~2018-06-29  8:58 UTC | newest]

Thread overview: 92+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2018-06-12 18:00 [patch, fortran] Handling of .and. and .or. expressions Thomas Koenig
2018-06-13  8:43 ` Toon Moene
2018-06-13 14:06 ` Janus Weil
2018-06-13 20:46   ` Thomas Koenig
2018-06-14 10:14     ` Janus Weil
2018-06-14 10:29     ` Jakub Jelinek
2018-06-15  0:10       ` Steve Kargl
2018-06-15 17:27       ` Thomas Koenig
2018-06-13 20:59 ` Steve Kargl
2018-06-14  9:41 ` Janne Blomqvist
2018-06-14  9:45   ` Janus Weil
2018-06-14  9:55     ` Janne Blomqvist
2018-06-14 10:40       ` Janus Weil
2018-06-14 13:40         ` Janne Blomqvist
2018-06-15 10:26           ` Janus Weil
2018-06-15 17:10             ` Janus Weil
2018-06-15 20:52             ` Janne Blomqvist
2018-06-16 11:20               ` Janus Weil
2018-06-16 17:57                 ` Thomas Koenig
2018-06-15 17:16     ` Thomas Koenig
2018-06-16 11:09       ` Janus Weil
2018-06-15 17:13   ` Thomas Koenig
2018-06-15 18:38     ` Janne Blomqvist
2018-06-15 20:59       ` Steve Kargl
2018-06-16 16:38         ` Janus Weil
2018-06-16 18:19           ` Steve Kargl
2018-06-16 20:00             ` Janus Weil
2018-06-16 20:40               ` Steve Kargl
2018-06-16 20:41                 ` Steve Kargl
2018-06-16 20:42                   ` Jakub Jelinek
2018-06-16 21:20                 ` Janus Weil
2018-06-16 21:22                   ` Thomas Koenig
2018-06-18  9:34                     ` Steve Kargl
2018-06-18 12:29                     ` Janus Weil
2018-06-26  1:04                       ` Janus Weil
2018-06-27  5:53                         ` Thomas Koenig
2018-06-27  6:16                           ` Jakub Jelinek
2018-06-27  7:36                             ` Janus Weil
2018-06-27  7:42                               ` Jakub Jelinek
2018-06-27  7:52                                 ` Janus Weil
2018-06-27  8:02                                   ` Jakub Jelinek
2018-06-27  8:10                                     ` Janus Weil
2018-06-27  9:21                                       ` Jakub Jelinek
2018-06-27 13:43                                       ` Janne Blomqvist
2018-06-27 13:48                                         ` Janus Weil
2018-06-27 14:26                                           ` N.M. Maclaren
2018-06-27 16:17                                             ` Janus Weil
2018-06-27 19:16                                               ` N.M. Maclaren
2018-06-27 19:57                                                 ` Janne Blomqvist
2018-06-27 20:46                                                   ` Thomas Koenig
2018-06-27 21:07                                                     ` Janus Weil
2018-06-28  6:33                                                       ` Steve Kargl
2018-06-28  6:40                                                         ` Janus Weil
2018-06-28  7:09                                                           ` Thomas Koenig
2018-06-28 11:37                                                             ` Janus Weil
2018-06-28 12:00                                                               ` N.M. Maclaren
2018-06-28 13:27                                                                 ` Janus Weil
2018-06-28 14:28                                                                   ` N.M. Maclaren
2018-06-28 14:41                                                                     ` Janus Weil
2018-06-28 15:52                                                                       ` N.M. Maclaren
2018-06-28  7:21                                                           ` Janne Blomqvist
2018-06-28 16:22                                                           ` Steve Kargl
2018-06-28 17:03                                                             ` Janus Weil
2018-06-28 17:17                                                               ` Steve Kargl
2018-06-28 17:34                                                                 ` Janus Weil
2018-06-28 17:37                                                                   ` Thomas Koenig
2018-06-28 18:51                                                                   ` Steve Kargl
2018-06-28 17:34                                                                 ` N.M. Maclaren
2018-06-28 19:04                                                                 ` Toon Moene
2018-06-28 19:29                                                                   ` N.M. Maclaren
2018-06-28 17:21                                                             ` Jakub Jelinek
2018-06-28 17:55                                                               ` Steve Kargl
2018-06-29  2:43                                                                 ` Jakub Jelinek
2018-06-28 11:05                                                     ` Janne Blomqvist
2018-06-27 21:07                                                   ` N.M. Maclaren
2018-06-29  7:28                                           ` Steve Kargl
2018-06-29 13:34                                             ` Jakub Jelinek
2018-06-29 18:22                                               ` Janus Weil
2018-06-27 19:05                                         ` Steve Kargl
2018-06-27 19:35                                           ` Janne Blomqvist
2018-06-27 17:26                                   ` Thomas Koenig
2018-06-27 16:46                                 ` Steve Kargl
2018-06-16 22:38                   ` Steve Kargl
2018-06-13 13:55 Dominique d'Humières
2018-06-13 20:42 ` Thomas Koenig
2018-06-13 22:25   ` Dominique d'Humières
2018-06-13 22:56     ` Adam Hirst
2018-06-14  8:38     ` Thomas Koenig
2018-06-14 14:47       ` Dominique d'Humières
2018-06-15 17:49         ` Thomas Koenig
2018-06-16 19:21 graham stott via fortran
2018-06-16 19:43 ` Steve Kargl

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).