The attached patch by Chris from the subject bug report.

Regression tested on x86_64.

OK to commit to mainline?

Regards,

Jerry

commit 7bf6896c1448382f27b86b17f75a7eec1ee7ffbc
Author: Jerry DeLisle <[email protected]>
Date:   Mon Nov 17 18:55:03 2025 -0800

    fortran: Enforce spec statement ordering [PR32365]

            PR fortran/32365

    gcc/fortran/ChangeLog:

            * parse.cc (parse_executable): Reject declaration/OpenMP
            specification statements seen after executable code
            unconditionally, keeping the legacy DATA diagnostic as
            a warning.

    gcc/testsuite/ChangeLog:

            * gfortran.dg/common_22.f90: Update.
            * gfortran.dg/common_24.f: Update.
            * gfortran.dg/goacc/routine-1.f90: Update.
            * gfortran.dg/goacc/routine-2.f90: Update.
            * gfortran.dg/gomp/declare-variant-17.f90: Update.
            * gfortran.dg/gomp/interop-1.f90: Update.
            * gfortran.dg/gomp/order-2.f90: Update.
            * gfortran.dg/gomp/pr78026.f03: Update.
            * gfortran.dg/gomp/requires-4.f90: Update.
            * gfortran.dg/gomp/requires-6.f90: Update.
            * gfortran.dg/pr61669.f90: Update.
            * gfortran.dg/spec_statement_in_exec.f90: New test exercises
            data/common/namelist/OpenMP directives with -fopenmp.

    Signed-off-by: Christopher Albert <[email protected]>
diff --git a/gcc/fortran/parse.cc b/gcc/fortran/parse.cc
index 19139ccb955..e4d65200f3a 100644
--- a/gcc/fortran/parse.cc
+++ b/gcc/fortran/parse.cc
@@ -7132,6 +7132,15 @@ loop:
 	  accept_statement (st);
 	  goto done;
 
+	/* Specification statements cannot appear after executable statements.  */
+	case_decl:
+	case_omp_decl:
+	  gfc_error ("%s statement at %C cannot appear after executable statements",
+		     gfc_ascii_statement (st));
+	  reject_statement ();
+	  st = next_statement ();
+	  continue;
+
 	default:
 	  break;
 	}
diff --git a/gcc/testsuite/gfortran.dg/common_22.f90 b/gcc/testsuite/gfortran.dg/common_22.f90
index e2254099d72..f92319b8076 100644
--- a/gcc/testsuite/gfortran.dg/common_22.f90
+++ b/gcc/testsuite/gfortran.dg/common_22.f90
@@ -7,18 +7,18 @@
 ! Contributed by Bud Davis  <[email protected]>
 
       CALL RCCFL (NVE,IR,NU3,VE (1,1,1,I))
