public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* Fortran patches
@ 2018-12-05  4:59 Steve Kargl
  2018-12-05 21:49 ` Fritz Reese
  0 siblings, 1 reply; 13+ messages in thread
From: Steve Kargl @ 2018-12-05  4:59 UTC (permalink / raw)
  To: fortran, gcc-patches

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

I intend to commit the attached patch on Saturday.

2018-12-02  Steven G. Kargl  <kargl@gcc.gnu.org>

	PR fortran/87922
	* io.c (gfc_match_open): ASYNCHRONOUS must be scalar.

	PR fortran/87945
	* decl.c (var_element): Inquiry parameter cannot be a data object.
	(match_data_constant): Inquiry parameter can be a data
	in a data statement.

	PR fortran/88139
	* dump-parse-tree.c (write_proc): Alternate return.

	PR fortran/88025
	* expr.c (gfc_apply_init): Remove asserts and check for valid
	ts->u.cl->length.

	PR fortran/88048
	* resolve.c (check_data_variable): Convert gfc_internal_error to 
	an gfc_error.  Add a nearby missing 'return false;'

	PR fortran/88116
	* simplify.c: Remove internal error and return gfc_bad_expr.

	PR fortran/88205
	* io.c (gfc_match_open): STATUS must be CHARACTER type.

	PR fortran/88206
	* match.c (gfc_match_type_spec): REAL can be an intrinsic function.

	PR fortran/88228
	* expr.c (check_null, check_elemental): Work around -fdec and
	initialization with logical operators operating on integers.

	PR fortran/88249
	* gfortran.h: Update prototype for gfc_resolve_filepos
	* io.c (gfc_resolve_filepos): Accept the locus to include in errors.
	* resolve.c (gfc_resolve_code): Pass locus.
 
	PR fortran/88269
	* io.c (io_constraint): Update macro.  Remove incompatible use
	of io_constraint and give explicit error.
 
	PR fortran/88328
	* io.c (resolve_tag_format): Detect zero-sized array.

2018-12-02  Steven G. Kargl  <kargl@gcc.gnu.org>

	PR fortran/87922
	* gfortran.dg/pr87922.f90: New test.

	PR fortran/887945
	* gfortran.dg/pr87945_1.f90: New test.
	* gfortran.dg/pr87945_2.f90: New test.

	PR fortran/87994
	* gfortran.dg/pr87994_1.f90: New test.
	* gfortran.dg/pr87994_2.f90: New test.
	* gfortran.dg/pr87994_3.f90: New test.

	PR fortran/88025
	* gfortran.dg/pr88025.f90: New test.

	PR fortran/88048
	* gfortran.dg/pr88048.f90: New test.

	PR fortran/88116
	* gfortran.dg/pr88116_1.f90: New test.
	* gfortran.dg/pr88116_2.f90: New test.

	PR fortran/88139
	* gfortran.dg/pr88139.f90: New test.

	PR fortran/88205
	* gfortran.dg/pr88205.f90: New test.

	PR fortran/88206
	* gfortran.dg/pr88206.f90: New test.

	PR fortran/88228
	* gfortran.dg/pr88228.f90: New test.

	PR fortran/88249
	* gfortran.dg/pr88249.f90: New test.

	PR fortran/88269
	* gfortran.dg/pr88269.f90: New test.

	PR fortran/88328
	* gfortran.dg/pr88328.f90: New test.

-- 
Steve

[-- Attachment #2: big.diff --]
[-- Type: text/x-diff, Size: 19676 bytes --]

Index: gcc/fortran/decl.c
===================================================================
--- gcc/fortran/decl.c	(revision 266718)
+++ gcc/fortran/decl.c	(working copy)
@@ -281,6 +281,14 @@ var_element (gfc_data_variable *new_var)
   if (m != MATCH_YES)
     return m;
 
+  if (new_var->expr->expr_type == EXPR_CONSTANT
+      && new_var->expr->symtree == NULL)
+    {
+      gfc_error ("Inquiry parameter cannot appear in a "
+		 "data-stmt-object-list at %C");
+      return MATCH_ERROR;
+    }
+
   sym = new_var->expr->symtree->n.sym;
 
   /* Symbol should already have an associated type.  */
@@ -391,6 +399,14 @@ match_data_constant (gfc_expr **result)
     }
   else if (m == MATCH_YES)
     {
+      /* If a parameter inquiry ends up here, symtree is NULL but **result
+	 contains the right constant expression.  Check here.  */
+      if ((*result)->symtree == NULL
+	  && (*result)->expr_type == EXPR_CONSTANT
+	  && ((*result)->ts.type == BT_INTEGER 
+	      || (*result)->ts.type == BT_REAL))
+	return m;
+
       /* F2018:R845 data-stmt-constant is initial-data-target.
 	 A data-stmt-constant shall be ... initial-data-target if and
 	 only if the corresponding data-stmt-object has the POINTER
Index: gcc/fortran/dump-parse-tree.c
===================================================================
--- gcc/fortran/dump-parse-tree.c	(revision 266718)
+++ gcc/fortran/dump-parse-tree.c	(working copy)
@@ -3259,6 +3259,14 @@ write_proc (gfc_symbol *sym)
     {
       gfc_symbol *s;
       s = f->sym;
+
+      if (!s)
+	{
+	  gfc_error_now ("Par %L, \"Nous sommes tous nes pour le mal\"",
+			 &sym->declared_at);
+	  return;
+	}
+
       rok = get_c_type_name (&(s->ts), NULL, &pre, &type_name, &asterisk,
 			     &post, false);
       if (rok == T_ERROR)
Index: gcc/fortran/expr.c
===================================================================
--- gcc/fortran/expr.c	(revision 266718)
+++ gcc/fortran/expr.c	(working copy)
@@ -2688,6 +2688,9 @@ check_transformational (gfc_expr *e)
 static match
 check_null (gfc_expr *e)
 {
+  if (flag_dec && e->expr_type == EXPR_CONSTANT)
+   return MATCH_NO;
+
   if (strcmp ("null", e->symtree->n.sym->name) != 0)
     return MATCH_NO;
 
@@ -2698,6 +2701,9 @@ check_null (gfc_expr *e)
 static match
 check_elemental (gfc_expr *e)
 {
+  if (flag_dec && e->expr_type == EXPR_CONSTANT)
+   return MATCH_NO;
+
   if (!e->value.function.isym
       || !e->value.function.isym->elemental)
     return MATCH_NO;
@@ -2793,10 +2799,15 @@ gfc_check_init_expr (gfc_expr *e)
 	    && (m = check_transformational (e)) == MATCH_NO
 	    && (m = check_elemental (e)) == MATCH_NO)
 	  {
-	    gfc_error ("Intrinsic function %qs at %L is not permitted "
-		       "in an initialization expression",
-		       e->symtree->n.sym->name, &e->where);
-	    m = MATCH_ERROR;
+	    if (flag_dec && e->expr_type == EXPR_CONSTANT)
+	      return true;
+	    else
+	      {
+		gfc_error ("Intrinsic function %qs at %L is not permitted "
+			   "in an initialization expression",
+			   e->symtree->n.sym->name, &e->where);
+		m = MATCH_ERROR;
+	      }
 	  }
 
 	if (m == MATCH_ERROR)
@@ -4485,12 +4496,10 @@ gfc_apply_init (gfc_typespec *ts, symbol_attribute *at
 {
   if (ts->type == BT_CHARACTER && !attr->pointer && init
       && ts->u.cl
-      && ts->u.cl->length && ts->u.cl->length->expr_type == EXPR_CONSTANT)
+      && ts->u.cl->length
+      && ts->u.cl->length->expr_type == EXPR_CONSTANT
+      && ts->u.cl->length->ts.type == BT_INTEGER)
     {
-      gcc_assert (ts->u.cl && ts->u.cl->length);
-      gcc_assert (ts->u.cl->length->expr_type == EXPR_CONSTANT);
-      gcc_assert (ts->u.cl->length->ts.type == BT_INTEGER);
-
       HOST_WIDE_INT len = gfc_mpz_get_hwi (ts->u.cl->length->value.integer);
 
       if (init->expr_type == EXPR_CONSTANT)
Index: gcc/fortran/gfortran.h
===================================================================
--- gcc/fortran/gfortran.h	(revision 266718)
+++ gcc/fortran/gfortran.h	(working copy)
@@ -3395,7 +3395,7 @@ bool gfc_resolve_open (gfc_open *);
 void gfc_free_close (gfc_close *);
 bool gfc_resolve_close (gfc_close *);
 void gfc_free_filepos (gfc_filepos *);
-bool gfc_resolve_filepos (gfc_filepos *);
+bool gfc_resolve_filepos (gfc_filepos *, locus *);
 void gfc_free_inquire (gfc_inquire *);
 bool gfc_resolve_inquire (gfc_inquire *);
 void gfc_free_dt (gfc_dt *);
Index: gcc/fortran/io.c
===================================================================
--- gcc/fortran/io.c	(revision 266718)
+++ gcc/fortran/io.c	(working copy)
@@ -1636,6 +1636,12 @@ resolve_tag_format (gfc_expr *e)
 	  gfc_expr *r;
 	  gfc_char_t *dest, *src;
 
+	  if (e->value.constructor == NULL)
+	    {
+	      gfc_error ("FORMAT tag at %C cannot be a zero-sized array");
+	      return false;
+	    }
+
 	  n = 0;
 	  c = gfc_constructor_first (e->value.constructor);
 	  len = c->expr->value.character.length;
@@ -2161,6 +2167,12 @@ gfc_match_open (void)
 
       if (!open->file && open->status)
         {
+	  if (open->status->ts.type != BT_CHARACTER)
+	    {
+	     gfc_error ("STATUS must be a default character type at %C");
+	     goto cleanup;
+	    }
+
 	  if (open->status->expr_type == EXPR_CONSTANT
 	     && gfc_wide_strncasecmp (open->status->value.character.string,
 				       "scratch", 7) != 0)
@@ -2232,6 +2244,21 @@ gfc_match_open (void)
       if (!is_char_type ("ASYNCHRONOUS", open->asynchronous))
 	goto cleanup;
 
+      if (open->asynchronous->ts.kind != 1)
+	{
+	  gfc_error ("ASYNCHRONOUS= specifier at %L must have default "
+		     "CHARACTER kind", &open->asynchronous->where);
+	  return MATCH_ERROR;
+	}
+
+      if (open->asynchronous->expr_type == EXPR_ARRAY
+	  || open->asynchronous->expr_type == EXPR_STRUCTURE)
+	{
+	  gfc_error ("ASYNCHRONOUS= specifier at %L must be scalar",
+		     &open->asynchronous->where);
+	  return MATCH_ERROR;
+	}
+
       if (open->asynchronous->expr_type == EXPR_CONSTANT)
 	{
 	  static const char * asynchronous[] = { "YES", "NO", NULL };
@@ -2834,22 +2861,21 @@ cleanup:
 
 
 bool
-gfc_resolve_filepos (gfc_filepos *fp)
+gfc_resolve_filepos (gfc_filepos *fp, locus *where)
 {
   RESOLVE_TAG (&tag_unit, fp->unit);
   RESOLVE_TAG (&tag_iostat, fp->iostat);
   RESOLVE_TAG (&tag_iomsg, fp->iomsg);
-  if (!gfc_reference_st_label (fp->err, ST_LABEL_TARGET))
-    return false;
 
-  if (!fp->unit && (fp->iostat || fp->iomsg))
+  if (!fp->unit && (fp->iostat || fp->iomsg || fp->err))
     {
-      locus where;
-      where = fp->iostat ? fp->iostat->where : fp->iomsg->where;
-      gfc_error ("UNIT number missing in statement at %L", &where);
+      gfc_error ("UNIT number missing in statement at %L", where);
       return false;
     }
 
+  if (!gfc_reference_st_label (fp->err, ST_LABEL_TARGET))
+    return false;
+
   if (fp->unit->expr_type == EXPR_CONSTANT
       && fp->unit->ts.type == BT_INTEGER
       && mpz_sgn (fp->unit->value.integer) < 0)
@@ -3231,12 +3257,21 @@ gfc_resolve_dt (gfc_dt *dt, locus *loc)
 {
   gfc_expr *e;
   io_kind k;
+  locus loc_tmp;
 
   /* This is set in any case.  */
   gcc_assert (dt->dt_io_kind);
   k = dt->dt_io_kind->value.iokind;
 
-  RESOLVE_TAG (&tag_format, dt->format_expr);
+  loc_tmp = gfc_current_locus;
+  gfc_current_locus = *loc;
+  if (!resolve_tag (&tag_format, dt->format_expr))
+    {
+      gfc_current_locus = loc_tmp;
+      return false;
+    }
+  gfc_current_locus = loc_tmp;
+
   RESOLVE_TAG (&tag_rec, dt->rec);
   RESOLVE_TAG (&tag_spos, dt->pos);
   RESOLVE_TAG (&tag_advance, dt->advance);
@@ -3681,7 +3716,10 @@ check_io_constraints (io_kind k, gfc_dt *dt, gfc_code 
 #define io_constraint(condition,msg,arg)\
 if (condition) \
   {\
-    gfc_error(msg,arg);\
+    if ((arg)->lb != NULL) \
+      gfc_error(msg,arg);\
+    else \
+      gfc_error(msg,&gfc_current_locus);\
     m = MATCH_ERROR;\
   }
 
@@ -3741,11 +3779,14 @@ if (condition) \
   if (expr && expr->ts.type != BT_CHARACTER)
     {
 
-      io_constraint (gfc_pure (NULL) && (k == M_READ || k == M_WRITE),
-		     "IO UNIT in %s statement at %C must be "
+      if (gfc_pure (NULL) && (k == M_READ || k == M_WRITE))
+	{
+	  gfc_error ("IO UNIT in %s statement at %C must be "
 		     "an internal file in a PURE procedure",
 		     io_kind_name (k));
-
+	  return MATCH_ERROR;
+	}
+	  
       if (k == M_READ || k == M_WRITE)
 	gfc_unset_implicit_pure (NULL);
     }
@@ -3792,6 +3833,21 @@ if (condition) \
 
       if (!is_char_type ("ASYNCHRONOUS", dt->asynchronous))
 	return MATCH_ERROR;
+
+      if (dt->asynchronous->ts.kind != 1)
+	{
+	  gfc_error ("ASYNCHRONOUS= specifier at %L must have default "
+		     "CHARACTER kind", &dt->asynchronous->where);
+	  return MATCH_ERROR;
+	}
+
+      if (dt->asynchronous->expr_type == EXPR_ARRAY
+	  || dt->asynchronous->expr_type == EXPR_STRUCTURE)
+	{
+	  gfc_error ("ASYNCHRONOUS= specifier at %L must be scalar",
+		     &dt->asynchronous->where);
+	  return MATCH_ERROR;
+	}
 
       if (!compare_to_allowed_values
 		("ASYNCHRONOUS", asynchronous, NULL, NULL,
Index: gcc/fortran/match.c
===================================================================
--- gcc/fortran/match.c	(revision 266718)
+++ gcc/fortran/match.c	(working copy)
@@ -2225,6 +2225,9 @@ found:
 	      return MATCH_NO;
 	    }
 
+	  if (e->expr_type != EXPR_CONSTANT)
+	    goto ohno;
+
 	  gfc_next_char (); /* Burn the ')'. */
 	  ts->kind = (int) mpz_get_si (e->value.integer);
 	  if (gfc_validate_kind (ts->type, ts->kind , true) == -1)
@@ -2238,6 +2241,8 @@ found:
 	  return MATCH_YES;
 	}
     }
+
+ohno:
 
   /* If a type is not matched, simply return MATCH_NO.  */
   gfc_current_locus = old_locus;
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 266718)
+++ gcc/fortran/resolve.c	(working copy)
@@ -11544,7 +11544,7 @@ start:
 	case EXEC_ENDFILE:
 	case EXEC_REWIND:
 	case EXEC_FLUSH:
-	  if (!gfc_resolve_filepos (code->ext.filepos))
+	  if (!gfc_resolve_filepos (code->ext.filepos, &code->loc))
 	    break;
 
 	  resolve_branch (code->ext.filepos->err, code);
@@ -15492,7 +15492,10 @@ check_data_variable (gfc_data_variable *var, locus *wh
     e = e->value.function.actual->expr;
 
   if (e->expr_type != EXPR_VARIABLE)
-    gfc_internal_error ("check_data_variable(): Bad expression");
+    {
+      gfc_error ("Expecting definable entity near %L", where);
+      return false;
+    }
 
   sym = e->symtree->n.sym;
 
@@ -15500,6 +15503,7 @@ check_data_variable (gfc_data_variable *var, locus *wh
     {
       gfc_error ("BLOCK DATA element %qs at %L must be in COMMON",
 		 sym->name, &sym->declared_at);
+      return false;
     }
 
   if (e->ref == NULL && sym->as)
Index: gcc/fortran/simplify.c
===================================================================
--- gcc/fortran/simplify.c	(revision 266718)
+++ gcc/fortran/simplify.c	(working copy)
@@ -8360,7 +8360,7 @@ gfc_convert_constant (gfc_expr *e, bt type, int kind)
 
     default:
     oops:
-      gfc_internal_error ("gfc_convert_constant(): Unexpected type");
+      return &gfc_bad_expr;
     }
 
   result = NULL;
Index: gcc/testsuite/gfortran.dg/io_constraints_8.f90
===================================================================
--- gcc/testsuite/gfortran.dg/io_constraints_8.f90	(revision 266718)
+++ gcc/testsuite/gfortran.dg/io_constraints_8.f90	(working copy)
@@ -14,7 +14,7 @@ integer :: i
 
 OPEN(99, access=4_'direct')     ! { dg-error "must be a character string of default kind" }
 OPEN(99, action=4_'read')       ! { dg-error "must be a character string of default kind" }
-OPEN(99, asynchronous=4_'no')   ! { dg-error "must be a character string of default kind" })
+OPEN(99, asynchronous=4_'no')   ! { dg-error "must have default CHARACTER kind" })
 OPEN(99, blank=4_'null')        ! { dg-error "must be a character string of default kind" }
 OPEN(99, decimal=4_'comma')     ! { dg-error "must be a character string of default kind" }
 OPEN(99, delim=4_'quote')       ! { dg-error "must be a character string of default kind" }
Index: gcc/testsuite/gfortran.dg/pr87922.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87922.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87922.f90	(working copy)
@@ -0,0 +1,10 @@
+! { dg-do compile }
+! PR fortran/87922
+subroutine p
+   read(1, asynchronous=['no'])           ! { dg-error "must be scalar" }
+   read(1, asynchronous=[character::])    ! { dg-error "must be scalar" }
+end
+subroutine q
+   write(1, asynchronous=['no'])          ! { dg-error "must be scalar" }
+   write(1, asynchronous=[character::])   ! { dg-error "must be scalar" }
+end
Index: gcc/testsuite/gfortran.dg/pr87945_1.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87945_1.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87945_1.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do compile }
+! PR fortran/87945
+program p
+   character :: a, b
+   data a%len /1/       ! { dg-error "parameter cannot appear in" }
+   data b%kind /'b'/    ! { dg-error "parameter cannot appear in" }
+end
Index: gcc/testsuite/gfortran.dg/pr87945_2.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87945_2.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87945_2.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do compile }
+! PR fortran/87945
+program p
+   character :: a, b
+   a%len = 1      ! { dg-error "to a constant expression" }
+   b%kind = 'b'   ! { dg-error "to a constant expression" }
+end
Index: gcc/testsuite/gfortran.dg/pr87994_1.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87994_1.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87994_1.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do run }
+! PR fortran/87994
+program p
+   real :: a, b
+   data b /a%kind/
+   if (b /= kind(a)) stop 1
+end
Index: gcc/testsuite/gfortran.dg/pr87994_2.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87994_2.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87994_2.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do run }
+! PR fortran/87994
+program p
+   real, parameter :: a = 1.0
+   data b /a%kind/
+   if (b /= kind(a)) stop 1
+end
Index: gcc/testsuite/gfortran.dg/pr87994_3.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr87994_3.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr87994_3.f90	(working copy)
@@ -0,0 +1,8 @@
+! { dg-do run }
+! PR fortran/87994
+program p
+   integer, parameter :: a = 1
+   integer :: b
+   data b /a%kind/
+   if (b /= kind(a)) stop = 1
+end
Index: gcc/testsuite/gfortran.dg/pr88025.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88025.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88025.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do compile }
+! PR fortran/88025
+program p
+   type t
+      character(('')) :: c = 'c'    ! { dg-error "must be of INTEGER type" }
+   end type
+end
Index: gcc/testsuite/gfortran.dg/pr88048.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88048.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88048.f90	(working copy)
@@ -0,0 +1,7 @@
+! { dg-do compile }
+! PR fortran/88048
+program p
+   integer, parameter :: a(2) = 1
+   data a(2) /a(1)/                 ! { dg-error "definable entity" }
+   print *, a
+end
Index: gcc/testsuite/gfortran.dg/pr88116_1.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88116_1.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88116_1.f90	(working copy)
@@ -0,0 +1,5 @@
+! { dg-do compile }
+! PR fortran/88116
+program p
+   print *, [integer :: 1, [integer(8) :: 2, ['3']]] ! { dg-error "convert" }
+end
Index: gcc/testsuite/gfortran.dg/pr88116_2.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88116_2.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88116_2.f90	(working copy)
@@ -0,0 +1,9 @@
+! { dg-do run }
+! PR fortran/88116
+program p
+  real :: a(2) = [real :: 1, [integer :: (real(k), k=2,1), 2]]
+  real :: b(1) = [real :: [integer :: (dble(k), k=1,0), 2]]
+  if (a(1) /= 1 .or. a(2) /= 2) stop 1
+  if (b(1) /= 2) stop 2
+end
+
Index: gcc/testsuite/gfortran.dg/pr88139.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88139.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88139.f90	(working copy)
@@ -0,0 +1,9 @@
+! { dg-do compile }
+! { dg-options "-fc-prototypes" }
+! PR fortran/88139
+module m
+contains
+   subroutine s(*) bind(c, name='f')   ! { dg-error "sommes tous nes" }
+   end
+end
+! { dg-prune-output "void f" }
Index: gcc/testsuite/gfortran.dg/pr88205.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88205.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88205.f90	(working copy)
@@ -0,0 +1,14 @@
+! { dg-do compile }
+! PR fortran/88205
+subroutine s1
+   real, parameter :: status = 0
+   open (newunit=n, status=status)        ! { dg-error "be a default character" }
+end
+subroutine s2
+   complex, parameter :: status = 0
+   open (newunit=n, status=status)        ! { dg-error "be a default character" }
+end
+program p
+  logical, parameter :: status = .false.
+  open (newunit=a, status=status)         ! { dg-error "be a default character" }
+end
Index: gcc/testsuite/gfortran.dg/pr88206.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88206.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88206.f90	(working copy)
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! PR fortran/88206
+program p
+   integer, parameter :: z(4) = [1,2,3,4]
+   integer :: k = 2
+   print *, [real(z(k))]
+end
+
Index: gcc/testsuite/gfortran.dg/pr88228.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88228.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88228.f90	(working copy)
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! { dg-options "-fdec" }
+! PR fortran/88228
+program p
+   integer :: n = .not. 1
+   integer :: j = .true. .or. 1
+end
+
Index: gcc/testsuite/gfortran.dg/pr88249.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88249.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88249.f90	(working copy)
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! PR fortran/88249
+program p
+   backspace(err=1)  ! { dg-error "number missing in statement" }
+   endfile(err=1)    ! { dg-error "number missing in statement" }
+   flush(err=1)      ! { dg-error "number missing in statement" }
+   rewind(err=1)     ! { dg-error "number missing in statement" }
+end
Index: gcc/testsuite/gfortran.dg/pr88269.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88269.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88269.f90	(working copy)
@@ -0,0 +1,6 @@
+! { dg-do compile }
+! PR fortran/88269
+program p
+   write (end=1e1) ! { dg-error "tag not allowed" }
+end
+
Index: gcc/testsuite/gfortran.dg/pr88328.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr88328.f90	(nonexistent)
+++ gcc/testsuite/gfortran.dg/pr88328.f90	(working copy)
@@ -0,0 +1,6 @@
+! { dg-do compile }
+! PR fortran/88328
+program p
+   character(3), parameter :: a(0) = [character(3)::]
+   print a ! { dg-error "zero-sized array" }
+end

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

* Re: Fortran patches
  2018-12-05  4:59 Fortran patches Steve Kargl
@ 2018-12-05 21:49 ` Fritz Reese
  2018-12-06  0:03   ` Steve Kargl
  0 siblings, 1 reply; 13+ messages in thread
From: Fritz Reese @ 2018-12-05 21:49 UTC (permalink / raw)
  To: Steve Kargl; +Cc: fortran, gcc-patches

On Wed, Dec 5, 2018 at 12:00 AM Steve Kargl
<sgk@troutmask.apl.washington.edu> wrote:
>
> I intend to commit the attached patch on Saturday.

Thanks for the work. I assume the patch bootstraps and passes regression tests?

RE:
>         PR fortran/88228
>         * expr.c (check_null, check_elemental): Work around -fdec and
>         initialization with logical operators operating on integers.

I plan to review this section of the patch later today -- though the
patch hides the segfault from the PR, I need more time to determine
whether it is correct and complete.

RE:
>        PR fortran/88139
>        * dump-parse-tree.c (write_proc): Alternate return.
I dissent with this patch. The introduced error is meaningless and, as
mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
is not directly the issue. The code should be rejected in parsing. In
gcc-8.1 the invalid code is accepted (without an ICE) even without the
-fc-prototypes flag: I haven't finished building the compiler with
your changes yet to see whether that is still true afterwards, but at
least the test case doesn't try this, so I strongly suspect the patch
is incomplete to fix the PR.

RE:
>        PR fortran/88205
>        * io.c (gfc_match_open): STATUS must be CHARACTER type.
[...]
>@@ -2161,6 +2167,12 @@ gfc_match_open (void)
>
>       if (!open->file && open->status)
>         {
>+         if (open->status->ts.type != BT_CHARACTER)
>+           {
>+            gfc_error ("STATUS must be a default character type at %C");
>+            goto cleanup;
>+           }
>+
>          if (open->status->expr_type == EXPR_CONSTANT
>             && gfc_wide_strncasecmp (open->status->value.character.string,
>                                       "scratch", 7) != 0)

Both resolve_tag() and is_char_type() actually already catch type
mismatches for STATUS (the latter for constant expressions). The real
problem is the following condition which checks STATUS before it has
been processed yet, since NEWUNIT is processed before STATUS. I think
the correct thing to do is actually to move the NEWUNIT/UNIT if-block
after the STATUS if-block, rather than adding a new phrasing for the
same error. Then we should see:

pr88205.f90:13:29:
   open (newunit=n, status=status)
                             1
Error: STATUS requires a scalar-default-char-expr at (1)

RE:
>        PR fortran/88328
>        * io.c (resolve_tag_format): Detect zero-sized array.
[...]
>Index: gcc/fortran/io.c
>===================================================================
>--- gcc/fortran/io.c    (revision 266718)
>+++ gcc/fortran/io.c    (working copy)
>@@ -1636,6 +1636,12 @@ resolve_tag_format (gfc_expr *e)
>          gfc_expr *r;
>          gfc_char_t *dest, *src;
>
>+         if (e->value.constructor == NULL)
>+           {
>+             gfc_error ("FORMAT tag at %C cannot be a zero-sized array");
>+             return false;
>+           }
>+
>          n = 0;
>          c = gfc_constructor_first (e->value.constructor);
>          len = c->expr->value.character.length;
[...]
>@ -3231,12 +3257,21 @@ gfc_resolve_dt (gfc_dt *dt, locus *loc)
> {
>   gfc_expr *e;
>   io_kind k;
>+  locus loc_tmp;
>
>   /* This is set in any case.  */
>   gcc_assert (dt->dt_io_kind);
>   k = dt->dt_io_kind->value.iokind;
>
>-  RESOLVE_TAG (&tag_format, dt->format_expr);
>+  loc_tmp = gfc_current_locus;
>+  gfc_current_locus = *loc;
>+  if (!resolve_tag (&tag_format, dt->format_expr))
>+    {
>+      gfc_current_locus = loc_tmp;
>+      return false;
>+    }
>+  gfc_current_locus = loc_tmp;
>+
>   RESOLVE_TAG (&tag_rec, dt->rec);
>   RESOLVE_TAG (&tag_spos, dt->pos);
>   RESOLVE_TAG (&tag_advance, dt->advance);

Is it really true that resolve_tag_format needs the locus at
gfc_resolve_dt::loc instead of e->where as with the other errors in
resolve_tag_format? If so, are the other errors also incorrect in
using e->where? Might it then be better to pass loc from
gfc_resolve_dt down to resolve_tag/RESOLVE_TAG and then
resolve_tag_format, instead of swapping gfc_current_locus?

RE:
>        PR fortran/88048
>        * resolve.c (check_data_variable): Convert gfc_internal_error to
>        an gfc_error.  Add a nearby missing 'return false;'
[...]
>        PR fortran/88025
>        * expr.c (gfc_apply_init): Remove asserts and check for valid
>        ts->u.cl->length.
[...]
>        PR fortran/88116
>        * simplify.c: Remove internal error and return gfc_bad_expr.

These look good.

A few pedantic comments:

RE:
>         PR fortran/88269
>         * io.c (io_constraint): Update macro.  Remove incompatible use
>         of io_constraint and give explicit error.
[...]

There should be two separate references to io_constraint and
check_io_constraints:

>         * io.c (io_constraint): Update macro.
>         (check_io_constraints) Remove incompatible use
>         of io_constraint and give explicit error.

RE:
> #define io_constraint(condition,msg,arg)\
> if (condition) \
>   {\
>-    gfc_error(msg,arg);\
>+    if ((arg)->lb != NULL) \
>+      gfc_error(msg,arg);\
>+    else \
>+      gfc_error(msg,&gfc_current_locus);\
>     m = MATCH_ERROR;\
>   }

I think you could safely follow style conventions here (Comma-Space
and Function-Space-Parenthesis):

-#define io_constraint(condition,msg,arg)\
+#define io_constraint(condition, msg, arg)\
 if (condition) \
   {\
-    gfc_error(msg,arg);\
+    if ((arg)->lb != NULL) \
+      gfc_error (msg, arg);\
+    else \
+      gfc_error (msg, &gfc_current_locus);\
     m = MATCH_ERROR;\
   }

RE:
>@@ -3741,11 +3779,14 @@ if (condition) \
>   if (expr && expr->ts.type != BT_CHARACTER)
>     {
>
>-      io_constraint (gfc_pure (NULL) && (k == M_READ || k == M_WRITE),
>-                    "IO UNIT in %s statement at %C must be "
>+      if (gfc_pure (NULL) && (k == M_READ || k == M_WRITE))
>+       {
>+         gfc_error ("IO UNIT in %s statement at %C must be "
>                     "an internal file in a PURE procedure",
>                     io_kind_name (k));
>-
>+         return MATCH_ERROR;
>+       }
>+
>       if (k == M_READ || k == M_WRITE)
>        gfc_unset_implicit_pure (NULL);
>     }

Trailing whitespace on line 3789 (post-patch).

RE:
>         PR fortran/87945
>         * decl.c (var_element): Inquiry parameter cannot be a data object.
>         (match_data_constant): Inquiry parameter can be a data
>         in a data statement.
[...]
>@@ -391,6 +399,14 @@ match_data_constant (gfc_expr **result)
>     }
>   else if (m == MATCH_YES)
>     {
>+      /* If a parameter inquiry ends up here, symtree is NULL but **result
>+        contains the right constant expression.  Check here.  */
>+      if ((*result)->symtree == NULL
>+         && (*result)->expr_type == EXPR_CONSTANT
>+         && ((*result)->ts.type == BT_INTEGER
>+             || (*result)->ts.type == BT_REAL))
>+       return m;
>+
>       /* F2018:R845 data-stmt-constant is initial-data-target.
>         A data-stmt-constant shall be ... initial-data-target if and
>         only if the corresponding data-stmt-object has the POINTER

Trailing whitespace on line 406 (post-patch).

Cheers,
Fritz

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

* Re: Fortran patches
  2018-12-05 21:49 ` Fritz Reese
