]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
fortran: Enforce spec statement ordering [PR32365]
authorJerry DeLisle <jvdelisle@gcc.gnu.org>
Tue, 18 Nov 2025 02:55:03 +0000 (18:55 -0800)
committerJerry DeLisle <jvdelisle@gcc.gnu.org>
Tue, 18 Nov 2025 16:47:58 +0000 (08:47 -0800)
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 <albert@tugraz.at>
13 files changed:
gcc/fortran/parse.cc
gcc/testsuite/gfortran.dg/common_22.f90
gcc/testsuite/gfortran.dg/common_24.f
gcc/testsuite/gfortran.dg/goacc/routine-1.f90
gcc/testsuite/gfortran.dg/goacc/routine-2.f90
gcc/testsuite/gfortran.dg/gomp/declare-variant-17.f90
gcc/testsuite/gfortran.dg/gomp/interop-1.f90
gcc/testsuite/gfortran.dg/gomp/order-2.f90
gcc/testsuite/gfortran.dg/gomp/pr78026.f03
gcc/testsuite/gfortran.dg/gomp/requires-4.f90
gcc/testsuite/gfortran.dg/gomp/requires-6.f90
gcc/testsuite/gfortran.dg/pr61669.f90
gcc/testsuite/gfortran.dg/spec_statement_in_exec.f90 [new file with mode: 0644]

index 19139ccb9559c668ad9d1b0c07d257475c1e3ac4..e4d65200f3abbf5985051db515778153fd63ec74 100644 (file)
@@ -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;
        }
index e2254099d72f581f463cf928ff8c957218c199df..f92319b8076701da2373f0efee8f1f0dcc86f473 100644 (file)
@@ -7,18 +7,18 @@
 ! Contributed by Bud Davis  <jmdavis@link.com>
 
       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
index ea37c2a8660e1b98ccdf779af5ab4d2003b56066..1f35a40158e8d6098c78afcd65b500e9d8bb73d5 100644 (file)
@@ -7,5 +7,5 @@ c Contributed by Ilya Enkovich <ienkovich@gcc.gnu.org>
 
       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
index 67c5f11be6a5817714b3cb348dd413cdaff8c790..6378c31309fb20f50fc9442418c8f9529ab38e6d 100644 (file)
@@ -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
index 3be335115816c84928cea90ef5ca45ed2a35f4b4..28d3205f4a77a1ca3c3fc398d76ef5d1616d68b9 100644 (file)
@@ -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
index df57f9c089cfd043683bbb57f58c83bc3a175f2f..9010a2369a8813ff53f022d25adb6091a43ef14b 100644 (file)
@@ -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
index eae0cb3ae16a43f87ca39e2d863962d436459b5b..9dd047006ffbe9d433f07b775c1bc9932e0094fa 100644 (file)
@@ -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
index 4ee3a82d5180fe636ce5d28bfc8c4dc2618fddf0..d1fb310f90f52c884dd2d746ae38a239dd3285f3 100644 (file)
@@ -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
index 61f945886e62fba96d040b03080805e4a74212cf..6995abc83672076ab02db325e4a9cf4b3b72debb 100644 (file)
@@ -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 }
index 9d936197f8f81d9e35f0f74396996263898e39dd..fd4d0a8d7c30deb92bd56383f3c220c51f712313 100644 (file)
@@ -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
index b20c218dd6bcc4662b6504f6af36b76312ea2403..10a6e6960910052a63d0f45cfe046dbc44c47a3e 100644 (file)
@@ -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
index 5bceafda7621e8661f72b4f06ee77ba5f0830759..ce38d13c979cec853308953bf519cfc25a9a79f0 100644 (file)
@@ -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 (file)
index 0000000..9134a1e
--- /dev/null
@@ -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