-      COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
-      COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
+      COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
+      COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
 !  the PR only contained the two above.
 !  success is no segfaults or infinite loops.
 !  let's check some combinations
      CALL ABC (INTG)
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
      CALL DEF (NT1)
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
      CALL GHI (NRESL)
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
-     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "Unexpected COMMON" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
+     COMMON /CCFILE/ INTG,NT1,NT2,NT3,NVM,NVE,NFRLE,NRESF,NRESL !{ dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
      END
diff --git a/gcc/testsuite/gfortran.dg/common_24.f b/gcc/testsuite/gfortran.dg/common_24.f
index ea37c2a8660..1f35a40158e 100644
--- a/gcc/testsuite/gfortran.dg/common_24.f
+++ b/gcc/testsuite/gfortran.dg/common_24.f
@@ -7,5 +7,5 @@ c Contributed by Ilya Enkovich <[email protected]>
 
       COMMON /FMCOM / X(80 000 000)
       CALL T(XX(A))
-      COMMON /FMCOM / XX(80 000 000) ! { dg-error "Unexpected COMMON" }
+      COMMON /FMCOM / XX(80 000 000) ! { dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
       END
diff --git a/gcc/testsuite/gfortran.dg/goacc/routine-1.f90 b/gcc/testsuite/gfortran.dg/goacc/routine-1.f90
index 67c5f11be6a..6378c31309f 100644
--- a/gcc/testsuite/gfortran.dg/goacc/routine-1.f90
+++ b/gcc/testsuite/gfortran.dg/goacc/routine-1.f90
@@ -4,7 +4,7 @@
   integer :: a(n), i
   integer, external :: fact
   i = 1
-  !$acc routine (fact)  ! { dg-error "Unexpected \\\!\\\$ACC ROUTINE" }
+  !$acc routine (fact)  ! { dg-error "\\!\\$ACC ROUTINE statement at \\(1\\) cannot appear after executable statements" }
   !$acc routine ()  ! { dg-error "Syntax error in \\\!\\\$ACC ROUTINE \\\( NAME \\\)" }
   !$acc parallel
   !$acc loop
@@ -21,7 +21,7 @@ recursive function fact (x) result (res)
   integer, intent(in) :: x
   integer :: res
   res = 1
-  !$acc routine  ! { dg-error "Unexpected \\\!\\\$ACC ROUTINE" }
+  !$acc routine  ! { dg-error "\\!\\$ACC ROUTINE statement at \\(1\\) cannot appear after executable statements" }
   if (x < 1) then
      res = 1
   else
@@ -32,6 +32,6 @@ subroutine incr (x)
   integer, intent(inout) :: x
   integer i
   i = 0
-  !$acc routine  ! { dg-error "Unexpected \\\!\\\$ACC ROUTINE" }
+  !$acc routine  ! { dg-error "\\!\\$ACC ROUTINE statement at \\(1\\) cannot appear after executable statements" }
   x = x + 1
 end subroutine incr
diff --git a/gcc/testsuite/gfortran.dg/goacc/routine-2.f90 b/gcc/testsuite/gfortran.dg/goacc/routine-2.f90
index 3be33511581..28d3205f4a7 100644
--- a/gcc/testsuite/gfortran.dg/goacc/routine-2.f90
+++ b/gcc/testsuite/gfortran.dg/goacc/routine-2.f90
@@ -7,7 +7,7 @@
       integer :: res
       integer i
       i = 0
-      !$acc routine  ! { dg-error "Unexpected \\\!\\\$ACC ROUTINE" }
+      !$acc routine  ! { dg-error "\\!\\$ACC ROUTINE statement at \\(1\\) cannot appear after executable statements" }
       if (x < 1) then
          res = 1
       else
diff --git a/gcc/testsuite/gfortran.dg/gomp/declare-variant-17.f90 b/gcc/testsuite/gfortran.dg/gomp/declare-variant-17.f90
index df57f9c089c..9010a2369a8 100644
--- a/gcc/testsuite/gfortran.dg/gomp/declare-variant-17.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/declare-variant-17.f90
@@ -7,11 +7,11 @@ program main
 
   continue
 
-  !$omp declare variant (base: variant) match (construct={parallel})  ! { dg-error "Unexpected \\\!\\\$OMP DECLARE VARIANT statement at .1." }
+  !$omp declare variant (base: variant) match (construct={parallel})  ! { dg-error "\\!\\$OMP DECLARE VARIANT statement at \\(1\\) cannot appear after executable statements" }
 contains
   subroutine base ()
     continue
 
-    !$omp declare variant (variant) match (construct={parallel})  ! { dg-error "Unexpected \\\!\\\$OMP DECLARE VARIANT statement at .1." }
+    !$omp declare variant (variant) match (construct={parallel})  ! { dg-error "\\!\\$OMP DECLARE VARIANT statement at \\(1\\) cannot appear after executable statements" }
   end subroutine
 end program
diff --git a/gcc/testsuite/gfortran.dg/gomp/interop-1.f90 b/gcc/testsuite/gfortran.dg/gomp/interop-1.f90
index eae0cb3ae16..9dd047006ff 100644
--- a/gcc/testsuite/gfortran.dg/gomp/interop-1.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/interop-1.f90
@@ -19,7 +19,7 @@ end module m
 
 subroutine sub1  ! { dg-error "Program unit at .1. has OpenMP device constructs/routines but does not set !.OMP REQUIRES REVERSE_OFFLOAD but other program units do" }
   !$omp interop
-  integer :: y ! { dg-error "Unexpected data declaration statement" }
+  integer :: y ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
 end subroutine sub1
 
 program main
diff --git a/gcc/testsuite/gfortran.dg/gomp/order-2.f90 b/gcc/testsuite/gfortran.dg/gomp/order-2.f90
index 4ee3a82d518..d1fb310f90f 100644
--- a/gcc/testsuite/gfortran.dg/gomp/order-2.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/order-2.f90
@@ -11,14 +11,14 @@ contains
     implicit none
     integer, save :: t
     t = 1
-    !$omp threadprivate (t1)	! { dg-error "Unexpected" }
+    !$omp threadprivate (t1)	! { dg-error "\\!\\$OMP THREADPRIVATE statement at \\(1\\) cannot appear after executable statements" }
   end subroutine f2
   subroutine f3
     use m
     implicit none
     integer :: j
     j = 1
-    !$omp declare reduction (foo:real:omp_out = omp_out + omp_in)	! { dg-error "Unexpected" }
+    !$omp declare reduction (foo:real:omp_out = omp_out + omp_in)	! { dg-error "\\!\\$OMP DECLARE REDUCTION statement at \\(1\\) cannot appear after executable statements" }
   end subroutine f3
   subroutine f4
     use m
@@ -26,12 +26,12 @@ contains
     !$omp declare target
     integer, save :: f4_1
     f4_1 = 1
-    !$omp declare target (f4_1)	! { dg-error "Unexpected" }
-    !$omp declare target	! { dg-error "Unexpected" }
+    !$omp declare target (f4_1)	! { dg-error "\\!\\$OMP DECLARE TARGET statement at \\(1\\) cannot appear after executable statements" }
+    !$omp declare target	! { dg-error "\\!\\$OMP DECLARE TARGET statement at \\(1\\) cannot appear after executable statements" }
   end subroutine f4
   integer function f5 (a, b)
     integer :: a, b
     a = 1; b = 2
-    !$omp declare simd (f5) notinbranch	! { dg-error "Unexpected" }
+    !$omp declare simd (f5) notinbranch	! { dg-error "\\!\\$OMP DECLARE SIMD statement at \\(1\\) cannot appear after executable statements" }
   end function f5
 end subroutine f1
diff --git a/gcc/testsuite/gfortran.dg/gomp/pr78026.f03 b/gcc/testsuite/gfortran.dg/gomp/pr78026.f03
index 61f945886e6..6995abc8367 100644
--- a/gcc/testsuite/gfortran.dg/gomp/pr78026.f03
+++ b/gcc/testsuite/gfortran.dg/gomp/pr78026.f03
@@ -1,5 +1,5 @@
 ! PR fortran/78026
 select type (a)		! { dg-error "Selector shall be polymorphic in SELECT TYPE statement" }
 end select
-!$omp declare simd(b)	! { dg-error "Unexpected !.OMP DECLARE SIMD statement" }
+!$omp declare simd(b)	! { dg-error "\\!\\$OMP DECLARE SIMD statement at \\(1\\) cannot appear after executable statements" }
 end			! { dg-error "should refer to containing procedure" "" { target *-*-* } .-1 }
diff --git a/gcc/testsuite/gfortran.dg/gomp/requires-4.f90 b/gcc/testsuite/gfortran.dg/gomp/requires-4.f90
index 9d936197f8f..fd4d0a8d7c3 100644
--- a/gcc/testsuite/gfortran.dg/gomp/requires-4.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/requires-4.f90
@@ -16,7 +16,7 @@ end
 
 subroutine foobar
 i = 5  ! < execution statement
-!$omp requires atomic_default_mem_order(seq_cst) ! { dg-error "Unexpected ..OMP REQUIRES statement" }
+!$omp requires atomic_default_mem_order(seq_cst) ! { dg-error "\\!\\$OMP REQUIRES statement at \\(1\\) cannot appear after executable statements" }
 end
 
 program main
diff --git a/gcc/testsuite/gfortran.dg/gomp/requires-6.f90 b/gcc/testsuite/gfortran.dg/gomp/requires-6.f90
index b20c218dd6b..10a6e696091 100644
--- a/gcc/testsuite/gfortran.dg/gomp/requires-6.f90
+++ b/gcc/testsuite/gfortran.dg/gomp/requires-6.f90
@@ -10,5 +10,5 @@ end
 subroutine foobar
 !$omp atomic
  i = i + 5
-!$omp requires atomic_default_mem_order(acq_rel) ! { dg-error "Unexpected !.OMP REQUIRES statement" }
+!$omp requires atomic_default_mem_order(acq_rel) ! { dg-error "\\!\\$OMP REQUIRES statement at \\(1\\) cannot appear after executable statements" }
 end
diff --git a/gcc/testsuite/gfortran.dg/pr61669.f90 b/gcc/testsuite/gfortran.dg/pr61669.f90
index 5bceafda762..ce38d13c979 100644
--- a/gcc/testsuite/gfortran.dg/pr61669.f90
+++ b/gcc/testsuite/gfortran.dg/pr61669.f90
@@ -1,7 +1,7 @@
 ! { dg-do compile }
       write (*,"(a)") char(12)
-      CHARACTER*80 A /"A"/      ! { dg-error "Unexpected data declaration statement" }
-      REAL*4 B                  ! { dg-error "Unexpected data declaration statement" }
+      CHARACTER*80 A /"A"/      ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+      REAL*4 B                  ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
       write (*,"(a)") char(12)
       DATA B / 0.02 /           ! { dg-warning "Obsolescent feature: DATA statement" }
       END
diff --git a/gcc/testsuite/gfortran.dg/spec_statement_in_exec.f90 b/gcc/testsuite/gfortran.dg/spec_statement_in_exec.f90
new file mode 100644
index 00000000000..9134a1ec315
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/spec_statement_in_exec.f90
@@ -0,0 +1,26 @@
+! { dg-do compile }
+! { dg-options "-fopenmp" }
+! Test improved error messages for specification statements in executable section
+! PR fortran/32365 - Better error message for specification statement in executable section
+
+subroutine test_spec_in_exec
+  implicit none
+  integer :: i
+
+  ! First executable statement
+  i = 1
+
+  ! Test key specification statement types
+  integer :: j                     ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  real :: x                       ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  complex :: z                    ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  logical :: flag                  ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  character(len=20) :: name       ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  double precision :: d           ! { dg-error "data declaration statement at \\(1\\) cannot appear after executable statements" }
+  common /myblock/ i              ! { dg-error "COMMON statement at \\(1\\) cannot appear after executable statements" }
+  equivalence (i, i)              ! { dg-error "EQUIVALENCE statement at \\(1\\) cannot appear after executable statements" }
+  namelist /nml/ i                ! { dg-error "NAMELIST statement at \\(1\\) cannot appear after executable statements" }
+!$omp threadprivate(i)             ! { dg-error "THREADPRIVATE statement at \\(1\\) cannot appear after executable statements" }
+!$omp declare target (i)           ! { dg-error "DECLARE TARGET statement at \\(1\\) cannot appear after executable statements" }
+
+end subroutine test_spec_in_exec

Reply via email to