@ 2018-12-06  0:03   ` Steve Kargl
  2018-12-06 19:03     ` Thomas Koenig
  2018-12-06 19:09     ` Fritz Reese
  0 siblings, 2 replies; 13+ messages in thread
From: Steve Kargl @ 2018-12-06  0:03 UTC (permalink / raw)
  To: Fritz Reese; +Cc: fortran, gcc-patches

On Wed, Dec 05, 2018 at 04:48:28PM -0500, Fritz Reese wrote:
> On Wed, Dec 5, 2018 at 12:00 AM Steve Kargl
> <sgk@troutmask.apl.washington.edu> wrote:
> >
> > I intend to commit the attached patch on Saturday.
> 
> Thanks for the work. I assume the patch bootstraps and passes
> regression tests?

The patch passed regression testing on i586-*-freebsd.
I'll also do regression testing on x86_64-*-freebsd 
prior to the commit.

> RE:
> >         PR fortran/88228
> >         * expr.c (check_null, check_elemental): Work around -fdec and
> >         initialization with logical operators operating on integers.
> 
> I plan to review this section of the patch later today -- though the
> patch hides the segfault from the PR, I need more time to determine
> whether it is correct and complete.

By the time the gfc_expr is given to check_check and check_elemental,
it has been reduced to a EXPR_CONSTANT, which neither routine expected.
I simply return early in that case.

> RE:
> >        PR fortran/88139
> >        * dump-parse-tree.c (write_proc): Alternate return.
> I dissent with this patch. The introduced error is meaningless and, as
> mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> is not directly the issue. The code should be rejected in parsing. In
> gcc-8.1 the invalid code is accepted (without an ICE) even without the
> -fc-prototypes flag: I haven't finished building the compiler with
> your changes yet to see whether that is still true afterwards, but at
> least the test case doesn't try this, so I strongly suspect the patch
> is incomplete to fix the PR.
 
Comment #3 does not contain a patch to fix the problem elsewhere.

In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
I cannot find a prohibition on an alternate return in a subroutine
interface with BIND(C).

I'm disinclined to let a patch fester in bugzilla to only attain
the same fate as my patch to PR68544.

> RE:
> >        PR fortran/88205
> >        * io.c (gfc_match_open): STATUS must be CHARACTER type.
> [...]
> >@@ -2161,6 +2167,12 @@ gfc_match_open (void)
> >
> >       if (!open->file && open->status)
> >         {
> >+         if (open->status->ts.type != BT_CHARACTER)
> >+           {
> >+            gfc_error ("STATUS must be a default character type at %C");
> >+            goto cleanup;
> >+           }
> >+
> >          if (open->status->expr_type == EXPR_CONSTANT
> >             && gfc_wide_strncasecmp (open->status->value.character.string,
> >                                       "scratch", 7) != 0)
> 
> Both resolve_tag() and is_char_type() actually already catch type
> mismatches for STATUS (the latter for constant expressions). The real
> problem is the following condition which checks STATUS before it has
> been processed yet, since NEWUNIT is processed before STATUS. I think
> the correct thing to do is actually to move the NEWUNIT/UNIT if-block
> after the STATUS if-block, rather than adding a new phrasing for the
> same error.

OK. I'll check to see if this works.

> Then we should see:
> 
> pr88205.f90:13:29:
>    open (newunit=n, status=status)
>                              1
> Error: STATUS requires a scalar-default-char-expr at (1)
> 
> RE:
> >        PR fortran/88328
> >        * io.c (resolve_tag_format): Detect zero-sized array.
> [...]
> >Index: gcc/fortran/io.c
> >===================================================================
> >--- gcc/fortran/io.c    (revision 266718)
> >+++ gcc/fortran/io.c    (working copy)
> >@@ -1636,6 +1636,12 @@ resolve_tag_format (gfc_expr *e)
> >          gfc_expr *r;
> >          gfc_char_t *dest, *src;
> >
> >+         if (e->value.constructor == NULL)
> >+           {
> >+             gfc_error ("FORMAT tag at %C cannot be a zero-sized array");
> >+             return false;
> >+           }
> >+
> >          n = 0;
> >          c = gfc_constructor_first (e->value.constructor);
> >          len = c->expr->value.character.length;
> [...]
> >@ -3231,12 +3257,21 @@ gfc_resolve_dt (gfc_dt *dt, locus *loc)
> > {
> >   gfc_expr *e;
> >   io_kind k;
> >+  locus loc_tmp;
> >
> >   /* This is set in any case.  */
> >   gcc_assert (dt->dt_io_kind);
> >   k = dt->dt_io_kind->value.iokind;
> >
> >-  RESOLVE_TAG (&tag_format, dt->format_expr);
> >+  loc_tmp = gfc_current_locus;
> >+  gfc_current_locus = *loc;
> >+  if (!resolve_tag (&tag_format, dt->format_expr))
> >+    {
> >+      gfc_current_locus = loc_tmp;
> >+      return false;
> >+    }
> >+  gfc_current_locus = loc_tmp;
> >+
> >   RESOLVE_TAG (&tag_rec, dt->rec);
> >   RESOLVE_TAG (&tag_spos, dt->pos);
> >   RESOLVE_TAG (&tag_advance, dt->advance);
> 
> Is it really true that resolve_tag_format needs the locus at
> gfc_resolve_dt::loc instead of e->where as with the other errors in
> resolve_tag_format? If so, are the other errors also incorrect in
> using e->where? Might it then be better to pass loc from
> gfc_resolve_dt down to resolve_tag/RESOLVE_TAG and then
> resolve_tag_format, instead of swapping gfc_current_locus?

program p
   character(3), parameter :: a(0) = [character(3)::]
   print a
end

With the patch using loc I get

a.f90:3:10:

    3 |    print a
      |          1
Error: FORMAT tag at (1) cannot be a zero-sized array

If I used e->where one gets

a.f90:2:32:

    2 |    character(3), parameter :: a(0) = [character(3)::] 
      |                               1
Error: FORMAT tag at (1) cannot be a zero-sized array

Now, imagine a few hundred lines separating the two statements.
I think the latter error locus is preferable.

I did not audit the other uses of e->where to see where the
locus ends up pointing if those errors are triggered.

> RE:
> >        PR fortran/88048
> >        * resolve.c (check_data_variable): Convert gfc_internal_error to
> >        an gfc_error.  Add a nearby missing 'return false;'
> [...]
> >        PR fortran/88025
> >        * expr.c (gfc_apply_init): Remove asserts and check for valid
> >        ts->u.cl->length.
> [...]
> >        PR fortran/88116
> >        * simplify.c: Remove internal error and return gfc_bad_expr.
> 
> These look good.
> 
> A few pedantic comments:
> 

I'll address these before the commit.

-- 
Steve

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

* Re: Fortran patches
  2018-12-06  0:03   ` Steve Kargl
@ 2018-12-06 19:03     ` Thomas Koenig
  2018-12-06 19:23       ` Steve Kargl
  2018-12-06 22:56       ` Steve Kargl
  2018-12-06 19:09     ` Fritz Reese
  1 sibling, 2 replies; 13+ messages in thread
From: Thomas Koenig @ 2018-12-06 19:03 UTC (permalink / raw)
  To: sgk, Fritz Reese; +Cc: fortran, gcc-patches

Hi Steve,

>>>         PR fortran/88139
>>>         * dump-parse-tree.c (write_proc): Alternate return.
>> I dissent with this patch. The introduced error is meaningless and, as
>> mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
>> is not directly the issue. The code should be rejected in parsing. In
>> gcc-8.1 the invalid code is accepted (without an ICE) even without the
>> -fc-prototypes flag: I haven't finished building the compiler with
>> your changes yet to see whether that is still true afterwards, but at
>> least the test case doesn't try this, so I strongly suspect the patch
>> is incomplete to fix the PR.
>   
> Comment #3 does not contain a patch to fix the problem elsewhere.

I know :-)

> In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> I cannot find a prohibition on an alternate return in a subroutine
> interface with BIND(C).

I also does not allow this, and does not offer a valid interpretation
of what it should mean.

If it has a meaning, it should be translatable into something prescribed
by the standard with -fc-prototypes.

I have assigned the error to myself, so I will not forget to fix
it before the gcc 9 release.

Regards

	Thomas

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

* Re: Fortran patches
  2018-12-06  0:03   ` Steve Kargl
  2018-12-06 19:03     ` Thomas Koenig
@ 2018-12-06 19:09     ` Fritz Reese
  2018-12-06 19:51       ` Steve Kargl
  2018-12-07  1:21       ` Steve Kargl
  1 sibling, 2 replies; 13+ messages in thread
From: Fritz Reese @ 2018-12-06 19:09 UTC (permalink / raw)
  To: Steve Kargl; +Cc: fortran, gcc-patches, Thomas Koenig

On Wed, Dec 5, 2018 at 7:03 PM Steve Kargl
<sgk@troutmask.apl.washington.edu> wrote:
>
> On Wed, Dec 05, 2018 at 04:48:28PM -0500, Fritz Reese wrote:
[...]
> > RE:
> > >         PR fortran/88228
> > >         * expr.c (check_null, check_elemental): Work around -fdec and
> > >         initialization with logical operators operating on integers.
> >
> > I plan to review this section of the patch later today -- though the
> > patch hides the segfault from the PR, I need more time to determine
> > whether it is correct and complete.
>
> By the time the gfc_expr is given to check_check and check_elemental,
> it has been reduced to a EXPR_CONSTANT, which neither routine expected.
> I simply return early in that case.

It appears the correct solution is simply the following patch:

diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index b2090218d48..775a5c52c65 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -4004,7 +4004,7 @@ resolve_operator (gfc_expr *e)
          if (op2->ts.type != e->ts.type || op2->ts.kind != e->ts.kind)
            gfc_convert_type (op2, &e->ts, 1);
          e = logical_to_bitwise (e);
-         return resolve_function (e);
+         break;
        }

       sprintf (msg, _("Operands of logical operator %%<%s%%> at %%L
are %s/%s"),
@@ -4020,7 +4020,7 @@ resolve_operator (gfc_expr *e)
          e->ts.type = BT_INTEGER;
          e->ts.kind = op1->ts.kind;
          e = logical_to_bitwise (e);
-         return resolve_function (e);
+         break;
        }

       if (op1->ts.type == BT_LOGICAL)

Returning immediately short-circuits various checks and
simplifications which are done in the remainder of resolve_operator,
including gfc_simplify_expr which handles the EXPR_CONSTANT case. The
comments on gfc_reduce_init_expr indicate that check_null and
check_elemental should never get EXPR_CONSTANT anyway if
gfc_resolve_expr is correct. Regression tests verify this patch is
correct. Please use this patch instead for PR 88228, or if you prefer
I can submit/commit the patch myself.

>
> > RE:
> > >        PR fortran/88139
> > >        * dump-parse-tree.c (write_proc): Alternate return.
> > I dissent with this patch. The introduced error is meaningless and, as
> > mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> > is not directly the issue. The code should be rejected in parsing. In
> > gcc-8.1 the invalid code is accepted (without an ICE) even without the
> > -fc-prototypes flag: I haven't finished building the compiler with
> > your changes yet to see whether that is still true afterwards, but at
> > least the test case doesn't try this, so I strongly suspect the patch
> > is incomplete to fix the PR.
>
> Comment #3 does not contain a patch to fix the problem elsewhere.
>
> In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> I cannot find a prohibition on an alternate return in a subroutine
> interface with BIND(C).
>
> I'm disinclined to let a patch fester in bugzilla to only attain
> the same fate as my patch to PR68544.

According to F2008 §15.3.7.2(5):

> any dummy argument without the VALUE attribute [...] is interoperable with an entity of the
> referenced type (ISO/IEC 9899:1999, 6.2.5, 7.17, and 7.18.1) of the formal parameter

Regardless of whether or not we accept alternate returns in BIND(C)
procedures, the compiler must be at least consistent: if we accept
them (which gfortran currently does), then we should be able to dump
the C prototype (with -fc-prototypes), providing a formal parameter
interoperable with the type of the alternate return dummy argument; if
we reject them, then we should issue the error in parsing (before
handling by -fc-prototypes). In either case, the error message should
not be obscure or meaningless. Even so, the patch here is inconsistent
since we accept the code, but issue an error when attempting to dump
the C prototype.

However, gfortran does not implement alternate return dummy arguments
as actual arguments, but rather using an integer return code
(regardless of the number of alternate return parameters in the
interface). One interpretation of the consequences of this are that
BIND(C) should be rejected, since there is no interoperable formal
parameter which can be used to mirror the dummy argument (required by
15.3.7.2.5 above). An alternate interpretation is that we can continue
to accept BIND(C) with alternate return dummy arguments, but just
ignore the alternate return arguments. The former is perhaps more
"correct"; the latter is perhaps more useful albeit potentially
error-prone.

To patch support for the latter case, rather than issuing an error in
write_proc for procedures with alternate return arguments, we should
output the actual interoperable prototype: in this case we would
output 'int' as the return type (rather than void, as usual for
subroutines) and alternate return dummy arguments would be ignored
(not output). So the output for the example in the PR should really be
'int f()'. Something like this should do it:

diff --git a/gcc/fortran/dump-parse-tree.c b/gcc/fortran/dump-parse-tree.c
index af64588786a..9d6c3945cc5 100644
--- a/gcc/fortran/dump-parse-tree.c
+++ b/gcc/fortran/dump-parse-tree.c
@@ -3239,19 +3239,41 @@ write_proc (gfc_symbol *sym)
   gfc_formal_arglist *f;
   const char *sym_name;
   const char *intent_in;
+  bool has_alternate_returns;

   if (sym->binding_label)
     sym_name = sym->binding_label;
   else
     sym_name = sym->name;

-  if (sym->ts.type == BT_UNKNOWN)
+  /* Look for alternate return placeholders.  */
+  for (f = gfc_sym_get_dummy_args (sym); f; f = f->next)
+    {
+      if (f->sym == NULL)
+       {
+         has_alternate_returns = true;
+         break;
+       }
+    }
+
+  gfc_typespec ts = sym->ts;
+  gfc_array_spec *as = sym->as;
+  if (has_alternate_returns)
+    {
+      /* Alternate returns are implemented as an integer return code from
+         an otherwise void subroutine; override this here.  */
+      ts.type = BT_INTEGER;
+      ts.kind = gfc_c_int_kind;
+      as = NULL;
+    }
+
+  if (!has_alternate_returns && sym->ts.type == BT_UNKNOWN)
     {
       fprintf (dumpfile, "void ");
       fputs (sym_name, dumpfile);
     }
   else
-    write_decl (&(sym->ts), sym->as, sym_name, true, &sym->declared_at);
+    write_decl (&ts, as, sym_name, true, &sym->declared_at);

   fputs (" (", dumpfile);

@@ -3259,6 +3281,12 @@ write_proc (gfc_symbol *sym)
     {
       gfc_symbol *s;
       s = f->sym;
+
+      /* Ignore alternate return dummy arguments, since they are handled
+         as an integer return value.  */
+      if (!s)
+       continue;
+
       rok = get_c_type_name (&(s->ts), NULL, &pre, &type_name, &asterisk,
                             &post, false);
       if (rok == T_ERROR)


EDIT:

It appears Thomas beat me to a reply - I believe he's suggested
something like what the above diff should provide. Perhaps this will
be a useful starting point for him.


> > RE:
> > >        PR fortran/88205
> > >        * io.c (gfc_match_open): STATUS must be CHARACTER type.
[...]
> If I used e->where one gets
>
> a.f90:2:32:
>
>     2 |    character(3), parameter :: a(0) = [character(3)::]
>       |                               1
> Error: FORMAT tag at (1) cannot be a zero-sized array
>
> Now, imagine a few hundred lines separating the two statements.
> I think the latter error locus is preferable.

Yes, I agree.

Swapping gfc_current_locus definitely works, but is possibly less
readable(+maintainable) than my other suggestion of passing loc down
as an argument... But that suggestion touches more code, so there are
merits to either approach. In either case I have no real issue with
this part of the patch regardless of implementation of the locus
workaround.


Fritz

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

* Re: Fortran patches
  2018-12-06 19:03     ` Thomas Koenig
@ 2018-12-06 19:23       ` Steve Kargl
  2018-12-06 22:56       ` Steve Kargl
  1 sibling, 0 replies; 13+ messages in thread
From: Steve Kargl @ 2018-12-06 19:23 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: Fritz Reese, fortran, gcc-patches

On Thu, Dec 06, 2018 at 08:02:43PM +0100, Thomas Koenig wrote:
> Hi Steve,
> 
> >>>         PR fortran/88139
> >>>         * dump-parse-tree.c (write_proc): Alternate return.
> >> I dissent with this patch. The introduced error is meaningless and, as
> >> mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> >> is not directly the issue. The code should be rejected in parsing. In
> >> gcc-8.1 the invalid code is accepted (without an ICE) even without the
> >> -fc-prototypes flag: I haven't finished building the compiler with
> >> your changes yet to see whether that is still true afterwards, but at
> >> least the test case doesn't try this, so I strongly suspect the patch
> >> is incomplete to fix the PR.
> >   
> > Comment #3 does not contain a patch to fix the problem elsewhere.
> 
> I know :-)
> 
> > In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> > I cannot find a prohibition on an alternate return in a subroutine
> > interface with BIND(C).
> 
> I also does not allow this, and does not offer a valid interpretation
> of what it should mean.
> 
> If it has a meaning, it should be translatable into something prescribed
> by the standard with -fc-prototypes.
> 
> I have assigned the error to myself, so I will not forget to fix
> it before the gcc 9 release.

I think it comes down to F2018, 18.3.7, where one has

  A Fortran procedure interface is interoperable with a C functioni
  prototype if

   (1) ...
   (2) ...
   (3) ...
   (4) ...
   (5) any dummy argument without the VALUE attribute corresponds to
       a formal parameter of the prototype that is of a pointer type,
       and either (4 bullets which cannot be satisfied).

I suppose we should check what other compilers do on the 
testcase, but I only have access to gfortran.

BTW, write_proc() starts to write out the prototype before the
argument list is checked.  If the current gfc_error
is trigger, you get 

void foo (Error: Cannot convert %qs to interoperable type... 

I think you want to scan the formal argument list for errors
before writing out "void foo (".

-- 
Steve

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

* Re: Fortran patches
  2018-12-06 19:09     ` Fritz Reese
@ 2018-12-06 19:51       ` Steve Kargl
  2018-12-07  1:21       ` Steve Kargl
  1 sibling, 0 replies; 13+ messages in thread
From: Steve Kargl @ 2018-12-06 19:51 UTC (permalink / raw)
  To: Fritz Reese; +Cc: fortran, gcc-patches, Thomas Koenig

On Thu, Dec 06, 2018 at 02:08:54PM -0500, Fritz Reese wrote:
> On Wed, Dec 5, 2018 at 7:03 PM Steve Kargl
> <sgk@troutmask.apl.washington.edu> wrote:
> >
> > On Wed, Dec 05, 2018 at 04:48:28PM -0500, Fritz Reese wrote:
> [...]
> > > RE:
> > > >         PR fortran/88228
> > > >         * expr.c (check_null, check_elemental): Work around -fdec and
> > > >         initialization with logical operators operating on integers.
> > >
> > > I plan to review this section of the patch later today -- though the
> > > patch hides the segfault from the PR, I need more time to determine
> > > whether it is correct and complete.
> >
> > By the time the gfc_expr is given to check_check and check_elemental,
> > it has been reduced to a EXPR_CONSTANT, which neither routine expected.
> > I simply return early in that case.
> 
> It appears the correct solution is simply the following patch:
> 
> diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
> index b2090218d48..775a5c52c65 100644
> --- a/gcc/fortran/resolve.c
> +++ b/gcc/fortran/resolve.c
> @@ -4004,7 +4004,7 @@ resolve_operator (gfc_expr *e)
>           if (op2->ts.type != e->ts.type || op2->ts.kind != e->ts.kind)
>             gfc_convert_type (op2, &e->ts, 1);
>           e = logical_to_bitwise (e);
> -         return resolve_function (e);
> +         break;
>         }
> 
>        sprintf (msg, _("Operands of logical operator %%<%s%%> at %%L
> are %s/%s"),
> @@ -4020,7 +4020,7 @@ resolve_operator (gfc_expr *e)
>           e->ts.type = BT_INTEGER;
>           e->ts.kind = op1->ts.kind;
>           e = logical_to_bitwise (e);
> -         return resolve_function (e);
> +         break;
>         }

Intersting.  I wonder why resolve_function() appears here.  
Hmmm, 'svn annotate' points to r241535 with the committer
being foreese. :-)  Log message says you are trying to convert
logical op on integers for DEC.  Were trying to catch the
logical functions like NOT()?

I'll include the above in my patch Saturday activities.


> > > >        PR fortran/88139
> > > >        * dump-parse-tree.c (write_proc): Alternate return.
> > > I dissent with this patch. The introduced error is meaningless and, as
> > > mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> > > is not directly the issue. The code should be rejected in parsing. In
> > > gcc-8.1 the invalid code is accepted (without an ICE) even without the
> > > -fc-prototypes flag: I haven't finished building the compiler with
> > > your changes yet to see whether that is still true afterwards, but at
> > > least the test case doesn't try this, so I strongly suspect the patch
> > > is incomplete to fix the PR.
> >
> > Comment #3 does not contain a patch to fix the problem elsewhere.
> >
> > In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> > I cannot find a prohibition on an alternate return in a subroutine
> > interface with BIND(C).
> >
> > I'm disinclined to let a patch fester in bugzilla to only attain
> > the same fate as my patch to PR68544.
> 
> According to F2008 §15.3.7.2(5):
> 
> > any dummy argument without the VALUE attribute [...] is interoperable with an entity of the
> > referenced type (ISO/IEC 9899:1999, 6.2.5, 7.17, and 7.18.1) of the formal parameter

Yep.

> Regardless of whether or not we accept alternate returns in BIND(C)
> procedures, the compiler must be at least consistent: if we accept
> them (which gfortran currently does), then we should be able to dump
> the C prototype (with -fc-prototypes), providing a formal parameter
> interoperable with the type of the alternate return dummy argument; if
> we reject them, then we should issue the error in parsing (before
> handling by -fc-prototypes). In either case, the error message should
> not be obscure or meaningless. Even so, the patch here is inconsistent
> since we accept the code, but issue an error when attempting to dump

I think we should determine what other compilers do with
BIND(C) and alternate return dummy arguments, and follow
suit.  


> > > >        PR fortran/88205
> > > >        * io.c (gfc_match_open): STATUS must be CHARACTER type.
> [...]
> > If I used e->where one gets
> >
> > a.f90:2:32:
> >
> >     2 |    character(3), parameter :: a(0) = [character(3)::]
> >       |                               1
> > Error: FORMAT tag at (1) cannot be a zero-sized array
> >
> > Now, imagine a few hundred lines separating the two statements.
> > I think the latter error locus is preferable.
> 
> Yes, I agree.
> 
> Swapping gfc_current_locus definitely works, but is possibly less
> readable(+maintainable) than my other suggestion of passing loc down
> as an argument... But that suggestion touches more code, so there are
> merits to either approach. In either case I have no real issue with
> this part of the patch regardless of implementation of the locus
> workaround.

I agree that this could get messy, but I'm hoping only
format strings need this special handling.  A Fortran
string must contain '(' and ')', so zero-sized arrays
can never appear as a fmt=array.  

-- 
Steve

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

* Re: Fortran patches
  2018-12-06 19:03     ` Thomas Koenig
  2018-12-06 19:23       ` Steve Kargl
@ 2018-12-06 22:56       ` Steve Kargl
  1 sibling, 0 replies; 13+ messages in thread
From: Steve Kargl @ 2018-12-06 22:56 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: Fritz Reese, fortran, gcc-patches

On Thu, Dec 06, 2018 at 08:02:43PM +0100, Thomas Koenig wrote:
> >>>         PR fortran/88139
> >>>         * dump-parse-tree.c (write_proc): Alternate return.
> >> I dissent with this patch. The introduced error is meaningless and, as
> >> mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> >> is not directly the issue. The code should be rejected in parsing. In
> >> gcc-8.1 the invalid code is accepted (without an ICE) even without the
> >> -fc-prototypes flag: I haven't finished building the compiler with
> >> your changes yet to see whether that is still true afterwards, but at
> >> least the test case doesn't try this, so I strongly suspect the patch
> >> is incomplete to fix the PR.
> >   
> > Comment #3 does not contain a patch to fix the problem elsewhere.
> 
> I know :-)
> 
> > In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> > I cannot find a prohibition on an alternate return in a subroutine
> > interface with BIND(C).
> 
> I also does not allow this, and does not offer a valid interpretation
> of what it should mean.
> 
> If it has a meaning, it should be translatable into something prescribed
> by the standard with -fc-prototypes.
> 
> I have assigned the error to myself, so I will not forget to fix
> it before the gcc 9 release.
> 

I have asked on c.l.f.  It seems NAG rejects alternate return
mixed with bind(c).  FortranFan provided a complete testcase:

   subroutine foo(*) bind(C, name='f')
   end subroutine foo
program p
   interface
      subroutine bar(*) bind(C, name='f')
      end subroutine bar
   end interface
   call bar( *10 )
   print *, "Return following 'bar' invocation: jumping to 20"
   go to 20
10 print *, "THIS IS UNEXPECTED: Alternate return to 10 after bar"
20 continue
   stop
end program p

NAG rejects it.  Intel, PGI, and gfortran accept it.

-- 
Steve

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

* Re: Fortran patches
  2018-12-06 19:09     ` Fritz Reese
  2018-12-06 19:51       ` Steve Kargl
@ 2018-12-07  1:21       ` Steve Kargl
  2018-12-07  1:49         ` Steve Kargl
  1 sibling, 1 reply; 13+ messages in thread
From: Steve Kargl @ 2018-12-07  1:21 UTC (permalink / raw)
  To: Fritz Reese; +Cc: fortran, gcc-patches, Thomas Koenig

On Thu, Dec 06, 2018 at 02:08:54PM -0500, Fritz Reese wrote:
> On Wed, Dec 5, 2018 at 7:03 PM Steve Kargl
> >
> > > RE:
> > > >        PR fortran/88139
> > > >        * dump-parse-tree.c (write_proc): Alternate return.
> > > I dissent with this patch. The introduced error is meaningless and, as
> > > mentioned by comment #3 in the PR, avoiding the ICE in dump-parse-tree
> > > is not directly the issue. The code should be rejected in parsing. In
> > > gcc-8.1 the invalid code is accepted (without an ICE) even without the
> > > -fc-prototypes flag: I haven't finished building the compiler with
> > > your changes yet to see whether that is still true afterwards, but at
> > > least the test case doesn't try this, so I strongly suspect the patch
> > > is incomplete to fix the PR.
> >
> > Comment #3 does not contain a patch to fix the problem elsewhere.
> >
> > In F2003, 15.2.6 "Interoperability of procedures and procedure interfaces",
> > I cannot find a prohibition on an alternate return in a subroutine
> > interface with BIND(C).
> >
> > I'm disinclined to let a patch fester in bugzilla to only attain
> > the same fate as my patch to PR68544.
> 
> According to F2008 §15.3.7.2(5):
> 
> > any dummy argument without the VALUE attribute [...] is interoperable with an entity of the
> > referenced type (ISO/IEC 9899:1999, 6.2.5, 7.17, and 7.18.1) of the formal parameter
> 
> Regardless of whether or not we accept alternate returns in BIND(C)
> procedures, the compiler must be at least consistent: if we accept
> them (which gfortran currently does), then we should be able to dump
> the C prototype (with -fc-prototypes), providing a formal parameter
> interoperable with the type of the alternate return dummy argument; if
> we reject them, then we should issue the error in parsing (before
> handling by -fc-prototypes). In either case, the error message should
> not be obscure or meaningless. Even so, the patch here is inconsistent
> since we accept the code, but issue an error when attempting to dump
> the C prototype.

Here's an alternative patch that would reject a subroutine
with an alternate return dummy argument with the bind(c)
attributes.  I'm still trying to determine if the code 
should be legal.  The c.l.f thread I started isn't helping :(

Index: decl.c
===================================================================
--- decl.c	(revision 266766)
+++ decl.c	(working copy)
@@ -7467,6 +7467,7 @@ gfc_match_subroutine (void)
   match is_bind_c;
   char peek_char;
   bool allow_binding_name;
+  locus loc;
 
   if (gfc_current_state () != COMP_NONE
       && gfc_current_state () != COMP_INTERFACE
@@ -7532,6 +7533,8 @@ gfc_match_subroutine (void)
   /* Here, we are just checking if it has the bind(c) attribute, and if
      so, then we need to make sure it's all correct.  If it doesn't,
      we still need to continue matching the rest of the subroutine line.  */
+  gfc_gobble_whitespace ();
+  loc = gfc_current_locus;
   is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
   if (is_bind_c == MATCH_ERROR)
     {
@@ -7543,6 +7546,8 @@ gfc_match_subroutine (void)
 
   if (is_bind_c == MATCH_YES)
     {
+      gfc_formal_arglist *arg;
+
       /* The following is allowed in the Fortran 2008 draft.  */
       if (gfc_current_state () == COMP_CONTAINS
 	  && sym->ns->proc_name->attr.flavor != FL_MODULE
@@ -7556,8 +7561,17 @@ gfc_match_subroutine (void)
           gfc_error ("Missing required parentheses before BIND(C) at %C");
           return MATCH_ERROR;
         }
-      if (!gfc_add_is_bind_c (&(sym->attr), sym->name,
-			      &(sym->declared_at), 1))
+
+      /* Scan the dummy arguments for an alternate return.  */
+      for (arg = sym->formal; arg; arg = arg->next)
+	if (!arg->sym)
+	  {
+	    gfc_error ("Alternate return dummy argument cannot appear in a "
+		       "SUBROUTINE with the BIND(C) attribute at %L", &loc);
+	    return MATCH_ERROR;
+	  }
+
+      if (!gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1))
         return MATCH_ERROR;
     }

-- 
steve

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

* Re: Fortran patches
  2018-12-07  1:21       ` Steve Kargl
@ 2018-12-07  1:49         ` Steve Kargl
  0 siblings, 0 replies; 13+ messages in thread
From: Steve Kargl @ 2018-12-07  1:49 UTC (permalink / raw)
  To: Fritz Reese; +Cc: fortran, gcc-patches, Thomas Koenig

On Thu, Dec 06, 2018 at 05:21:32PM -0800, Steve Kargl wrote:
> 
> Here's an alternative patch that would reject a subroutine
> with an alternate return dummy argument with the bind(c)
> attributes.  I'm still trying to determine if the code 
> should be legal.  The c.l.f thread I started isn't helping :(

I think I have found the restriction.  In F2018,

C1554  If proc-language-binding-spec is specified for a procedure, each
       of its dummy arguments shall be an interoperable procedure (18.3.7)
       or a variable that is interoperable (18.3.5, 18.3.6), assumed-shape,
       assumed-rank, assumed-type, of type CHARACTER with assumed length,
       or that has the ALLOCATABLE or POINTER attribute.


> 
> Index: decl.c
> ===================================================================
> --- decl.c	(revision 266766)
> +++ decl.c	(working copy)
> @@ -7467,6 +7467,7 @@ gfc_match_subroutine (void)
>    match is_bind_c;
>    char peek_char;
>    bool allow_binding_name;
> +  locus loc;
>  
>    if (gfc_current_state () != COMP_NONE
>        && gfc_current_state () != COMP_INTERFACE
> @@ -7532,6 +7533,8 @@ gfc_match_subroutine (void)
>    /* Here, we are just checking if it has the bind(c) attribute, and if
>       so, then we need to make sure it's all correct.  If it doesn't,
>       we still need to continue matching the rest of the subroutine line.  */
> +  gfc_gobble_whitespace ();
> +  loc = gfc_current_locus;
>    is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
>    if (is_bind_c == MATCH_ERROR)
>      {
> @@ -7543,6 +7546,8 @@ gfc_match_subroutine (void)
>  
>    if (is_bind_c == MATCH_YES)
>      {
> +      gfc_formal_arglist *arg;
> +
>        /* The following is allowed in the Fortran 2008 draft.  */
>        if (gfc_current_state () == COMP_CONTAINS
>  	  && sym->ns->proc_name->attr.flavor != FL_MODULE
> @@ -7556,8 +7561,17 @@ gfc_match_subroutine (void)
>            gfc_error ("Missing required parentheses before BIND(C) at %C");
>            return MATCH_ERROR;
>          }
> -      if (!gfc_add_is_bind_c (&(sym->attr), sym->name,
> -			      &(sym->declared_at), 1))
> +
> +      /* Scan the dummy arguments for an alternate return.  */
> +      for (arg = sym->formal; arg; arg = arg->next)
> +	if (!arg->sym)
> +	  {
> +	    gfc_error ("Alternate return dummy argument cannot appear in a "
> +		       "SUBROUTINE with the BIND(C) attribute at %L", &loc);
> +	    return MATCH_ERROR;
> +	  }
> +
> +      if (!gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1))
>          return MATCH_ERROR;
>      }
> 
> -- 
> steve

-- 
Steve
20170425 https://www.youtube.com/watch?v=VWUpyCsUKR4
20161221 https://www.youtube.com/watch?v=IbCHE-hONow

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

* Re: Fortran Patches
  2011-09-16  8:14 ` Janus Weil
@ 2011-09-17 13:31   ` Janus Weil
  0 siblings, 0 replies; 13+ messages in thread
From: Janus Weil @ 2011-09-17 13:31 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc patches, gfortran

>> Regarding the last patch, the GNU style puts a line break after the ")" in:
>>
>> +  if (!sym) return NULL;
>> +
>
> In principle I'm aware of the GNU coding style, but apparently I
> didn't pay enough attention. Sorry again. I'll fix it ...


Fixed with r178928.

Cheers,
Janus

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

* Re: Fortran Patches
  2011-09-16  7:44 Fortran Patches Tobias Burnus
@ 2011-09-16  8:14 ` Janus Weil
  2011-09-17 13:31   ` Janus Weil
  0 siblings, 1 reply; 13+ messages in thread
From: Janus Weil @ 2011-09-16  8:14 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc patches, gfortran

Hi Tobias,

> could you also patches, which you commit as obvious to the mailing lists?

yes, I usually do this, but this time I just forgot. Sorry.


> Regarding the last patch, the GNU style puts a line break after the ")" in:
>
> +  if (!sym) return NULL;
> +

In principle I'm aware of the GNU coding style, but apparently I
didn't pay enough attention. Sorry again. I'll fix it ...

Cheers,
Janus

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

* Fortran Patches
@ 2011-09-16  7:44 Tobias Burnus
  2011-09-16  8:14 ` Janus Weil
  0 siblings, 1 reply; 13+ messages in thread
From: Tobias Burnus @ 2011-09-16  7:44 UTC (permalink / raw)
  To: Janus Weil, gcc patches, gfortran

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

Hi Janus,

could you also patches, which you commit as obvious to the mailing lists?

Regarding the last patch, the GNU style puts a line break after the ")" in:

+  if (!sym) return NULL;
+

Tobias

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

commit 12c8610481cc199a6019cd41d07dbdf8906032d0
Author: janus <janus@138bc75d-0d04-0410-961f-82ee72b054a4>
Date:   Thu Sep 15 17:48:27 2011 +0000

    2011-09-15  Janus Weil  <janus@gcc.gnu.org>
    
    	PR fortran/50401
    	* resolve.c (resolve_transfer): Check if component 'ref' is defined.
    
    	PR fortran/50403
    	* symbol.c (gfc_use_derived): Check if argument 'sym' is defined.
    
    
    2011-09-15  Janus Weil  <janus@gcc.gnu.org>
    
    	PR fortran/50401
    	PR fortran/50403
    	* gfortran.dg/function_types_3.f90: New.
    
    
    git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@178889 138bc75d-0d04-0410-961f-82ee72b054a4

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index eeb462f..a8e0273 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,11 @@
+2011-09-15  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/50401
+	* resolve.c (resolve_transfer): Check if component 'ref' is defined.
+
+	PR fortran/50403
+	* symbol.c (gfc_use_derived): Check if argument 'sym' is defined.
+
 2011-09-14  Tobias Burnus  <burnus@net-b.de>
 
 	PR fortran/34547
diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index 9aab836..62750af 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -8222,7 +8222,7 @@ resolve_transfer (gfc_code *code)
 	}
     }
 
-  if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
+  if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
     {
       gfc_error ("Data transfer element at %L cannot be a full reference to "
diff --git a/gcc/fortran/symbol.c b/gcc/fortran/symbol.c
index b2f0f2b..e2f13b8 100644
--- a/gcc/fortran/symbol.c
+++ b/gcc/fortran/symbol.c
@@ -1945,6 +1945,8 @@ gfc_use_derived (gfc_symbol *sym)
   gfc_symtree *st;
   int i;
 
+  if (!sym) return NULL;
+
   if (sym->components != NULL || sym->attr.zero_comp)
     return sym;               /* Already defined.  */
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 86cdde0..0accd60 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,9 @@
+2011-09-15  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/50401
+	PR fortran/50403
+	* gfortran.dg/function_types_3.f90: New.
+
 2011-09-15  Jason Merrill  <jason@redhat.com>
 
 	PR c++/50365
diff --git a/gcc/testsuite/gfortran.dg/function_types_3.f90 b/gcc/testsuite/gfortran.dg/function_types_3.f90
new file mode 100644
index 0000000..8d00f5f
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/function_types_3.f90
@@ -0,0 +1,19 @@
+! { dg-do compile }
+!
+! Contributed by Vittorio Zecca <zeccav@gmail.com>
+!
+! PR 50401: SIGSEGV in resolve_transfer
+
+  interface 
+    function f()      ! { dg-error "must be a dummy argument" }
+      dimension f(*)
+    end function
+  end interface
+  print *,f()
+end
+
+! PR 50403: SIGSEGV in gfc_use_derived
+
+type(f) function f()  ! { dg-error "conflicts with DERIVED attribute|is not accessible" }
+  f=110               ! { dg-error "Unclassifiable statement" }
+end

[-- Attachment #3: janus2.diff --]
[-- Type: text/x-patch, Size: 2095 bytes --]

commit cde48a27b12d2c4d1a5aababb94f6695e9c00469
Author: janus <janus@138bc75d-0d04-0410-961f-82ee72b054a4>
Date:   Tue Sep 13 18:37:33 2011 +0000

    2011-09-13  Janus Weil  <janus@gcc.gnu.org>
    
    	PR fortran/50379
    	* symbol.c (check_conflict): Check conflict between GENERIC and RESULT
    	attributes.
    
    
    2011-09-13  Janus Weil  <janus@gcc.gnu.org>
    
    	PR fortran/50379
    	* gfortran.dg/result_2.f90: New.
    
    
    git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@178829 138bc75d-0d04-0410-961f-82ee72b054a4

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 836967d..6e82538 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,9 @@
+2011-09-13  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/50379
+	* symbol.c (check_conflict): Check conflict between GENERIC and RESULT
+	attributes.
+
 2011-09-11  Thomas Koenig  <tkoenig@gcc.gnu.org>
 
 	PR fortran/50327
diff --git a/gcc/fortran/symbol.c b/gcc/fortran/symbol.c
index ce4ab3d..b2f0f2b 100644
--- a/gcc/fortran/symbol.c
+++ b/gcc/fortran/symbol.c
@@ -373,7 +373,7 @@ check_conflict (symbol_attribute *attr, const char *name, locus *where)
     *volatile_ = "VOLATILE", *is_protected = "PROTECTED",
     *is_bind_c = "BIND(C)", *procedure = "PROCEDURE",
     *asynchronous = "ASYNCHRONOUS", *codimension = "CODIMENSION",
-    *contiguous = "CONTIGUOUS";
+    *contiguous = "CONTIGUOUS", *generic = "GENERIC";
   static const char *threadprivate = "THREADPRIVATE";
 
   const char *a1, *a2;
@@ -490,8 +490,6 @@ check_conflict (symbol_attribute *attr, const char *name, locus *where)
   conf (in_common, codimension);
   conf (in_common, result);
 
-  conf (dummy, result);
-
   conf (in_equivalence, use_assoc);
   conf (in_equivalence, codimension);
   conf (in_equivalence, dummy);
@@ -503,7 +501,9 @@ check_conflict (symbol_attribute *attr, const char *name, locus *where)
   conf (in_equivalence, allocatable);
   conf (in_equivalence, threadprivate);
 
+  conf (dummy, result);
   conf (entry, result);
+  conf (generic, result);
 
   conf (function, subroutine);
 

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

end of thread, other threads:[~2018-12-07  1:49 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2018-12-05  4:59 Fortran patches Steve Kargl
2018-12-05 21:49 ` Fritz Reese
2018-12-06  0:03   ` Steve Kargl
2018-12-06 19:03     ` Thomas Koenig
2018-12-06 19:23       ` Steve Kargl
2018-12-06 22:56       ` Steve Kargl
2018-12-06 19:09     ` Fritz Reese
2018-12-06 19:51       ` Steve Kargl
2018-12-07  1:21       ` Steve Kargl
2018-12-07  1:49         ` Steve Kargl
  -- strict thread matches above, loose matches on Subject: below --
2011-09-16  7:44 Fortran Patches Tobias Burnus
2011-09-16  8:14 ` Janus Weil
2011-09-17 13:31   ` Janus Weil

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).